Changeset 7508


Ignore:
Timestamp:
2022-03-04T12:18:30+01:00 (2 years ago)
Author:
josefine.ghattas
Message:
  • Removed DRY_SOIL_HEAT_COND and related variable so_cond_dry
  • Replaced previous scalar variable so_capa_dry with vector variable so_capa_dry_ns and moved read from run.def to thermosoil. In the end, so_capa_dry_ns is renamed so_capa_dry.

See ticket #780

No change in results.

Location:
branches/ORCHIDEE_2_2/ORCHIDEE
Files:
4 edited

Legend:

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

    r7485 r7508  
    14021402PRINTLEV_modname =  PRINTLEV  
    14031403 
    1404 # DRY_SOIL_HEAT_CAPACITY ([J.m^{-3}.K^{-1}] ) :  Dry soil Heat capacity of soils        {OK_SECHIBA } 
    1405 DRY_SOIL_HEAT_CAPACITY =  1.80e+6  
    1406  
    1407 # 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  
    14101404# SNOW_HEAT_COND ([W.m^{-2}.K^{-1}]) :  Thermal Conductivity of snow    {OK_SECHIBA  } 
    14111405SNOW_HEAT_COND =  0.3  
     
    15581552BEDROCK_FLAG =  0  
    15591553 
     1554# DRY_SOIL_HEAT_CAPACITY ([J.m^{-3}.K^{-1}] ) :  Dry soil Heat capacity of soils        {OK_SECHIBA} 
     1555DRY_SOIL_HEAT_CAPACITY =  (1.47, 1.41, 1.34, 1.27, 1.21, 1.21, 1.18, 1.32, 1.23, 1.18, 1.15, 1.09, 1.09)*e+6  
     1556 
    15601557# THERMOSOIL_TPRO (Kelvin [K]) :  Initial soil temperature profile if not found in restart      {OK_SECHIBA} 
    15611558THERMOSOIL_TPRO =  280.  
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_parameters/constantes_soil.f90

    r7199 r7508  
    7070    ! Following initializations are only done for option impose_param 
    7171    IF ( ok_sechiba .AND. impose_param ) THEN 
    72  
    73        !Config Key   = DRY_SOIL_HEAT_CAPACITY 
    74        !Config Desc  = Dry soil Heat capacity of soils 
    75        !Config If    = OK_SECHIBA  
    76        !Config Def   = 1.80e+6 
    77        !Config Help  = Values taken from : PIELKE,'MESOSCALE METEOROLOGICAL MODELING',P.384. 
    78        !Config Units = [J.m^{-3}.K^{-1}]  
    79        CALL getin_p("DRY_SOIL_HEAT_CAPACITY",so_capa_dry) 
    80  
    81        !! Check parameter value (correct range) 
    82        IF ( so_capa_dry <= zero ) THEN 
    83           CALL ipslerr_p(error_level, "config_soil_parameters.", & 
    84                &     "Wrong parameter value for DRY_SOIL_HEAT_CAPACITY.", & 
    85                &     "This parameter should be positive. ", & 
    86                &     "Please, check parameter value in run.def. ") 
    87        END IF 
    88  
    89  
    90        !Config Key   = DRY_SOIL_HEAT_COND 
    91        !Config Desc  = Dry soil Thermal Conductivity of soils 
    92        !Config If    = OK_SECHIBA 
    93        !Config Def   = 0.40  
    94        !Config Help  = Values taken from : PIELKE,'MESOSCALE METEOROLOGICAL MODELING',P.384. 
    95        !Config Units = [W.m^{-2}.K^{-1}]  
    96        CALL getin_p("DRY_SOIL_HEAT_COND",so_cond_dry) 
    97  
    98        !! Check parameter value (correct range) 
    99        IF ( so_cond_dry <= zero ) THEN 
    100           CALL ipslerr_p(error_level, "config_soil_parameters.", & 
    101                &     "Wrong parameter value for DRY_SOIL_HEAT_COND.", & 
    102                &     "This parameter should be positive. ", & 
    103                &     "Please, check parameter value in run.def. ") 
    104        END IF 
    105  
    10672 
    10773       !Config Key   = SNOW_HEAT_COND 
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_parameters/constantes_soil_var.f90

    r7432 r7508  
    7575 
    7676  !! Parameters for soil thermodynamics 
    77  
    78   REAL(r_std), SAVE :: so_capa_dry = 1.80e+6            !! Dry soil Heat capacity of soils  
    79                                                         !! @tex $(J.m^{-3}.K^{-1})$ @endtex  
    80 !$OMP THREADPRIVATE(so_capa_dry) 
    81   REAL(r_std), SAVE :: so_cond_dry = 0.40               !! Dry soil Thermal Conductivity of soils 
    82                                                         !! @tex $(W.m^{-2}.K^{-1})$ @endtex 
    83 !$OMP THREADPRIVATE(so_cond_dry) 
    8477  REAL(r_std), SAVE :: sn_cond = 0.3                    !! Thermal Conductivity of snow  
    8578                                                        !! @tex $(W.m^{-2}.K^{-1})$ @endtex   
     
    206199&     0.25_r_std /)  ! oxisols                  
    207200 
    208   REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: so_capa_dry_ns_usda = &  !! Dry soil Heat capacity of soils,J.m^{-3}.K^{-1} 
     201  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: so_capa_dry_usda = &     !! Dry soil Heat capacity of soils,J.m^{-3}.K^{-1} 
    209202 & (/ 1.47e+6_r_std, 1.41e+6_r_std, 1.34e+6_r_std, 1.27e+6_r_std, &      !! Pielke [2002, 2013] 
    210203 &    1.21e+6_r_std, 1.21e+6_r_std, 1.18e+6_r_std, 1.32e+6_r_std, & 
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_sechiba/thermosoil.f90

    r7506 r7508  
    154154  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: QZ                       !! quartz content [-] 
    155155!$OMP THREADPRIVATE(QZ) 
    156   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: so_capa_dry_ns           !! Dry soil Heat capacity of soils,J.m^{-3}.K^{-1}  
    157 !$OMP THREADPRIVATE(so_capa_dry_ns) 
     156  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: so_capa_dry              !! Dry soil Heat capacity of soils,J.m^{-3}.K^{-1}  
     157!$OMP THREADPRIVATE(so_capa_dry) 
    158158  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: so_capa_ice              !! Heat capacity of saturated frozen soil (J/K/m3) 
    159159!$OMP THREADPRIVATE(so_capa_ice)    
     
    372372    IF (ier /= 0) CALL ipslerr_p(3,'thermosoil_initialize', 'Error in allocation of QZ','','') 
    373373 
    374     ALLOCATE (so_capa_dry_ns(nscm),stat=ier) 
    375     IF (ier /= 0) CALL ipslerr_p(3,'thermosoil_initialize', 'Error in allocation of so_capa_dry_ns','','') 
     374    ALLOCATE (so_capa_dry(nscm),stat=ier) 
     375    IF (ier /= 0) CALL ipslerr_p(3,'thermosoil_initialize', 'Error in allocation of so_capa_dry','','') 
    376376     
    377377    ALLOCATE (so_capa_ice(kjpindex),stat=ier) 
     
    381381    !! Soil texture choose : Now useless since njsc defines the dominant texture within 13 classes whichever the soil map 
    382382    QZ(:) = QZ_usda(:) 
    383     so_capa_dry_ns(:) = so_capa_dry_ns_usda(:) 
    384      
     383    so_capa_dry(:) = so_capa_dry_usda(:) 
     384     
     385    !Config Key   = DRY_SOIL_HEAT_CAPACITY 
     386    !Config Desc  = Dry soil Heat capacity of soils 
     387    !Config If    = OK_SECHIBA 
     388    !Config Def   = (1.47, 1.41, 1.34, 1.27, 1.21, 1.21, 1.18, 1.32, 1.23, 1.18, 1.15, 1.09, 1.09)*e+6 
     389    !Config Help  = Values taken from : Pielke [2002, 2013] 
     390    !Config Units = [J.m^{-3}.K^{-1}]  
     391    CALL getin_p("DRY_SOIL_HEAT_CAPACITY",so_capa_dry) 
     392     
     393    !! Check parameter value (correct range) 
     394    IF ( MINVAL(so_capa_dry(:)) <= zero ) THEN 
     395       CALL ipslerr_p(3, "thermosoil_initialize", & 
     396            "Wrong parameter value for DRY_SOIL_HEAT_CAPACITY.", & 
     397            "This parameter should be positive. ", & 
     398            "Please, check parameter value in run.def or orchidee.def. ") 
     399    END IF 
     400 
     401 
    385402    !! 2. Initialize variable from restart file or with default values  
    386403     
     
    16271644      DO jg = 1, ngrnd 
    16281645         jst = njsc(ji) 
    1629          pcapa_tmp(ji, jg) = so_capa_dry_ns(jst) * (1-mcs(ji)) + water_capa * tmc_layt(ji,jg)/mille/dlt(jg) 
     1646         pcapa_tmp(ji, jg) = so_capa_dry(jst) * (1-mcs(ji)) + water_capa * tmc_layt(ji,jg)/mille/dlt(jg) 
    16301647         ! 
    16311648         ! 2. Calculate volumetric heat capacity with allowance for permafrost 
     
    16381655            profil_froz(ji,jg) = 1. 
    16391656            pcappa_supp(ji,jg)= 0. 
    1640             pcapa(ji, jg) = so_capa_dry_ns(jst) * (1-mcs(ji)) + so_capa_ice(ji) * tmc_layt(ji,jg) / mille / dlt(jg) 
     1657            pcapa(ji, jg) = so_capa_dry(jst) * (1-mcs(ji)) + so_capa_ice(ji) * tmc_layt(ji,jg) / mille / dlt(jg) 
    16411658            rho_tot = rho_soil * (1-mcs(ji)) + rho_ice * tmc_layt(ji,jg) / mille / dlt(jg)  
    16421659            pcapa_spec(ji, jg) = pcapa(ji, jg) / rho_tot 
     
    16551672 
    16561673           IF (ok_freeze_thaw_latent_heat) THEN 
    1657               pcapa(ji, jg) = so_capa_dry_ns(jst) * (1-mcs(ji)) + & 
     1674              pcapa(ji, jg) = so_capa_dry(jst) * (1-mcs(ji)) + & 
    16581675                water_capa * tmc_layt(ji,jg)/mille / dlt(jg) * xx + & 
    16591676                so_capa_ice(ji) * tmc_layt(ji,jg) / mille/dlt(jg) * (1.-xx) + & 
    16601677                shum_ngrnd_perma(ji,jg)*mcs(ji)*lhf*rho_water/fr_dT 
    16611678           ELSE 
    1662               pcapa(ji, jg) = so_capa_dry_ns(jst) * (1-mcs(ji)) + & 
     1679              pcapa(ji, jg) = so_capa_dry(jst) * (1-mcs(ji)) + & 
    16631680                water_capa * tmc_layt(ji,jg)/mille / dlt(jg) * xx + & 
    16641681                so_capa_ice(ji) * tmc_layt(ji,jg) / mille/dlt(jg) * (1.-xx) 
     
    17521769         DO ji = 1,kjpindex 
    17531770            jst = njsc(ji) 
    1754             pcapa_tmp(ji, jg) = so_capa_dry_ns(jst) * (1-mcs(ji)) + water_capa * tmc_layt(ji,jg)/mille/dlt(jg) 
     1771            pcapa_tmp(ji, jg) = so_capa_dry(jst) * (1-mcs(ji)) + water_capa * tmc_layt(ji,jg)/mille/dlt(jg) 
    17551772            pcapa(ji,jg) = pcapa_tmp(ji, jg) 
    17561773            pcapa_en(ji,jg) = pcapa_tmp(ji, jg) 
Note: See TracChangeset for help on using the changeset viewer.