Changeset 7199


Ignore:
Timestamp:
2021-05-27T14:35:32+02:00 (3 years ago)
Author:
agnes.ducharne
Message:

Inclusion of r6499, r6505, r6508 of the trunk, for consistent soil parameters in hydrola and thermosoil, as detailed in ticket #604. Checked step by step by 5d simulations on jean-zay: the only changes are weak and due to replacing poros=0.41 by variable mcs.

Location:
branches/ORCHIDEE_2_2/ORCHIDEE
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • branches/ORCHIDEE_2_2/ORCHIDEE/orchidee.default

    r6393 r7199  
    14061406 
    14071407# DRY_SOIL_HEAT_COND ([W.m^{-2}.K^{-1}] ) :  Dry soil Thermal Conductivity of soils     {OK_SECHIBA} 
    1408 DRY_SOIL_HEAT_COND =  0.40   
    1409  
    1410 # WET_SOIL_HEAT_CAPACITY ([J.m^{-3}.K^{-1}]) :  Wet soil Heat capacity of soils         {OK_SECHIBA} 
    1411 WET_SOIL_HEAT_CAPACITY =  3.03e+6  
    1412  
    1413 # WET_SOIL_HEAT_COND ([W.m^{-2}.K^{-1}]) :  Wet soil Thermal Conductivity of soils      {OK_SECHIBA } 
    1414 WET_SOIL_HEAT_COND =  1.89   
     1408DRY_SOIL_HEAT_COND =  0.40  
    14151409 
    14161410# SNOW_HEAT_COND ([W.m^{-2}.K^{-1}]) :  Thermal Conductivity of snow    {OK_SECHIBA  } 
     
    14411435OK_FREEZE_THAW_LATENT_HEAT =  FALSE   
    14421436 
    1443 # POROS ([-] ) :  Soil porosity         {OK_SECHIBA} 
    1444 POROS =  0.41  
    1445  
    14461437# fr_dT ([K] ) :  Freezing window       {OK_SECHIBA} 
    14471438fr_dT =  2.0  
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_parameters/constantes_soil_var.f90

    r6954 r7199  
    8080                                                        !! @tex $(W.m^{-2}.K^{-1})$ @endtex 
    8181!$OMP THREADPRIVATE(so_cond_dry) 
    82   REAL(r_std), SAVE :: so_capa_wet = 3.03e+6            !! Wet soil Heat capacity of soils  
    83                                                         !! @tex $(J.m^{-3}.K^{-1})$ @endtex 
    84 !$OMP THREADPRIVATE(so_capa_wet) 
    85   REAL(r_std), SAVE :: so_cond_wet = 1.89               !! Wet soil Thermal Conductivity of soils  
    86                                                         !! @tex $(W.m^{-2}.K^{-1})$ @endtex  
    87 !$OMP THREADPRIVATE(so_cond_wet) 
    8882  REAL(r_std), SAVE :: sn_cond = 0.3                    !! Thermal Conductivity of snow  
    8983                                                        !! @tex $(W.m^{-2}.K^{-1})$ @endtex   
     
    163157 & (/ 0.1_r_std, 0.1_r_std, 0.1_r_std /)                               !!  @tex $(m^{3} m^{-3})$ @endtex 
    164158 
    165   REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: SMCMAX_fao = &          !! porosity 
    166  & (/ 0.41_r_std, 0.43_r_std, 0.41_r_std /)                            !! & (/ 0.434_r_std, 0.439_r_std, 0.465_r_std /) !!noah lsm 
    167  
    168159  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: QZ_fao = &              !! QUARTZ CONTENT (SOIL TYPE DEPENDENT) 
    169160 & (/ 0.60_r_std, 0.40_r_std, 0.35_r_std /)                            !! Peters et al [1998] 
     
    247238 &    0.1_r_std, 0.1_r_std, 0.1_r_std, 0.1_r_std, & 
    248239 &    0.1_r_std /) ! oxisols 
    249  
    250   REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: SMCMAX_usda = &          !! porosity for thermosoil 
    251  & (/ 0.43_r_std, 0.41_r_std, 0.41_r_std, 0.45_r_std, & 
    252  &    0.46_r_std, 0.43_r_std, 0.39_r_std, 0.43_r_std, & 
    253  &    0.41_r_std, 0.38_r_std, 0.36_r_std, 0.38_r_std, & 
    254  &    0.503_r_std  /) ! oxisols 
    255240  
    256241  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: QZ_usda = &              !! QUARTZ CONTENT (SOIL TYPE DEPENDENT) 
     
    283268  LOGICAL, SAVE        :: read_reftemp                !! Flag to initialize soil temperature using climatological temperature 
    284269!$OMP THREADPRIVATE(read_reftemp) 
    285   REAL(r_std), SAVE    :: poros                       !! Soil porosity (from USDA classification, mean value)(-) 
    286 !$OMP THREADPRIVATE(poros) 
    287270  REAL(r_std), SAVE    :: fr_dT                       !! Freezing window (K) 
    288271!$OMP THREADPRIVATE(fr_dT) 
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_parameters/constantes_var.f90

    r6393 r7199  
    380380  !! Heat capacity 
    381381  REAL(r_std), PARAMETER :: capa_ice = 2.228*1.E3       !! Heat capacity of ice (J/kg/K) 
    382   REAL(r_std), SAVE      :: so_capa_ice                 !! Heat capacity of saturated frozen soil (J/K/m3) 
    383 !$OMP THREADPRIVATE(so_capa_ice) 
    384382  REAL(r_std), PARAMETER :: rho_water = 1000.           !! Density of water (kg/m3) 
    385383  REAL(r_std), PARAMETER :: rho_ice = 920.              !! Density of ice (kg/m3) 
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_sechiba/thermosoil.f90

    r6954 r7199  
    145145  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:) :: profil_froz              !! Frozen fraction of the soil on hydrological levels (-) 
    146146!$OMP THREADPRIVATE(profil_froz) 
    147   REAL(r_std),ALLOCATABLE, SAVE, DIMENSION (:) :: e_soil_lat                  !! Accumulated latent heat for the whole soil (J) 
     147  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION (:) :: e_soil_lat                  !! Latent heat released or consumed in the freezing/thawing processes summed vertically 
     148                                                                              !! for the whole soil (J/m2) and on the whole simulation to check/correct energy conservation 
    148149!$OMP THREADPRIVATE(e_soil_lat) 
    149   REAL(r_std),ALLOCATABLE, SAVE, DIMENSION (:,:) :: pcappa_supp               !! Additional heat capacity due to soil freezing for each soil layer (J/K) 
     150  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION (:,:) :: pcappa_supp               !! Additional surfacic heat capacity due to soil freezing for each soil layer (J/K/m2) 
    150151!$OMP THREADPRIVATE(pcappa_supp)     
    151152  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: dz5                      !! Used for numerical calculation [-] 
     
    153154  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: mcs                      !! Saturation humidity [m3/m3] 
    154155!$OMP THREADPRIVATE(mcs) 
    155   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: SMCMAX                   !! Soil porosity [m3/m3] 
    156 !$OMP THREADPRIVATE(SMCMAX) 
    157156  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: QZ                       !! quartz content [-] 
    158157!$OMP THREADPRIVATE(QZ) 
    159158  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: so_capa_dry_ns           !! Dry soil Heat capacity of soils,J.m^{-3}.K^{-1}  
    160159!$OMP THREADPRIVATE(so_capa_dry_ns) 
     160  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: so_capa_ice              !! Heat capacity of saturated frozen soil (J/K/m3) 
     161!$OMP THREADPRIVATE(so_capa_ice)    
    161162  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:) :: mc_layt                  !! Volumetric soil moisture (liquid+ice) (m3/m3) on the thermodynamical levels at interface 
    162163!$OMP THREADPRIVATE(mc_layt) 
     
    271272 
    272273    !! 0.4 Local variables 
    273     INTEGER(i_std)                                        :: ier, i, jg 
     274    INTEGER(i_std)                                        :: ier, i, jg, jsc 
    274275    LOGICAL                                               :: calculate_coef   !! Local flag to initialize variables by call to thermosoil_coef    
    275276!_ ================================================================================================================================ 
     
    372373    IF (ier /= 0) CALL ipslerr_p(3,'thermosoil_initialize', 'Error in allocation of mcs','','') 
    373374 
    374     ALLOCATE (SMCMAX(nscm),stat=ier) 
    375     IF (ier /= 0) CALL ipslerr_p(3,'thermosoil_initialize', 'Error in allocation of SMCMAX','','') 
    376  
    377375    ALLOCATE (QZ(nscm),stat=ier) 
    378376    IF (ier /= 0) CALL ipslerr_p(3,'thermosoil_initialize', 'Error in allocation of QZ','','') 
     
    380378    ALLOCATE (so_capa_dry_ns(nscm),stat=ier) 
    381379    IF (ier /= 0) CALL ipslerr_p(3,'thermosoil_initialize', 'Error in allocation of so_capa_dry_ns','','') 
     380     
     381    ALLOCATE (so_capa_ice(nscm),stat=ier) 
     382    IF (ier /= 0) CALL ipslerr_p(3,'thermosoil_initialize', 'Error in allocation of so_capa_ice','','') 
    382383 
    383384 
     
    385386    SELECTCASE (nscm) 
    386387    CASE (3) 
    387        SMCMAX(:) = SMCMAX_fao(:) 
    388388       QZ(:) = QZ_fao(:) 
    389389       so_capa_dry_ns(:) = so_capa_dry_ns_fao(:) 
    390390       mcs(:) = mcs_fao(:) 
    391391    CASE (13) !Salma changed from 12 to 13 for the new class Oxisols 
    392        SMCMAX(:) = SMCMAX_usda(:) 
    393       QZ(:) = QZ_usda(:) 
     392       QZ(:) = QZ_usda(:) 
    394393       so_capa_dry_ns(:) = so_capa_dry_ns_usda(:) 
    395394       mcs(:) = mcs_usda(:) 
     
    505504 
    506505    ! Calculate so_capa_ice 
    507     so_capa_ice = so_capa_dry + poros*capa_ice*rho_ice 
    508     IF (printlev>=2) WRITE(numout,*) 'Calculation of so_capa_ice=', so_capa_ice,' using poros=',poros,' and capa_ice=',capa_ice 
     506    DO jsc = 1, nscm   
     507       so_capa_ice(jsc) = so_capa_dry + mcs(jsc)*capa_ice*rho_ice  
     508    END DO 
     509    IF (printlev>=2) WRITE(numout,*) 'Calculation of so_capa_ice(:)=', so_capa_ice(:),' and capa_ice=',capa_ice 
    509510     
    510511    ! Computing some usefull constants for the numerical scheme 
     
    12571258!================================================================================================================================ 
    12581259 
    1259   SUBROUTINE thermosoil_cond (kjpindex, njsc, smc, qz, smcmax, sh2o, cnd) 
     1260  SUBROUTINE thermosoil_cond (kjpindex, njsc, smc, qz, sh2o, cnd) 
    12601261 
    12611262    !! 0. Variables and parameter declaration 
     
    12651266    INTEGER(i_std), DIMENSION (kjpindex), INTENT (in)          :: njsc          !! Index of the dominant soil textural class in the grid cell (1-nscm, unitless) 
    12661267    REAL(r_std), DIMENSION (kjpindex,ngrnd), INTENT(IN)        :: smc           !! Volumetric Soil Moisture Content (m3/m3) 
    1267     REAL(r_std), DIMENSION (nscm), INTENT(IN)                  :: qz            !! Quartz Content (Soil Type Dependent) (0-1)                
    1268     REAL(r_std), DIMENSION (nscm), INTENT(IN)                  :: smcmax        !! Soil Porosity (0-1) 
     1268    REAL(r_std), DIMENSION (nscm), INTENT(IN)                  :: qz            !! Quartz Content (Soil Type Dependent) (0-1) 
    12691269    REAL(r_std), DIMENSION (kjpindex,ngrnd), INTENT(IN)        :: sh2o          !! Unfrozen Soil Moisture Content; Frozen Soil Moisture = smc - sh2o 
    12701270     
     
    12971297 
    12981298      !! 1.1. Dry density (Kg/m3) and Dry thermal conductivity (W.M-1.K-1) 
    1299       gammd = (1. - smcmax(jst))*2700. 
     1299      gammd = (1. - mcs(jst))*2700. 
    13001300      thkdry = (0.135* gammd+ 64.7)/ (2700. - 0.947* gammd) 
    13011301 
     
    13121312      DO jg = 1,ngrnd       
    13131313        !! 1.4. saturation ratio 
    1314         satratio(ji,jg) = smc(ji,jg) / smcmax(jst) 
     1314        satratio(ji,jg) = smc(ji,jg) / mcs(jst) 
    13151315     
    13161316        !! 1.5. Saturated Thermal Conductivity (thksat) 
    13171317        IF ( smc(ji,jg) > min_sechiba ) THEN 
    13181318           xunfroz(ji,jg) = sh2o(ji,jg) / smc(ji,jg)   ! Unfrozen Fraction (From i.e., 100%Liquid, to 0. (100% Frozen)) 
    1319            xu(ji,jg) = xunfroz(ji,jg) * smcmax(jst)  ! Unfrozen volume for saturation (porosity*xunfroz) 
    1320            thksat(ji,jg) = thks ** (1. - smcmax(jst))* THKICE ** (smcmax(jst) - xu(ji,jg))* THKW ** (xu(ji,jg)) 
     1319           xu(ji,jg) = xunfroz(ji,jg) * mcs(jst)  ! Unfrozen volume for saturation (porosity*xunfroz) 
     1320           thksat(ji,jg) = thks ** (1. - mcs(jst))* THKICE ** (mcs(jst) - xu(ji,jg))* THKW ** (xu(ji,jg)) 
    13211321        ELSE 
    13221322           ! this value will not be used since ake=0 for this case 
     
    16221622    REAL                                                :: xx         !! Unfrozen fraction of the soil 
    16231623    REAL(r_std), DIMENSION(kjpindex)                    :: snow_h 
    1624     REAL(r_std), DIMENSION(kjpindex,ngrnd)              :: zx1, zx2     
    1625     REAL                                                :: cap_iw     !! Heat capacity of ice/water mixture  
     1624    REAL(r_std), DIMENSION(kjpindex,ngrnd)              :: zx1, zx2 
    16261625    INTEGER                                             :: ji,jg 
    16271626    INTEGER                                             :: jst 
     
    16521651            profil_froz(ji,jg) = 1. 
    16531652            pcappa_supp(ji,jg)= 0. 
    1654             pcapa(ji, jg) = so_capa_dry_ns(jst) * (1-mcs(jst)) + so_capa_ice * tmc_layt(ji,jg) / mille / dlt(jg) 
     1653            pcapa(ji, jg) = so_capa_dry_ns(jst) * (1-mcs(jst)) + so_capa_ice(jst) * tmc_layt(ji,jg) / mille / dlt(jg) 
    16551654            rho_tot = rho_soil * (1-mcs(jst)) + rho_ice * tmc_layt(ji,jg) / mille / dlt(jg)  
    16561655            pcapa_spec(ji, jg) = pcapa(ji, jg) / rho_tot 
     
    16681667           profil_froz(ji,jg) = (1. - xx) 
    16691668 
    1670            ! net heat capacity of the ice/water mixture 
    1671            cap_iw = xx * so_capa_wet + (1.-xx) * so_capa_ice 
    16721669           IF (ok_freeze_thaw_latent_heat) THEN 
    16731670              pcapa(ji, jg) = so_capa_dry_ns(jst) * (1-mcs(jst)) + & 
    16741671                water_capa * tmc_layt(ji,jg)/mille / dlt(jg) * xx + & 
    1675                 so_capa_ice * tmc_layt(ji,jg) / mille/dlt(jg) * (1.-xx) + & 
    1676                 shum_ngrnd_perma(ji,jg)*poros*lhf*rho_water/fr_dT 
     1672                so_capa_ice(jst) * tmc_layt(ji,jg) / mille/dlt(jg) * (1.-xx) + & 
     1673                shum_ngrnd_perma(ji,jg)*mcs(jst)*lhf*rho_water/fr_dT 
    16771674           ELSE 
    16781675              pcapa(ji, jg) = so_capa_dry_ns(jst) * (1-mcs(jst)) + & 
    16791676                water_capa * tmc_layt(ji,jg)/mille / dlt(jg) * xx + & 
    1680                 so_capa_ice * tmc_layt(ji,jg) / mille/dlt(jg) * (1.-xx) 
     1677                so_capa_ice(jst) * tmc_layt(ji,jg) / mille/dlt(jg) * (1.-xx) 
    16811678           ENDIF 
    16821679 
     
    16861683           pcapa_spec(ji, jg) = pcapa(ji, jg) / rho_tot 
    16871684 
    1688            pcappa_supp(ji,jg)= shum_ngrnd_perma(ji,jg)*poros*lhf*rho_water/fr_dT*zx2(ji,jg)*dlt(jg) 
     1685           pcappa_supp(ji,jg)= shum_ngrnd_perma(ji,jg)*mcs(jst)*lhf*rho_water/fr_dT*zx2(ji,jg)*dlt(jg) 
    16891686 
    16901687         ENDIF 
     
    17131710    ! 
    17141711    IF (ok_freeze_thaw_latent_heat) THEN 
    1715         CALL thermosoil_cond (kjpindex, njsc, mc_layt, QZ, SMCMAX, mcl_layt*(1-profil_froz), pkappa) 
     1712        CALL thermosoil_cond (kjpindex, njsc, mc_layt, QZ, mcl_layt*(1-profil_froz), pkappa) 
    17161713    ELSE 
    1717         CALL thermosoil_cond (kjpindex, njsc, mc_layt, QZ, SMCMAX, mcl_layt, pkappa) 
     1714        CALL thermosoil_cond (kjpindex, njsc, mc_layt, QZ, mcl_layt, pkappa) 
    17181715    ENDIF 
    17191716 
     
    17731770      ENDDO 
    17741771 
    1775       CALL thermosoil_cond (kjpindex, njsc, mc_layt, QZ, SMCMAX, mcl_layt, pkappa) 
     1772      CALL thermosoil_cond (kjpindex, njsc, mc_layt, QZ, mcl_layt, pkappa) 
    17761773 
    17771774      IF (brk_flag == 1) THEN 
Note: See TracChangeset for help on using the changeset viewer.