Ignore:
Timestamp:
2022-07-20T11:30:43+02:00 (2 years ago)
Author:
josefine.ghattas
Message:

Integrated new irrigation scheme developed by Pedro Arboleda. See ticket #857
This corresponds to revsion 7708 of version pedro.arboleda/ORCHIDEE. Following differences were made but were not made on the pedro.arboleda/ORCHIDEE :

  • argumet place in call to routing_wrapper_intialize changed order
  • lines with only change in space were not taken
  • some indentation changed
  • set irrigation output as enalbled false if not do_irrigation
File:
1 edited

Legend:

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

    r7576 r7709  
    3535  USE routing_highres 
    3636  USE routing_simple 
     37  USE constantes_soil 
    3738 
    3839  IMPLICIT NONE 
     
    100101       rest_id,     hist_id,        hist2_id,   lalo,      & 
    101102       neighbours,  resolution,     contfrac,   stempdiag, & 
     103       soiltile,    irrig_frac,     veget_max,  irrigated_next, &     
    102104       returnflow,  reinfiltration, irrigation, riverflow, & 
    103105       coastalflow, flood_frac,     flood_res ) 
     106        
    104107 
    105108 
     
    118121    REAL(r_std), INTENT(in)        :: contfrac(nbpt)       !! Fraction of land in each grid box (unitless;0-1) 
    119122    REAL(r_std), INTENT(in)        :: stempdiag(nbpt,nslm) !! Diagnostic soil temperature profile 
     123    REAL(r_std), INTENT(in)        :: soiltile(nbpt,nstm)  !! Fraction of each soil tile within vegtot (0-1, unitless) 
     124    REAL(r_std), INTENT(in)        :: veget_max(nbpt,nvm)  !! Maximal fraction of vegetation (unitless;0-1) ! 
     125    REAL(r_std), INTENT(in)        :: irrigated_next (nbpt)!! Dynamic irrig. area, calculated in slowproc and passed to routing! 
     126    REAL(r_std), INTENT(in)        :: irrig_frac(nbpt)     !! Irrig. fraction interpolated in routing, and saved to pass to slowproc if irrigated_soiltile = .TRUE. 
     127 
    120128 
    121129    !! 0.2 Output variables 
     
    153161                                 neighbours,  resolution,     contfrac,   stempdiag, & 
    154162                                 returnflow,  reinfiltration, irrigation, riverflow, & 
    155                                  coastalflow, flood_frac,     flood_res ) 
     163                                 coastalflow, flood_frac,     flood_res,  soiltile,  & 
     164                                 irrig_frac,  veget_max,      irrigated_next) 
    156165 
    157166    ELSE IF (routing_method == 'highres') THEN 
     
    206215       lalo, neighbours, resolution, contfrac, totfrac_nobio, veget_max, floodout, runoff, & 
    207216       drainage, transpot, precip_rain, humrel, k_litt, flood_frac, flood_res, & 
    208        stempdiag, reinf_slope, returnflow, reinfiltration, irrigation, riverflow, coastalflow, rest_id, hist_id, hist2_id) 
    209  
     217       stempdiag, reinf_slope, returnflow, reinfiltration, irrigation, riverflow, coastalflow, rest_id, hist_id, hist2_id, & 
     218       soiltile, root_deficit, irrigated_next, irrig_frac, fraction_aeirrig_sw)  
    210219 
    211220 
     
    234243    REAL(r_std), INTENT(in)        :: stempdiag(nbpt,nslm) !! Diagnostic soil temperature profile 
    235244    REAL(r_std), INTENT(in)        :: reinf_slope(nbpt)    !! Coefficient which determines the reinfiltration ratio in the grid box due to flat areas (unitless;0-1) 
     245    REAL(r_std), INTENT(in)        :: root_deficit(nbpt)   !! soil water deficit 
     246    REAL(r_std), INTENT(in)        :: soiltile(nbpt,nstm)  !! Fraction of each soil tile within vegtot (0-1, unitless) 
     247    REAL(r_std), INTENT(in)        :: irrig_frac(nbpt)     !! Irrig. fraction interpolated in routing, and saved to pass to slowproc if irrigated_soiltile = .TRUE. 
     248    REAL(r_std), INTENT(in)        :: irrigated_next (nbpt)!! Dynamic irrig. area, calculated in slowproc and passed to routing 
     249    REAL(r_std), INTENT(in)        :: fraction_aeirrig_sw(nbpt) !! Fraction of area equipped for irrigation from surface water, of irrig_frac 
    236250 
    237251    !! 0.2 Output variables 
     
    254268            lalo, neighbours, resolution, contfrac, totfrac_nobio, veget_max, floodout, runoff, & 
    255269            drainage, transpot, precip_rain, humrel, k_litt, flood_frac, flood_res, & 
    256             stempdiag, reinf_slope, returnflow, reinfiltration, irrigation, riverflow, coastalflow, rest_id, hist_id, hist2_id) 
     270            stempdiag, reinf_slope, returnflow, reinfiltration, irrigation, riverflow, coastalflow, rest_id, hist_id, hist2_id, & 
     271            soiltile, root_deficit, irrigated_next, irrig_frac, fraction_aeirrig_sw) 
    257272 
    258273    ELSE IF (routing_method=='highres') THEN 
Note: See TracChangeset for help on using the changeset viewer.