source: branches/ORCHIDEE_3_CMIP6/ORCHIDEE/src_parameters/constantes_soil_var.f90 @ 8367

Last change on this file since 8367 was 6505, checked in by josefine.ghattas, 4 years ago

Removed externalized parameters WET_SOIL_HEAT_CAPACITY and WET_SOIL_HEAT_COND never used. This corresponds to point 2 in ticket #604

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