source: branches/publications/ORCHIDEE-ICE_SurfaceMassBalance/src_parameters/constantes_soil_var.f90 @ 8398

Last change on this file since 8398 was 7396, checked in by christophe.dumas, 2 years ago

New 3 layer ice scheme on ice-sheet area that can be activated via the OK_ICE_SHEET flag

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