source: branches/ORCHIDEE_2_2/ORCHIDEE/src_parameters/constantes_soil_var.f90 @ 7337

Last change on this file since 7337 was 7337, checked in by agnes.ducharne, 3 years ago

Simplification of soil texture processing, cf ticket #416: when using the Zobler map, the soil parameters are no more taken from 3-value "FAO" vectors in constantes_soil_var.f90, but from 13-value USDA vectors, owing to a pointer fao2usda. A 5-day running test with the Zobler map shows no changes, but over Greenland (class 6=ice in Zobler map).

File size: 15.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!!                   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 propriétés du sol sur l’hydrologie simulee dans le
42!! modÚle 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_fao            !! Default value for nscm
74!$OMP THREADPRIVATE(nscm)
75
76  !! Parameters for soil thermodynamics
77
78  REAL(r_std), SAVE :: so_capa_dry = 1.80e+6            !! Dry soil Heat capacity of soils
79                                                        !! @tex $(J.m^{-3}.K^{-1})$ @endtex
80!$OMP THREADPRIVATE(so_capa_dry)
81  REAL(r_std), SAVE :: so_cond_dry = 0.40               !! Dry soil Thermal Conductivity of soils
82                                                        !! @tex $(W.m^{-2}.K^{-1})$ @endtex
83!$OMP THREADPRIVATE(so_cond_dry)
84  REAL(r_std), SAVE :: sn_cond = 0.3                    !! Thermal Conductivity of snow
85                                                        !! @tex $(W.m^{-2}.K^{-1})$ @endtex 
86!$OMP THREADPRIVATE(sn_cond)
87  REAL(r_std), SAVE :: sn_dens = 330.0                  !! Snow density for the soil thermodynamics
88                                                        !! (kg/m3)
89!$OMP THREADPRIVATE(sn_dens)
90  REAL(r_std), SAVE :: sn_capa                          !! Heat capacity for snow
91                                                        !! @tex $(J.m^{-3}.K^{-1})$ @endtex
92!$OMP THREADPRIVATE(sn_capa)
93  REAL(r_std), SAVE :: water_capa = 4.18e+6             !! Water heat capacity
94                                                        !! @tex $(J.m^{-3}.K^{-1})$ @endtex
95!$OMP THREADPRIVATE(water_capa)
96  REAL(r_std), SAVE :: brk_capa = 2.0e+6                !! Heat capacity of generic rock
97                                                        !! @tex $(J.m^{-3}.K^{-1})$ @endtex
98!$OMP THREADPRIVATE(brk_capa)
99  REAL(r_std), SAVE :: brk_cond = 3.0                   !! Thermal conductivity of saturated granitic rock
100                                                        !! @tex $(W.m^{-1}.K^{-1})$ @endtex
101!$OMP THREADPRIVATE(brk_cond)
102
103  REAL(r_std), SAVE :: qsintcst = 0.02                  !! Transforms leaf area index into size of interception reservoir
104                                                        !! (unitless)
105!$OMP THREADPRIVATE(qsintcst)
106  REAL(r_std), SAVE :: mx_eau_nobio = 150.              !! Volumetric available soil water capacity in nobio fractions
107                                                        !! @tex $(kg.m^{-3} of soil)$ @endtex
108!$OMP THREADPRIVATE(mx_eau_nobio)
109
110  !! Parameters specific for the CWRR hydrology.
111
112  !!  1. Parameters for FAO-Zobler Map
113
114  INTEGER(i_std), PARAMETER,DIMENSION(nscm_fao) :: fao2usda = (/ 3,6,9 /) !! To find the values of Coarse, Medium, Fine in Zobler map
115  !! from the USDA lookup tables
116 
117!!$  REAL(r_std),DIMENSION(nscm_fao),SAVE :: soilclass_default_fao = &   !! Default soil texture distribution for fao :
118!!$ & (/ 0.28, 0.52, 0.20 /)                                             !! in the following order : COARSE, MEDIUM, FINE (unitless)
119!!$!$OMP THREADPRIVATE(soilclass_default_fao)
120
121  !!  2. Parameters for USDA Classification
122
123  !! Parameters for soil type distribution :
124  !! Sand, Loamy Sand, Sandy Loam, Silt Loam, Silt, Loam, Sandy Clay Loam, Silty Clay Loam, Clay Loam, Sandy Clay, Silty Clay, Clay
125
126  ! AD-Warning: I don't understand correctly the use of soilclass_default; when removing the _fao vectors, the default texture in
127  ! Greenland, where the Zobler map has no data, were changed, even when having 0.28 at the 3rd place below
128  ! I kept the original soilclass_default_usda to keep the Reynolds map unchanged
129 
130  REAL(r_std),DIMENSION(nscm_usda),SAVE :: soilclass_default_usda = &    !! Default soil texture distribution in the above order :
131 & (/ 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
132  !! which have indices 3,6,9 in the 12-texture vector
133  !$OMP THREADPRIVATE(soilclass_default_usda)
134
135!!$  REAL(r_std),DIMENSION(nscm_usda),SAVE :: soilclass_default_usda = &       !! Default soil texture distribution, to be coherent with the
136!!$ & (/ 0.0, 0.0, 0.28, 0.0, 0.0, 0.52, 0.0, 0.0, 0.20, 0.0, 0.0, 0.0, 0.0 /) !! original FAO/Zobler values
137!!$  !$OMP THREADPRIVATE(soilclass_default_usda) 
138
139  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: nvan_usda = &            !! Van Genuchten coefficient n (unitless)
140 & (/ 2.68_r_std, 2.28_r_std, 1.89_r_std, 1.41_r_std, &                   !  RK: 1/n=1-m
141 &    1.37_r_std, 1.56_r_std, 1.48_r_std, 1.23_r_std, &
142 &    1.31_r_std, 1.23_r_std, 1.09_r_std, 1.09_r_std, &
143 &    1.552_r_std    /) ! oxisols
144
145  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: avan_usda = &            !! Van Genuchten coefficient a
146 & (/ 0.0145_r_std, 0.0124_r_std, 0.0075_r_std, 0.0020_r_std, &          !!  @tex $(mm^{-1})$ @endtex
147 &    0.0016_r_std, 0.0036_r_std, 0.0059_r_std, 0.0010_r_std, &
148 &    0.0019_r_std, 0.0027_r_std, 0.0005_r_std, 0.0008_r_std, &
149 &    0.0132_r_std /) ! oxisols
150
151  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mcr_usda = &             !! Residual volumetric water content
152 & (/ 0.045_r_std, 0.057_r_std, 0.065_r_std, 0.067_r_std, &              !!  @tex $(m^{3} m^{-3})$ @endtex
153 &    0.034_r_std, 0.078_r_std, 0.100_r_std, 0.089_r_std, &
154 &    0.095_r_std, 0.100_r_std, 0.070_r_std, 0.068_r_std, &
155 &    0.068_r_std /) ! oxisols
156
157  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mcs_usda = &             !! Saturated volumetric water content
158 & (/ 0.43_r_std, 0.41_r_std, 0.41_r_std, 0.45_r_std, &                  !!  @tex $(m^{3} m^{-3})$ @endtex
159 &    0.46_r_std, 0.43_r_std, 0.39_r_std, 0.43_r_std, &
160 &    0.41_r_std, 0.38_r_std, 0.36_r_std, 0.38_r_std, &
161 &    0.503_r_std  /) ! oxisols
162
163  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: ks_usda = &              !! Hydraulic conductivity at saturation
164 & (/ 7128.0_r_std, 3501.6_r_std, 1060.8_r_std, 108.0_r_std, &           !!  @tex $(mm d^{-1})$ @endtex
165 &    60.0_r_std, 249.6_r_std, 314.4_r_std, 16.8_r_std, &
166 &    62.4_r_std, 28.8_r_std, 4.8_r_std, 48.0_r_std, &
167 &    6131.4_r_std  /) ! oxisols
168
169! The max available water content is smaller when mcw and mcf depend on texture,
170! so we increase pcent to a classical value of 80% 
171  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: pcent_usda = &           !! Fraction of saturated volumetric soil moisture
172 & (/ 0.8_r_std, 0.8_r_std, 0.8_r_std, 0.8_r_std, &                      !! above which transpir is max (0-1, unitless)
173 &    0.8_r_std, 0.8_r_std, 0.8_r_std, 0.8_r_std, &
174 &    0.8_r_std, 0.8_r_std, 0.8_r_std, 0.8_r_std, &
175 &    0.8_r_std /) ! oxisols
176
177  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: free_drain_max_usda = &  !! Max=default value of the permeability coeff
178 & (/ 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)
179 &    1.0_r_std, 1.0_r_std, 1.0_r_std, 1.0_r_std, &
180 &    1.0_r_std, 1.0_r_std, 1.0_r_std, 1.0_r_std,  &
181 &    1.0_r_std /)
182 
183!! We use the VG relationships to derive mcw and mcf depending on soil texture
184!! assuming that the matric potential for wilting point and field capacity is
185!! -150m (permanent WP) and -3.3m respectively
186!! (-1m for FC for the three sandy soils following Richards, L.A. and Weaver, L.R. (1944)
187!! Note that mcw GE mcr
188  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mcf_usda = &             !! Volumetric water content at field capacity
189 & (/ 0.0493_r_std, 0.0710_r_std, 0.1218_r_std, 0.2402_r_std, &          !!  @tex $(m^{3} m^{-3})$ @endtex
190      0.2582_r_std, 0.1654_r_std, 0.1695_r_std, 0.3383_r_std, &
191      0.2697_r_std, 0.2672_r_std, 0.3370_r_std, 0.3469_r_std, &
192      0.172_r_std  /) ! oxisols
193 
194  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mcw_usda = &             !! Volumetric water content at wilting point
195 & (/ 0.0450_r_std, 0.0570_r_std, 0.0657_r_std, 0.1039_r_std, &          !!  @tex $(m^{3} m^{-3})$ @endtex
196      0.0901_r_std, 0.0884_r_std, 0.1112_r_std, 0.1967_r_std, &
197      0.1496_r_std, 0.1704_r_std, 0.2665_r_std, 0.2707_r_std, &
198      0.075_r_std  /) ! oxisols
199
200  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mc_awet_usda = &         !! Vol. wat. cont. above which albedo is cst
201 & (/ 0.25_r_std, 0.25_r_std, 0.25_r_std, 0.25_r_std, &                  !!  @tex $(m^{3} m^{-3})$ @endtex
202 &    0.25_r_std, 0.25_r_std, 0.25_r_std, 0.25_r_std, &
203 &    0.25_r_std, 0.25_r_std, 0.25_r_std, 0.25_r_std, &
204 &    0.25_r_std /)
205
206  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mc_adry_usda = &         !! Vol. wat. cont. below which albedo is cst
207 & (/ 0.1_r_std, 0.1_r_std, 0.1_r_std, 0.1_r_std, &                      !!  @tex $(m^{3} m^{-3})$ @endtex
208 &    0.1_r_std, 0.1_r_std, 0.1_r_std, 0.1_r_std, &
209 &    0.1_r_std, 0.1_r_std, 0.1_r_std, 0.1_r_std, &
210 &    0.1_r_std /) ! oxisols
211 
212  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: QZ_usda = &              !! QUARTZ CONTENT (SOIL TYPE DEPENDENT)
213 & (/ 0.92_r_std, 0.82_r_std, 0.60_r_std, 0.25_r_std, &                  !! Peters et al [1998]
214 &    0.10_r_std, 0.40_r_std, 0.60_r_std, 0.10_r_std, &
215 &    0.35_r_std, 0.52_r_std, 0.10_r_std, 0.25_r_std, &
216&     0.25_r_std /)  ! oxisols                 
217
218  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: so_capa_dry_ns_usda = &  !! Dry soil Heat capacity of soils,J.m^{-3}.K^{-1}
219 & (/ 1.47e+6_r_std, 1.41e+6_r_std, 1.34e+6_r_std, 1.27e+6_r_std, &      !! Pielke [2002, 2013]
220 &    1.21e+6_r_std, 1.21e+6_r_std, 1.18e+6_r_std, 1.32e+6_r_std, &
221 &    1.23e+6_r_std, 1.18e+6_r_std, 1.15e+6_r_std, 1.09e+6_r_std, &
222 &    1.09e+6_r_std /) ! oxisols     
223 
224  !! Parameters for the numerical scheme used by CWRR
225
226  INTEGER(i_std), PARAMETER :: imin = 1                                 !! Start for CWRR linearisation (unitless)
227  INTEGER(i_std), PARAMETER :: nbint = 50                               !! Number of interval for CWRR linearisation (unitless)
228  INTEGER(i_std), PARAMETER :: imax = nbint+1                           !! Number of points for CWRR linearisation (unitless)
229  REAL(r_std), PARAMETER    :: w_time = 1.0_r_std                       !! Time weighting for CWRR numerical integration (unitless)
230
231
232  !! Variables related to soil freezing, in thermosoil :
233  LOGICAL, SAVE        :: ok_Ecorr                    !! Flag for energy conservation correction
234!$OMP THREADPRIVATE(ok_Ecorr)
235  LOGICAL, SAVE        :: ok_freeze_thermix           !! Flag to activate thermal part of the soil freezing scheme
236!$OMP THREADPRIVATE(ok_freeze_thermix)
237  LOGICAL, SAVE        :: ok_freeze_thaw_latent_heat  !! Flag to activate latent heat part of the soil freezing scheme
238!$OMP THREADPRIVATE(ok_freeze_thaw_latent_heat)
239  LOGICAL, SAVE        :: read_reftemp                !! Flag to initialize soil temperature using climatological temperature
240!$OMP THREADPRIVATE(read_reftemp)
241  REAL(r_std), SAVE    :: fr_dT                       !! Freezing window (K)
242!$OMP THREADPRIVATE(fr_dT)
243
244  !! Variables related to soil freezing, in hydrol :
245  LOGICAL, SAVE        :: ok_freeze_cwrr              !! CWRR freezing scheme by I. Gouttevin
246!$OMP THREADPRIVATE(ok_freeze_cwrr)
247  LOGICAL, SAVE        :: ok_thermodynamical_freezing !! Calculate frozen fraction thermodynamically
248!$OMP THREADPRIVATE(ok_thermodynamical_freezing)
249
250 
251END MODULE constantes_soil_var
Note: See TracBrowser for help on using the repository browser.