source: tags/ORCHIDEE_4_1/ORCHIDEE/src_parameters/constantes_soil_var.f90 @ 7852

Last change on this file since 7852 was 7649, checked in by sebastiaan.luyssaert, 2 years ago

Manually tuned qsintcst, a1 and b1 for global testing

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