source: branches/publications/ORCHIDEE_2.2_r7266/ORCHIDEE/src_parameters/constantes_soil_var.f90 @ 7541

Last change on this file since 7541 was 7541, checked in by fabienne.maignan, 2 years ago
  1. Zhang publication on coupling factor
File size: 17.0 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): AD: mcw and mcf depend now on soil texture, based on Van Genuchten equations
18!!                   and classical matric potential values, and pcent is adapted
19!!                   November 2020 by Salma Tafasca and Agnes Ducharne : we introduce a new texture class
20!!                   for clay oxisols (cf. Tafasca, 2020, PhD thesis; Tafasca et al., in prep for GRL).
21!!                   It makes no change if we read a soil texture map with only 12 USDA classes.
22!!
23!! REFERENCE(S) :
24!!- Roger A.Pielke, (2002), Mesoscale meteorological modeling, Academic Press Inc.
25!!- Polcher, J., Laval, K., DÃŒmenil, L., Lean, J., et Rowntree, P. R. (1996).
26!! Comparing three land surface schemes used in general circulation models. Journal of Hydrology, 180(1-4), 373--394.
27!!- Ducharne, A., Laval, K., et Polcher, J. (1998). Sensitivity of the hydrological cycle
28!! to the parametrization of soil hydrology in a GCM. Climate Dynamics, 14, 307--327.
29!!- Rosnay, P. de et Polcher, J. (1999). Modelling root water uptake in a complex land surface
30!! scheme coupled to a GCM. Hydrol. Earth Syst. Sci., 2(2/3), 239--255.
31!!- d'Orgeval, T. et Polcher, J. (2008). Impacts of precipitation events and land-use changes
32!! on West African river discharges during the years 1951--2000. Climate Dynamics, 31(2), 249--262.
33!!- Carsel, R. and Parrish, R.: Developing joint probability distributions of soil water
34!! retention characteristics, Water Resour. Res.,24, 755–769, 1988.
35!!- Mualem Y (1976). A new model for predicting the hydraulic conductivity 
36!! of unsaturated porous media. Water Resources Research 12(3):513-522
37!!- Van Genuchten M (1980). A closed-form equation for predicting the 
38!! hydraulic conductivity of unsaturated soils. Soil Sci Soc Am J, 44(5):892-898
39!!- Tafasca S. (2020). Evaluation de l’impact des propriétés du sol sur l’hydrologie simulee dans le
40!! modÚle ORCHIDEE, PhD thesis, Sorbonne Universite.
41!!- Tafasca S., Ducharne A. and Valentin C. Accounting for soil structure in pedo-transfer functions:
42!!  swelling vs non swelling clays. In prep for GRL.
43!!
44!! SVN          :
45!! $HeadURL: $
46!! $Date: $
47!! $Revision: $
48!! \n
49!_ ================================================================================================================================
50
51MODULE constantes_soil_var
52
53  USE defprec
54  USE vertical_soil_var
55
56  IMPLICIT NONE
57
58  LOGICAL, SAVE             :: check_cwrr               !! Calculate diagnostics to check the water balance in hydrol (true/false)
59!$OMP THREADPRIVATE(check_cwrr)
60
61  !! Number of soil classes
62
63  INTEGER(i_std), PARAMETER :: ntext=3                  !! Number of soil textures (Silt, Sand, Clay)
64  INTEGER(i_std), PARAMETER :: nstm=3                   !! Number of soil tiles (unitless)
65  CHARACTER(LEN=30)         :: soil_classif             !! Type of classification used for the map of soil types.
66                                                        !! It must be consistent with soil file given by
67                                                        !! SOILCLASS_FILE parameter.
68!$OMP THREADPRIVATE(soil_classif)
69  INTEGER(i_std), PARAMETER :: nscm_fao=3               !! For FAO Classification (unitless)
70  INTEGER(i_std), PARAMETER :: nscm_usda=13             !! For USDA Classification (unitless)
71  INTEGER(i_std), SAVE      :: nscm=nscm_fao            !! Default value for nscm
72!$OMP THREADPRIVATE(nscm)
73
74  !! Parameters for soil thermodynamics
75
76  REAL(r_std), SAVE :: so_capa_dry = 1.80e+6            !! Dry soil Heat capacity of soils
77                                                        !! @tex $(J.m^{-3}.K^{-1})$ @endtex
78!$OMP THREADPRIVATE(so_capa_dry)
79  REAL(r_std), SAVE :: so_cond_dry = 0.40               !! Dry soil Thermal Conductivity of soils
80                                                        !! @tex $(W.m^{-2}.K^{-1})$ @endtex
81!$OMP THREADPRIVATE(so_cond_dry)
82  REAL(r_std), SAVE :: sn_cond = 0.3                    !! Thermal Conductivity of snow
83                                                        !! @tex $(W.m^{-2}.K^{-1})$ @endtex 
84!$OMP THREADPRIVATE(sn_cond)
85  REAL(r_std), SAVE :: sn_dens = 330.0                  !! Snow density for the soil thermodynamics
86                                                        !! (kg/m3)
87!$OMP THREADPRIVATE(sn_dens)
88  REAL(r_std), SAVE :: sn_capa                          !! Heat capacity for snow
89                                                        !! @tex $(J.m^{-3}.K^{-1})$ @endtex
90!$OMP THREADPRIVATE(sn_capa)
91  REAL(r_std), SAVE :: water_capa = 4.18e+6             !! Water heat capacity
92                                                        !! @tex $(J.m^{-3}.K^{-1})$ @endtex
93!$OMP THREADPRIVATE(water_capa)
94  REAL(r_std), SAVE :: brk_capa = 2.0e+6                !! Heat capacity of generic rock
95                                                        !! @tex $(J.m^{-3}.K^{-1})$ @endtex
96!$OMP THREADPRIVATE(brk_capa)
97  REAL(r_std), SAVE :: brk_cond = 3.0                   !! Thermal conductivity of saturated granitic rock
98                                                        !! @tex $(W.m^{-1}.K^{-1})$ @endtex
99!$OMP THREADPRIVATE(brk_cond)
100
101  REAL(r_std), SAVE :: qsintcst = 0.02                  !! Transforms leaf area index into size of interception reservoir
102                                                        !! (unitless)
103!$OMP THREADPRIVATE(qsintcst)
104  REAL(r_std), SAVE :: mx_eau_nobio = 150.              !! Volumetric available soil water capacity in nobio fractions
105                                                        !! @tex $(kg.m^{-3} of soil)$ @endtex
106!$OMP THREADPRIVATE(mx_eau_nobio)
107
108
109  !! Parameters specific for the CWRR hydrology.
110
111  !!  1. Parameters for FAO Classification
112
113  !! Parameters for soil type distribution
114
115  REAL(r_std),DIMENSION(nscm_fao),SAVE :: soilclass_default_fao = &   !! Default soil texture distribution for fao :
116 & (/ 0.28, 0.52, 0.20 /)                                             !! in the following order : COARSE, MEDIUM, FINE (unitless)
117!$OMP THREADPRIVATE(soilclass_default_fao)
118
119  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: nvan_fao = &            !! Van Genuchten coefficient n (unitless)
120 & (/ 1.89_r_std, 1.56_r_std, 1.31_r_std /)                             !  RK: 1/n=1-m
121
122  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: avan_fao = &            !! Van Genuchten coefficient a
123  & (/ 0.0075_r_std, 0.0036_r_std, 0.0019_r_std /)                     !!  @tex $(mm^{-1})$ @endtex
124
125  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mcr_fao = &             !! Residual volumetric water content
126 & (/ 0.065_r_std, 0.078_r_std, 0.095_r_std /)                         !!  @tex $(m^{3} m^{-3})$ @endtex
127
128  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mcs_fao = &             !! Saturated volumetric water content
129 & (/ 0.41_r_std, 0.43_r_std, 0.41_r_std /)                            !!  @tex $(m^{3} m^{-3})$ @endtex
130
131  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: ks_fao = &              !! Hydraulic conductivity at saturation
132 & (/ 1060.8_r_std, 249.6_r_std, 62.4_r_std /)                         !!  @tex $(mm d^{-1})$ @endtex
133
134! The max available water content is smaller when mcw and mcf depend on texture,
135! so we increase pcent to a classical value of 80%
136  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: pcent_fao = &           !! Fraction of saturated volumetric soil moisture
137 & (/ 0.8_r_std, 0.8_r_std, 0.8_r_std /)                               !! above which transpir is max (0-1, unitless)
138
139  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: free_drain_max_fao = &  !! Max=default value of the permeability coeff 
140 & (/ 1.0_r_std, 1.0_r_std, 1.0_r_std /)                               !! at the bottom of the soil (0-1, unitless)
141
142!! We use the VG relationships to derive mcw and mcf depending on soil texture
143!! assuming that the matric potential for wilting point and field capacity is
144!! -150m (permanent WP) and -3.3m respectively
145!! (-1m for FC for the three sandy soils following Richards, L.A. and Weaver, L.R. (1944)
146!! Note that mcw GE mcr
147  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mcf_fao = &             !! Volumetric water content at field capacity
148 & (/ 0.1218_r_std, 0.1654_r_std, 0.2697_r_std /)                      !!  @tex $(m^{3} m^{-3})$ @endtex
149
150  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mcw_fao = &             !! Volumetric water content at wilting point
151 & (/ 0.0657_r_std,  0.0884_r_std, 0.1496_r_std/)                      !!  @tex $(m^{3} m^{-3})$ @endtex
152
153  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mc_awet_fao = &         !! Vol. wat. cont. above which albedo is cst
154 & (/ 0.25_r_std, 0.25_r_std, 0.25_r_std /)                            !!  @tex $(m^{3} m^{-3})$ @endtex
155
156  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mc_adry_fao = &         !! Vol. wat. cont. below which albedo is cst
157 & (/ 0.1_r_std, 0.1_r_std, 0.1_r_std /)                               !!  @tex $(m^{3} m^{-3})$ @endtex
158
159  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: QZ_fao = &              !! QUARTZ CONTENT (SOIL TYPE DEPENDENT)
160 & (/ 0.60_r_std, 0.40_r_std, 0.35_r_std /)                            !! Peters et al [1998]
161
162  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: so_capa_dry_ns_fao = &  !! Dry soil Heat capacity of soils,J.m^{-3}.K^{-1}
163 & (/ 1.34e+6_r_std, 1.21e+6_r_std, 1.23e+6_r_std /)                   !! Pielke [2002, 2013]
164
165  !!  2. Parameters for USDA Classification
166
167  !! Parameters for soil type distribution :
168  !! Sand, Loamy Sand, Sandy Loam, Silt Loam, Silt, Loam, Sandy Clay Loam, Silty Clay Loam, Clay Loam, Sandy Clay, Silty Clay, Clay
169
170  REAL(r_std),DIMENSION(nscm_usda),SAVE :: soilclass_default_usda = &    !! Default soil texture distribution in the above order :
171 & (/ 0.28, 0.52, 0.20, 0.0, 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
172                                                                         !! which have indices 3,6,9 in the 12-texture vector
173  !$OMP THREADPRIVATE(soilclass_default_usda)
174
175  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: nvan_usda = &            !! Van Genuchten coefficient n (unitless)
176 & (/ 2.68_r_std, 2.28_r_std, 1.89_r_std, 1.41_r_std, &                   !  RK: 1/n=1-m
177 &    1.37_r_std, 1.56_r_std, 1.48_r_std, 1.23_r_std, &
178 &    1.31_r_std, 1.23_r_std, 1.09_r_std, 1.09_r_std, &
179 &    1.552_r_std    /) ! oxisols
180
181  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: avan_usda = &            !! Van Genuchten coefficient a
182 & (/ 0.0145_r_std, 0.0124_r_std, 0.0075_r_std, 0.0020_r_std, &          !!  @tex $(mm^{-1})$ @endtex
183 &    0.0016_r_std, 0.0036_r_std, 0.0059_r_std, 0.0010_r_std, &
184 &    0.0019_r_std, 0.0027_r_std, 0.0005_r_std, 0.0008_r_std, &
185 &    0.0132_r_std /) ! oxisols
186
187  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mcr_usda = &             !! Residual volumetric water content
188 & (/ 0.045_r_std, 0.057_r_std, 0.065_r_std, 0.067_r_std, &              !!  @tex $(m^{3} m^{-3})$ @endtex
189 &    0.034_r_std, 0.078_r_std, 0.100_r_std, 0.089_r_std, &
190 &    0.095_r_std, 0.100_r_std, 0.070_r_std, 0.068_r_std, &
191 &    0.068_r_std /) ! oxisols
192
193  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mcs_usda = &             !! Saturated volumetric water content
194 & (/ 0.43_r_std, 0.41_r_std, 0.41_r_std, 0.45_r_std, &                  !!  @tex $(m^{3} m^{-3})$ @endtex
195 &    0.46_r_std, 0.43_r_std, 0.39_r_std, 0.43_r_std, &
196 &    0.41_r_std, 0.38_r_std, 0.36_r_std, 0.38_r_std, &
197 &    0.503_r_std  /) ! oxisols
198
199  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: ks_usda = &              !! Hydraulic conductivity at saturation
200 & (/ 7128.0_r_std, 3501.6_r_std, 1060.8_r_std, 108.0_r_std, &           !!  @tex $(mm d^{-1})$ @endtex
201 &    60.0_r_std, 249.6_r_std, 314.4_r_std, 16.8_r_std, &
202 &    62.4_r_std, 28.8_r_std, 4.8_r_std, 48.0_r_std, &
203 &    6131.4_r_std  /) ! oxisols
204
205  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: pcent_usda = &           !! Fraction of saturated volumetric soil moisture
206 & (/ 0.8_r_std, 0.8_r_std, 0.8_r_std, 0.8_r_std, &                      !! above which transpir is max (0-1, unitless)
207 &    0.8_r_std, 0.8_r_std, 0.8_r_std, 0.8_r_std, &
208 &    0.8_r_std, 0.8_r_std, 0.8_r_std, 0.8_r_std, &
209 &    0.8_r_std /) ! oxisols
210
211  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: free_drain_max_usda = &  !! Max=default value of the permeability coeff
212 & (/ 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)
213 &    1.0_r_std, 1.0_r_std, 1.0_r_std, 1.0_r_std, &
214 &    1.0_r_std, 1.0_r_std, 1.0_r_std, 1.0_r_std,  &
215 &    1.0_r_std /)
216
217  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mcf_usda = &             !! Volumetric water content at field capacity
218 & (/ 0.0493_r_std, 0.0710_r_std, 0.1218_r_std, 0.2402_r_std, &          !!  @tex $(m^{3} m^{-3})$ @endtex
219      0.2582_r_std, 0.1654_r_std, 0.1695_r_std, 0.3383_r_std, &
220      0.2697_r_std, 0.2672_r_std, 0.3370_r_std, 0.3469_r_std, &
221      0.172_r_std  /) ! oxisols
222 
223  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mcw_usda = &             !! Volumetric water content at wilting point
224 & (/ 0.0450_r_std, 0.0570_r_std, 0.0657_r_std, 0.1039_r_std, &          !!  @tex $(m^{3} m^{-3})$ @endtex
225      0.0901_r_std, 0.0884_r_std, 0.1112_r_std, 0.1967_r_std, &
226      0.1496_r_std, 0.1704_r_std, 0.2665_r_std, 0.2707_r_std, &
227      0.075_r_std  /) ! oxisols
228
229  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mc_awet_usda = &         !! Vol. wat. cont. above which albedo is cst
230 & (/ 0.25_r_std, 0.25_r_std, 0.25_r_std, 0.25_r_std, &                  !!  @tex $(m^{3} m^{-3})$ @endtex
231 &    0.25_r_std, 0.25_r_std, 0.25_r_std, 0.25_r_std, &
232 &    0.25_r_std, 0.25_r_std, 0.25_r_std, 0.25_r_std, &
233 &    0.25_r_std /)
234
235  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mc_adry_usda = &         !! Vol. wat. cont. below which albedo is cst
236 & (/ 0.1_r_std, 0.1_r_std, 0.1_r_std, 0.1_r_std, &                      !!  @tex $(m^{3} m^{-3})$ @endtex
237 &    0.1_r_std, 0.1_r_std, 0.1_r_std, 0.1_r_std, &
238 &    0.1_r_std, 0.1_r_std, 0.1_r_std, 0.1_r_std, &
239 &    0.1_r_std /) ! oxisols
240 
241  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: QZ_usda = &              !! QUARTZ CONTENT (SOIL TYPE DEPENDENT)
242 & (/ 0.92_r_std, 0.82_r_std, 0.60_r_std, 0.25_r_std, &                  !! Peters et al [1998]
243 &    0.10_r_std, 0.40_r_std, 0.60_r_std, 0.10_r_std, &
244 &    0.35_r_std, 0.52_r_std, 0.10_r_std, 0.25_r_std, &
245&     0.25_r_std /)  ! oxisols                 
246
247  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: so_capa_dry_ns_usda = &  !! Dry soil Heat capacity of soils,J.m^{-3}.K^{-1}
248 & (/ 1.47e+6_r_std, 1.41e+6_r_std, 1.34e+6_r_std, 1.27e+6_r_std, &      !! Pielke [2002, 2013]
249 &    1.21e+6_r_std, 1.21e+6_r_std, 1.18e+6_r_std, 1.32e+6_r_std, &
250 &    1.23e+6_r_std, 1.18e+6_r_std, 1.15e+6_r_std, 1.09e+6_r_std, &
251 &    1.09e+6_r_std /) ! oxisols     
252 
253  !! Parameters for the numerical scheme used by CWRR
254
255  INTEGER(i_std), PARAMETER :: imin = 1                                 !! Start for CWRR linearisation (unitless)
256  INTEGER(i_std), PARAMETER :: nbint = 50                               !! Number of interval for CWRR linearisation (unitless)
257  INTEGER(i_std), PARAMETER :: imax = nbint+1                           !! Number of points for CWRR linearisation (unitless)
258  REAL(r_std), PARAMETER    :: w_time = 1.0_r_std                       !! Time weighting for CWRR numerical integration (unitless)
259
260
261  !! Variables related to soil freezing, in thermosoil :
262  LOGICAL, SAVE        :: ok_Ecorr                    !! Flag for energy conservation correction
263!$OMP THREADPRIVATE(ok_Ecorr)
264  LOGICAL, SAVE        :: ok_freeze_thermix           !! Flag to activate thermal part of the soil freezing scheme
265!$OMP THREADPRIVATE(ok_freeze_thermix)
266  LOGICAL, SAVE        :: ok_freeze_thaw_latent_heat  !! Flag to activate latent heat part of the soil freezing scheme
267!$OMP THREADPRIVATE(ok_freeze_thaw_latent_heat)
268  LOGICAL, SAVE        :: read_reftemp                !! Flag to initialize soil temperature using climatological temperature
269!$OMP THREADPRIVATE(read_reftemp)
270  REAL(r_std), SAVE    :: fr_dT                       !! Freezing window (K)
271!$OMP THREADPRIVATE(fr_dT)
272
273  !! Variables related to soil freezing, in hydrol :
274  LOGICAL, SAVE        :: ok_freeze_cwrr              !! CWRR freezing scheme by I. Gouttevin
275!$OMP THREADPRIVATE(ok_freeze_cwrr)
276  LOGICAL, SAVE        :: ok_thermodynamical_freezing !! Calculate frozen fraction thermodynamically
277!$OMP THREADPRIVATE(ok_thermodynamical_freezing)
278
279 
280END MODULE constantes_soil_var
Note: See TracBrowser for help on using the repository browser.