!$Header: /home/ssipsl/CVSREP/ORCHIDEE/src_parameters/constantes_soil.f90,v 1.11 2010/04/06 14:38:48 ssipsl Exp $ !IPSL (2006) ! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC !- MODULE constantes_soil !!-------------------------------------------------------------------- !! "constantes_soil" module contains public data for the soils !!-------------------------------------------------------------------- USE constantes !- IMPLICIT NONE !- ! Dimensioning parameters !- ! Number of soil level INTEGER(i_std),PARAMETER :: ngrnd=7 ! Number of diagnostic levels in the soil INTEGER(i_std),PARAMETER :: nbdl=11 !MM : if you want to compare hydrology variables with old TAG 1.6 and lower, ! you must set the Number of diagnostic levels in the soil to 6 : ! INTEGER(i_std),PARAMETER :: nbdl=6 ! Number of levels in CWRR INTEGER(i_std),PARAMETER :: nslm=11 ! Number of soil types INTEGER(i_std),PARAMETER :: nstm=3 !- !- Parameters for soil thermodynamics !- ! Average Thermal Conductivity of soils REAL(r_std),PARAMETER :: so_cond = 1.5396 ! Average Heat capacity of soils REAL(r_std),PARAMETER :: so_capa = 2.0514e+6 !- ! Values taken from : PIELKE,'MESOSCALE METEOROLOGICAL MODELING',P.384 ! Dry soil heat capacity was decreased and conductivity increased. !- ! Dry soil Heat capacity of soils !*REAL(r_std),PARAMETER :: so_capa_dry = 1.35e+6 REAL(r_std),PARAMETER :: so_capa_dry = 1.80e+6 ! Dry soil Thermal Conductivity of soils !*REAL(r_std),PARAMETER :: so_cond_dry = 0.28 REAL(r_std),PARAMETER :: so_cond_dry = 0.40 !- ! Wet soil Heat capacity of soils REAL(r_std),PARAMETER :: so_capa_wet = 3.03e+6 ! Wet soil Thermal Conductivity of soils REAL(r_std),PARAMETER :: so_cond_wet = 1.89 !- ! Thermal Conductivity of snow REAL(r_std),PARAMETER :: sn_cond = 0.3 ! Snow density for the soil thermodynamics REAL(r_std),PARAMETER :: sn_dens = 330.0 ! Heat capacity for snow REAL(r_std),PARAMETER :: sn_capa = 2100.0_r_std*sn_dens !- ! Constantes from the Choisnel hydrology !- ! Wilting point (Has a numerical role for the moment) REAL(r_std),PARAMETER :: qwilt = 5.0 ! Total depth of soil reservoir (for hydrolc) REAL(r_std),SAVE :: dpu_cste=2.0_r_std ! The minimal size we allow for the upper reservoir (m) REAL(r_std),PARAMETER :: min_resdis = 2.e-5 ! Diffusion constant for the slow regime ! (This is for the diffusion between reservoirs) REAL(r_std),PARAMETER :: min_drain = 0.001 ! Diffusion constant for the fast regime REAL(r_std),PARAMETER :: max_drain = 0.1 ! The exponential in the diffusion law REAL(r_std),PARAMETER :: exp_drain = 1.5 ! Transforms leaf area index into size of interception reservoir REAL(r_std),SAVE :: qsintcst = 0.1 ! Maximum quantity of water (Kg/M3) REAL(r_std),PARAMETER :: mx_eau_eau = 150. !- ! Constant in the computation of resistance for bare soil evaporation REAL(r_std),PARAMETER :: rsol_cste = 33.E3 ! Scaling depth for litter humidity (m) !SZ changed this according to SP from 0.03 to 0.08, 080806 REAL(r_std),PARAMETER :: hcrit_litter=0.08_r_std !- ! Parameters for soil type distribution !- ! Default soil texture distribution in the following order : ! sand, loam and clay REAL(r_std),DIMENSION(nstm),SAVE :: soiltype_default = & & (/ 0.0, 1.0, 0.0 /) !- ! Parameters specific for the CWRR hydrology. !- ! Van genuchten coefficient n REAL(r_std),PARAMETER,DIMENSION(nstm) :: nvan = & & (/ 1.89_r_std, 1.56_r_std, 1.31_r_std /) !!$! Van genuchten coefficient a (cm^{-1}) !!$ REAL(r_std),PARAMETER,DIMENSION(nstm) :: avan = & !!$ & (/ 0.036_r_std, 0.036_r_std, 0.036_r_std /) !TdO ! Van genuchten coefficient a (mm^{-1}) REAL(r_std),PARAMETER,DIMENSION(nstm) :: avan = & & (/ 0.0075_r_std, 0.0036_r_std, 0.0019_r_std /) ! CWRR linearisation INTEGER(i_std),PARAMETER :: imin = 1 ! number of interval for CWRR INTEGER(i_std),PARAMETER :: nbint = 100 ! number of points for CWRR INTEGER(i_std),PARAMETER :: imax = nbint+1 ! Residual soil water content REAL(r_std),PARAMETER,DIMENSION(nstm) :: mcr = & & (/ 0.065_r_std, 0.078_r_std, 0.095_r_std /) ! Saturated soil water content REAL(r_std),PARAMETER,DIMENSION(nstm) :: mcs = & & (/ 0.41_r_std, 0.43_r_std, 0.41_r_std /) ! Total depth of soil reservoir (m) REAL(r_std),SAVE,DIMENSION(nstm) :: dpu = & & (/ 2.0_r_std, 2.0_r_std, 2.0_r_std /) ! dpu must be constant over the different soil types ! Hydraulic conductivity Saturation (mm/d) REAL(r_std),PARAMETER,DIMENSION(nstm) :: ks = & & (/ 1060.8_r_std, 249.6_r_std, 62.4_r_std /) ! Soil moisture above which transpir is max REAL(r_std),PARAMETER,DIMENSION(nstm) :: pcent = & & (/ 0.5_r_std, 0.5_r_std, 0.5_r_std /) ! Max value of the permeability coeff at the bottom of the soil REAL(r_std),PARAMETER,DIMENSION(nstm) :: free_drain_max = & & (/ 1.0_r_std, 1.0_r_std, 1.0_r_std /) ! Volumetric water content field capacity REAL(r_std),PARAMETER,DIMENSION(nstm) :: mcf = & & (/ 0.32_r_std, 0.32_r_std, 0.32_r_std /) ! Volumetric water content Wilting pt REAL(r_std),PARAMETER,DIMENSION(nstm) :: mcw = & & (/ 0.10_r_std, 0.10_r_std, 0.10_r_std /) ! Vol. wat. cont. above which albedo is cst REAL(r_std),PARAMETER,DIMENSION(nstm) :: mc_awet = & & (/ 0.25_r_std, 0.25_r_std, 0.25_r_std /) ! Vol. wat. cont. below which albedo is cst REAL(r_std),PARAMETER,DIMENSION(nstm) :: mc_adry = & & (/ 0.1_r_std, 0.1_r_std, 0.1_r_std /) ! Matrix potential at saturation (mm) REAL(r_std),PARAMETER,DIMENSION(nstm) :: psis = & & (/ -300.0_r_std, -300.0_r_std, -300.0_r_std /) ! Time weighting for discretisation REAL(r_std),PARAMETER :: w_time = 1.0_r_std !- ! Diagnostic variables !- ! The lower limit of the layer on which soil moisture (relative) ! and temperature are going to be diagnosed. ! These variables are made for transfering the information ! to the biogeophyical processes modelled in STOMATE. !- REAL(r_std),DIMENSION(nbdl),SAVE :: diaglev !------------------------- END MODULE constantes_soil