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

Last change on this file since 7519 was 7519, checked in by josefine.ghattas, 2 years ago

Correct comments and moved capa_ice as proposed by Catherine Ottle, see ticket #809

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