source: branches/publications/ORCHIDEE_CAN_r3069/src_parameters/constantes_soil_var.f90 @ 7346

Last change on this file since 7346 was 2945, checked in by sebastiaan.luyssaert, 9 years ago

DEV: tested 1 year global. This code contains the latest version for anthropogenic tree species channges, several bug fixes to forest management as well as the code for the fully integrated multi-layer energy budget. This implies that the multi-layer energy budget makes use Pinty's albedo scheme, the rognostic canopy structure as well as a vertical profile for stomatal conductance. This is an intermediate version because species change code is not complete as some management changes have not been implemented yet. Further the multi-layer albedo code needs more work in terms of calculating average fluxes at the pixel rather than the PFT level

File size: 16.6 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 three main 
15!!                 soil textures (coarse, medium and fine) come from Carsel and Parrish 
16!!                 (1988).
17!!
18!! RECENT CHANGE(S): Sonke Zaehle changed hcrit_litter value according to Shilong Piao from 0.03 to 0.08, 080806
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
48  IMPLICIT NONE
49
50
51  LOGICAL, SAVE             :: check_waterbal=.TRUE.    !! The check the water balance (true/false)
52!$OMP THREADPRIVATE(check_waterbal)
53
54  !! Dimensioning parameters
55
56  INTEGER(i_std), SAVE      :: ngrnd                    !! Number of soil level for thermo (unitless)
57  !$OMP THREADPRIVATE(ngrnd)
58  INTEGER(i_std), PARAMETER :: nbdl=11                  !! Number of diagnostic levels in the soil
59                                                        !! To compare hydrologic variables with tag 1.6 and lower,
60                                                        !! set nbdl to 6 : INTEGER(i_std), PARAMETER :: nbdl = 6
61                                                        !! (unitless)
62  INTEGER(i_std), PARAMETER :: nslm=11                  !! Number of levels in CWRR (unitless)
63
64  REAL(r_std), SAVE         :: dpu_max                  !! Maximum depth of soil reservoir (m). Default value is set
65                                                        !! in intsurf_config depending on Choisnel(4m) or CWRR(2m)
66!$OMP THREADPRIVATE(dpu_max)
67
68  !! Number of soil classes
69
70  INTEGER(i_std), PARAMETER :: ntext=3                  !! Number of soil textures (Silt, Sand, Clay)
71  INTEGER(i_std), PARAMETER :: nstm=3                   !! Number of soil tiles (unitless)
72  CHARACTER(LEN=30)         :: soil_classif             !! Type of classification used for the map of soil types.
73                                                        !! It must be consistent with soil file given by
74                                                        !! SOILCLASS_FILE parameter.
75  INTEGER(i_std), PARAMETER :: nscm_fao=3               !! For FAO Classification (unitless)
76  INTEGER(i_std), PARAMETER :: nscm_usda=12             !! For USDA Classification (unitless)
77  INTEGER(i_std), SAVE      :: nscm=nscm_fao            !! Default value for nscm
78!$OMP THREADPRIVATE(nscm)
79
80
81  !! Soil types for stomate_windfall
82
83  INTEGER(i_std), PARAMETER :: n_soil_types = 4         !! Total number of soil types used in
84                                                        !! windfall according to XXX
85  INTEGER(i_std), PARAMETER :: ifree_draining = 1       !! Free-draining mineral soil
86  INTEGER(i_std), PARAMETER :: igleyed = 2              !! Gleyed mineral soil
87  INTEGER(i_std), PARAMETER :: ipeaty = 3               !! Peaty mineral soil
88  INTEGER(i_std), PARAMETER :: ipeat = 4                !! Deep peat
89
90  INTEGER(i_std), PARAMETER :: n_soil_depths = 2        !! Total number of soil depths used in
91                                                        !! windfall according to XXX
92  INTEGER(i_std), PARAMETER :: ideep = 1                !! Deep-rooted
93  INTEGER(i_std), PARAMETER :: ishallow = 2             !! Shallow-rooted
94
95
96  !! Parameters for soil thermodynamics
97
98  REAL(r_std), SAVE :: so_capa_dry = 1.80e+6            !! Dry soil Heat capacity of soils
99                                                        !! @tex $(J.m^{-3}.K^{-1})$ @endtex
100!$OMP THREADPRIVATE(so_capa_dry)
101  REAL(r_std), SAVE :: so_cond_dry = 0.40               !! Dry soil Thermal Conductivity of soils
102                                                        !! @tex $(W.m^{-2}.K^{-1})$ @endtex
103!$OMP THREADPRIVATE(so_cond_dry)
104  REAL(r_std), SAVE :: so_capa_wet = 3.03e+6            !! Wet soil Heat capacity of soils
105                                                        !! @tex $(J.m^{-3}.K^{-1})$ @endtex
106!$OMP THREADPRIVATE(so_capa_wet)
107  REAL(r_std), SAVE :: so_cond_wet = 1.89               !! Wet soil Thermal Conductivity of soils
108                                                        !! @tex $(W.m^{-2}.K^{-1})$ @endtex
109!$OMP THREADPRIVATE(so_cond_wet)
110  REAL(r_std), SAVE :: sn_cond = 0.3                    !! Thermal Conductivity of snow
111                                                        !! @tex $(W.m^{-2}.K^{-1})$ @endtex 
112!$OMP THREADPRIVATE(sn_cond)
113  REAL(r_std), SAVE :: sn_dens = 330.0                  !! Snow density for the soil thermodynamics
114                                                        !! @tex $(kg.m^{-3})$ @endtex
115!$OMP THREADPRIVATE(sn_dens)
116  REAL(r_std), SAVE :: sn_capa                          !! Heat capacity for snow
117                                                        !! @tex $(J.m^{-3}.K^{-1})$ @endtex
118!$OMP THREADPRIVATE(sn_capa)
119
120
121  !! Specific parameters for the Choisnel hydrology
122
123  REAL(r_std), SAVE :: min_drain = 0.001                !! Diffusion constant for the slow regime
124                                                        !! (This is for the diffusion between reservoirs)
125                                                        !! @tex $(kg.m^{-2}.dt^{-1})$ @endtex
126!$OMP THREADPRIVATE(min_drain)
127  REAL(r_std), SAVE :: max_drain = 0.1                  !! Diffusion constant for the fast regime
128                                                        !! @tex $(kg.m^{-2}.dt^{-1})$ @endtex
129!$OMP THREADPRIVATE(max_drain)
130  REAL(r_std), SAVE :: exp_drain = 1.5                  !! The exponential in the diffusion law (unitless)
131!$OMP THREADPRIVATE(exp_drain)
132  REAL(r_std), SAVE :: qsintcst = 0.1                   !! Transforms leaf area index into size of interception reservoir
133                                                        !! (unitless)
134!$OMP THREADPRIVATE(qsintcst)
135  REAL(r_std), SAVE :: mx_eau_nobio = 150.              !! Volumetric available soil water capacity in nobio fractions
136                                                        !! @tex $(kg.m^{-3} of soil)$ @endtex
137!$OMP THREADPRIVATE(mx_eau_nobio)
138  REAL(r_std), SAVE :: rsol_cste = 33.E3                !! Constant in the computation of resistance for bare soil evaporation
139                                                        !! @tex $(s.m^{-2})$ @endtex
140!$OMP THREADPRIVATE(rsol_cste)
141  REAL(r_std), SAVE :: hcrit_litter=0.08_r_std          !! Scaling depth for litter humidity (m)
142!$OMP THREADPRIVATE(hcrit_litter)
143
144
145  !! Parameters specific for the CWRR hydrology.
146
147  !!  1. Parameters for FAO Classification
148
149  !! Parameters for soil type distribution
150
151  REAL(r_std),DIMENSION(nscm_fao),SAVE :: soilclass_default_fao = &   !! Default soil texture distribution for fao :
152 & (/ 0.28, 0.52, 0.20 /)                                             !! in the following order : COARSE, MEDIUM, FINE (unitless)
153!$OMP THREADPRIVATE(soilclass_default_fao)
154
155  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: nvan_fao = &            !! Van genuchten coefficient n
156 & (/ 1.89_r_std, 1.56_r_std, 1.31_r_std /)
157
158  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: avan_fao = &            !! Van genuchten coefficient a (mm^{-1})
159  & (/ 0.0075_r_std, 0.0036_r_std, 0.0019_r_std /) 
160
161  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mcr_fao = &             !! Residual soil water content
162 & (/ 0.065_r_std, 0.078_r_std, 0.095_r_std /)
163
164  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mcs_fao = &             !! Saturated soil water content
165 & (/ 0.41_r_std, 0.43_r_std, 0.41_r_std /)
166
167  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: ks_fao = &              !! Hydraulic conductivity Saturation (mm/d)
168 & (/ 1060.8_r_std, 249.6_r_std, 62.4_r_std /)
169
170  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: pcent_fao = &           !! Fraction of saturated volumetric soil moisture
171 & (/ 0.5_r_std, 0.5_r_std, 0.5_r_std /)                               !! above which transpir is max (0-1, unitless)
172
173  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: free_drain_max_fao = &  !! Max value of the permeability coeff at
174 & (/ 1.0_r_std, 1.0_r_std, 1.0_r_std /)                               !! the bottom of the soil
175
176  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mcf_fao = &             !! Volumetric water content field capacity
177 & (/ 0.32_r_std, 0.32_r_std, 0.32_r_std /)
178
179  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mcw_fao = &             !! Volumetric water content Wilting pt
180 & (/ 0.10_r_std, 0.10_r_std, 0.10_r_std /)
181
182  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mc_awet_fao = &         !! Vol. wat. cont. above which albedo is cst
183 & (/ 0.25_r_std, 0.25_r_std, 0.25_r_std /)
184
185  REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mc_adry_fao = &         !! Vol. wat. cont. below which albedo is cst
186 & (/ 0.1_r_std, 0.1_r_std, 0.1_r_std /)
187
188
189  !!  2. Parameters for USDA Classification
190
191  !! Parameters for soil type distribution :
192  !! Sand, Loamy Sand, Sandy Loam, Silt Loam, Silt, Loam, Sandy Clay Loam, Silty Clay Loam, Clay Loam, Sandy Clay, Silty Clay, Clay
193
194  REAL(r_std),DIMENSION(nscm_usda),SAVE :: soilclass_default_usda = &    !! Default soil texture distribution in the following order :
195 & (/ 0.28, 0.52, 0.20, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0 /)   !!    sand, loam and clay ??? OR COARSE, MEDIUM, FINE???
196!$OMP THREADPRIVATE(soilclass_default_usda)
197
198  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: nvan_usda = &            !! Van genuchten coefficient n
199 & (/ 2.68_r_std, 2.28_r_std, 1.89_r_std, 1.41_r_std, &
200 &    1.37_r_std, 1.56_r_std, 1.48_r_std, 1.23_r_std, &
201 &    1.31_r_std, 1.23_r_std, 1.09_r_std, 1.09_r_std /)
202
203  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: avan_usda = &            !! Van genuchten coefficient a (mm^{-1})
204 & (/ 0.0145_r_std, 0.0124_r_std, 0.0075_r_std, 0.0020_r_std, &
205 &    0.0016_r_std, 0.0036_r_std, 0.0059_r_std, 0.0010_r_std, &
206 &    0.0019_r_std, 0.0027_r_std, 0.0005_r_std, 0.0008_r_std /)
207
208  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mcr_usda = &             !! Residual soil water content
209 & (/ 0.045_r_std, 0.057_r_std, 0.065_r_std, 0.067_r_std, &
210 &    0.034_r_std, 0.078_r_std, 0.100_r_std, 0.089_r_std, &
211 &    0.095_r_std, 0.100_r_std, 0.070_r_std, 0.068_r_std /)
212
213  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mcs_usda = &             !! Saturated soil water content
214 & (/ 0.43_r_std, 0.41_r_std, 0.41_r_std, 0.45_r_std, &
215 &    0.46_r_std, 0.43_r_std, 0.39_r_std, 0.43_r_std, &
216 &    0.41_r_std, 0.38_r_std, 0.36_r_std, 0.38_r_std /)
217
218  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: ks_usda = &              !! Hydraulic conductivity Saturation (mm/d)
219 & (/ 7128.0_r_std, 3501.6_r_std, 1060.8_r_std, 108.0_r_std, &
220 &    60.0_r_std, 249.6_r_std, 314.4_r_std, 16.8_r_std, &
221 &    62.4_r_std, 28.8_r_std, 4.8_r_std, 48.0_r_std /)
222
223  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: pcent_usda = &           !! Soil moisture above which transpir is max
224 & (/ 0.5_r_std, 0.5_r_std, 0.5_r_std, 0.5_r_std, &
225 &    0.5_r_std, 0.5_r_std, 0.5_r_std, 0.5_r_std, &
226 &    0.5_r_std, 0.5_r_std, 0.5_r_std, 0.5_r_std /)
227
228  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: free_drain_max_usda = &  !! Max value of the permeability coeff at
229 & (/ 1.0_r_std, 1.0_r_std, 1.0_r_std, 1.0_r_std, &                      !! the bottom of the soil
230 &    1.0_r_std, 1.0_r_std, 1.0_r_std, 1.0_r_std, &
231 &    1.0_r_std, 1.0_r_std, 1.0_r_std, 1.0_r_std /)
232
233  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mcf_usda = &             !! Volumetric water content field capacity
234 & (/ 0.32_r_std, 0.32_r_std, 0.32_r_std, 0.32_r_std, &
235 &    0.32_r_std, 0.32_r_std, 0.32_r_std, 0.32_r_std, &
236 &    0.32_r_std, 0.32_r_std, 0.32_r_std, 0.32_r_std /)
237
238  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mcw_usda = &             !! Volumetric water content Wilting pt
239 & (/ 0.10_r_std, 0.10_r_std, 0.10_r_std, 0.10_r_std, &
240 &    0.10_r_std, 0.10_r_std, 0.10_r_std, 0.10_r_std, &
241 &    0.10_r_std, 0.10_r_std, 0.10_r_std, 0.10_r_std /)
242
243  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mc_awet_usda = &         !! Vol. wat. cont. above which albedo is cst
244 & (/ 0.25_r_std, 0.25_r_std, 0.25_r_std, 0.25_r_std, &
245 &    0.25_r_std, 0.25_r_std, 0.25_r_std, 0.25_r_std, &
246 &    0.25_r_std, 0.25_r_std, 0.25_r_std, 0.25_r_std /)
247
248  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mc_adry_usda = &         !! Vol. wat. cont. below which albedo is cst
249 & (/ 0.1_r_std, 0.1_r_std, 0.1_r_std, 0.1_r_std, &
250 &    0.1_r_std, 0.1_r_std, 0.1_r_std, 0.1_r_std, &
251 &    0.1_r_std, 0.1_r_std, 0.1_r_std, 0.1_r_std /)
252
253
254  !! Parameters for the numerical scheme used by CWRR
255
256  INTEGER(i_std), PARAMETER :: imin = 1                                 !! CWRR linearisation (unitless)
257  INTEGER(i_std), PARAMETER :: nbint = 50                               !! Number of interval for CWRR (unitless)
258  INTEGER(i_std), PARAMETER :: imax = nbint+1                           !! Number of points for CWRR (unitless)
259  REAL(r_std), PARAMETER    :: w_time = 1.0_r_std                       !! Time weighting for discretisation (unitless)
260
261
262  !! Diagnostic variables
263
264  REAL(r_std),DIMENSION(nbdl),SAVE :: diaglev                           !! The lower limit of the layer on which soil moisture
265                                                                        !! (relative) and temperature are going to be diagnosed.
266                                                                        !! These variables are made for transfering the information
267                                                                        !! to the biogeophyical processes modelled in STOMATE.
268                                                                        !! (unitless)
269!$OMP THREADPRIVATE(diaglev)
270
271
272  !! Variables related to soil freezing, in thermosoil :
273 
274  LOGICAL, SAVE        :: ok_Ecorr                                      !! Flag for energy conservation correction
275  LOGICAL, SAVE        :: ok_freeze_thermix                             !! Flag to activate thermal part of the soil freezing scheme
276  LOGICAL, SAVE        :: read_reftemp                                  !! Flag to initialize soil temperature using climatological
277                                                                        !! emperature
278  LOGICAL, SAVE        :: read_permafrost_map                           !! Read information about ice content, overburden and permafrost
279                                                                        !! type from IPA map
280  REAL(r_std), SAVE    :: poros                                         !! Soil porosity (from USDA classification, mean value)(-)
281  REAL(r_std), SAVE    :: fr_dT                                         !! Freezing window (K)
282
283         
284  !! Variables related to soil freezing, in diffuco : 
285  LOGICAL, SAVE        ::  ok_snowfact                                  !! Activate snow smoothering
286
287
288  !! Variables related to soil freezing, in hydrol : 
289  LOGICAL, SAVE        :: ok_freeze_cwrr                                !! CWRR freezing scheme by I. Gouttevin
290  LOGICAL, SAVE        :: ok_thermodynamical_freezing                   !! Calculate frozen fraction thermodynamically
291
292END MODULE Constantes_soil_var
Note: See TracBrowser for help on using the repository browser.