Changeset 7710


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

Location:
branches/ORCHIDEE_2_2/ORCHIDEE
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_parallel/xios_orchidee.f90

    r7709 r7710  
    302302           
    303303       ELSE IF (grid_type==regular_xy ) THEN 
    304  
    305304          ! Global domain 
    306305          CALL xios_set_domain_attr("domain_landpoints", ni_glo=iim_g, nj_glo=jjm_g) 
     
    414413          CALL xios_set_field_attr("netirrig",enabled=.FALSE.) 
    415414          CALL xios_set_field_attr("SurfStor",enabled=.FALSE.) 
     415          CALL xios_set_field_attr("htutempmon",enabled=.FALSE.) 
     416          CALL xios_set_field_attr("streamlimit",enabled=.FALSE.) 
     417          CALL xios_set_field_attr("StreamT_TotTend",enabled=.FALSE.) 
     418          CALL xios_set_field_attr("StreamT_AdvTend",enabled=.FALSE.) 
     419          CALL xios_set_field_attr("StreamT_RelTend",enabled=.FALSE.) 
    416420       END IF 
    417421 
     
    433437          CALL xios_set_field_attr("floodmap",enabled=.FALSE.) 
    434438          CALL xios_set_field_attr("floodh",enabled=.FALSE.)        
     439          CALL xios_set_field_attr("floodr",enabled=.FALSE.) 
    435440          CALL xios_set_field_attr("floodout",enabled=.FALSE.) 
    436441          CALL xios_set_field_attr("flood_frac",enabled=.FALSE.)        
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_sechiba/routing_highres.f90

    r7576 r7710  
    1 ! ================================================================================================================================= 
     1! ================================================================================================================================ 
    22! MODULE       : routing_highres 
    33! 
     
    9696  INTEGER(i_std), SAVE                                       :: overflow_repetition = 1     !! Number of repetition of overflow for each routing step 
    9797  !$OMP THREADPRIVATE(overflow_repetition) 
     98  ! Soil temperature depth to be used to estimate runoff and drainage temperatures 
     99  ! 
     100  REAL(r_std), PARAMETER, DIMENSION(2) :: runofftempdepth = (/ 0.0, 0.3 /)                  !! Layer which will determine the temperature of runoff 
     101  REAL(r_std), PARAMETER, DIMENSION(2) :: drainagetempdepth = (/ 3.0, 90.0 /)               !! Layer which will determine the temperature of runoff 
     102  ! 
    98103  ! 
    99104  !  Relation between maximum surface of ponds and basin surface, and drainage (mm/j) to the slow_res 
     
    123128  LOGICAL, SAVE                                              :: doponds = .FALSE.           !! Logical to choose if ponds are activated or not (true/false) 
    124129!$OMP THREADPRIVATE(doponds) 
    125   LOGICAL, SAVE                                              :: do_rivertemp = .FALSE. 
    126 !$OMP THREADPRIVATE(do_rivertemp) 
    127130  REAL(r_std), SAVE                                          :: conduct_factor = 1.         !! Adjustment factor for floodplains reinfiltration 
    128131!$OMP THREADPRIVATE(conduct_factor) 
     
    221224!!! 
    222225 
    223   REAL(r_std),  SAVE, ALLOCATABLE, DIMENSION(:,:)            :: stempdiag_mean              !! Averaged soil temperatures 
    224 !$OMP THREADPRIVATE(stempdiag_mean) 
     226  REAL(r_std),  SAVE, ALLOCATABLE, DIMENSION(:,:)            :: tempdiag_mean              !! Averaged soil temperatures 
     227!$OMP THREADPRIVATE(tempdiag_mean) 
    225228! 
    226229! FLOOD OVERFLOW 
     
    404407  SUBROUTINE routing_highres_initialize( kjit,       nbpt,           index,                 & 
    405408                                rest_id,     hist_id,        hist2_id,   lalo,      & 
    406                                 neighbours,  resolution,     contfrac,   stempdiag, & 
     409                                neighbours,  resolution,     contfrac,   tempdiag, & 
    407410                                returnflow,  reinfiltration, irrigation, riverflow, & 
    408411                                coastalflow, flood_frac,     flood_res ) 
     
    423426    REAL(r_std), INTENT(in)        :: resolution(nbpt,2)   !! The size of each grid box in X and Y (m) 
    424427    REAL(r_std), INTENT(in)        :: contfrac(nbpt)       !! Fraction of land in each grid box (unitless;0-1) 
    425     REAL(r_std), INTENT(in)        :: stempdiag(nbpt,nslm) !! Diagnostic soil temperature profile 
     428    REAL(r_std), INTENT(in)        :: tempdiag(nbpt,ngrnd) !! Diagnostic soil temperature profile 
    426429 
    427430    !! 0.2 Output variables 
     
    455458 
    456459    CALL routing_hr_init (kjit, nbpt, index, returnflow, reinfiltration, irrigation, & 
    457          riverflow, coastalflow, flood_frac, flood_res, stempdiag, rest_id) 
     460         riverflow, coastalflow, flood_frac, flood_res, tempdiag, rest_id) 
    458461 
    459462    routing_area => routing_area_loc   
     
    643646    IF (printlev >= 5) WRITE(numout,*) 'End of routing_highres_initialize' 
    644647 
    645     !! Define XIOS axis size needed for the model output 
    646     !CALL xios_orchidee_addaxis("nbhtu", nbasmax, (/(REAL(ib,r_std),ib=1,nbasmax)/)) 
    647     !CALL xios_orchidee_addaxis("nbasmon", nbasmon, (/(REAL(ib,r_std),ib=1,nbasmon)/)) 
    648      
    649648  END SUBROUTINE routing_highres_initialize 
    650649 
     
    758757       & lalo, neighbours, resolution, contfrac, totfrac_nobio, veget_max, floodout, runoff, & 
    759758       & drainage, transpot, precip_rain, humrel, k_litt, flood_frac, flood_res, & 
    760        & stempdiag, reinf_slope, returnflow, reinfiltration, irrigation, riverflow, coastalflow, rest_id, hist_id, hist2_id) 
     759       & tempdiag, reinf_slope, returnflow, reinfiltration, irrigation, riverflow, coastalflow, rest_id, hist_id, hist2_id) 
    761760 
    762761    IMPLICIT NONE 
     
    782781    REAL(r_std), INTENT(in)        :: k_litt(nbpt)         !! Averaged conductivity for saturated infiltration in the 'litter' layer (kg/m^2/dt) 
    783782    REAL(r_std), INTENT(in)        :: humrel(nbpt,nvm)     !! Soil moisture stress, root extraction potential (unitless) 
    784     REAL(r_std), INTENT(in)        :: stempdiag(nbpt,nslm) !! Diagnostic soil temperature profile 
     783    REAL(r_std), INTENT(in)        :: tempdiag(nbpt,ngrnd) !! Diagnostic soil temperature profile 
    785784    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) 
    786785 
     
    816815    REAL(r_std), DIMENSION(nbpt,nbasmax)   :: stemp_total_tend, stemp_advec_tend, stemp_relax_tend 
    817816    ! 
    818     LOGICAL, SAVE                  :: xios_sendonce=.TRUE. 
    819     ! 
    820817!_ ================================================================================================================================ 
    821818 
     
    834831    runoff_mean(:) = runoff_mean(:) + runoff(:) 
    835832    drainage_mean(:) = drainage_mean(:) + drainage(:) 
    836     floodtemp(:) = stempdiag(:,floodtemp_lev) 
     833    floodtemp(:) = tempdiag(:,floodtemp_lev) 
    837834    precip_mean(:) =  precip_mean(:) + precip_rain(:) 
    838835    ! 
     
    867864    totnobio_mean(:) = totnobio_mean(:) + totfrac_nobio(:)*dt_sechiba/dt_routing 
    868865    k_litt_mean(:) = k_litt_mean(:) + k_litt(:)*dt_sechiba/dt_routing 
    869     stempdiag_mean(:,:) = stempdiag_mean(:,:) + stempdiag(:,:)*dt_sechiba/dt_routing 
     866    tempdiag_mean(:,:) = tempdiag_mean(:,:) + tempdiag(:,:)*dt_sechiba/dt_routing 
    870867    ! 
    871868    ! Only potentially vegetated surfaces are taken into account. At the start of 
     
    889886       CALL routing_hr_flow(nbpt, dt_routing, lalo, floodout_mean, runoff_mean, drainage_mean, & 
    890887            & vegtot_mean, totnobio_mean, transpot_mean, precip_mean, humrel_mean, k_litt_mean, floodtemp, & 
    891             & stempdiag_mean, reinf_slope, lakeinflow_mean, returnflow_mean, reinfiltration_mean, & 
     888            & tempdiag_mean, reinf_slope, lakeinflow_mean, returnflow_mean, reinfiltration_mean, & 
    892889            & irrigation_mean, riverflow_mean, coastalflow_mean, hydrographs, slowflow_diag, flood_frac, & 
    893890            & flood_res, netflow_stream_diag, netflow_fast_diag, netflow_slow_diag, & 
     
    911908       totnobio_mean(:) = zero 
    912909       k_litt_mean(:) = zero 
    913        stempdiag_mean(:,:) = zero 
     910       tempdiag_mean(:,:) = zero 
    914911       vegtot_mean(:) = zero 
    915912 
     
    937934       CALL xios_orchidee_send_field("wbr_lake",  (lake_diag   - lake_diag_old - & 
    938935            lakeinflow_mean + return_lakes)/dt_routing) 
    939        IF ( do_rivertemp ) THEN 
    940           CALL xios_orchidee_send_field("StreamT_TotTend", stemp_total_tend) 
    941           CALL xios_orchidee_send_field("StreamT_AdvTend", stemp_advec_tend) 
    942           CALL xios_orchidee_send_field("StreamT_RelTend", stemp_relax_tend) 
    943        ENDIF 
     936       CALL xios_orchidee_send_field("StreamT_TotTend", stemp_total_tend) 
     937       CALL xios_orchidee_send_field("StreamT_AdvTend", stemp_advec_tend) 
     938       CALL xios_orchidee_send_field("StreamT_RelTend", stemp_relax_tend) 
    944939    ENDIF 
    945940 
     
    956951    ! Write diagnostics 
    957952    ! 
    958     IF ( xios_sendonce ) THEN 
    959        ! 
    960        CALL xios_orchidee_send_field("mask_coast",mask_coast) 
    961  
    962        IF ( do_irrigation ) THEN  
    963           CALL xios_orchidee_send_field("irrigmap",irrigated) 
    964        ENDIF 
     953    ! 
     954    CALL xios_orchidee_send_field("mask_coast",mask_coast) 
     955 
     956    IF ( do_irrigation ) THEN  
     957       CALL xios_orchidee_send_field("irrigmap",irrigated) 
     958    ENDIF 
    965959        
    966        IF ( do_floodplains ) THEN 
    967           !! May be improved by performing the operation with XIOS 
    968           floodmap(:) = 0.0 
    969           DO ig=1,nbpt 
    970              floodmap(ig) = SUM(floodplains(ig,:)) / (area(ig)*contfrac(ig)) 
    971           END DO 
    972           CALL xios_orchidee_send_field("floodmap",floodmap) 
    973        ENDIF 
     960    IF ( do_floodplains ) THEN 
     961       !! May be improved by performing the operation with XIOS 
     962       floodmap(:) = 0.0 
     963       DO ig=1,nbpt 
     964          floodmap(ig) = SUM(floodplains(ig,:)) / (area(ig)*contfrac(ig)) 
     965       END DO 
     966       CALL xios_orchidee_send_field("floodmap",floodmap) 
     967    ENDIF 
    974968        
    975        IF ( doswamps ) THEN 
    976           CALL xios_orchidee_send_field("swampmap",swamp) 
    977        ENDIF 
     969    IF ( doswamps ) THEN 
     970       CALL xios_orchidee_send_field("swampmap",swamp) 
     971    ENDIF 
    978972        
    979        xios_sendonce=.FALSE. 
    980     ENDIF 
    981973    ! 
    982974    ! Water storage in reservoirs [kg/m^2] 
     
    10091001    CALL xios_orchidee_send_field("hydrographs",hydrographs/mille/dt_sechiba) 
    10101002    CALL xios_orchidee_send_field("htuhgmon",HTUhgmon/mille/dt_sechiba) 
    1011     IF ( do_rivertemp ) THEN 
    1012        CALL xios_orchidee_send_field("htutempmon",HTUtempmon) 
    1013        CALL xios_orchidee_send_field("hydrotemp", hydrotemp) 
    1014        CALL xios_orchidee_send_field("streamlimit", streamlimit) 
    1015     ENDIF 
     1003    CALL xios_orchidee_send_field("htutempmon",HTUtempmon) 
     1004    CALL xios_orchidee_send_field("hydrotemp", hydrotemp) 
     1005    CALL xios_orchidee_send_field("streamlimit", streamlimit) 
     1006 
    10161007    CALL xios_orchidee_send_field("slowflow",slowflow_diag/mille/dt_sechiba) ! previous id name: Qb 
    10171008    CALL xios_orchidee_send_field("coastalflow",coastalflow/dt_sechiba) 
     
    11641155    CALL restput_p (rest_id, 'flood_res', nbp_glo, 1, 1, kjit, flood_res, 'scatter', nbp_glo, index_g) 
    11651156 
    1166     IF ( do_rivertemp ) THEN 
    1167        CALL restput_p (rest_id, 'fasttemp', nbp_glo, nbasmax, 1, kjit, fast_temp, 'scatter',  nbp_glo, index_g) 
    1168        CALL restput_p (rest_id, 'slowtemp', nbp_glo, nbasmax, 1, kjit, slow_temp, 'scatter',  nbp_glo, index_g) 
    1169        CALL restput_p (rest_id, 'streamtemp', nbp_glo, nbasmax, 1, kjit, stream_temp, 'scatter',nbp_glo,index_g) 
    1170     ENDIF 
     1157    CALL restput_p (rest_id, 'fasttemp', nbp_glo, nbasmax, 1, kjit, fast_temp, 'scatter',  nbp_glo, index_g) 
     1158    CALL restput_p (rest_id, 'slowtemp', nbp_glo, nbasmax, 1, kjit, slow_temp, 'scatter',  nbp_glo, index_g) 
     1159    CALL restput_p (rest_id, 'streamtemp', nbp_glo, nbasmax, 1, kjit, stream_temp, 'scatter',nbp_glo,index_g) 
    11711160  
    11721161     
     
    11821171    CALL restput_p (rest_id, 'htuhgmon', nbp_glo, nbasmon, 1, kjit, HTUhgmon, 'scatter',  nbp_glo, index_g) 
    11831172    CALL restput_p (rest_id, 'slowflow_diag', nbp_glo, 1, 1, kjit, slowflow_diag, 'scatter',  nbp_glo, index_g) 
    1184     IF ( do_rivertemp ) THEN 
    1185        CALL restput_p (rest_id, 'hydrotemp', nbp_glo, 1, 1, kjit, hydrotemp, 'scatter',  nbp_glo, index_g) 
    1186        CALL restput_p (rest_id, 'htutempmon', nbp_glo, nbasmon, 1, kjit, HTUtempmon, 'scatter',  nbp_glo, index_g) 
    1187     ENDIF 
     1173    CALL restput_p (rest_id, 'hydrotemp', nbp_glo, 1, 1, kjit, hydrotemp, 'scatter',  nbp_glo, index_g) 
     1174    CALL restput_p (rest_id, 'htutempmon', nbp_glo, nbasmon, 1, kjit, HTUtempmon, 'scatter',  nbp_glo, index_g) 
    11881175    ! 
    11891176    ! Keep track of the accumulated variables 
     
    11981185    CALL restput_p (rest_id, 'k_litt_route', nbp_glo, 1, 1, kjit, k_litt_mean, 'scatter',  nbp_glo, index_g) 
    11991186    CALL restput_p (rest_id, 'vegtot_route', nbp_glo, 1, 1, kjit, vegtot_mean, 'scatter',  nbp_glo, index_g) 
    1200     CALL restput_p (rest_id, 'stempdiag_route', nbp_glo, nslm, 1, kjit, stempdiag_mean, 'scatter',  nbp_glo, index_g) 
     1187    CALL restput_p (rest_id, 'tempdiag_route', nbp_glo, ngrnd, 1, kjit, tempdiag_mean, 'scatter',  nbp_glo, index_g) 
    12011188 
    12021189    CALL restput_p (rest_id, 'gridrephtu', nbp_glo, 1, 1, kjit, REAL(hydrodiag,r_std), 'scatter',  nbp_glo, index_g) 
     
    12401227 
    12411228  SUBROUTINE routing_hr_init(kjit, nbpt, index, returnflow, reinfiltration, irrigation, & 
    1242        &                  riverflow, coastalflow, flood_frac, flood_res, stempdiag, rest_id) 
     1229       &                  riverflow, coastalflow, flood_frac, flood_res, tempdiag, rest_id) 
    12431230    ! 
    12441231    IMPLICIT NONE 
     
    12501237    INTEGER(i_std), INTENT(in)                   :: nbpt           !! Domain size (unitless) 
    12511238    INTEGER(i_std), DIMENSION (nbpt), INTENT(in) :: index          !! Indices of the points on the map (unitless) 
    1252     REAL(r_std), DIMENSION(nbpt,nslm),INTENT(in) :: stempdiag      !! Temperature profile in soil 
     1239    REAL(r_std), DIMENSION(nbpt,ngrnd),INTENT(in) :: tempdiag      !! Temperature profile in soil 
    12531240    INTEGER(i_std), INTENT(in)                   :: rest_id        !! Restart file identifier (unitless) 
    12541241    ! 
     
    12871274    !Config Units = [seconds] 
    12881275    ! 
    1289     dt_routing = one_day 
     1276    dt_routing = dt_sechiba 
    12901277    CALL getin_p('DT_ROUTING', dt_routing) 
    12911278    ! 
     
    14421429    CALL getin_p("MAX_LAKE_RESERVOIR", max_lake_reservoir) 
    14431430 
    1444     !Config Key   = DO_RIVERTEMP 
    1445     !Config Desc  = Activates the river temperature calculations 
    1446     !Config If    =  
    1447     !Config Def   = False 
    1448     !Config Help  =  
    1449     !Config Units = - 
    1450     do_rivertemp = .FALSE. 
    1451     CALL getin_p("DO_RIVERTEMP", do_rivertemp) 
    14521431    ! 
    14531432    ! 
     
    19631942    irrigation(:) = irrigation_mean(:) 
    19641943     
    1965     IF ( do_rivertemp ) THEN 
    1966        ALLOCATE (fast_temp(nbpt,nbasmax), stat=ier) 
    1967        IF (ier /= 0) CALL ipslerr_p(3,'routing_hr_init','Pb in allocate for fast_temp','','') 
    1968        var_name = 'fasttemp' 
    1969        CALL ioconf_setatt_p('UNITS', 'K') 
    1970        CALL ioconf_setatt_p('LONG_NAME','Water temperature in the fast reservoir') 
    1971        CALL restget_p (rest_id, var_name, nbp_glo, nbasmax, 1, kjit, .TRUE., fast_temp, "gather", nbp_glo, index_g) 
    1972  
    1973        ALLOCATE (slow_temp(nbpt,nbasmax), stat=ier) 
    1974        IF (ier /= 0) CALL ipslerr_p(3,'routing_hr_init','Pb in allocate for slow_temp','','') 
    1975        var_name = 'slowtemp' 
    1976        CALL ioconf_setatt_p('UNITS', 'K') 
    1977        CALL ioconf_setatt_p('LONG_NAME','Water temperature in the slow reservoir') 
    1978        CALL restget_p (rest_id, var_name, nbp_glo, nbasmax, 1, kjit, .TRUE., slow_temp, "gather", nbp_glo, index_g) 
     1944    ALLOCATE (fast_temp(nbpt,nbasmax), stat=ier) 
     1945    IF (ier /= 0) CALL ipslerr_p(3,'routing_hr_init','Pb in allocate for fast_temp','','') 
     1946    var_name = 'fasttemp' 
     1947    CALL ioconf_setatt_p('UNITS', 'K') 
     1948    CALL ioconf_setatt_p('LONG_NAME','Water temperature in the fast reservoir') 
     1949    CALL restget_p (rest_id, var_name, nbp_glo, nbasmax, 1, kjit, .TRUE., fast_temp, "gather", nbp_glo, index_g) 
     1950 
     1951    ALLOCATE (slow_temp(nbpt,nbasmax), stat=ier) 
     1952    IF (ier /= 0) CALL ipslerr_p(3,'routing_hr_init','Pb in allocate for slow_temp','','') 
     1953    var_name = 'slowtemp' 
     1954    CALL ioconf_setatt_p('UNITS', 'K') 
     1955    CALL ioconf_setatt_p('LONG_NAME','Water temperature in the slow reservoir') 
     1956    CALL restget_p (rest_id, var_name, nbp_glo, nbasmax, 1, kjit, .TRUE., slow_temp, "gather", nbp_glo, index_g) 
    19791957        
    1980        IF ( COUNT(fast_temp == val_exp) == nbpt*nbasmax ) THEN 
    1981           CALL groudwatertemp(nbpt, nbasmax, nslm, stempdiag, diaglev, fast_temp, slow_temp) 
    1982        ENDIF 
     1958    IF ( COUNT(fast_temp == val_exp) == nbpt*nbasmax ) THEN 
     1959       CALL groundwatertemp(nbpt, nbasmax, ngrnd, tempdiag, znt, dlt, fast_temp, slow_temp) 
     1960    ENDIF 
    19831961        
    1984        ALLOCATE (stream_temp(nbpt,nbasmax), stat=ier) 
    1985        IF (ier /= 0) CALL ipslerr_p(3,'routing_hr_init','Pb in allocate for stream_temp','','') 
    1986        var_name = 'streamtemp' 
    1987        CALL ioconf_setatt_p('UNITS', 'K') 
    1988        CALL ioconf_setatt_p('LONG_NAME','Water temperature in the stream reservoir') 
    1989        CALL restget_p (rest_id, var_name, nbp_glo, nbasmax, 1, kjit, .TRUE., stream_temp, "gather", nbp_glo, index_g) 
    1990  
    1991        IF ( COUNT(stream_temp == val_exp) == nbpt*nbasmax ) THEN 
    1992           DO ig=1,nbpt  
    1993              stream_temp(ig,:) = stempdiag(ig,1) 
    1994           ENDDO 
    1995        ENDIF 
     1962    ALLOCATE (stream_temp(nbpt,nbasmax), stat=ier) 
     1963    IF (ier /= 0) CALL ipslerr_p(3,'routing_hr_init','Pb in allocate for stream_temp','','') 
     1964    var_name = 'streamtemp' 
     1965    CALL ioconf_setatt_p('UNITS', 'K') 
     1966    CALL ioconf_setatt_p('LONG_NAME','Water temperature in the stream reservoir') 
     1967    CALL restget_p (rest_id, var_name, nbp_glo, nbasmax, 1, kjit, .TRUE., stream_temp, "gather", nbp_glo, index_g) 
     1968 
     1969    IF ( COUNT(stream_temp == val_exp) == nbpt*nbasmax ) THEN 
     1970       DO ig=1,nbpt  
     1971         stream_temp(ig,:) = tempdiag(ig,1) 
     1972       ENDDO 
    19961973    ENDIF 
    19971974     
     
    20191996    ALLOCATE (floodtemp(nbpt), stat=ier) 
    20201997    IF (ier /= 0) CALL ipslerr_p(3,'routing_hr_init','Pb in allocate for floodtemp','','') 
    2021     floodtemp(:) = stempdiag(:,floodtemp_lev) 
     1998    floodtemp(:) = tempdiag(:,floodtemp_lev) 
    20221999     
    20232000    ALLOCATE(hydrographs(nbpt), stat=ier) 
     
    22442221    CALL setvar_p (vegtot_mean, val_exp, 'NO_KEYWORD', un) 
    22452222    ! 
    2246     ALLOCATE(stempdiag_mean(nbpt,nslm), stat=ier) 
    2247     IF (ier /= 0) CALL ipslerr_p(3,'routing_hr_init','Pb in allocate for stempdiag_mean','','') 
    2248     var_name = 'stempdiag_route' 
     2223    ALLOCATE(tempdiag_mean(nbpt,ngrnd), stat=ier) 
     2224    IF (ier /= 0) CALL ipslerr_p(3,'routing_hr_init','Pb in allocate for tempdiag_mean','','') 
     2225    var_name = 'tempdiag_route' 
    22492226    CALL ioconf_setatt_p('UNITS', 'K') 
    22502227    CALL ioconf_setatt_p('LONG_NAME','Mean temperature profile') 
    2251     CALL restget_p (rest_id, var_name, nbp_glo, nslm, 1, kjit, .TRUE., stempdiag_mean, "gather", nbp_glo, index_g) 
    2252     CALL setvar_p (stempdiag_mean, val_exp, 'NO_KEYWORD', Zero) 
     2228    CALL restget_p (rest_id, var_name, nbp_glo, ngrnd, 1, kjit, .TRUE., tempdiag_mean, "gather", nbp_glo, index_g) 
     2229    CALL setvar_p (tempdiag_mean, val_exp, 'NO_KEYWORD', Zero) 
    22532230    ! 
    22542231    DEALLOCATE(tmp_real_g) 
     
    23552332    IF (ALLOCATED(humrel_mean)) DEALLOCATE(humrel_mean) 
    23562333    IF (ALLOCATED(k_litt_mean)) DEALLOCATE(k_litt_mean) 
    2357     IF (ALLOCATED(stempdiag_mean)) DEALLOCATE(stempdiag_mean) 
     2334    IF (ALLOCATED(tempdiag_mean)) DEALLOCATE(tempdiag_mean) 
    23582335    IF (ALLOCATED(totnobio_mean)) DEALLOCATE(totnobio_mean) 
    23592336    IF (ALLOCATED(vegtot_mean)) DEALLOCATE(vegtot_mean) 
     
    24662443 
    24672444  SUBROUTINE routing_hr_flow(nbpt, dt_routing, lalo, floodout, runoff, drainage, & 
    2468        &                  vegtot, totnobio, transpot_mean, precip, humrel, k_litt, floodtemp, stempdiag, & 
     2445       &                  vegtot, totnobio, transpot_mean, precip, humrel, k_litt, floodtemp, tempdiag, & 
    24692446       &                  reinf_slope, lakeinflow, returnflow, reinfiltration, irrigation, riverflow, & 
    24702447       &                  coastalflow, hydrographs, slowflow_diag, flood_frac, flood_res, & 
     
    24882465    REAL(r_std), INTENT(in)                      :: k_litt(nbpt)              !! Averaged conductivity for saturated infiltration in the 'litter' layer (kg/m^2/dt) 
    24892466    REAL(r_std), INTENT(in)                      :: floodtemp(nbpt)           !! Temperature to decide if floodplains work (K) 
    2490     REAL(r_std), INTENT(in)                      :: stempdiag(nbpt,nslm)      !! Soil temperature profiles (K) 
     2467    REAL(r_std), INTENT(in)                      :: tempdiag(nbpt,ngrnd)      !! Soil temperature profiles (K) 
    24912468    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) 
    24922469    REAL(r_std), INTENT(out)                     :: lakeinflow(nbpt)          !! Water inflow to the lakes (kg/dt) 
     
    25212498    REAL(r_std), DIMENSION(nbpt, nbasmax)        :: return_swamp              !! Inflow to the swamp (kg/dt) 
    25222499    REAL(r_std), DIMENSION(nbpt, nbasmax)        :: source 
    2523     REAL(r_std), DIMENSION(nbpt, nbasmax)        :: ewh, wrr 
     2500    REAL(r_std), DIMENSION(nbpt, nbasmax)        :: ewh 
    25242501    ! 
    25252502    ! Irrigation per basin 
     
    25802557 
    25812558    REAL(r_std)                                  :: reduced                   !! Discharge reduction due to floodplains 
    2582     REAL(r_std)                                  :: restime, minrestime, maxrestime!! Scaling for residence times in the relaxation of temperature. 
    25832559    REAL(r_std)                                  :: htmp, hscale              !! Water height scalingfor temperature relaxation 
    25842560    REAL(r_std)                                  :: krelax, den 
    25852561    !! PARAMETERS 
    25862562    LOGICAL, PARAMETER                           :: check_reservoir = .FALSE. !! Logical to choose if we write informations when a negative amount of water is occurring in a reservoir (true/false) 
    2587     LOGICAL, SAVE                                :: origformula = .FALSE. 
    25882563!_ ================================================================================================================================ 
    25892564    ! 
    2590     minrestime = 86400/2.0 
    2591     maxrestime = stream_maxresid * stream_tcst 
    2592     ! 
    2593     origformula = .FALSE. 
    2594     CALL getin_p('ELIOTTFORMULA',origformula) 
     2565    ! 
    25952566    hscale = 1. 
    2596     CALL getin_p('HSCALEKH',hscale) 
     2567    CALL getin_p('ROUTING_HSCALEKH',hscale) 
    25972568    ! 
    25982569    transport(:,:) = zero 
    25992570    transport_glo(:,:) = zero 
    2600     IF ( do_rivertemp ) THEN 
    2601        transport_temp(:,:) = zero !tp_00  its a transport, not a temperature !! 
    2602        transport_temp_glo(:,:) = zero !tp_00 
    2603     ENDIF 
     2571    transport_temp(:,:) = zero !tp_00  its a transport, not a temperature !! 
     2572    transport_temp_glo(:,:) = zero !tp_00 
     2573     
    26042574    irrig_netereq(:) = zero 
    26052575    irrig_needs(:,:) = zero 
     
    26312601!> the sub-basin considered and its downstream neighbor. 
    26322602    ! 
    2633     IF ( do_rivertemp ) THEN 
    2634        CALL groudwatertemp(nbpt, nbasmax, nslm, stempdiag, diaglev, fast_temp, slow_temp) 
    2635     ENDIF 
     2603    CALL groundwatertemp(nbpt, nbasmax, ngrnd, tempdiag, znt, dlt, fast_temp, slow_temp) 
    26362604    ! 
    26372605    streamlimit(:) = zero 
     
    27992767    source(:,:) = fast_flow(:,:) + slow_flow(:,:) + stream_flow(:,:) 
    28002768    CALL downstreamsum(nbpt, nbasmax, source, transport) 
    2801     IF ( do_rivertemp ) THEN 
    2802        source(:,:) = fast_flow(:,:)*fast_temp(:,:) + slow_flow(:,:)*slow_temp(:,:) +  & 
     2769    source(:,:) = fast_flow(:,:)*fast_temp(:,:) + slow_flow(:,:)*slow_temp(:,:) +  & 
    28032770            &                  stream_flow(:,:)*stream_temp(:,:) 
    2804        CALL downstreamsum(nbpt, nbasmax, source, transport_temp) 
    2805     ENDIF 
     2771    CALL downstreamsum(nbpt, nbasmax, source, transport_temp) 
    28062772    !- 
    28072773    !- Do the floodings - First initialize 
     
    28682834               & slow_flow(ig,ib) 
    28692835          ! 
    2870           IF ( do_rivertemp ) THEN 
    2871              oldstream = stream_reservoir(ig, ib) * stream_temp(ig,ib) 
    2872           ENDIF 
     2836          oldstream = stream_reservoir(ig, ib) * stream_temp(ig,ib) 
    28732837          ! 
    28742838          stream_reservoir(ig,ib) = stream_reservoir(ig,ib) + flood_flow(ig,ib) + transport(ig,ib) - & 
    28752839               & stream_flow(ig,ib) - return_swamp(ig,ib) - floods(ig,ib) 
    28762840          ! 
    2877           ! Code d'Eliott 
    2878           ! 
    2879           IF ( do_rivertemp ) THEN 
     2841          ! Diagnostics of the stream reservoir  
     2842          ! 
     2843          IF ( routing_area(ig,ib) > zero ) THEN 
     2844             ! 1000 to transform kg into m^3 
     2845             htmp = stream_reservoir(ig,ib)*1000/routing_area(ig,ib) 
     2846             ewh(ig,ib) = 1.0/(1.0+htmp*hscale) 
     2847          ELSE 
     2848             ewh(ig,ib) = 1.0 
     2849          ENDIF 
     2850          ! 
     2851          !reste du calcul 
     2852          ! 
     2853          krelax = ewh(ig,ib) 
     2854          ! 
     2855          den = 1.0/(1.0+dt_routing*krelax) 
     2856          IF ( stream_reservoir(ig,ib) > 1.e-6 ) THEN 
     2857             oldtemp = stream_temp(ig,ib) 
     2858             stream_temp(ig,ib) = den * dt_routing * krelax * fast_temp(ig,ib) + & 
     2859                  & den * oldstream/stream_reservoir(ig,ib) + & 
     2860                  & den * transport_temp(ig, ib)/stream_reservoir(ig,ib) - & 
     2861                  & den * oldtemp*stream_flow(ig,ib)/stream_reservoir(ig,ib) 
    28802862             ! 
    2881              ! Diagnostics of the stream reservoir  
    2882              ! 
    2883              IF ( routing_area(ig,ib) > zero ) THEN 
    2884                 ! 1000 to transform kg into m^3 
    2885                 htmp = stream_reservoir(ig,ib)*1000/routing_area(ig,ib) 
    2886                 ewh(ig,ib) = 1.0/(1.0+htmp*hscale) 
    2887              ELSE 
    2888                 ewh(ig,ib) = 1.0 
    2889              ENDIF 
    2890              ! 
    2891              IF (stream_reservoir(ig,ib) > zero ) THEN 
    2892                 ! Residence time in seconds 
    2893                 restime = stream_resid(ig,ib)*stream_tcst 
    2894                 wrr(ig,ib) =ABS((restime-minrestime)/(maxrestime-minrestime)) 
    2895              ELSE 
    2896                 wrr(ig,ib) = 1.0 
    2897              ENDIF 
    2898              ! 
    2899              !reste du calcul 
    2900              ! 
    2901              IF ( origformula ) THEN 
    2902                 IF (stream_reservoir(ig,ib) .LT. 1.) THEN 
    2903                    ! 
    2904                    stream_temp(ig,ib) = max(stempdiag(ig,1), ZeroCelsius) 
    2905                    !  
    2906                 ELSE 
    2907                    ! 
    2908                    stream_temp(ig,ib) = oldstream/stream_reservoir(ig,ib) + & 
    2909                         & transport_temp(ig, ib)/stream_reservoir(ig,ib) - & 
    2910                         & stream_temp(ig,ib)*stream_flow(ig,ib)/stream_reservoir(ig,ib) 
    2911                 ENDIF 
    2912              ELSE 
    2913                 krelax = ewh(ig,ib) 
    2914                 ! 
    2915                 den = 1.0/(1.0+dt_routing*krelax) 
    2916                 IF ( stream_reservoir(ig,ib) > 1.e-6 ) THEN 
    2917                    oldtemp = stream_temp(ig,ib) 
    2918                    stream_temp(ig,ib) = den * dt_routing * krelax * fast_temp(ig,ib) + & 
    2919                         & den * oldstream/stream_reservoir(ig,ib) + & 
    2920                         & den * transport_temp(ig, ib)/stream_reservoir(ig,ib) - & 
    2921                         & den * oldtemp*stream_flow(ig,ib)/stream_reservoir(ig,ib) 
    2922                    ! 
    2923                    !Stream_temp [K], stream_reservoir [kg], WaterCp [J/g/K] yields tendencies in GJ/s 
    2924                    !  
    2925                    stemp_total_tend(ig,ib) = WaterCp*1.e-6*(stream_temp(ig,ib)*stream_reservoir(ig,ib) - oldstream)/dt_routing 
    2926                    stemp_advec_tend(ig,ib) = WaterCp*1.e-6*(transport_temp(ig, ib) - oldtemp*stream_flow(ig,ib))/dt_routing 
    2927                    stemp_relax_tend(ig,ib) = WaterCp*1.e-6*stream_reservoir(ig,ib)*krelax*(fast_temp(ig,ib)-stream_temp(ig,ib)) 
    2928                 ELSE 
    2929                    stream_temp(ig,ib) = MAX(fast_temp(ig,ib), ZeroCelsius) 
    2930                    stemp_total_tend(ig,ib) = zero 
    2931                    stemp_advec_tend(ig,ib) = zero 
    2932                    stemp_relax_tend(ig,ib) = zero 
    2933                 ENDIF 
    2934              ENDIF 
     2863             !Stream_temp [K], stream_reservoir [kg], WaterCp [J/g/K] yields tendencies in GJ/s 
     2864             !  
     2865             stemp_total_tend(ig,ib) = WaterCp*1.e-6*(stream_temp(ig,ib)*stream_reservoir(ig,ib) - oldstream)/dt_routing 
     2866             stemp_advec_tend(ig,ib) = WaterCp*1.e-6*(transport_temp(ig, ib) - oldtemp*stream_flow(ig,ib))/dt_routing 
     2867             stemp_relax_tend(ig,ib) = WaterCp*1.e-6*stream_reservoir(ig,ib)*krelax*(fast_temp(ig,ib)-stream_temp(ig,ib)) 
     2868          ELSE 
     2869             stream_temp(ig,ib) = MAX(fast_temp(ig,ib), ZeroCelsius) 
     2870             stemp_total_tend(ig,ib) = zero 
     2871             stemp_advec_tend(ig,ib) = zero 
     2872             stemp_relax_tend(ig,ib) = zero 
    29352873          ENDIF 
    29362874          ! 
     
    32643202             IF (HTUdiag_loc(ig,im) > 0 .AND. HTUdiag_loc(ig,im) .EQ. ib ) THEN 
    32653203                HTUhgmon(ig,im) = fast_flow(ig,ib) + slow_flow(ig,ib) + stream_flow(ig,ib) 
    3266                 IF ( do_rivertemp ) THEN 
    3267                    HTUtempmon(ig,im) = stream_temp(ig,ib) 
    3268                 ENDIF 
     3204                HTUtempmon(ig,im) = stream_temp(ig,ib) 
    32693205             ENDIF 
    32703206          ENDDO 
     
    32723208          IF (hydrodiag(ig) == ib) THEN 
    32733209             hydrographs(ig) = fast_flow(ig,ib) + slow_flow(ig,ib) + stream_flow(ig,ib) 
    3274              IF ( do_rivertemp ) THEN 
    3275                 hydrotemp(ig) = stream_temp(ig,ib) 
    3276              ENDIF 
     3210             hydrotemp(ig) = stream_temp(ig,ib) 
    32773211             slowflow_diag(ig) = slowflow_diag(ig) + slow_flow(ig,ib) 
    32783212          ENDIF 
     
    33373271  ! 
    33383272!! ================================================================================================================================ 
    3339 !! SUBROUTINE   : groundwater_temp 
     3273!! SUBROUTINE   : groundwatertemp 
    33403274!! 
    33413275!>\BRIEF        : This subroutine computes the temperature of the groundwater leaving the HTU 
     
    33543288!_ ================================================================================================================================ 
    33553289    !- 
    3356   SUBROUTINE groudwatertemp(nbpt, nbasmax, nslm, stempdiag, diaglev, fast_temp, slow_temp) 
     3290  SUBROUTINE groundwatertemp(nbpt, nbasmax, nl, tempdiag, lev, dlz, fast_temp, slow_temp) 
    33573291    ! INPUT 
    3358     INTEGER(i_std), INTENT(in)                   :: nbpt, nbasmax, nslm 
    3359     REAL(r_std), INTENT(in)                      :: stempdiag(nbpt,nslm) 
    3360     REAL(r_std), INTENT(in)                      :: diaglev(nslm) 
     3292    INTEGER(i_std), INTENT(in)                   :: nbpt, nbasmax, nl 
     3293    REAL(r_std), INTENT(in)                      :: tempdiag(nbpt,nl) 
     3294    REAL(r_std), INTENT(in)                      :: lev(nl), dlz(nl) 
    33613295    REAL(r_std), INTENT(inout)                   :: slow_temp(nbpt,nbasmax), fast_temp(nbpt,nbasmax) 
    33623296    ! OUTPUT 
    33633297    ! LOCAL 
    33643298    INTEGER(i_std)                               :: ig, ib, im 
    3365     REAL(r_std)                                  :: ft, st, fw, sw, ubnd, lbnd, dz 
    3366     LOGICAL, SAVE                                :: lowestt = .FALSE., alltop=.FALSE. 
    3367     ! 
    3368     lowestt=.FALSE. 
    3369     CALL getin_p('LOWESTT', lowestt) 
    3370     alltop=.FALSE. 
    3371     CALL getin_p('ALLTOPTT', alltop) 
    3372     ! 
    3373     DO ib=1,nbasmax 
    3374        DO ig=1,nbpt 
    3375           ft=zero 
    3376           st=zero 
    3377           fw=zero 
    3378           sw=zero 
    3379           ubnd=zero 
    3380           lbnd=diaglev(nslm)+(diaglev(nslm)+diaglev(nslm-1))*0.5 
    3381           ! The sums are weighted by the thickness of the soil layers ! 
    3382           DO im=1,ntemp_layer 
    3383              dz = ((diaglev(im)+diaglev(im+1))*0.5-ubnd) 
    3384              ft = ft + stempdiag(ig,im)*dz 
    3385              fw = fw + dz 
    3386              ubnd=(diaglev(im)+diaglev(im+1))*0.5 
    3387              ! 
    3388              dz = (lbnd-(diaglev(nslm-(im))+diaglev(nslm-(im)+1))*0.5) 
    3389              st = st + stempdiag(ig,nslm-(im-1))*dz 
    3390              sw = sw + dz 
    3391              lbnd = (diaglev(nslm-(im))+diaglev(nslm-(im)+1))*0.5 
     3299    REAL(r_std)                                  :: sw 
     3300    REAL(r_std)                                  :: rw(nl), dw(nl) 
     3301    LOGICAL, SAVE                                :: alltop=.FALSE. 
     3302    LOGICAL, SAVE                                :: FirstCall=.TRUE. 
     3303    ! 
     3304    IF ( FirstCall ) THEN 
     3305       !Config Key   = ROUTING_ALLTOPT 
     3306       !Config Desc  = Should drainage have the temperature of the top soil (0.3m) ? 
     3307       !Config Def   = False 
     3308       !Config Help  = The default behaviour of the scheme is that runoff has the temperature 
     3309       !Config Help    of the top 30 cm of soil. Drainage will have the temperature of the lowest 
     3310       !Config Help    soil layer (3-17m). If set to True this flag will give drainage the same 
     3311       !Config Help    temperature as runoff. 
     3312       !Config Units = Logical 
     3313       alltop=.FALSE. 
     3314       CALL getin_p('ROUTING_ALLTOPT', alltop) 
     3315       ! 
     3316       WRITE(numout,*) "Runoff will have the average soil temperature of layers from ", runofftempdepth(1),& 
     3317            &          " to ", runofftempdepth(2), "[m]" 
     3318       ! 
     3319       IF ( alltop ) THEN 
     3320          WRITE(numout,*) "Drainage will have the average soil temperature of layers from ", runofftempdepth(1),& 
     3321            &          " to ", runofftempdepth(2), "[m]" 
     3322       ELSE 
     3323          WRITE(numout,*) "Drainage will have the average soil temperature of layers from ", drainagetempdepth(1),& 
     3324               &          " to ", MIN(drainagetempdepth(2), SUM(dlz)), "[m]" 
     3325       ENDIF 
     3326       FirstCall=.FALSE. 
     3327    ENDIF 
     3328    ! 
     3329    CALL tempdepthweight(nl, dlz, runofftempdepth(1), runofftempdepth(2), rw) 
     3330    CALL tempdepthweight(nl, dlz, drainagetempdepth(1), MIN(drainagetempdepth(2), SUM(dlz)), dw) 
     3331    ! 
     3332    slow_temp(:,:) = zero 
     3333    fast_temp(:,:) = zero 
     3334    ! Compute for each HTU the temperature of runoff and drainage water. 
     3335    DO im = 1,nl 
     3336       DO ib=1,nbasmax 
     3337          DO ig=1,nbpt 
     3338             fast_temp(ig,ib) = fast_temp(ig,ib) + tempdiag(ig,im)*rw(im) 
     3339             ! The option to have drainage water at the same temperature as runoff 
     3340             IF ( alltop ) THEN 
     3341                slow_temp(ig,ib) = slow_temp(ig,ib) + tempdiag(ig,im)*rw(im) 
     3342             ELSE 
     3343                slow_temp(ig,ib) = slow_temp(ig,ib) + tempdiag(ig,im)*dw(im) 
     3344             ENDIF 
    33923345          ENDDO 
    3393           ! 
    3394           IF ( lowestt ) THEN 
    3395              slow_temp(ig,ib) = stempdiag(ig,nslm) 
    3396           ELSE 
    3397              slow_temp(ig,ib) = st/sw 
    3398           ENDIF 
    3399           fast_temp(ig,ib) = ft/fw 
    3400           IF ( alltop ) THEN 
    3401              slow_temp(ig,ib) = fast_temp(ig,ib) 
    3402           ENDIF 
    34033346       ENDDO 
    34043347    ENDDO 
    3405   END SUBROUTINE groudwatertemp 
     3348 
     3349  END SUBROUTINE groundwatertemp 
     3350 
     3351  SUBROUTINE tempdepthweight(n, dz, top, bot, w) 
     3352    ! Input 
     3353    INTEGER(i_std), INTENT(in)                   :: n 
     3354    REAL(r_std), INTENT(in)                      :: dz(n) 
     3355    REAL(r_std), INTENT(in)                      :: top, bot 
     3356    ! Output 
     3357    REAL(r_std), INTENT(out)                     :: w(n) 
     3358    ! Local 
     3359    INTEGER(i_std)                               :: i 
     3360    REAL(r_std)                                  :: sw 
     3361    w(:) = zero 
     3362    sw = zero 
     3363    DO i=1,n 
     3364       w(i) = MAX(zero, MIN(sw+dz(i), bot) - MAX(top, sw)) 
     3365       sw = sw + dz(i) 
     3366    ENDDO 
     3367    w(:) = w(:)/(bot-top) 
     3368  END SUBROUTINE tempdepthweight 
     3369 
    34063370!! ================================================================================================================================ 
    34073371!! SUBROUTINE   : downstreamsum 
  • 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  
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_sechiba/sechiba.f90

    r7709 r7710  
    1313!! processes as well. 
    1414!! 
    15 !!\n DESCRIPTION  : :: shumdiag, :: litterhumdiag and :: stempdiag are not  
     15!!\n DESCRIPTION  : :: shumdiag, :: litterhumdiag and :: stempdiag :: ftempdiag are not  
    1616!! saved in the restart file because at the first time step because they  
    1717!! are recalculated. However, they must be saved as they are in slowproc  
     
    148148  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)  :: stempdiag      !! Temperature which controls canopy evolution (K) 
    149149!$OMP THREADPRIVATE(stempdiag) 
     150  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)  :: ftempdiag      !! Temperature over the full soil column for river temperature (K) 
     151!$OMP THREADPRIVATE(ftempdiag) 
    150152  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)  :: qsintveg       !! Water on vegetation due to interception  
    151153                                                                     !! @tex $(kg m^{-2})$ @endtex 
     
    511513    CALL thermosoil_initialize (kjit, kjpindex, rest_id, mcs,  & 
    512514         temp_sol_new, snow,       shumdiag_perma,        & 
    513          soilcap,      soilflx,    stempdiag,             & 
     515         soilcap,      soilflx,    stempdiag, ftempdiag,             & 
    514516         gtemp,               & 
    515517         mc_layh,  mcl_layh,   soilmoist,       njsc ,     & 
     
    525527            kjit,        kjpindex,       index,                 & 
    526528            rest_id,     hist_id,        hist2_id,   lalo,      & 
    527             neighbours,  resolution,     contfrac,   stempdiag, & 
     529            neighbours,  resolution,     contfrac,   stempdiag, ftempdiag, & 
    528530            soiltile,    irrig_frac,     veget_max,  irrigated_next, & 
    529531            returnflow,  reinfiltration, irrigation, riverflow, & 
     
    786788         index, indexgrnd, mcs, & 
    787789         temp_sol_new, snow, soilcap, soilflx, & 
    788          shumdiag_perma, stempdiag, ptnlev1, rest_id, hist_id, hist2_id, & 
     790         shumdiag_perma, stempdiag, ftempdiag, ptnlev1, rest_id, hist_id, hist2_id, & 
    789791         snowdz,snowrho,snowtemp,gtemp,pb,& 
    790792         mc_layh, mcl_layh, soilmoist, njsc,frac_snow_veg,frac_snow_nobio,totfrac_nobio,temp_sol_add, & 
     
    797799       CALL routing_wrapper_main (kjit, kjpindex, index, & 
    798800            & lalo, neighbours, resolution, contfrac, totfrac_nobio, veget_max, floodout, runoff, & 
    799             & drainage, transpot, precip_rain, humrel, k_litt, flood_frac, flood_res, & 
    800             & stempdiag, reinf_slope, returnflow, reinfiltration, irrigation, riverflow, coastalflow, rest_id, hist_id, hist2_id, & 
     801            & drainage, transpot, precip_rain, humrel, k_litt, flood_frac, flood_res, stempdiag, & 
     802            & ftempdiag, reinf_slope, returnflow, reinfiltration, irrigation, riverflow, coastalflow, rest_id, hist_id, hist2_id, & 
    801803            & soiltile, root_deficit, irrigated_next, irrig_frac, fraction_aeirrig_sw) 
    802804    ELSE 
     
    17531755    IF (ier /= 0) CALL ipslerr_p(3,'sechiba_init','Pb in alloc for stempdiag','','') 
    17541756 
     1757    ALLOCATE (ftempdiag(kjpindex, ngrnd),stat=ier) 
     1758    IF (ier /= 0) CALL ipslerr_p(3,'sechiba_init','Pb in alloc for ftempdiag','','') 
     1759 
    17551760    ALLOCATE (co2_flux(kjpindex,nvm),stat=ier) 
    17561761    IF (ier /= 0) CALL ipslerr_p(3,'sechiba_init','Pb in alloc for co2_flux','','') 
     
    20122017    IF ( ALLOCATED (deadleaf_cover)) DEALLOCATE (deadleaf_cover) 
    20132018    IF ( ALLOCATED (stempdiag)) DEALLOCATE (stempdiag) 
     2019    IF ( ALLOCATED (ftempdiag)) DEALLOCATE (ftempdiag) 
    20142020    IF ( ALLOCATED (co2_flux)) DEALLOCATE (co2_flux) 
    20152021    IF ( ALLOCATED (shumdiag)) DEALLOCATE (shumdiag) 
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_sechiba/thermosoil.f90

    r7515 r7710  
    229229  !! \n 
    230230  !_ ============================================================================================================================== 
    231   SUBROUTINE thermosoil_initialize (kjit,          kjpindex,   rest_id,          mcs,     & 
    232                                     temp_sol_new,  snow,       shumdiag_perma,            & 
    233                                     soilcap,       soilflx,    stempdiag,                & 
     231  SUBROUTINE thermosoil_initialize (kjit,          kjpindex,   rest_id,          mcs,       & 
     232                                    temp_sol_new,  snow,       shumdiag_perma,              & 
     233                                    soilcap,       soilflx,    stempdiag,        ftempdiag, & 
    234234                                    gtemp,                   & 
    235235                                    mc_layh,       mcl_layh,   tmc_layh,        njsc,     & 
     
    263263    REAL(r_std),DIMENSION (kjpindex), INTENT (out)        :: soilflx          !! apparent soil heat flux considering snow and soil surface (W m-2) 
    264264    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (out)   :: stempdiag        !! temperature profile on the levels in hydrol(K) 
     265    REAL(r_std),DIMENSION (kjpindex,ngrnd), INTENT (out)  :: ftempdiag        !! temperature profile on full depth for stream temperature (K) 
    265266    REAL(r_std),DIMENSION (kjpindex),INTENT(out)          :: gtemp            !! First soil layer temperature 
    266267 
     
    519520    ! Send out the temperature profile on the first nslm levels(the levels treated in hydrol) 
    520521    stempdiag(:,:) = ptn(:,1:nslm) 
     522    ftempdiag(:,:) = ptn(:,1:ngrnd) 
    521523     
    522524 
     
    583585       index, indexgrnd, mcs, & 
    584586       temp_sol_new, snow, soilcap, soilflx, & 
    585        shumdiag_perma, stempdiag, ptnlev1, rest_id, hist_id, hist2_id, & 
     587       shumdiag_perma, stempdiag, ftempdiag, ptnlev1, rest_id, hist_id, hist2_id, & 
    586588       snowdz,snowrho,snowtemp,gtemp,pb,& 
    587589       mc_layh, mcl_layh, tmc_layh, njsc, frac_snow_veg,frac_snow_nobio,totfrac_nobio,temp_sol_add, & 
     
    646648                                                                              !! see EQ3. 
    647649    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (out)   :: stempdiag        !! temperature profile @tex ($K$) @endtex 
     650    REAL(r_std),DIMENSION (kjpindex,ngrnd), INTENT (out)  :: ftempdiag        !! temperature profile @tex ($K$) @endtex 
    648651    REAL(r_std),DIMENSION (kjpindex), INTENT(inout)       :: lambda_snow      !! Coefficient of the linear extrapolation of surface temperature  
    649652    REAL(r_std),DIMENSION (kjpindex,nsnow), INTENT (inout):: cgrnd_snow       !! Integration coefficient for snow numerical scheme 
     
    768771    !! Initialize output arguments to be used in sechiba 
    769772    ptnlev1(:) = ptn(:,1) 
     773 
     774    !! Write the new temperature in the full in a the diagnostic variable. 
     775    ftempdiag(:,:) = ptn(:,1:ngrnd) 
    770776 
    771777    !! Surface temperature is forced to zero celcius if its value is larger than melting point 
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_xml/field_def_orchidee.xml

    r7709 r7710  
    252252    <field id="riverflow_cpl" name="riverflow_cpl" long_name="River flow to the oceans, variable distributed over a time period before sent to ocean." unit="m^3/s"/> 
    253253    <field id="hydrographs" name="hydrographs" long_name="Hydrographs of gridbox outflow" unit="m^3/s"/> 
     254    <field id="hydrotemp" name="hydrotemp" long_name="River temperature at representative gridbox outflow" unit="K"/> 
     255    <field id="htutempmon" name="HTUstreamtemp" long_name="River temperature at monitored HTUs" unit="K" grid_ref="grid_nbasmon"/> 
    254256    <field id="htuhgmon" name="htuhgmon" long_name="Hydrographs at monitored HTUs" unit="m^3/s" grid_ref="grid_nbasmon"/> 
     257    <field id="streamlimit" long_name="Number of HTU with stream limiter" unit="-"/> 
     258    <field id="StreamT_TotTend" name="ST_TotTend" long_name="Total Stream Energy Tendency" unit="GJ/s" grid_ref="grid_nbhtu"/> 
     259    <field id="StreamT_AdvTend" name="ST_AdvTend" long_name="Stream Energy Advection Tendency" unit="GJ/s" grid_ref="grid_nbhtu"/> 
     260    <field id="StreamT_RelTend" name="ST_RelTend" long_name="Stream Energy Relaxation Tendency" unit="GJ/s" grid_ref="grid_nbhtu"/> 
    255261    <field id="fastr" name="fastr" long_name="Fast flow reservoir" unit="kg/m^2"/> 
    256262    <field id="slowr" name="slowr" long_name="Slow flow reservoir" unit="kg/m^2"/> 
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_xml/file_def_orchidee.xml

    r7709 r7710  
    7474    <field field_ref="riversret" level="2"/> 
    7575    <field field_ref="hydrographs" level="2"/> 
    76     <field field_ref="htuhgmon" name="HTUhydrographs" grid_ref="grid_nbasmon_out" level="2"/>  
     76    <field field_ref="htuhgmon" name="HTUhydrographs" grid_ref="grid_nbasmon_out" level="2"/> 
     77    <field field_ref="hydrotemp" name="RiverTemp" level="2"/> 
     78    <field field_ref="htutempmon" name="HTUTemp" grid_ref="grid_nbasmon_out" level="2"/> 
     79    <field field_ref="streamlimit" level="2"/> 
    7780    <field field_ref="vevapnu" name="evapnu" level="0" unit="mm/d" > @vevapnu*86400  </field> 
    7881    <field field_ref="evap_bare_lim" level="2"/> 
Note: See TracChangeset for help on using the changeset viewer.