source: branches/publications/ORCHIDEE-PEAT_r5488/src_parameters/constantes_soil_var.f90 @ 5491

Last change on this file since 5491 was 5080, checked in by chunjing.qiu, 6 years ago

soil freezing, soil moisture, fwet bugs fixed

File size: 22.7 KB
Line 
1! =================================================================================================================================
2! MODULE        : constantes_soil_var
3!
4! CONTACT       : orchidee-help _at_ ipsl.jussieu.fr
5!
6! LICENCE       : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF         "constantes_soil_var" module contains the parameters related to soil and hydrology.
10!!
11!!\n DESCRIPTION : The non saturated hydraulic properties are defined from the 
12!!                 formulations of van Genuchten (1980) and Mualem (1976), combined as 
13!!                 explained in d'Orgeval (2006). \n
14!!                 The related parameters for main soil textures (coarse, medium and fine if "fao",
15!!                 12 USDA testures if "usda") come from Carsel and Parrish (1988).
16!!
17!! RECENT CHANGE(S): Sonke Zaehle changed hcrit_litter value according to Shilong Piao
18!!                   from 0.03 to 0.08, 080806
19!!                   AD: mcw and mcf depend now on soil texture, based on Van Genuchten equations
20!!                   and classical matric potential values, and pcent is adapted
21!!
22!! REFERENCE(S) :
23!!- Roger A.Pielke, (2002), Mesoscale meteorological modeling, Academic Press Inc.
24!!- Polcher, J., Laval, K., DÃŒmenil, L., Lean, J., et Rowntree, P. R. (1996).
25!! Comparing three land surface schemes used in general circulation models. Journal of Hydrology, 180(1-4), 373--394.
26!!- Ducharne, A., Laval, K., et Polcher, J. (1998). Sensitivity of the hydrological cycle
27!! to the parametrization of soil hydrology in a GCM. Climate Dynamics, 14, 307--327.
28!!- Rosnay, P. de et Polcher, J. (1999). Modelling root water uptake in a complex land surface
29!! scheme coupled to a GCM. Hydrol. Earth Syst. Sci., 2(2/3), 239--255.
30!!- d'Orgeval, T. et Polcher, J. (2008). Impacts of precipitation events and land-use changes
31!! on West African river discharges during the years 1951--2000. Climate Dynamics, 31(2), 249--262.
32!!- Carsel, R. and Parrish, R.: Developing joint probability distributions of soil water
33!! retention characteristics, Water Resour. Res.,24, 755–769, 1988.
34!!- Mualem Y (1976) A new model for predicting the hydraulic conductivity 
35!! of unsaturated porous media. Water Resources Research 12(3):513-522
36!!- Van Genuchten M (1980) A closed-form equation for predicting the 
37!! hydraulic conductivity of unsaturated soils. Soil Sci Soc Am J, 44(5):892-898
38!!
39!! SVN          :
40!! $HeadURL: $
41!! $Date: $
42!! $Revision: $
43!! \n
44!_ ================================================================================================================================
45
46MODULE constantes_soil_var
47
48  USE defprec
49  USE vertical_soil_var
50
51  IMPLICIT NONE
52
53  LOGICAL, SAVE             :: check_cwrr          !! To check the water balance in hydrol (true/false)
54!$OMP THREADPRIVATE(check_cwrr)
55  LOGICAL, SAVE             :: check_cwrr2         !! Calculate diagnostics to check the water balance in hydrol (true/false)
56!$OMP THREADPRIVATE(check_cwrr2)
57  LOGICAL, SAVE             :: check_waterbal      !! The check the water balance (true/false)
58!$OMP THREADPRIVATE(check_waterbal)
59
60
61  INTEGER(i_std),PARAMETER  :: ndeep=32
62  REAL(r_std), PARAMETER    :: zalph=1.18
63  REAL(r_std), PARAMETER    :: z_deepsoil = 2.          !! depth below which soil humidity is set to fixed values
64
65  !! Number of soil classes
66
67  INTEGER(i_std), PARAMETER :: ntext=3                  !! Number of soil textures (Silt, Sand, Clay)
68 
69  INTEGER(i_std), SAVE      :: nstm=3                   !! Number of soil tiles (unitless)
70                                                        !! When CROP, nstm = 6, 4 wheat 5 maize 6 rice
71  CHARACTER(LEN=30)         :: soil_classif             !! Type of classification used for the map of soil types.
72                                                        !! It must be consistent with soil file given by
73                                                        !! SOILCLASS_FILE parameter.
74!$OMP THREADPRIVATE(soil_classif)
75  INTEGER(i_std), PARAMETER :: nscm_fao=3               !! For FAO Classification (unitless)
76  INTEGER(i_std), PARAMETER :: nscm_usda=12             !! For USDA Classification (unitless)
77  INTEGER(i_std), SAVE      :: nscm=nscm_fao            !! Default value for nscm
78!$OMP THREADPRIVATE(nscm)
79
80  !! Parameters for soil thermodynamics
81
82  REAL(r_std), SAVE :: so_capa_dry = 1.80e+6            !! Dry soil Heat capacity of soils
83                                                        !! @tex $(J.m^{-3}.K^{-1})$ @endtex
84!$OMP THREADPRIVATE(so_capa_dry)
85  REAL(r_std), SAVE :: so_cond_dry = 0.40               !! Dry soil Thermal Conductivity of soils
86                                                        !! @tex $(W.m^{-2}.K^{-1})$ @endtex
87!$OMP THREADPRIVATE(so_cond_dry)
88  REAL(r_std), SAVE :: so_capa_wet = 3.03e+6            !! Wet soil Heat capacity of soils
89                                                        !! @tex $(J.m^{-3}.K^{-1})$ @endtex
90!$OMP THREADPRIVATE(so_capa_wet)
91  REAL(r_std), SAVE :: so_cond_wet = 1.89               !! Wet soil Thermal Conductivity of soils
92                                                        !! @tex $(W.m^{-2}.K^{-1})$ @endtex
93!$OMP THREADPRIVATE(so_cond_wet)
94  REAL(r_std), SAVE :: sn_cond = 0.3                    !! Thermal Conductivity of snow
95                                                        !! @tex $(W.m^{-2}.K^{-1})$ @endtex 
96!$OMP THREADPRIVATE(sn_cond)
97  REAL(r_std), SAVE :: sn_dens = 330.0                  !! Snow density for the soil thermodynamics
98                                                        !! (kg/m3)
99!$OMP THREADPRIVATE(sn_dens)
100  REAL(r_std), SAVE :: sn_capa                          !! Heat capacity for snow
101                                                        !! @tex $(J.m^{-3}.K^{-1})$ @endtex
102!$OMP THREADPRIVATE(sn_capa)
103  REAL(r_std), PARAMETER :: poros_org = 0.92            !! for now just a number from dmitry's code
104  REAL(r_std), PARAMETER :: cond_solid_org = 0.25       !! W/m/K from Farouki via Lawrence and Slater
105  REAL(r_std), PARAMETER :: cond_dry_org = 0.05         !! W/m/K from Lawrence and Slater
106  REAL(r_std), PARAMETER :: so_capa_dry_org = 2.5e6     !! J/K/m^3 from Farouki via Lawrence and Slater
107  REAL(r_std), SAVE :: water_capa = 4.18e+6             !! Water heat capacity
108                                                        !! @tex $(J.m^{-3}.K^{-1})$ @endtex
109!$OMP THREADPRIVATE(water_capa)
110  REAL(r_std), SAVE :: brk_capa = 2.0e+6                !! Heat capacity of generic rock
111                                                        !! @tex $(J.m^{-3}.K^{-1})$ @endtex
112!$OMP THREADPRIVATE(brk_capa)
113  REAL(r_std), SAVE :: brk_cond = 3.0                   !! Thermal conductivity of saturated granitic rock
114                                                        !! @tex $(W.m^{-1}.K^{-1})$ @endtex
115!$OMP THREADPRIVATE(brk_cond)
116
117  !REAL(r_std),PARAMETER :: sn_capa = 2100.0_r_std*sn_dens !! Heat capacity
118  !for snow @tex $(J.m^{-3}.K^{-1})$ @endtex
119  REAL(r_std), PARAMETER   :: soilc_max =  130000.      !! g/m^3 from lawrence and slater
120
121  !! Specific parameters for the Choisnel hydrology
122
123  REAL(r_std), SAVE :: min_drain = 0.001                !! Diffusion constant for the slow regime
124                                                        !! (This is for the diffusion between reservoirs)
125                                                        !! @tex $(kg.m^{-2}.dt^{-1})$ @endtex
126!$OMP THREADPRIVATE(min_drain)
127  REAL(r_std), SAVE :: max_drain = 0.1                  !! Diffusion constant for the fast regime
128                                                        !! @tex $(kg.m^{-2}.dt^{-1})$ @endtex
129!$OMP THREADPRIVATE(max_drain)
130  REAL(r_std), SAVE :: exp_drain = 1.5                  !! The exponential in the diffusion law (unitless)
131!$OMP THREADPRIVATE(exp_drain)
132  REAL(r_std), SAVE :: qsintcst = 0.1                   !! Transforms leaf area index into size of interception reservoir
133                                                        !! (unitless)
134!$OMP THREADPRIVATE(qsintcst)
135  REAL(r_std), SAVE :: mx_eau_nobio = 150.              !! Volumetric available soil water capacity in nobio fractions
136                                                        !! @tex $(kg.m^{-3} of soil)$ @endtex
137!$OMP THREADPRIVATE(mx_eau_nobio)
138  REAL(r_std), SAVE :: rsol_cste = 33.E3                !! Constant in the computation of resistance for bare soil evaporation
139                                                        !! @tex $(s.m^{-2})$ @endtex
140!$OMP THREADPRIVATE(rsol_cste)
141  REAL(r_std), SAVE :: hcrit_litter=0.08_r_std          !! Scaling depth for litter humidity (m)
142!$OMP THREADPRIVATE(hcrit_litter)
143
144  INTEGER(i_std), SAVE :: SO_DISCRETIZATION_METHOD      !! Soil layer discretization method selected, 0 = thermix, 1 = permafrost 
145!$OMP THREADPRIVATE(SO_DISCRETIZATION_METHOD)
146  INTEGER(i_std), PARAMETER :: SLD_THERMIX = 0          !! Soil layers discretization constant for thermix method
147  INTEGER(i_std), PARAMETER :: SLD_PERMAFROST = 1       !! Soil layers discretization constant for permafrost method
148
149  REAL(r_std), SAVE         :: THKICE = 2.2             !! Ice Thermal Conductivity (W/m/k)
150!$OMP THREADPRIVATE(THKICE)
151  REAL(r_std), SAVE         :: THKQTZ = 7.7             !! Thermal Conductivity for Quartz (W/m/k)
152!$OMP THREADPRIVATE(THKQTZ)
153  REAL(r_std), SAVE         :: THKW = 0.57              !! Water Thermal Conductivity (W/m/k)
154!$OMP THREADPRIVATE(THKW)
155
156  !! Parameters specific for the CWRR hydrology.
157
158  !!  1. Parameters for FAO Classification
159
160  !! Parameters for soil type distribution
161
162!!!qcj++ peatland
163  REAL(r_std), PARAMETER ::  nvan_peat=1.38_r_std
164  REAL(r_std), PARAMETER ::  avan_peat=0.00507_r_std
165  REAL(r_std), PARAMETER ::  mcr_peat=0.15_r_std
166  REAL(r_std), PARAMETER ::  mcs_peat=0.80_r_std
167  REAL(r_std), PARAMETER ::  ks_peat=2120_r_std !229000_r_std !2120_r_std
168  REAL(r_std), PARAMETER ::  mcw_peat=0.210_r_std 
169  REAL(r_std), PARAMETER ::  mcf_peat=0.406_r_std 
170  REAL(r_std), PARAMETER ::  mc_awet_peat =0.25_r_std 
171  REAL(r_std), PARAMETER ::  mc_adry_peat =0.1_r_std 
172  REAL(r_std), PARAMETER ::  pcent_peat=0.8_r_std 
173
174  REAL(r_std), SAVE ::  tau_peat =3.1536E8    !!k0 = 0.1yr**-1, tau_peat in s
175  REAL(r_std), SAVE ::  z_tau= 1.E6  !!the e-folding depth of turnover rates
176  REAL(r_std), SAVE ::  lim1=0.1
177  REAL(r_std), SAVE ::  lim2=0.1
178  REAL(r_std), SAVE ::  q10_peat=2.0
179
180!  REAL(r_std), PARAMETER, DIMENSION(ndeep) :: peat_bulk_density =  &    !!in g/cm3,mean of core measurement
181!  & (/ 0.080, 0.080, 0.080, 0.071, 0.086, 0.082, 0.091, 0.101, 0.111, 0.126, 0.127, &
182!  &    0.117, 0.124, 0.118, 0.108, 0.097, 0.089, 0.09, 0.09, 0.09, 0.09, 0.09, &
183!  &    0.09, 0.09, 0.09, 0.09, 0.09, 0.09, 0.09, 0.09, 0.09, 0.09 /)
184
185  REAL(r_std), PARAMETER, DIMENSION(ndeep) :: peat_bulk_density =  &    !!in g/cm3, median of core measurement
186  & (/ 0.063, 0.063, 0.063, 0.047, 0.064, 0.066, 0.079, 0.091, 0.101, 0.109, 0.109, &
187  &    0.103, 0.112, 0.110, 0.104, 0.073, 0.092, 0.092, 0.092, 0.092, 0.092, 0.092, &
188  &    0.092, 0.092, 0.092, 0.092, 0.092, 0.092, 0.092, 0.092, 0.092, 0.092 /)
189
190  REAL(r_std),DIMENSION(nscm_fao),SAVE :: soilclass_default_fao = &   !! Default soil texture distribution for fao :
191 & (/ 0.28, 0.52, 0.20 /)                                             !! in the following order : COARSE, MEDIUM, FINE (unitless)
192!$OMP THREADPRIVATE(soilclass_default_fao)
193
194  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: nvan_fao = &            !! Van Genuchten coefficient n (unitless)
195 & (/ 1.89_r_std, 1.56_r_std, 1.31_r_std /)                             !  RK: 1/n=1-m
196
197  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: avan_fao = &            !! Van Genuchten coefficient a
198  & (/ 0.0075_r_std, 0.0036_r_std, 0.0019_r_std /)                     !!  @tex $(mm^{-1})$ @endtex
199
200  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mcr_fao = &             !! Residual volumetric water content
201 & (/ 0.065_r_std, 0.078_r_std, 0.095_r_std /)                         !!  @tex $(m^{3} m^{-3})$ @endtex
202
203  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mcs_fao = &             !! Saturated volumetric water content
204 & (/ 0.41_r_std, 0.43_r_std, 0.41_r_std /)                            !!  @tex $(m^{3} m^{-3})$ @endtex
205
206  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: ks_fao = &              !! Hydraulic conductivity at saturation
207 & (/ 1060.8_r_std, 249.6_r_std, 62.4_r_std /)                         !!  @tex $(mm d^{-1})$ @endtex
208
209! The max available water content is smaller when mcw and mcf depend on texture,
210! so we increase pcent to a classical value of 80%
211  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: pcent_fao = &           !! Fraction of saturated volumetric soil moisture
212 & (/ 0.8_r_std, 0.8_r_std, 0.8_r_std /)                               !! above which transpir is max (0-1, unitless)
213
214  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: free_drain_max_fao = &  !! Max=default value of the permeability coeff 
215 & (/ 1.0_r_std, 1.0_r_std, 1.0_r_std /)                               !! at the bottom of the soil (0-1, unitless)
216
217!! We use the VG relationships to derive mcw and mcf depending on soil texture
218!! assuming that the matric potential for wilting point and field capacity is
219!! -150m (permanent WP) and -3.3m respectively
220!! (-1m for FC for the three sandy soils following Richards, L.A. and Weaver, L.R. (1944)
221!! Note that mcw GE mcr
222  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mcf_fao = &             !! Volumetric water content at field capacity
223 & (/ 0.1218_r_std, 0.1654_r_std, 0.2697_r_std /)                      !!  @tex $(m^{3} m^{-3})$ @endtex
224
225  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mcw_fao = &             !! Volumetric water content at wilting point
226 & (/ 0.0657_r_std,  0.0884_r_std, 0.1496_r_std/)                      !!  @tex $(m^{3} m^{-3})$ @endtex
227
228  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mc_awet_fao = &         !! Vol. wat. cont. above which albedo is cst
229 & (/ 0.25_r_std, 0.25_r_std, 0.25_r_std /)                            !!  @tex $(m^{3} m^{-3})$ @endtex
230
231  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mc_adry_fao = &         !! Vol. wat. cont. below which albedo is cst
232 & (/ 0.1_r_std, 0.1_r_std, 0.1_r_std /)                               !!  @tex $(m^{3} m^{-3})$ @endtex
233
234  REAL(r_std),DIMENSION(nscm_fao),SAVE :: SMCMAX_fao = &               !! porosity
235 & (/ 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
236
237  REAL(r_std),SAVE,DIMENSION(nscm_fao) :: QZ_fao = &              !! QUARTZ CONTENT (SOIL TYPE DEPENDENT)
238 & (/ 0.60_r_std, 0.40_r_std, 0.35_r_std /)                            !! Peters et al [1998]
239
240  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: so_capa_dry_ns_fao = &  !! Dry soil Heat capacity of soils,J.m^{-3}.K^{-1}
241 & (/ 1.34e+6_r_std, 1.21e+6_r_std, 1.23e+6_r_std /)                   !! Pielke [2002, 2013]
242
243  !!  2. Parameters for USDA Classification
244
245  !! Parameters for soil type distribution :
246  !! Sand, Loamy Sand, Sandy Loam, Silt Loam, Silt, Loam, Sandy Clay Loam, Silty Clay Loam, Clay Loam, Sandy Clay, Silty Clay, Clay
247
248  REAL(r_std),DIMENSION(nscm_usda),SAVE :: soilclass_default_usda = &    !! Default soil texture distribution in the above order :
249 & (/ 0.28, 0.52, 0.20, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0 /)   !! Thus different from "FAO"'s COARSE, MEDIUM, FINE
250                                                                         !! which have indices 3,6,9 in the 12-texture vector
251  !$OMP THREADPRIVATE(soilclass_default_usda)
252
253  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: nvan_usda = &            !! Van Genuchten coefficient n (unitless)
254 & (/ 2.68_r_std, 2.28_r_std, 1.89_r_std, 1.41_r_std, &                   !  RK: 1/n=1-m
255 &    1.37_r_std, 1.56_r_std, 1.48_r_std, 1.23_r_std, &
256 &    1.31_r_std, 1.23_r_std, 1.09_r_std, 1.09_r_std /)
257
258  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: avan_usda = &            !! Van Genuchten coefficient a
259 & (/ 0.0145_r_std, 0.0124_r_std, 0.0075_r_std, 0.0020_r_std, &          !!  @tex $(mm^{-1})$ @endtex
260 &    0.0016_r_std, 0.0036_r_std, 0.0059_r_std, 0.0010_r_std, &
261 &    0.0019_r_std, 0.0027_r_std, 0.0005_r_std, 0.0008_r_std /)
262
263  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mcr_usda = &             !! Residual volumetric water content
264 & (/ 0.045_r_std, 0.057_r_std, 0.065_r_std, 0.067_r_std, &              !!  @tex $(m^{3} m^{-3})$ @endtex
265 &    0.034_r_std, 0.078_r_std, 0.100_r_std, 0.089_r_std, &
266 &    0.095_r_std, 0.100_r_std, 0.070_r_std, 0.068_r_std /)
267
268  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mcs_usda = &             !! Saturated volumetric water content
269 & (/ 0.43_r_std, 0.41_r_std, 0.41_r_std, 0.45_r_std, &                  !!  @tex $(m^{3} m^{-3})$ @endtex
270 &    0.46_r_std, 0.43_r_std, 0.39_r_std, 0.43_r_std, &
271 &    0.41_r_std, 0.38_r_std, 0.36_r_std, 0.38_r_std /)
272
273  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: ks_usda = &              !! Hydraulic conductivity at saturation
274 & (/ 7128.0_r_std, 3501.6_r_std, 1060.8_r_std, 108.0_r_std, &           !!  @tex $(mm d^{-1})$ @endtex
275 &    60.0_r_std, 249.6_r_std, 314.4_r_std, 16.8_r_std, &
276 &    62.4_r_std, 28.8_r_std, 4.8_r_std, 48.0_r_std /)
277
278  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: pcent_usda = &           !! Fraction of saturated volumetric soil moisture
279 & (/ 0.8_r_std, 0.8_r_std, 0.8_r_std, 0.8_r_std, &                      !! above which transpir is max (0-1, unitless)
280 &    0.8_r_std, 0.8_r_std, 0.8_r_std, 0.8_r_std, &
281 &    0.8_r_std, 0.8_r_std, 0.8_r_std, 0.8_r_std /)
282
283  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: free_drain_max_usda = &  !! Max=default value of the permeability coeff
284 & (/ 1.0_r_std, 1.0_r_std, 1.0_r_std, 1.0_r_std, &                      !! at the bottom of the soil (0-1, unitless)
285 &    1.0_r_std, 1.0_r_std, 1.0_r_std, 1.0_r_std, &
286 &    1.0_r_std, 1.0_r_std, 1.0_r_std, 1.0_r_std /)
287
288  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mcf_usda = &             !! Volumetric water content at field capacity
289 & (/ 0.0493_r_std, 0.0710_r_std, 0.1218_r_std, 0.2402_r_std, &          !!  @tex $(m^{3} m^{-3})$ @endtex
290      0.2582_r_std, 0.1654_r_std, 0.1695_r_std, 0.3383_r_std, &
291      0.2697_r_std, 0.2672_r_std, 0.3370_r_std, 0.3469_r_std /)
292 
293  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mcw_usda = &             !! Volumetric water content at wilting point
294 & (/ 0.0450_r_std, 0.0570_r_std, 0.0657_r_std, 0.1039_r_std, &          !!  @tex $(m^{3} m^{-3})$ @endtex
295      0.0901_r_std, 0.0884_r_std, 0.1112_r_std, 0.1967_r_std, &
296      0.1496_r_std, 0.1704_r_std, 0.2665_r_std, 0.2707_r_std /)
297
298  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: VG_m_usda = &             
299 & (/ 0.6269_r_std, 0.5614_r_std, 0.4709_r_std, 0.2908_r_std, &                 
300 &    0.2701_r_std, 0.359_r_std,  0.3243_r_std, 0.187_r_std, &
301 &    0.2366_r_std, 0.187_r_std,  0.0826_r_std, 0.0826_r_std /)
302
303  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: VG_n_usda = &             
304 & (/ 2.68_r_std, 2.28_r_std, 1.89_r_std, 1.41_r_std, &                 
305 &    1.37_r_std, 1.56_r_std, 1.48_r_std, 1.23_r_std, &
306 &    1.31_r_std, 1.23_r_std, 1.09_r_std, 1.09_r_std /)
307
308  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: VG_alpha_usda = &             
309 & (/ 0.0145_r_std, 0.0124_r_std, 0.0075_r_std, 0.002_r_std, &                 
310 &    0.0016_r_std, 0.0036_r_std, 0.0059_r_std, 0.001_r_std, &
311 &    0.0019_r_std, 0.0027_r_std, 0.0005_r_std, 0.0008_r_std /)
312
313  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: VG_psi_fc_usda = &             
314 & (/ 1000_r_std, 1000_r_std, 1000_r_std, 3300_r_std, &                 
315 &    3300_r_std, 3300_r_std, 3300_r_std, 3300_r_std, &                 
316 &    3300_r_std, 3300_r_std, 3300_r_std, 3300_r_std /)
317
318  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: VG_psi_wp_usda = &             
319 & (/ 150000_r_std, 150000_r_std, 150000_r_std, 150000_r_std, &                 
320 &    150000_r_std, 150000_r_std, 150000_r_std, 150000_r_std, &                 
321 &    150000_r_std, 150000_r_std, 150000_r_std, 150000_r_std /)
322
323  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mc_awet_usda = &         !! Vol. wat. cont. above which albedo is cst
324 & (/ 0.25_r_std, 0.25_r_std, 0.25_r_std, 0.25_r_std, &                  !!  @tex $(m^{3} m^{-3})$ @endtex
325 &    0.25_r_std, 0.25_r_std, 0.25_r_std, 0.25_r_std, &
326 &    0.25_r_std, 0.25_r_std, 0.25_r_std, 0.25_r_std /)
327
328  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mc_adry_usda = &         !! Vol. wat. cont. below which albedo is cst
329 & (/ 0.1_r_std, 0.1_r_std, 0.1_r_std, 0.1_r_std, &                      !!  @tex $(m^{3} m^{-3})$ @endtex
330 &    0.1_r_std, 0.1_r_std, 0.1_r_std, 0.1_r_std, &
331 &    0.1_r_std, 0.1_r_std, 0.1_r_std, 0.1_r_std /)
332
333  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: SMCMAX_usda = &          !! porosity
334 & (/ 0.43_r_std, 0.41_r_std, 0.41_r_std, 0.45_r_std, &
335 &    0.46_r_std, 0.43_r_std, 0.39_r_std, 0.43_r_std, &
336 &    0.41_r_std, 0.38_r_std, 0.36_r_std, 0.38_r_std /)
337 
338  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: QZ_usda = &              !! QUARTZ CONTENT (SOIL TYPE DEPENDENT)
339 & (/ 0.92_r_std, 0.82_r_std, 0.60_r_std, 0.25_r_std, &
340 &    0.10_r_std, 0.40_r_std, 0.60_r_std, 0.10_r_std, &
341 &    0.35_r_std, 0.52_r_std, 0.10_r_std, 0.25_r_std /)                  !! Peters et al [1998]
342
343  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: so_capa_dry_ns_usda = &  !! Dry soil Heat capacity of soils,J.m^{-3}.K^{-1}
344 & (/ 1.47e+6_r_std, 1.41e+6_r_std, 1.34e+6_r_std, 1.27e+6_r_std, &
345 &    1.21e+6_r_std, 1.21e+6_r_std, 1.18e+6_r_std, 1.32e+6_r_std, &
346 &    1.23e+6_r_std, 1.18e+6_r_std, 1.15e+6_r_std, 1.09e+6_r_std /)      !! Pielke [2002, 2013]
347 
348  !! Parameters for the numerical scheme used by CWRR
349
350  INTEGER(i_std), PARAMETER :: imin = 1                                 !! Start for CWRR linearisation (unitless)
351  INTEGER(i_std), PARAMETER :: nbint = 50                               !! Number of interval for CWRR linearisation (unitless)
352  INTEGER(i_std), PARAMETER :: imax = nbint+1                           !! Number of points for CWRR linearisation (unitless)
353  REAL(r_std), PARAMETER    :: w_time = 1.0_r_std                       !! Time weighting for CWRR numerical integration (unitless)
354
355
356  !! Variables related to soil freezing, in thermosoil :
357  LOGICAL, SAVE        :: ok_Ecorr                    !! Flag for energy conservation correction
358  LOGICAL, SAVE        :: ok_freeze_thermix           !! Flag to activate thermal part of the soil freezing scheme
359  LOGICAL, SAVE        :: read_reftemp                !! Flag to initialize soil temperature using climatological temperature
360  REAL(r_std), SAVE    :: poros                       !! Soil porosity (from USDA classification, mean value)(-)
361  REAL(r_std), SAVE    :: fr_dT                       !! Freezing window (K)
362
363  !! Variables related to soil freezing, in diffuco :
364  LOGICAL, SAVE        ::  ok_snowfact                !! Activate snow smoothering
365
366  !! Variables related to soil freezing, in hydrol :
367  LOGICAL, SAVE        :: ok_freeze_cwrr              !! CWRR freezing scheme by I. Gouttevin
368  LOGICAL, SAVE        :: ok_thermodynamical_freezing !! Calculate frozen fraction thermodynamically
369
370 
371END MODULE constantes_soil_var
Note: See TracBrowser for help on using the repository browser.