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/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) 
Note: See TracChangeset for help on using the changeset viewer.