source: branches/publications/ORCHIDEE_GLUC_r6545/src_parameters/constantes_soil_var.f90 @ 8398

Last change on this file since 8398 was 4719, checked in by albert.jornet, 7 years ago

Merge: from revisions [4491:4695/trunk/ORCHIDEE]

Merge done in [4671:4718/perso/albert.jornet/MICT_MERGE]

File size: 21.1 KB
Line 
1! =================================================================================================================================
2! MODULE        : constantes_soil_var
3!
4! CONTACT       : orchidee-help _at_ listes.ipsl.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  INTEGER(i_std), SAVE      :: nstm=3                   !! Number of soil tiles (unitless)
69                                                        !! When CROP, nstm = 6, 4 wheat 5 maize 6 rice
70  CHARACTER(LEN=30)         :: soil_classif             !! Type of classification used for the map of soil types.
71                                                        !! It must be consistent with soil file given by
72                                                        !! SOILCLASS_FILE parameter.
73!$OMP THREADPRIVATE(soil_classif)
74  INTEGER(i_std), PARAMETER :: nscm_fao=3               !! For FAO Classification (unitless)
75  INTEGER(i_std), PARAMETER :: nscm_usda=12             !! For USDA Classification (unitless)
76  INTEGER(i_std), SAVE      :: nscm=nscm_fao            !! Default value for nscm
77!$OMP THREADPRIVATE(nscm)
78
79  !! Parameters for soil thermodynamics
80
81  REAL(r_std), SAVE :: so_capa_dry = 1.80e+6            !! Dry soil Heat capacity of soils
82                                                        !! @tex $(J.m^{-3}.K^{-1})$ @endtex
83!$OMP THREADPRIVATE(so_capa_dry)
84  REAL(r_std), SAVE :: so_cond_dry = 0.40               !! Dry soil Thermal Conductivity of soils
85                                                        !! @tex $(W.m^{-2}.K^{-1})$ @endtex
86!$OMP THREADPRIVATE(so_cond_dry)
87  REAL(r_std), SAVE :: so_capa_wet = 3.03e+6            !! Wet soil Heat capacity of soils
88                                                        !! @tex $(J.m^{-3}.K^{-1})$ @endtex
89!$OMP THREADPRIVATE(so_capa_wet)
90  REAL(r_std), SAVE :: so_cond_wet = 1.89               !! Wet soil Thermal Conductivity of soils
91                                                        !! @tex $(W.m^{-2}.K^{-1})$ @endtex
92!$OMP THREADPRIVATE(so_cond_wet)
93  REAL(r_std), SAVE :: sn_cond = 0.3                    !! Thermal Conductivity of snow
94                                                        !! @tex $(W.m^{-2}.K^{-1})$ @endtex 
95!$OMP THREADPRIVATE(sn_cond)
96  REAL(r_std), SAVE :: sn_dens = 330.0                  !! Snow density for the soil thermodynamics
97                                                        !! (kg/m3)
98!$OMP THREADPRIVATE(sn_dens)
99  REAL(r_std), SAVE :: sn_capa                          !! Heat capacity for snow
100                                                        !! @tex $(J.m^{-3}.K^{-1})$ @endtex
101!$OMP THREADPRIVATE(sn_capa)
102  REAL(r_std), PARAMETER :: poros_org = 0.92            !! for now just a number from dmitry's code
103  REAL(r_std), PARAMETER :: cond_solid_org = 0.25       !! W/m/K from Farouki via Lawrence and Slater
104  REAL(r_std), PARAMETER :: cond_dry_org = 0.05         !! W/m/K from Lawrence and Slater
105  REAL(r_std), PARAMETER :: so_capa_dry_org = 2.5e6     !! J/K/m^3 from Farouki via Lawrence and Slater
106  REAL(r_std), SAVE :: water_capa = 4.18e+6             !! Water heat capacity
107                                                        !! @tex $(J.m^{-3}.K^{-1})$ @endtex
108!$OMP THREADPRIVATE(water_capa)
109  REAL(r_std), SAVE :: brk_capa = 2.0e+6                !! Heat capacity of generic rock
110                                                        !! @tex $(J.m^{-3}.K^{-1})$ @endtex
111!$OMP THREADPRIVATE(brk_capa)
112  REAL(r_std), SAVE :: brk_cond = 3.0                   !! Thermal conductivity of saturated granitic rock
113                                                        !! @tex $(W.m^{-1}.K^{-1})$ @endtex
114!$OMP THREADPRIVATE(brk_cond)
115
116  !REAL(r_std),PARAMETER :: sn_capa = 2100.0_r_std*sn_dens !! Heat capacity
117  !for snow @tex $(J.m^{-3}.K^{-1})$ @endtex
118  REAL(r_std), SAVE   :: soilc_max =  130000.      !! g/m^3 from lawrence and slater
119
120  !! Specific parameters for the Choisnel hydrology
121
122  REAL(r_std), SAVE :: min_drain = 0.001                !! Diffusion constant for the slow regime
123                                                        !! (This is for the diffusion between reservoirs)
124                                                        !! @tex $(kg.m^{-2}.dt^{-1})$ @endtex
125!$OMP THREADPRIVATE(min_drain)
126  REAL(r_std), SAVE :: max_drain = 0.1                  !! Diffusion constant for the fast regime
127                                                        !! @tex $(kg.m^{-2}.dt^{-1})$ @endtex
128!$OMP THREADPRIVATE(max_drain)
129  REAL(r_std), SAVE :: exp_drain = 1.5                  !! The exponential in the diffusion law (unitless)
130!$OMP THREADPRIVATE(exp_drain)
131  REAL(r_std), SAVE :: qsintcst = 0.1                   !! Transforms leaf area index into size of interception reservoir
132                                                        !! (unitless)
133!$OMP THREADPRIVATE(qsintcst)
134  REAL(r_std), SAVE :: mx_eau_nobio = 150.              !! Volumetric available soil water capacity in nobio fractions
135                                                        !! @tex $(kg.m^{-3} of soil)$ @endtex
136!$OMP THREADPRIVATE(mx_eau_nobio)
137  REAL(r_std), SAVE :: rsol_cste = 33.E3                !! Constant in the computation of resistance for bare soil evaporation
138                                                        !! @tex $(s.m^{-2})$ @endtex
139!$OMP THREADPRIVATE(rsol_cste)
140  REAL(r_std), SAVE :: hcrit_litter=0.08_r_std          !! Scaling depth for litter humidity (m)
141!$OMP THREADPRIVATE(hcrit_litter)
142
143  INTEGER(i_std), SAVE :: SO_DISCRETIZATION_METHOD      !! Soil layer discretization method selected, 0 = thermix, 1 = permafrost 
144!$OMP THREADPRIVATE(SO_DISCRETIZATION_METHOD)
145  INTEGER(i_std), PARAMETER :: SLD_THERMIX = 0          !! Soil layers discretization constant for thermix method
146  INTEGER(i_std), PARAMETER :: SLD_PERMAFROST = 1       !! Soil layers discretization constant for permafrost method
147
148  REAL(r_std), SAVE         :: THKICE = 2.2             !! Ice Thermal Conductivity (W/m/k)
149!$OMP THREADPRIVATE(THKICE)
150  REAL(r_std), SAVE         :: THKQTZ = 7.7             !! Thermal Conductivity for Quartz (W/m/k)
151!$OMP THREADPRIVATE(THKQTZ)
152  REAL(r_std), SAVE         :: THKW = 0.57              !! Water Thermal Conductivity (W/m/k)
153!$OMP THREADPRIVATE(THKW)
154
155  !! Parameters specific for the CWRR hydrology.
156
157  !!  1. Parameters for FAO Classification
158
159  !! Parameters for soil type distribution
160
161  REAL(r_std),DIMENSION(nscm_fao),SAVE :: soilclass_default_fao = &   !! Default soil texture distribution for fao :
162 & (/ 0.28, 0.52, 0.20 /)                                             !! in the following order : COARSE, MEDIUM, FINE (unitless)
163!$OMP THREADPRIVATE(soilclass_default_fao)
164
165  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: nvan_fao = &            !! Van Genuchten coefficient n (unitless)
166 & (/ 1.89_r_std, 1.56_r_std, 1.31_r_std /)                             !  RK: 1/n=1-m
167
168  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: avan_fao = &            !! Van Genuchten coefficient a
169  & (/ 0.0075_r_std, 0.0036_r_std, 0.0019_r_std /)                     !!  @tex $(mm^{-1})$ @endtex
170
171  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mcr_fao = &             !! Residual volumetric water content
172 & (/ 0.065_r_std, 0.078_r_std, 0.095_r_std /)                         !!  @tex $(m^{3} m^{-3})$ @endtex
173
174  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mcs_fao = &             !! Saturated volumetric water content
175 & (/ 0.41_r_std, 0.43_r_std, 0.41_r_std /)                            !!  @tex $(m^{3} m^{-3})$ @endtex
176
177  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: ks_fao = &              !! Hydraulic conductivity at saturation
178 & (/ 1060.8_r_std, 249.6_r_std, 62.4_r_std /)                         !!  @tex $(mm d^{-1})$ @endtex
179
180! The max available water content is smaller when mcw and mcf depend on texture,
181! so we increase pcent to a classical value of 80%
182  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: pcent_fao = &           !! Fraction of saturated volumetric soil moisture
183 & (/ 0.8_r_std, 0.8_r_std, 0.8_r_std /)                               !! above which transpir is max (0-1, unitless)
184
185  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: free_drain_max_fao = &  !! Max=default value of the permeability coeff 
186 & (/ 1.0_r_std, 1.0_r_std, 1.0_r_std /)                               !! at the bottom of the soil (0-1, unitless)
187
188!! We use the VG relationships to derive mcw and mcf depending on soil texture
189!! assuming that the matric potential for wilting point and field capacity is
190!! -150m (permanent WP) and -3.3m respectively
191!! (-1m for FC for the three sandy soils following Richards, L.A. and Weaver, L.R. (1944)
192!! Note that mcw GE mcr
193  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mcf_fao = &             !! Volumetric water content at field capacity
194 & (/ 0.1218_r_std, 0.1654_r_std, 0.2697_r_std /)                      !!  @tex $(m^{3} m^{-3})$ @endtex
195
196  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mcw_fao = &             !! Volumetric water content at wilting point
197 & (/ 0.0657_r_std,  0.0884_r_std, 0.1496_r_std/)                      !!  @tex $(m^{3} m^{-3})$ @endtex
198
199  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mc_awet_fao = &         !! Vol. wat. cont. above which albedo is cst
200 & (/ 0.25_r_std, 0.25_r_std, 0.25_r_std /)                            !!  @tex $(m^{3} m^{-3})$ @endtex
201
202  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mc_adry_fao = &         !! Vol. wat. cont. below which albedo is cst
203 & (/ 0.1_r_std, 0.1_r_std, 0.1_r_std /)                               !!  @tex $(m^{3} m^{-3})$ @endtex
204
205  REAL(r_std),DIMENSION(nscm_fao),SAVE :: SMCMAX_fao = &               !! porosity
206 & (/ 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
207
208  REAL(r_std),SAVE,DIMENSION(nscm_fao) :: QZ_fao = &              !! QUARTZ CONTENT (SOIL TYPE DEPENDENT)
209 & (/ 0.60_r_std, 0.40_r_std, 0.35_r_std /)                            !! Peters et al [1998]
210
211  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: so_capa_dry_ns_fao = &  !! Dry soil Heat capacity of soils,J.m^{-3}.K^{-1}
212 & (/ 1.34e+6_r_std, 1.21e+6_r_std, 1.23e+6_r_std /)                   !! Pielke [2002, 2013]
213
214  !!  2. Parameters for USDA Classification
215
216  !! Parameters for soil type distribution :
217  !! Sand, Loamy Sand, Sandy Loam, Silt Loam, Silt, Loam, Sandy Clay Loam, Silty Clay Loam, Clay Loam, Sandy Clay, Silty Clay, Clay
218
219  REAL(r_std),DIMENSION(nscm_usda),SAVE :: soilclass_default_usda = &    !! Default soil texture distribution in the above order :
220 & (/ 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
221                                                                         !! which have indices 3,6,9 in the 12-texture vector
222  !$OMP THREADPRIVATE(soilclass_default_usda)
223
224  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: nvan_usda = &            !! Van Genuchten coefficient n (unitless)
225 & (/ 2.68_r_std, 2.28_r_std, 1.89_r_std, 1.41_r_std, &                   !  RK: 1/n=1-m
226 &    1.37_r_std, 1.56_r_std, 1.48_r_std, 1.23_r_std, &
227 &    1.31_r_std, 1.23_r_std, 1.09_r_std, 1.09_r_std /)
228
229  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: avan_usda = &            !! Van Genuchten coefficient a
230 & (/ 0.0145_r_std, 0.0124_r_std, 0.0075_r_std, 0.0020_r_std, &          !!  @tex $(mm^{-1})$ @endtex
231 &    0.0016_r_std, 0.0036_r_std, 0.0059_r_std, 0.0010_r_std, &
232 &    0.0019_r_std, 0.0027_r_std, 0.0005_r_std, 0.0008_r_std /)
233
234  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mcr_usda = &             !! Residual volumetric water content
235 & (/ 0.045_r_std, 0.057_r_std, 0.065_r_std, 0.067_r_std, &              !!  @tex $(m^{3} m^{-3})$ @endtex
236 &    0.034_r_std, 0.078_r_std, 0.100_r_std, 0.089_r_std, &
237 &    0.095_r_std, 0.100_r_std, 0.070_r_std, 0.068_r_std /)
238
239  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mcs_usda = &             !! Saturated volumetric water content
240 & (/ 0.43_r_std, 0.41_r_std, 0.41_r_std, 0.45_r_std, &                  !!  @tex $(m^{3} m^{-3})$ @endtex
241 &    0.46_r_std, 0.43_r_std, 0.39_r_std, 0.43_r_std, &
242 &    0.41_r_std, 0.38_r_std, 0.36_r_std, 0.38_r_std /)
243
244  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: ks_usda = &              !! Hydraulic conductivity at saturation
245 & (/ 7128.0_r_std, 3501.6_r_std, 1060.8_r_std, 108.0_r_std, &           !!  @tex $(mm d^{-1})$ @endtex
246 &    60.0_r_std, 249.6_r_std, 314.4_r_std, 16.8_r_std, &
247 &    62.4_r_std, 28.8_r_std, 4.8_r_std, 48.0_r_std /)
248
249  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: pcent_usda = &           !! Fraction of saturated volumetric soil moisture
250 & (/ 0.8_r_std, 0.8_r_std, 0.8_r_std, 0.8_r_std, &                      !! above which transpir is max (0-1, unitless)
251 &    0.8_r_std, 0.8_r_std, 0.8_r_std, 0.8_r_std, &
252 &    0.8_r_std, 0.8_r_std, 0.8_r_std, 0.8_r_std /)
253
254  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: free_drain_max_usda = &  !! Max=default value of the permeability coeff
255 & (/ 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)
256 &    1.0_r_std, 1.0_r_std, 1.0_r_std, 1.0_r_std, &
257 &    1.0_r_std, 1.0_r_std, 1.0_r_std, 1.0_r_std /)
258
259  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mcf_usda = &             !! Volumetric water content at field capacity
260 & (/ 0.0493_r_std, 0.0710_r_std, 0.1218_r_std, 0.2402_r_std, &          !!  @tex $(m^{3} m^{-3})$ @endtex
261      0.2582_r_std, 0.1654_r_std, 0.1695_r_std, 0.3383_r_std, &
262      0.2697_r_std, 0.2672_r_std, 0.3370_r_std, 0.3469_r_std /)
263 
264  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mcw_usda = &             !! Volumetric water content at wilting point
265 & (/ 0.0450_r_std, 0.0570_r_std, 0.0657_r_std, 0.1039_r_std, &          !!  @tex $(m^{3} m^{-3})$ @endtex
266      0.0901_r_std, 0.0884_r_std, 0.1112_r_std, 0.1967_r_std, &
267      0.1496_r_std, 0.1704_r_std, 0.2665_r_std, 0.2707_r_std /)
268
269  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: VG_m_usda = &             
270 & (/ 0.6269_r_std, 0.5614_r_std, 0.4709_r_std, 0.2908_r_std, &                 
271 &    0.2701_r_std, 0.359_r_std,  0.3243_r_std, 0.187_r_std, &
272 &    0.2366_r_std, 0.187_r_std,  0.0826_r_std, 0.0826_r_std /)
273
274  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: VG_n_usda = &             
275 & (/ 2.68_r_std, 2.28_r_std, 1.89_r_std, 1.41_r_std, &                 
276 &    1.37_r_std, 1.56_r_std, 1.48_r_std, 1.23_r_std, &
277 &    1.31_r_std, 1.23_r_std, 1.09_r_std, 1.09_r_std /)
278
279  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: VG_alpha_usda = &             
280 & (/ 0.0145_r_std, 0.0124_r_std, 0.0075_r_std, 0.002_r_std, &                 
281 &    0.0016_r_std, 0.0036_r_std, 0.0059_r_std, 0.001_r_std, &
282 &    0.0019_r_std, 0.0027_r_std, 0.0005_r_std, 0.0008_r_std /)
283
284  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: VG_psi_fc_usda = &             
285 & (/ 1000_r_std, 1000_r_std, 1000_r_std, 3300_r_std, &                 
286 &    3300_r_std, 3300_r_std, 3300_r_std, 3300_r_std, &                 
287 &    3300_r_std, 3300_r_std, 3300_r_std, 3300_r_std /)
288
289  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: VG_psi_wp_usda = &             
290 & (/ 150000_r_std, 150000_r_std, 150000_r_std, 150000_r_std, &                 
291 &    150000_r_std, 150000_r_std, 150000_r_std, 150000_r_std, &                 
292 &    150000_r_std, 150000_r_std, 150000_r_std, 150000_r_std /)
293
294  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mc_awet_usda = &         !! Vol. wat. cont. above which albedo is cst
295 & (/ 0.25_r_std, 0.25_r_std, 0.25_r_std, 0.25_r_std, &                  !!  @tex $(m^{3} m^{-3})$ @endtex
296 &    0.25_r_std, 0.25_r_std, 0.25_r_std, 0.25_r_std, &
297 &    0.25_r_std, 0.25_r_std, 0.25_r_std, 0.25_r_std /)
298
299  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mc_adry_usda = &         !! Vol. wat. cont. below which albedo is cst
300 & (/ 0.1_r_std, 0.1_r_std, 0.1_r_std, 0.1_r_std, &                      !!  @tex $(m^{3} m^{-3})$ @endtex
301 &    0.1_r_std, 0.1_r_std, 0.1_r_std, 0.1_r_std, &
302 &    0.1_r_std, 0.1_r_std, 0.1_r_std, 0.1_r_std /)
303
304  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: SMCMAX_usda = &          !! porosity
305 & (/ 0.43_r_std, 0.41_r_std, 0.41_r_std, 0.45_r_std, &
306 &    0.46_r_std, 0.43_r_std, 0.39_r_std, 0.43_r_std, &
307 &    0.41_r_std, 0.38_r_std, 0.36_r_std, 0.38_r_std /)
308 
309  REAL(r_std),DIMENSION(nscm_usda),SAVE      :: QZ_usda = &              !! QUARTZ CONTENT (SOIL TYPE DEPENDENT)
310 & (/ 0.92_r_std, 0.82_r_std, 0.60_r_std, 0.25_r_std, &
311 &    0.10_r_std, 0.40_r_std, 0.60_r_std, 0.10_r_std, &
312 &    0.35_r_std, 0.52_r_std, 0.10_r_std, 0.25_r_std /)                  !! Peters et al [1998]
313
314  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: so_capa_dry_ns_usda = &  !! Dry soil Heat capacity of soils,J.m^{-3}.K^{-1}
315 & (/ 1.47e+6_r_std, 1.41e+6_r_std, 1.34e+6_r_std, 1.27e+6_r_std, &
316 &    1.21e+6_r_std, 1.21e+6_r_std, 1.18e+6_r_std, 1.32e+6_r_std, &
317 &    1.23e+6_r_std, 1.18e+6_r_std, 1.15e+6_r_std, 1.09e+6_r_std /)      !! Pielke [2002, 2013]
318 
319  !! Parameters for the numerical scheme used by CWRR
320
321  INTEGER(i_std), PARAMETER :: imin = 1                                 !! Start for CWRR linearisation (unitless)
322  INTEGER(i_std), PARAMETER :: nbint = 50                               !! Number of interval for CWRR linearisation (unitless)
323  INTEGER(i_std), PARAMETER :: imax = nbint+1                           !! Number of points for CWRR linearisation (unitless)
324  REAL(r_std), PARAMETER    :: w_time = 1.0_r_std                       !! Time weighting for CWRR numerical integration (unitless)
325
326
327  !! Variables related to soil freezing, in thermosoil :
328  LOGICAL, SAVE        :: ok_Ecorr                    !! Flag for energy conservation correction
329  LOGICAL, SAVE        :: ok_freeze_thermix           !! Flag to activate thermal part of the soil freezing scheme
330  LOGICAL, SAVE        :: read_reftemp                !! Flag to initialize soil temperature using climatological temperature
331  REAL(r_std), SAVE    :: poros                       !! Soil porosity (from USDA classification, mean value)(-)
332  REAL(r_std), SAVE    :: fr_dT                       !! Freezing window (K)
333
334  !! Variables related to soil freezing, in hydrol :
335  LOGICAL, SAVE        :: ok_freeze_cwrr              !! CWRR freezing scheme by I. Gouttevin
336  LOGICAL, SAVE        :: ok_thermodynamical_freezing !! Calculate frozen fraction thermodynamically
337
338 
339END MODULE constantes_soil_var
Note: See TracBrowser for help on using the repository browser.