Ignore:
Timestamp:
2022-07-20T13:09:05+02:00 (2 years ago)
Author:
josefine.ghattas
Message:

Integration of temperature of water in highres routing scheme. Done by Jan Polcer and Lucia Rinchiuso

File:
1 edited

Legend:

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

    r7709 r7710  
    100100       kjit,        nbpt,           index,                 & 
    101101       rest_id,     hist_id,        hist2_id,   lalo,      & 
    102        neighbours,  resolution,     contfrac,   stempdiag, & 
     102       neighbours,  resolution,     contfrac,   stempdiag, ftempdiag, & 
    103103       soiltile,    irrig_frac,     veget_max,  irrigated_next, &     
    104104       returnflow,  reinfiltration, irrigation, riverflow, & 
    105105       coastalflow, flood_frac,     flood_res ) 
    106         
    107106 
    108107 
     
    121120    REAL(r_std), INTENT(in)        :: contfrac(nbpt)       !! Fraction of land in each grid box (unitless;0-1) 
    122121    REAL(r_std), INTENT(in)        :: stempdiag(nbpt,nslm) !! Diagnostic soil temperature profile 
     122    REAL(r_std), INTENT(in)        :: ftempdiag(nbpt,ngrnd)!! Diagnostic soil temperature profile over full column 
    123123    REAL(r_std), INTENT(in)        :: soiltile(nbpt,nstm)  !! Fraction of each soil tile within vegtot (0-1, unitless) 
    124124    REAL(r_std), INTENT(in)        :: veget_max(nbpt,nvm)  !! Maximal fraction of vegetation (unitless;0-1) ! 
     
    214214  SUBROUTINE routing_wrapper_main(kjit, nbpt, index, & 
    215215       lalo, neighbours, resolution, contfrac, totfrac_nobio, veget_max, floodout, runoff, & 
    216        drainage, transpot, precip_rain, humrel, k_litt, flood_frac, flood_res, & 
    217        stempdiag, reinf_slope, returnflow, reinfiltration, irrigation, riverflow, coastalflow, rest_id, hist_id, hist2_id, & 
     216       drainage, transpot, precip_rain, humrel, k_litt, flood_frac, flood_res, stempdiag, & 
     217       ftempdiag, reinf_slope, returnflow, reinfiltration, irrigation, riverflow, coastalflow, rest_id, hist_id, hist2_id, & 
    218218       soiltile, root_deficit, irrigated_next, irrig_frac, fraction_aeirrig_sw)  
    219  
    220219 
    221220    IMPLICIT NONE 
     
    242241    REAL(r_std), INTENT(in)        :: humrel(nbpt,nvm)     !! Soil moisture stress, root extraction potential (unitless) 
    243242    REAL(r_std), INTENT(in)        :: stempdiag(nbpt,nslm) !! Diagnostic soil temperature profile 
     243    REAL(r_std), INTENT(in)        :: ftempdiag(nbpt,ngrnd)!! Diagnostic soil temperature profile over full column 
    244244    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) 
    245245    REAL(r_std), INTENT(in)        :: root_deficit(nbpt)   !! soil water deficit 
     
    276276            lalo, neighbours, resolution, contfrac, totfrac_nobio, veget_max, floodout, runoff, & 
    277277            drainage, transpot, precip_rain, humrel, k_litt, flood_frac, flood_res, & 
    278             stempdiag, reinf_slope, returnflow, reinfiltration, irrigation, riverflow, coastalflow, rest_id, hist_id, hist2_id) 
     278            ftempdiag, reinf_slope, returnflow, reinfiltration, irrigation, riverflow, coastalflow, rest_id, hist_id, hist2_id) 
    279279 
    280280    ELSE IF(routing_method=='simple') THEN  
Note: See TracChangeset for help on using the changeset viewer.