Ignore:
Timestamp:
2022-04-14T10:01:23+02:00 (2 years ago)
Author:
josefine.ghattas
Message:

Integrate routing scheme "highres" developped by Jan Polcher, tested and integrated in ORCHIDEE_2_2 by Lucia Rinchiuso. This corresponds to the revision 7574 of perso/lucia.rinchiuso/myORCHIDEE_2_2_r7481. The developements of the routing scheme from branches/ORCHIDEE-ROUTING at revision 7545 are taken into account.

See also ticket #842

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_sechiba/routing_wrapper.f90

    r6102 r7576  
    1515!!                available routing modules:  
    1616!!                - ROUTING_METOD=standard for the standard routing scheme available in module routing.  
    17 !!                - ROUTING_METHOD=simple for the routing scheme in module routing_simple.  
     17!!                - ROUTING_METHOD=simple for the routing scheme in module routing_simple. 
     18!!                - ROUTING_METHOD=highres for the high resolution routing scheme in module routing_highres. 
    1819!! 
    1920!! REFERENCE(S) : None 
     
    3233  USE grid 
    3334  USE routing 
     35  USE routing_highres 
    3436  USE routing_simple 
    3537 
    3638  IMPLICIT NONE 
    3739 
    38   CHARACTER(LEN=255), SAVE :: routing_method                      !! 'standard' or 'simple': Character string used to switch between routing modules 
     40  CHARACTER(LEN=255), SAVE :: routing_method                      !! 'standard', 'highres' or 'simple': Character string used to switch between routing modules 
    3941  !$OMP THREADPRIVATE(routing_method)  
    4042 
     
    6769    routing_method='standard' 
    6870    CALL getin_p("ROUTING_METHOD",routing_method) 
    69     IF(routing_method=='simple') THEN   
     71    IF(routing_method=='standard') THEN 
     72       CALL routing_xios_initialize 
     73    ELSEIF(routing_method=='highres') THEN 
     74       CALL routing_highres_xios_initialize 
     75    ELSEIF(routing_method=='simple') THEN   
    7076       CALL routing_simple_xios_initialize 
    7177    ENDIF 
     
    144150 
    145151       CALL routing_initialize(  kjit,        nbpt,           index,                 & 
     152                                 rest_id,     hist_id,        hist2_id,   lalo,      & 
     153                                 neighbours,  resolution,     contfrac,   stempdiag, & 
     154                                 returnflow,  reinfiltration, irrigation, riverflow, & 
     155                                 coastalflow, flood_frac,     flood_res ) 
     156 
     157    ELSE IF (routing_method == 'highres') THEN 
     158 
     159       CALL routing_highres_initialize(  kjit,        nbpt,           index,                 & 
    146160                                 rest_id,     hist_id,        hist2_id,   lalo,      & 
    147161                                 neighbours,  resolution,     contfrac,   stempdiag, & 
     
    242256            stempdiag, reinf_slope, returnflow, reinfiltration, irrigation, riverflow, coastalflow, rest_id, hist_id, hist2_id) 
    243257 
     258    ELSE IF (routing_method=='highres') THEN 
     259 
     260       CALL routing_highres_main (kjit, nbpt, index, & 
     261            lalo, neighbours, resolution, contfrac, totfrac_nobio, veget_max, floodout, runoff, & 
     262            drainage, transpot, precip_rain, humrel, k_litt, flood_frac, flood_res, & 
     263            stempdiag, reinf_slope, returnflow, reinfiltration, irrigation, riverflow, coastalflow, rest_id, hist_id, hist2_id) 
     264 
    244265    ELSE IF(routing_method=='simple') THEN  
    245266 
     
    287308       CALL routing_finalize( kjit, nbpt, rest_id, flood_frac, flood_res ) 
    288309 
     310    ELSE IF (routing_method=='highres') THEN 
     311 
     312       CALL routing_highres_finalize( kjit, nbpt, rest_id, flood_frac, flood_res ) 
     313 
    289314    ELSE IF(routing_method=='simple') THEN  
    290315 
     
    316341       CALL routing_clear 
    317342 
     343    ELSE IF (routing_method=='highres') THEN 
     344 
     345       CALL routing_highres_clear 
     346 
    318347    ELSE IF(routing_method=='simple') THEN  
    319348 
Note: See TracChangeset for help on using the changeset viewer.