source: tags/ORCHIDEE_1_9_5/ORCHIDEE/src_parameters/constantes_soil.f90 @ 8

Last change on this file since 8 was 8, checked in by orchidee, 14 years ago

import first tag equivalent to CVS orchidee_1_9_5 + OOL_1_9_5

File size: 5.8 KB
Line 
1!$Header: /home/ssipsl/CVSREP/ORCHIDEE/src_parameters/constantes_soil.f90,v 1.11 2010/04/06 14:38:48 ssipsl Exp $
2!IPSL (2006)
3! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
4!-
5MODULE constantes_soil
6!!--------------------------------------------------------------------
7!! "constantes_soil" module contains public data for the soils
8!!--------------------------------------------------------------------
9  USE constantes
10!-
11  IMPLICIT NONE
12!-
13! Dimensioning parameters
14!-
15! Number of soil level
16  INTEGER(i_std),PARAMETER :: ngrnd=7
17! Number of diagnostic levels in the soil
18  INTEGER(i_std),PARAMETER :: nbdl=11
19!MM : if you want to compare hydrology variables with old TAG 1.6 and lower,
20!     you must set the Number of diagnostic levels in the soil to 6 :
21!  INTEGER(i_std),PARAMETER :: nbdl=6
22! Number of levels in CWRR
23  INTEGER(i_std),PARAMETER :: nslm=11
24! Number of soil types
25  INTEGER(i_std),PARAMETER :: nstm=3
26!-
27!- Parameters for soil thermodynamics
28!-
29! Average Thermal Conductivity of soils
30  REAL(r_std),PARAMETER :: so_cond = 1.5396
31! Average Heat capacity of soils
32  REAL(r_std),PARAMETER :: so_capa = 2.0514e+6
33!-
34! Values taken from : PIELKE,'MESOSCALE METEOROLOGICAL MODELING',P.384
35! Dry soil heat capacity was decreased and conductivity increased.
36!-
37! Dry soil Heat capacity of soils
38!*REAL(r_std),PARAMETER :: so_capa_dry = 1.35e+6
39  REAL(r_std),PARAMETER :: so_capa_dry = 1.80e+6
40! Dry soil Thermal Conductivity of soils
41!*REAL(r_std),PARAMETER :: so_cond_dry = 0.28
42  REAL(r_std),PARAMETER :: so_cond_dry = 0.40
43!-
44! Wet soil Heat capacity of soils
45  REAL(r_std),PARAMETER :: so_capa_wet = 3.03e+6
46! Wet soil Thermal Conductivity of soils
47  REAL(r_std),PARAMETER :: so_cond_wet = 1.89
48!-
49! Thermal Conductivity of snow
50  REAL(r_std),PARAMETER :: sn_cond = 0.3
51! Snow density for the soil thermodynamics
52  REAL(r_std),PARAMETER :: sn_dens = 330.0
53! Heat capacity for snow
54  REAL(r_std),PARAMETER :: sn_capa = 2100.0_r_std*sn_dens
55!-
56! Constantes from the Choisnel hydrology
57!-
58! Wilting point (Has a numerical role for the moment)
59  REAL(r_std),PARAMETER :: qwilt = 5.0
60! Total depth of soil reservoir (for hydrolc)
61  REAL(r_std),SAVE :: dpu_cste=2.0_r_std
62! The minimal size we allow for the upper reservoir (m)
63  REAL(r_std),PARAMETER :: min_resdis = 2.e-5
64! Diffusion constant for the slow regime
65! (This is for the diffusion between reservoirs)
66  REAL(r_std),PARAMETER :: min_drain = 0.001
67! Diffusion constant for the fast regime
68  REAL(r_std),PARAMETER :: max_drain = 0.1
69! The exponential in the diffusion law
70  REAL(r_std),PARAMETER :: exp_drain = 1.5
71! Transforms leaf area index into size of interception reservoir
72  REAL(r_std),SAVE      :: qsintcst = 0.1
73! Maximum quantity of water (Kg/M3)
74  REAL(r_std),PARAMETER :: mx_eau_eau = 150.
75!-
76! Constant in the computation of resistance for bare  soil evaporation
77  REAL(r_std),PARAMETER :: rsol_cste = 33.E3
78! Scaling depth for litter humidity (m)
79!SZ changed this according to SP from 0.03 to 0.08, 080806
80  REAL(r_std),PARAMETER :: hcrit_litter=0.08_r_std
81!-
82! Parameters for soil type distribution
83!-
84! Default soil texture distribution in the following order :
85!    sand, loam and clay
86  REAL(r_std),DIMENSION(nstm),SAVE :: soiltype_default = &
87 & (/ 0.0, 1.0, 0.0 /)
88!-
89! Parameters specific for the CWRR hydrology.
90!-
91! Van genuchten coefficient n
92  REAL(r_std),PARAMETER,DIMENSION(nstm) :: nvan = &
93 & (/ 1.89_r_std, 1.56_r_std, 1.31_r_std /)
94!!$! Van genuchten coefficient a (cm^{-1})
95!!$  REAL(r_std),PARAMETER,DIMENSION(nstm) :: avan = &
96!!$ & (/ 0.036_r_std, 0.036_r_std, 0.036_r_std /)
97!TdO
98! Van genuchten coefficient a (mm^{-1})
99  REAL(r_std),PARAMETER,DIMENSION(nstm) :: avan = &
100  & (/ 0.0075_r_std, 0.0036_r_std, 0.0019_r_std /) 
101! CWRR linearisation
102  INTEGER(i_std),PARAMETER :: imin = 1
103! number of interval for CWRR
104  INTEGER(i_std),PARAMETER :: nbint = 100
105! number of points for CWRR
106  INTEGER(i_std),PARAMETER :: imax = nbint+1
107! Residual soil water content
108  REAL(r_std),PARAMETER,DIMENSION(nstm) :: mcr = &
109 & (/ 0.065_r_std, 0.078_r_std, 0.095_r_std /)
110! Saturated soil water content
111  REAL(r_std),PARAMETER,DIMENSION(nstm) :: mcs = &
112 & (/ 0.41_r_std, 0.43_r_std, 0.41_r_std /)
113! Total depth of soil reservoir (m)
114  REAL(r_std),SAVE,DIMENSION(nstm) :: dpu = &
115 & (/ 2.0_r_std, 2.0_r_std, 2.0_r_std /)
116  ! dpu must be constant over the different soil types
117! Hydraulic conductivity Saturation (mm/d)
118  REAL(r_std),PARAMETER,DIMENSION(nstm) :: ks = &
119 & (/ 1060.8_r_std, 249.6_r_std, 62.4_r_std /)
120! Soil moisture above which transpir is max
121  REAL(r_std),PARAMETER,DIMENSION(nstm) :: pcent = &
122 & (/ 0.5_r_std, 0.5_r_std, 0.5_r_std /)
123! Max value of the permeability coeff at the bottom of the soil
124  REAL(r_std),PARAMETER,DIMENSION(nstm) :: free_drain_max = &
125 & (/ 1.0_r_std, 1.0_r_std, 1.0_r_std /)
126! Volumetric water content field capacity
127  REAL(r_std),PARAMETER,DIMENSION(nstm) :: mcf = &
128 & (/ 0.32_r_std, 0.32_r_std, 0.32_r_std /)
129! Volumetric water content Wilting pt
130  REAL(r_std),PARAMETER,DIMENSION(nstm) :: mcw = &
131 & (/ 0.10_r_std, 0.10_r_std, 0.10_r_std /)
132! Vol. wat. cont. above which albedo is cst
133  REAL(r_std),PARAMETER,DIMENSION(nstm) :: mc_awet = &
134 & (/ 0.25_r_std, 0.25_r_std, 0.25_r_std /)
135! Vol. wat. cont. below which albedo is cst
136  REAL(r_std),PARAMETER,DIMENSION(nstm) :: mc_adry = &
137 & (/ 0.1_r_std, 0.1_r_std, 0.1_r_std /)
138! Matrix potential at saturation (mm)
139  REAL(r_std),PARAMETER,DIMENSION(nstm) :: psis = &
140 & (/ -300.0_r_std, -300.0_r_std, -300.0_r_std /)
141! Time weighting for discretisation
142  REAL(r_std),PARAMETER :: w_time = 1.0_r_std
143!-
144! Diagnostic variables
145!-
146! The lower limit of the layer on which soil moisture (relative)
147! and temperature are going to be diagnosed.
148! These variables are made for transfering the information
149! to the biogeophyical processes modelled in STOMATE.
150!-
151  REAL(r_std),DIMENSION(nbdl),SAVE :: diaglev 
152!-------------------------
153END MODULE constantes_soil
Note: See TracBrowser for help on using the repository browser.