source: tags/ORCHIDEE_1_9_6/ORCHIDEE/src_parameters/constantes.f90 @ 3663

Last change on this file since 3663 was 846, checked in by didier.solyga, 12 years ago

Formatted labels so a script can automatically generate the orchidee.default file.

  • Property svn:keywords set to Date Revision
File size: 125.4 KB
Line 
1! =================================================================================================================================
2! MODULE       : constantes
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" module contains some public technical constants like
10!! pi, Earth radius, etc...and non-PFTs externalized parameters.
11!!
12!!\n DESCRIPTION: In this module, you can set the flag diag_qsat in order to detect the pixel where the
13!!                temperature is out of range (look qsatcalc and dev_qsatcalc in qsat_moisture.f90).\n
14!!                The Earth radius is approximated by the Equatorial radius.The Earth's equatorial radius a,
15!!                or semi-major axis, is the distance from its center to the equator and equals 6,378.1370 km.
16!!                The equatorial radius is often used to compare Earth with other planets.\n
17!!                The meridional mean is well approximated by the semicubic mean of the two axe yielding
18!!                6367.4491 km or less accurately by the quadratic mean of the two axes about 6,367.454 km
19!!                or even just the mean of the two axes about 6,367.445 km.\n
20!!
21!! RECENT CHANGE(S): Didier Solyga : This module contains now all the externalized parameters of ORCHIDEE
22!!                   listed by modules which are not pft-dependent 
23!!
24!! REFERENCE(S) :
25!! - Louis, Jean-Francois (1979), A parametric model of vertical eddy fluxes in the atmosphere.
26!! Boundary Layer Meteorology, 187-202.
27!!
28!! SVN          :
29!! $HeadURL: $
30!! $Date$
31!! $Revision$
32!! \n
33!_ ================================================================================================================================
34
35MODULE constantes
36
37  USE defprec
38  USE parallel
39!-
40  IMPLICIT NONE
41!-
42
43                         !-----------------------!
44                         !  ORCHIDEE CONSTANTS   !
45                         !-----------------------!
46
47
48  !
49  ! FLAGS
50  !
51  TYPE control_type
52    LOGICAL :: river_routing    !! activate river routing (true/false)
53    LOGICAL :: hydrol_cwrr      !! activate 11 layers hydrolgy model (true/false)
54    LOGICAL :: ok_sechiba       !! activate physic of the model (true/false)
55    LOGICAL :: ok_co2           !! activate photosynthesis (true/false)
56    LOGICAL :: ok_stomate       !! activate carbon cycle (true/false)
57    LOGICAL :: ok_dgvm          !! activate dynamic vegetation (true/false)
58    LOGICAL :: stomate_watchout !! activate the creation of restart files for STOMATE even if STOMATE is not activated (true/false)
59    LOGICAL :: ok_pheno         !! activate the calculation of lai using stomate rather than a prescription (true/false)
60  END TYPE control_type
61  !-
62  TYPE(control_type), SAVE :: control  !! Flags that (de)activate parts of the model
63
64
65  !
66  ! TIME
67  !
68  REAL(r_std), SAVE :: one_day  !! One day in seconds (s)
69  REAL(r_std), SAVE :: one_year !! One year in seconds (s)
70
71
72  !
73  ! SPECIAL VALUES
74  !
75  INTEGER(i_std), PARAMETER :: undef_int = 999999999     !! undef integer for integer arrays (unitless)
76  !-
77  REAL(r_std), SAVE :: val_exp = 999999.                 !! Specific value if no restart value  (unitless)
78  REAL(r_std), PARAMETER :: undef = -9999.               !! Special value for stomate (unitless)
79  !-
80  REAL(r_std), PARAMETER :: min_sechiba = 1.E-8_r_std    !! Epsilon to detect a near zero floating point (unitless)
81  REAL(r_std), PARAMETER :: undef_sechiba = 1.E+20_r_std !! The undef value used in SECHIBA (unitless)
82  !-
83  REAL(r_std), PARAMETER :: min_stomate = 1.E-8_r_std    !! Epsilon to detect a near zero floating point (unitless)
84  REAL(r_std), PARAMETER :: large_value = 1.E33_r_std    !! some large value (for stomate) (unitless)
85
86
87  !
88  !  DIMENSIONING AND INDICES PARAMETERS 
89  !
90  INTEGER(i_std), PARAMETER :: ivis = 1          !! index for visible albedo (unitless)
91  INTEGER(i_std), PARAMETER :: inir = 2          !! index for near infrared albedo (unitless)
92  INTEGER(i_std), PARAMETER :: nnobio = 1        !! Number of other surface types: land ice (lakes,cities, ...) (unitless)
93  INTEGER(i_std), PARAMETER :: iice = 1          !! Index for land ice (see nnobio) (unitless)
94  !-
95  !! Soil
96  INTEGER(i_std), PARAMETER :: ngrnd = 7         !! Number of soil level (unitless)
97  INTEGER(i_std), PARAMETER :: nbdl = 11         !! Number of diagnostic levels in the soil (unitless)
98!MM : if you want to compare hydrology variables with old TAG 1.6 and lower,
99!     you must set the Number of diagnostic levels in the soil to 6 :
100!    INTEGER(i_std),PARAMETER :: nbdl=6
101  INTEGER(i_std), PARAMETER :: nslm = 11         !! Number of levels in CWRR (unitless)
102  INTEGER(i_std), PARAMETER :: nstm = 3          !! Number of soil types (unitless)
103  INTEGER(i_std), PARAMETER :: classnb = 9       !! Dimensioning parameter for the soil color numbers and their albedo (unitless)
104  !-
105  INTEGER(i_std), PARAMETER :: nleafages = 4     !! leaf age discretisation ( 1 = no discretisation )(unitless)
106  !-
107  !! litter fractions: indices (unitless)
108  INTEGER(i_std), PARAMETER :: ileaf = 1         !! Index for leaf compartment (unitless)
109  INTEGER(i_std), PARAMETER :: isapabove = 2     !! Index for sapwood above compartment (unitless)
110  INTEGER(i_std), PARAMETER :: isapbelow = 3     !! Index for sapwood below compartment (unitless)
111  INTEGER(i_std), PARAMETER :: iheartabove = 4   !! Index for heartwood above compartment (unitless)
112  INTEGER(i_std), PARAMETER :: iheartbelow = 5   !! Index for heartwood below compartment (unitless)
113  INTEGER(i_std), PARAMETER :: iroot = 6         !! Index for roots compartment (unitless)
114  INTEGER(i_std), PARAMETER :: ifruit = 7        !! Index for fruits compartment (unitless)
115  INTEGER(i_std), PARAMETER :: icarbres = 8      !! Index for reserve compartment (unitless)
116  INTEGER(i_std), PARAMETER :: nparts = 8        !! Number of biomass compartments (unitless)
117  !-
118  !! indices for assimilation parameters
119  INTEGER(i_std), PARAMETER :: itmin = 1         !! Index for minimum photosynthesis temperature (assimilation parameters) (unitless)
120  INTEGER(i_std), PARAMETER :: itopt = 2         !! Index for optimal photosynthesis temperature (assimilation parameters) (unitless)
121  INTEGER(i_std), PARAMETER :: itmax = 3         !! Index for maxmimum photosynthesis temperature (assimilation parameters) (unitless)
122  INTEGER(i_std), PARAMETER :: ivcmax = 4        !! Index for vcmax (assimilation parameters) (unitless)
123  INTEGER(i_std), PARAMETER :: ivjmax = 5        !! Index for vjmax (assimilation parameters) (unitless)
124  INTEGER(i_std), PARAMETER :: npco2 = 5         !! Number of assimilation parameters (unitless)
125  !-
126  !! trees and litter: indices for the parts of heart-
127  !! and sapwood above and below the ground
128  INTEGER(i_std), PARAMETER :: iabove = 1       !! Index for above part (unitless)
129  INTEGER(i_std), PARAMETER :: ibelow = 2       !! Index for below part (unitless)
130  INTEGER(i_std), PARAMETER :: nlevs = 2        !! Number of levels for trees and litter (unitless)
131  !-
132  !! litter: indices for metabolic and structural part
133  INTEGER(i_std), PARAMETER :: imetabolic = 1   !! Index for metabolic litter (unitless)
134  INTEGER(i_std), PARAMETER :: istructural = 2  !! Index for structural litter (unitless)
135  INTEGER(i_std), PARAMETER :: nlitt = 2        !! Number of levels for litter compartments (unitless)
136  !-
137  !! carbon pools: indices
138  INTEGER(i_std), PARAMETER :: iactive = 1      !! Index for active carbon pool (unitless)
139  INTEGER(i_std), PARAMETER :: islow = 2        !! Index for slow carbon pool (unitless)
140  INTEGER(i_std), PARAMETER :: ipassive = 3     !! Index for passive carbon pool (unitless)
141  INTEGER(i_std), PARAMETER :: ncarb = 3        !! Number of soil carbon pools (unitless)
142
143
144  !
145  ! NUMERICAL AND PHYSICS CONSTANTS
146  !
147  !
148
149  !-
150  ! 1. Mathematical and numerical constants
151  !-
152  REAL(r_std), PARAMETER :: pi = 3.141592653589793238   !! pi souce : http://mathworld.wolfram.com/Pi.html (unitless)
153  REAL(r_std), PARAMETER :: euler = 2.71828182845904523 !! e source : http://mathworld.wolfram.com/e.html (unitless)
154  REAL(r_std), PARAMETER :: zero = 0._r_std             !! Numerical constant set to 0 (unitless)
155  REAL(r_std), PARAMETER :: undemi = 0.5_r_std          !! Numerical constant set to 1/2 (unitless)
156  REAL(r_std), PARAMETER :: un = 1._r_std               !! Numerical constant set to 1 (unitless)
157  REAL(r_std), PARAMETER :: moins_un = -1._r_std        !! Numerical constant set to -1 (unitless)
158  REAL(r_std), PARAMETER :: deux = 2._r_std             !! Numerical constant set to 2 (unitless)
159  REAL(r_std), PARAMETER :: trois = 3._r_std            !! Numerical constant set to 3 (unitless)
160  REAL(r_std), PARAMETER :: quatre = 4._r_std           !! Numerical constant set to 4 (unitless)
161  REAL(r_std), PARAMETER :: cinq = 5._r_std             !![DISPENSABLE] Numerical constant set to 5 (unitless)
162  REAL(r_std), PARAMETER :: six = 6._r_std              !![DISPENSABLE] Numerical constant set to 6 (unitless)
163  REAL(r_std), PARAMETER :: huit = 8._r_std             !! Numerical constant set to 8 (unitless)
164  REAL(r_std), PARAMETER :: mille = 1000._r_std         !! Numerical constant set to 1000 (unitless)
165
166  !-
167  ! 2 . Physics
168  !-
169  REAL(r_std), PARAMETER :: R_Earth = 6378000.              !! radius of the Earth : Earth radius ~= Equatorial radius (m)
170  REAL(r_std), PARAMETER :: mincos  = 0.0001                !! Minimum cosine value used for interpolation (unitless)
171  REAL(r_std), PARAMETER :: pb_std = 1013.                  !! standard pressure (hPa)
172  REAL(r_std), PARAMETER :: ZeroCelsius = 273.15            !! Freezing point (K)
173  REAL(r_std), PARAMETER :: tp_00 = 273.15                  !! 0 degre Celsius in degre Kelvin (K)
174  REAL(r_std), PARAMETER :: chalsu0 = 2.8345E06             !! Latent heat of sublimation (J.kg^{-1})
175  REAL(r_std), PARAMETER :: chalev0 = 2.5008E06             !! Latent heat of evaporation (J.kg^{-1})
176  REAL(r_std), PARAMETER :: chalfu0 = chalsu0-chalev0       !! Latent heat of fusion (J.kg^{-1})
177  REAL(r_std), PARAMETER :: c_stefan = 5.6697E-8            !! Stefan-Boltzman constant (W.m^{-2}.K^{-4})
178  REAL(r_std), PARAMETER :: cp_air = 1004.675               !! Specific heat of dry air (J.kg^{-1}.K^{-1})
179  REAL(r_std), PARAMETER :: cte_molr = 287.05               !! Specific constant of dry air (kg.mol^{-1})
180  REAL(r_std), PARAMETER :: kappa = cte_molr/cp_air         !! Kappa : ratio between specific constant and specific heat
181                                                            !! of dry air (unitless)
182  REAL(r_std), PARAMETER :: msmlr_air = 28.964E-03          !! Molecular weight of dry air (kg.mol^{-1})
183  REAL(r_std), PARAMETER :: msmlr_h2o = 18.02E-03           !! Molecular weight of water vapor (kg.mol^{-1})
184  REAL(r_std), PARAMETER :: cp_h2o = &                      !! Specific heat of water vapor (J.kg^{-1}.K^{-1})
185       & cp_air*(quatre*msmlr_air)/( 3.5_r_std*msmlr_h2o) 
186  REAL(r_std), PARAMETER :: cte_molr_h2o = cte_molr/quatre  !! Specific constant of water vapor (J.kg^{-1}.K^{-1})
187  REAL(r_std), PARAMETER :: retv = msmlr_air/msmlr_h2o-un   !! Ratio between molecular weight of dry air and water
188                                                            !! vapor minus 1(unitless) 
189  REAL(r_std), PARAMETER :: rvtmp2 = cp_h2o/cp_air-un       !! Ratio between specific heat of water vapor and dry air
190                                                            !! minus 1 (unitless)
191  REAL(r_std), PARAMETER :: cepdu2 = (0.1_r_std)**2         !! Squared wind shear (m^2.s^{-2})
192  REAL(r_std), PARAMETER :: ct_karman = 0.35_r_std          !! Van Karmann Constant (unitless)
193  REAL(r_std), PARAMETER :: cte_grav = 9.80665_r_std        !! Acceleration of the gravity (m.s^{-2})
194  REAL(r_std), PARAMETER :: pa_par_hpa = 100._r_std         !! Transform pascal into hectopascal (unitless)
195
196  !-
197  ! 3. Climatic constants
198  !-
199  !! Constantes of the Louis scheme
200  REAL(r_std), PARAMETER :: cb = 5._r_std         !! Constant of the Louis scheme (unitless);
201                                                  !! reference to Louis (1979)
202  REAL(r_std), PARAMETER :: cc = 5._r_std         !! Constant of the Louis scheme (unitless);
203                                                  !! reference to Louis (1979)
204  REAL(r_std), PARAMETER :: cd = 5._r_std         !! Constant of the Louis scheme (unitless);
205                                                  !! reference to Louis (1979)
206  !-
207  REAL(r_std), PARAMETER :: rayt_cste = 125.      !! Constant in the computation of surface resistance (W.m^{-2})
208  REAL(r_std), PARAMETER :: defc_plus = 23.E-3    !! Constant in the computation of surface resistance (K.W^{-1})
209  REAL(r_std), PARAMETER :: defc_mult = 1.5       !! Constant in the computation of surface resistance (K.W^{-1})
210
211  !-
212  ! 4. Soil thermodynamics constants
213  !-
214  REAL(r_std), PARAMETER :: so_cond = 1.5396       !! Average Thermal Conductivity of soils (W.m^{-2}.K^{-1})
215  REAL(r_std), PARAMETER :: so_capa = 2.0514e+6    !! Average Heat capacity of soils (J.m^{-3}.K^{-1})
216  !-
217  !! Values taken from : PIELKE,'MESOSCALE METEOROLOGICAL MODELING',P.384
218  !  Dry soil heat capacity was decreased and conductivity increased.
219  REAL(r_std), PARAMETER :: so_capa_dry = 1.80e+6  !! Dry soil Heat capacity of soils (J.m^{-3}.K^{-1})
220  REAL(r_std), PARAMETER :: so_cond_dry = 0.40     !! Dry soil Thermal Conductivity of soils (W.m^{-2}.K^{-1})
221  REAL(r_std), PARAMETER :: so_capa_wet = 3.03e+6  !! Wet soil Heat capacity of soils (J.m^{-3}.K^{-1})
222  REAL(r_std), PARAMETER :: so_cond_wet = 1.89     !! Wet soil Thermal Conductivity of soils (W.m^{-2}.K^{-1})
223  REAL(r_std), PARAMETER :: sn_cond = 0.3          !! Thermal Conductivity of snow (W.m^{-2}.K^{-1})
224  REAL(r_std), PARAMETER :: sn_dens = 330.0        !! Snow density for the soil thermodynamics (unitless)
225  REAL(r_std), PARAMETER :: sn_capa = 2100.0_r_std*sn_dens !! Heat capacity for snow (J.m^{-3}.K^{-1})
226
227  !
228  ! OPTIONAL PARTS OF THE MODEL
229  !
230  LOGICAL, SAVE     :: long_print = .FALSE.       !! To set for more printing
231  LOGICAL,PARAMETER :: diag_qsat = .TRUE.         !! One of the most frequent problems is a temperature out of range
232                                                  !! we provide here a way to catch that in the calling procedure.
233                                                  !! (from Jan Polcher)(true/false)
234  LOGICAL            :: almaoutput                !! Selects the type of output for the model.(true/false)
235                                                  !! Value is read from run.def in intersurf_history
236
237  !
238  ! DIAGNOSTIC VARIABLES
239  !
240  REAL(r_std),DIMENSION(nbdl),SAVE :: diaglev     !! The lower limit of the layer on which soil moisture (relative)
241                                                  !! and temperature are going to be diagnosed.
242                                                  !! These variables are made for transfering the information
243                                                  !! to the biogeophyical processes modelled in STOMATE. (unitless)
244  !
245  ! DIVERSE
246  !
247  CHARACTER(LEN=100) :: stomate_forcing_name='NONE'  !! NV080800 Name of STOMATE forcing file (unitless)
248                                                     ! Compatibility with Nicolas Viovy driver.
249  CHARACTER(LEN=100) :: stomate_Cforcing_name='NONE' !! NV080800 Name of soil forcing file (unitless)
250                                                     ! Compatibility with Nicolas Viovy driver.
251  INTEGER(i_std), SAVE :: forcing_id                 !! Index of the forcing file (unitless)
252
253
254
255
256                         !------------------------!
257                         !  SECHIBA PARAMETERS    !
258                         !------------------------!
259 
260
261  !
262  ! GLOBAL PARAMETERS   
263  !
264  REAL(r_std), SAVE :: min_wind = 0.1      !! The minimum wind (m.s^{-1})
265  REAL(r_std), SAVE :: snowcri = 1.5       !! Sets the amount above which only sublimation occures (kg.m^{-2})
266  REAL(r_std), SAVE :: qsintcst = 0.1      !! Transforms leaf area index into size of interception reservoir (unitless)
267  REAL(r_std), SAVE :: dpu_cste = 4.0      !! Total depth of soil reservoir (for hydrolc) (m)
268  REAL(r_std), SAVE, DIMENSION(nstm) :: dpu = (/ 2.0, 2.0, 2.0 /) !! Total depth of soil reservoir (m)
269
270  !
271  ! FLAGS ACTIVATING SUB-MODELS
272  !
273  LOGICAL, SAVE :: doirrigation = .FALSE.      !! Active irrigation ?  (true/false)
274  LOGICAL, SAVE :: dofloodplains = .FALSE.     !! Active floodplains ? (true/false)
275  LOGICAL, SAVE :: treat_expansion = .FALSE.   !! Do we treat PFT expansion across a grid point after introduction? (true/false)
276  LOGICAL, SAVE :: ok_herbivores = .FALSE.     !! herbivores? (true/false)
277  LOGICAL, SAVE :: harvest_agri = .TRUE.       !! harvesting ? (true/false)
278  LOGICAL, SAVE :: lpj_gap_const_mort = .TRUE. !! constant moratlity (true/false)
279  LOGICAL, SAVE :: disable_fire = .FALSE.      !! flag that disable fire (true/false)
280
281  !
282  ! CONFIGURATION VEGETATION
283  !
284  LOGICAL, SAVE :: agriculture = .TRUE.    !! allow agricultural PFTs (true/false)
285  LOGICAL, SAVE :: impveg = .FALSE.        !! Impose vegetation ? (true/false)
286  LOGICAL, SAVE :: impsoilt = .FALSE.      !! Impose soil ? (true/false)
287  LOGICAL, SAVE :: lcchange = .FALSE.      !! Land cover change flag (true/false)
288  LOGICAL, SAVE :: read_lai = .FALSE.      !! Lai Map (true/false)
289  LOGICAL, SAVE :: old_lai = .FALSE.       !! Old Lai Map interpolation  (true/false)
290  LOGICAL, SAVE :: old_veget = .FALSE.     !! Old veget Map interpolation  (true/false)
291  LOGICAL, SAVE :: land_use = .TRUE.       !! Land Use (true/false)
292  LOGICAL, SAVE :: veget_reinit = .TRUE.   !! To change LAND USE file in a run. (true/false)
293
294  !
295  ! PARAMETERS USED BY BOTH HYDROLOGY MODELS
296  !
297  REAL(r_std), SAVE :: max_snow_age = 50._r_std !! Maximum period of snow aging (days)
298  REAL(r_std), SAVE :: snow_trans = 0.3_r_std   !! Transformation time constant for snow (m)
299  REAL(r_std), SAVE :: sneige                   !! Lower limit of snow amount (kg.m^{-2})
300  REAL(r_std), SAVE :: maxmass_glacier = 3000.  !! The maximum mass of a glacier (kg.m^{-2})
301  REAL(r_std), SAVE :: mx_eau_eau = 150.        !! Maximum quantity of water (kg.m^{-3})
302 
303
304  !
305  ! condveg.f90
306  !
307
308  ! 1. Scalar
309
310  ! 1.1 Flags used inside the module
311
312  LOGICAL, SAVE :: alb_bare_model = .FALSE. !! Switch to old (albedo bare depend on soil wetness)
313                                            !! or new one (mean of soilalb) (true/false)
314  LOGICAL, SAVE :: impaze = .FALSE.         !! Choice on the surface parameters (true/false)
315  LOGICAL, SAVE :: z0cdrag_ave = .TRUE.     !! Chooses the method for the z0 average (true/false)
316
317  ! 1.2 Others
318
319  REAL(r_std), SAVE :: z0_over_height = un/16.           !! to get z0 from height (unitless)
320  REAL(r_std), SAVE :: height_displacement = 0.75        !! Magic number which relates the height to
321                                                         !! the displacement height. (m)
322  REAL(r_std), SAVE :: z0_bare = 0.01                    !! bare soil roughness length (m)
323  REAL(r_std), SAVE :: z0_ice = 0.001                    !! ice roughness length (m)
324  REAL(r_std), SAVE :: tcst_snowa = 5.0                  !! Time constant of the albedo decay of snow (days)
325  REAL(r_std), SAVE :: snowcri_alb = 10.                 !! Critical value for computation of snow albedo (kg.m^{-2})
326  REAL(r_std), SAVE :: fixed_snow_albedo = undef_sechiba !! In case we wish a fxed snow albedo (unitless)
327  REAL(r_std), SAVE :: z0_scal = 0.15                    !! Roughness height used to initialize the scheme (m)
328  REAL(r_std), SAVE :: roughheight_scal = zero           !! Height to displace the surface from the zero wind height (m)
329  REAL(r_std), SAVE :: emis_scal = un                    !! Surface emissivity used to initialize the scheme (unitless)
330
331  ! 2. Arrays
332
333  REAL(r_std), SAVE, DIMENSION(2) :: alb_deadleaf = (/ .12, .35/)    !! albedo of dead leaves, VIS+NIR (unitless)
334  REAL(r_std), SAVE, DIMENSION(2) :: alb_ice = (/ .60, .20/)         !! albedo of ice, VIS+NIR (unitless)
335  REAL(r_std), SAVE, DIMENSION(2) :: albedo_scal = (/ 0.25, 0.25 /)  !! albedo values need for initialisation (unitless)
336  REAL(r_std), DIMENSION(classnb) :: vis_dry = &                     !! The correspondance table for the soil color numbers
337       & (/0.24, 0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.27/)    !! and their albedo (unitless)
338  REAL(r_std), DIMENSION(classnb) :: nir_dry = &                     !! The correspondance table for the soil color numbers
339       & (/0.48, 0.44, 0.40, 0.36, 0.32, 0.28, 0.24, 0.20, 0.55/)    !! and their albedo (unitless)
340  REAL(r_std), DIMENSION(classnb) :: vis_wet =  &                    !! The correspondance table for the soil color numbers
341       & (/0.12, 0.11, 0.10, 0.09, 0.08, 0.07, 0.06, 0.05, 0.15/)    !! and their albedo (unitless)
342  REAL(r_std), DIMENSION(classnb) :: nir_wet = &                     !! The correspondance table for the soil color numbers
343       & (/0.24, 0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.31/)    !! and their albedo (unitless)
344  !   
345  REAL(r_std), DIMENSION(classnb) :: albsoil_vis = (/0.18, 0.16, 0.16, 0.15, 0.12, 0.105, 0.09, 0.075, 0.25/)
346  REAL(r_std), DIMENSION(classnb) :: albsoil_nir = (/0.36, 0.34, 0.34, 0.33, 0.30, 0.25, 0.20, 0.15, 0.45/) 
347
348
349
350  !
351  ! diffuco.f90
352  !
353
354  ! 0. Constants
355
356  REAL(r_std), PARAMETER :: Tetens_1 = 0.622         !! Ratio between molecular weight of water vapor and molecular weight 
357                                                     !! of dry air (unitless)
358  REAL(r_std), PARAMETER :: Tetens_2 = 0.378         !!
359  REAL(r_std), PARAMETER :: std_ci_frac = 0.667      !!
360  REAL(r_std), PARAMETER :: alpha_j = 0.8855         !! Quantum yield of RuBP regeneration
361  REAL(r_std), PARAMETER :: curve_assim = 0.7        !! Curvature of the quantum response (unitless)
362  REAL(r_std), PARAMETER :: WJ_coeff1 = 4.5          !! First coefficient for calculating the generation-limited rate RuBP (unitless)
363  REAL(r_std), PARAMETER :: WJ_coeff2 = 10.5         !! Second coefficient for calculating the generation-limited rate RuBP (unitless)
364  REAL(r_std), PARAMETER :: Vc_to_Rd_ratio = 0.011   !!
365  REAL(r_std), PARAMETER :: O2toCO2_stoechio = 1.6   !! Ratio of water vapor diffusivity to the CO2 diffusivity (unitless)
366  REAL(r_std), PARAMETER :: mmol_to_m_1 = 0.0244     !!
367  REAL(r_std), PARAMETER :: RG_to_PAR = 0.5          !!
368  REAL(r_std), PARAMETER :: W_to_mmol = 4.6          !! W_to_mmol * RG_to_PAR = 2.3
369
370  ! 1. Scalar
371
372  INTEGER(i_std), SAVE :: nlai = 20             !! Number of LAI levels (unitless)
373  LOGICAL, SAVE :: ldq_cdrag_from_gcm = .FALSE. !! Set to .TRUE. if you want q_cdrag coming from GCM
374  REAL(r_std), SAVE :: laimax = 12.             !! maximum LAI (m^2.m^{-2})
375  REAL(r_std), SAVE :: xc4_1 = 0.83             !! Factor in the first Collatz equation for C4 plants (unitless)
376  REAL(r_std), SAVE :: xc4_2 = 0.93             !! Factor in the second Collatz equation for C4 plants (unitless)
377
378  ! 3. Coefficients of equations
379
380  REAL(r_std), SAVE :: lai_level_depth = 0.15  !!
381  REAL(r_std), SAVE :: x1_coef =  0.177        !! Multiplicative factor for calculating the pseudo first order rate constant
382                                               !! of assimilation response to co2 kt (unitless)
383  REAL(r_std), SAVE :: x1_Q10 =  0.069         !! Exponential factor in the equation defining kt (unitless)
384  REAL(r_std), SAVE :: quantum_yield =  0.092  !!
385  REAL(r_std), SAVE :: kt_coef = 0.7           !! Multiplicative factor in the equation defining kt (unitless)
386  REAL(r_std), SAVE :: kc_coef = 39.09         !! Multiplicative factor for calculating the Michaelis-Menten
387                                               !! coefficient Kc (unitless)
388  REAL(r_std), SAVE :: Ko_Q10 = 0.085          !! Exponential factor for calculating the Michaelis-Menten coefficients
389                                               !! Kc and Ko (unitless)
390  REAL(r_std), SAVE :: Oa = 210000.            !! Intercellular concentration of O2 (ppm)
391  REAL(r_std), SAVE :: Ko_coef =  2.412        !! Multiplicative factor for calculating the Michaelis-Menten coefficient Ko (unitless)
392  REAL(r_std), SAVE :: CP_0 = 42.              !! Multiplicative factor for calculating the CO2 compensation point CP (unitless)
393  REAL(r_std), SAVE :: CP_temp_coef = 9.46     !! Exponential factor for calculating the CO2 compensation point CP (unitless)
394  REAL(r_std), SAVE :: CP_temp_ref = 25.       !! Reference temperature for the CO2 compensation point CP (C)
395  !
396  REAL(r_std), SAVE, DIMENSION(2) :: rt_coef = (/ 0.8, 1.3 /)    !!
397  REAL(r_std), SAVE, DIMENSION(2) :: vc_coef = (/ 0.39, 0.3 /)   !!
398  !
399  REAL(r_std), SAVE, DIMENSION(6) :: dew_veg_poly_coeff = &            !! coefficients of the 5 degree polynomomial used
400  & (/ 0.887773, 0.205673, 0.110112, 0.014843,  0.000824,  0.000017 /) !! in the equation of coeff_dew_veg
401
402
403
404  !
405  ! hydrolc.f90
406  !
407
408  ! 1. Scalar
409
410  LOGICAL, SAVE     :: ok_hdiff  = .FALSE.        !! do horizontal diffusion? (true/false)
411  REAL(r_std), SAVE :: qwilt = 5.0                !! Wilting point (Has a numerical role for the moment) (unitless)
412  REAL(r_std), SAVE :: min_resdis = 2.e-5         !! The minimal size we allow for the upper reservoir (m)
413  REAL(r_std), SAVE :: min_drain = 0.001          !! Diffusion constant for the slow regime (kg.m^{-2}.dt^{-1})
414                                                  !! (This is for the diffusion between reservoirs)
415  REAL(r_std), SAVE :: max_drain = 0.1            !! Diffusion constant for the fast regime (kg.m^{-2}.dt^{-1})
416  REAL(r_std), SAVE :: exp_drain = 1.5            !! The exponential in the diffusion law (unitless)
417  REAL(r_std), SAVE :: rsol_cste = 33.E3          !! Constant in the computation of resistance for bare soil evaporation (s.m^{-2})
418  REAL(r_std), SAVE :: hcrit_litter = 0.08_r_std  !! Scaling depth for litter humidity (m)
419
420
421
422  !
423  ! hydrol.f90
424  !
425
426  ! 0. Constants
427
428  INTEGER(i_std),PARAMETER :: imin = 1       !! CWRR linearisation (unitless)
429  INTEGER(i_std),PARAMETER :: nbint = 100    !! number of interval for CWRR (unitless)
430  INTEGER(i_std),PARAMETER :: imax = nbint+1 !! number of points for CWRR (unitless)
431
432  ! 1. Scalar
433
434  REAL(r_std), SAVE :: dmcs = 0.002 !! Allowed moisture above mcs (boundary conditions)
435  REAL(r_std), SAVE :: dmcr = 0.002 !! Allowed moisture below mcr (boundary conditions)
436  REAL(r_std), SAVE :: w_time = un  !! Time weighting for discretisation (unitless)
437
438  ! 2. Arrays
439
440  REAL(r_std), SAVE, DIMENSION(nstm) :: &
441       & nvan = (/ 1.89_r_std, 1.56_r_std, 1.31_r_std /)       !! Van genuchten coefficient n
442  REAL(r_std), SAVE, DIMENSION(nstm) :: &
443       & avan = (/ 0.0075_r_std, 0.0036_r_std, 0.0019_r_std /) !! Van genuchten coefficient a (mm^{-1})
444  REAL(r_std), SAVE, DIMENSION(nstm) :: &
445       & mcr = (/ 0.065_r_std, 0.078_r_std, 0.095_r_std /)     !! Residual soil water content
446  REAL(r_std), SAVE, DIMENSION(nstm) :: &
447       & mcs = (/ 0.41_r_std, 0.43_r_std, 0.41_r_std /)        !! Saturated soil water content
448  REAL(r_std), SAVE, DIMENSION(nstm) :: &                      !! dpu must be constant over the different soil types
449       & ks = (/ 1060.8_r_std, 249.6_r_std, 62.4_r_std /)      !! Hydraulic conductivity Saturation (mm/d)
450  REAL(r_std), SAVE, DIMENSION(nstm) :: &
451       & pcent = (/ 0.5_r_std, 0.5_r_std, 0.5_r_std /)         !! Soil moisture above which transpir is max
452  REAL(r_std), SAVE, DIMENSION(nstm) :: &
453       & free_drain_max = (/ 1._r_std, 1._r_std, 1._r_std /)   !! Max value of the permeability coeff at the bottom of the soil
454  REAL(r_std), SAVE, DIMENSION(nstm) :: & 
455       & mcf = (/ 0.32_r_std, 0.32_r_std, 0.32_r_std /)        !! Volumetric water content field capacity (unitless)
456  REAL(r_std), SAVE, DIMENSION(nstm) :: &
457       & mcw = (/ 0.1_r_std, 0.1_r_std, 0.1_r_std /)           !! Volumetric water content Wilting pt (unitless)
458  REAL(r_std), SAVE, DIMENSION(nstm) :: &
459       & mc_awet = (/ 0.25_r_std, 0.25_r_std, 0.25_r_std /)    !! Volumetric water content above which albedo is cst (unitless)
460  REAL(r_std), SAVE, DIMENSION(nstm) :: & 
461       & mc_adry = (/ 0.1_r_std, 0.1_r_std, 0.1_r_std /)       !! Volumetric water content below which albedo is cst (unitless)
462 
463
464
465  !
466  ! routing.f90
467  !
468
469  ! 1. Scalar
470
471  REAL(r_std), SAVE :: crop_coef = 1.5   !! Empirical crop coefficient dependent on vegetation characteristics
472                                         !! according to Kassel irrigation parametrization.
473                                         !! When potential transpiration is used this coefficient has another interpretation (unitless)
474
475  !
476  ! slowproc.f90
477  !
478
479  ! 1. Scalar
480
481  INTEGER(i_std), SAVE :: veget_year_orig = 1        !! first year for landuse (unitless)
482  REAL(r_std), SAVE :: clayfraction_default = 0.2    !! default value for clay fraction (0-1, unitless)
483  REAL(r_std), SAVE :: min_vegfrac = 0.001           !! Minimal fraction of mesh a vegetation type can occupy (0-1, unitless)
484  REAL(r_std), SAVE :: frac_nobio_fixed_test_1 = 0.0 !! Value for frac_nobio for tests in 0-dim simulations (0-1, unitless)
485                                                     
486  REAL(r_std), SAVE :: stempdiag_bid = 280.          !! only needed for an initial LAI if there is no restart file
487
488  ! 2. Arrays
489
490  REAL(r_std),SAVE, DIMENSION(nstm) :: soiltype_default = (/ 0.0, 1.0, 0.0 /)  !! Default soil texture distribution in the
491                                                                               !! following order : sand, loam and clay
492                                                                               !! (0-1, unitless)
493
494
495
496                           !-----------------------------!
497                           !  STOMATE AND LPJ PARAMETERS !
498                           !-----------------------------!
499
500
501  !
502  ! lpj_constraints.f90
503  !
504 
505  ! 1. Scalar
506
507  REAL(r_std), SAVE  :: too_long = 5.      !! longest sustainable time without regeneration (vernalization) (years)
508
509
510
511  !
512  ! lpj_establish.f90
513  !
514
515  ! 1. Scalar
516
517  REAL(r_std), SAVE :: estab_max_tree = 0.12   !! Maximum tree establishment rate (0-1, unitless)
518  REAL(r_std), SAVE :: estab_max_grass = 0.12  !! Maximum grass establishment rate (0-1, unitless)
519 
520  ! 3. Coefficients of equations
521
522  REAL(r_std), SAVE :: establish_scal_fact = 5.  !!
523  REAL(r_std), SAVE :: max_tree_coverage = 0.98  !! (0-1, unitless)
524  REAL(r_std), SAVE :: ind_0_estab = 0.2         !! = ind_0 * 10.
525
526
527
528  !
529  ! lpj_fire.f90
530  !
531
532  ! 1. Scalar
533
534  REAL(r_std), SAVE :: tau_fire = 30.           !! Time scale for memory of the fire index (days).
535                                                !  Validated for one year in the DGVM.
536  REAL(r_std), SAVE :: litter_crit = 200.       !! Critical litter quantity for fire (gC.m^{-2})
537  !
538  REAL(r_std), SAVE :: fire_resist_struct = 0.5 !!
539
540  ! 2. Arrays
541
542  REAL(r_std), SAVE, DIMENSION(nparts) :: co2frac = &    !! What fraction of a burned plant compartment goes into the atmosphere
543       & (/ .95, .95, 0., 0.3, 0., 0., .95, .95 /)       !! (rest into litter) (0-1, unitless)
544
545  ! 3. Coefficients of equations
546
547  REAL(r_std), SAVE, DIMENSION(3) :: bcfrac_coeff = (/ .3,  1.3,  88.2 /)         !! (unitless)
548  REAL(r_std), SAVE, DIMENSION(4) :: firefrac_coeff = (/ 0.45, 0.8, 0.6, 0.13 /)  !! (unitless)
549
550
551  !
552  ! lpj_gap.f90
553  !
554
555  ! 1. Scalar
556
557  REAL(r_std), SAVE :: ref_greff = 0.035         !! Asymptotic maximum mortality rate (year^{-1})
558
559  ! 3. Coefficients of equations
560
561  REAL(r_std), SAVE :: availability_fact = 0.1   !!
562
563
564  !               
565  ! lpj_light.f90
566  !             
567
568  ! 1. Scalar
569 
570  LOGICAL, SAVE :: annual_increase = .TRUE. !! for diagnosis of fpc increase, compare today's fpc to last year's maximum (T) or
571                                            !! to fpc of last time step (F)? (true/false)
572  REAL(r_std), SAVE :: min_cover = 0.05     !! For trees, minimum fraction of crown area occupied
573                                            !! (due to its branches etc.) (0-1, unitless)
574                                            !! This means that only a small fraction of its crown area
575                                            !! can be invaded by other trees.
576  !
577  ! lpj_pftinout.f90
578  !
579
580  ! 1. Scalar
581
582  REAL(r_std), SAVE :: min_avail = 0.01         !! minimum availability
583  REAL(r_std), SAVE :: ind_0 = 0.02             !! initial density of individuals
584
585  ! 3. Coefficients of equations
586 
587  REAL(r_std), SAVE :: RIP_time_min = 1.25      !! (years)
588  REAL(r_std), SAVE :: npp_longterm_init = 10.  !! Initialisation value for npp_longterm (gC.m^{-2}.year^{-1})
589  REAL(r_std), SAVE :: everywhere_init = 0.05   !!
590
591
592
593  !
594  ! stomate_alloc.f90
595  !
596
597  ! 0. Constants
598
599  REAL(r_std), PARAMETER :: max_possible_lai = 10. !! (m^2.m^{-2})
600  REAL(r_std), PARAMETER :: Nlim_Q10 = 10.         !!
601
602  ! 1. Scalar
603
604  LOGICAL, SAVE :: ok_minres = .TRUE.              !! [DISPENSABLE] Do we try to reach a minimum reservoir even if
605                                                   !! we are severely stressed? (true/false)
606
607  REAL(r_std), SAVE :: tau_leafinit = 10.          !! time to attain the initial foliage using the carbohydrate reserve (days)
608  REAL(r_std), SAVE :: reserve_time_tree = 30.     !! maximum time during which reserve is used (trees) (days)
609  REAL(r_std), SAVE :: reserve_time_grass = 20.    !! maximum time during which reserve is used (grasses) (days)
610  REAL(r_std), SAVE :: R0 = 0.3                    !! Default root allocation (0-1, unitless)
611  REAL(r_std), SAVE :: S0 = 0.3                    !! Default sapwood allocation (0-1, unitless)
612  REAL(r_std), SAVE :: L0                          !! Default leaf allocation (0-1, unitless)
613  REAL(r_std), SAVE :: f_fruit = 0.1               !! Default fruit allocation (0-1, unitless)
614  REAL(r_std), SAVE :: alloc_sap_above_grass = 1.0 !! fraction of sapwood allocation above ground (0-1, unitless)
615  REAL(r_std), SAVE :: min_LtoLSR = 0.2            !! extrema of leaf allocation fraction (0-1, unitless)
616  REAL(r_std), SAVE :: max_LtoLSR = 0.5            !! extrema of leaf allocation fraction (0-1, unitless)
617  REAL(r_std), SAVE :: z_nitrogen = 0.2            !! scaling depth for nitrogen limitation (m)
618
619  ! 3. Coefficients of equations
620
621  REAL(r_std), SAVE :: lai_max_to_happy = 0.5      !!
622  REAL(r_std), SAVE :: Nlim_tref = 25.             !! (C)
623
624
625
626  !
627  ! stomate_data.f90
628  !
629
630  ! 1. Scalar
631
632  ! 1.1 Parameters for the pipe model
633
634  REAL(r_std), SAVE :: pipe_tune1 = 100.0        !! crown area = pipe_tune1. stem diameter**(1.6) (Reinicke's theory) (unitless)
635  REAL(r_std), SAVE :: pipe_tune2 = 40.0         !! height=pipe_tune2 * diameter**pipe_tune3 (unitless)
636  REAL(r_std), SAVE :: pipe_tune3 = 0.5          !! height=pipe_tune2 * diameter**pipe_tune3 (unitless)
637  REAL(r_std), SAVE :: pipe_tune4 = 0.3          !! needed for stem diameter (unitless)
638  REAL(r_std), SAVE :: pipe_density = 2.e5       !! Density
639  REAL(r_std), SAVE :: pipe_k1 = 8.e3            !! one more SAVE
640  REAL(r_std), SAVE :: pipe_tune_exp_coeff = 1.6 !! pipe tune exponential coeff (unitless)
641
642  ! 1.2 climatic parameters
643
644  REAL(r_std), SAVE :: precip_crit = 100.        !! minimum precip, in (mm/year)
645  REAL(r_std), SAVE :: gdd_crit_estab = 150.     !! minimum gdd for establishment of saplings
646  REAL(r_std), SAVE :: fpc_crit = 0.95           !! critical fpc, needed for light competition and establishment (0-1, unitless)
647
648  ! 1.3 sapling characteristics
649
650  REAL(r_std), SAVE :: alpha_grass = 0.5         !! alpha coefficient for grasses (unitless)
651  REAL(r_std), SAVE :: alpha_tree = 1.           !! alpha coefficient for trees (unitless)
652  REAL(r_std), SAVE :: mass_ratio_heart_sap = 3. !! mass ratio (heartwood+sapwood)/sapwood (unitless)
653  REAL(r_std), SAVE :: frac_growthresp = 0.28    !! fraction of GPP which is lost as growth respiration (0-1, unitless)
654
655  ! 1.4  time scales for phenology and other processes (in days)
656
657  REAL(r_std), SAVE :: tau_hum_month = 20.        !! (days)       
658  REAL(r_std), SAVE :: tau_hum_week = 7.          !! (days) 
659  REAL(r_std), SAVE :: tau_t2m_month = 20.        !! (days)     
660  REAL(r_std), SAVE :: tau_t2m_week = 7.          !! (days) 
661  REAL(r_std), SAVE :: tau_tsoil_month = 20.      !! (days)     
662  REAL(r_std), SAVE :: tau_soilhum_month = 20.    !! (days)     
663  REAL(r_std), SAVE :: tau_gpp_week = 7.          !! (days) 
664  REAL(r_std), SAVE :: tau_gdd = 40.              !! (days) 
665  REAL(r_std), SAVE :: tau_ngd = 50.              !! (days) 
666  REAL(r_std), SAVE :: coeff_tau_longterm = 3.    !! (unitless)
667  REAL(r_std), SAVE :: tau_longterm               !! (days) 
668
669  ! 3. Coefficients of equations
670
671  REAL(r_std), SAVE :: bm_sapl_carbres = 5.             !!
672  REAL(r_std), SAVE :: bm_sapl_sapabove = 0.5           !!
673  REAL(r_std), SAVE :: bm_sapl_heartabove = 2.          !!
674  REAL(r_std), SAVE :: bm_sapl_heartbelow = 2.          !!
675  REAL(r_std), SAVE :: init_sapl_mass_leaf_nat = 0.1    !!
676  REAL(r_std), SAVE :: init_sapl_mass_leaf_agri = 1.    !!
677  REAL(r_std), SAVE :: init_sapl_mass_carbres = 5.      !!
678  REAL(r_std), SAVE :: init_sapl_mass_root = 0.1        !!
679  REAL(r_std), SAVE :: init_sapl_mass_fruit = 0.3       !! 
680  REAL(r_std), SAVE :: cn_sapl_init = 0.5               !!
681  REAL(r_std), SAVE :: migrate_tree = 10.*1.E3          !!
682  REAL(r_std), SAVE :: migrate_grass = 10.*1.E3         !!
683  REAL(r_std), SAVE :: lai_initmin_tree = 0.3           !!
684  REAL(r_std), SAVE :: lai_initmin_grass = 0.1          !!
685  REAL(r_std), SAVE, DIMENSION(2) :: dia_coeff = (/ 4., 0.5 /)            !!
686  REAL(r_std), SAVE, DIMENSION(2) :: maxdia_coeff =(/ 100., 0.01/)        !!
687  REAL(r_std), SAVE, DIMENSION(4) :: bm_sapl_leaf = (/ 4., 4., 0.8, 5./)  !!
688
689
690
691  !
692  ! stomate_litter.f90
693  !
694
695  ! 0. Constants
696
697  REAL(r_std), PARAMETER :: Q10 = 10.               !!
698
699  ! 1. Scalar
700
701  REAL(r_std), SAVE :: z_decomp = 0.2               !!  Maximum depth for soil decomposer's activity (m)
702
703  ! 2. Arrays
704
705  REAL(r_std), SAVE :: frac_soil_struct_aa = 0.55   !! corresponding to frac_soil(istructural,iactive,iabove)
706  REAL(r_std), SAVE :: frac_soil_struct_ab = 0.45   !! corresponding to frac_soil(istructural,iactive,ibelow)
707  REAL(r_std), SAVE :: frac_soil_struct_sa = 0.7    !! corresponding to frac_soil(istructural,islow,iabove)
708  REAL(r_std), SAVE :: frac_soil_struct_sb = 0.7    !! corresponding to frac_soil(istructural,islow,ibelow)
709  REAL(r_std), SAVE :: frac_soil_metab_aa = 0.45    !! corresponding to frac_soil(imetabolic,iactive,iabove)
710  REAL(r_std), SAVE :: frac_soil_metab_ab = 0.45    !! corresponding to frac_soil(imetabolic,iactive,ibelow)
711  REAL(r_std), SAVE, DIMENSION(nparts) :: CN = &    !! C/N ratio (0-100, unitless)
712       & (/ 40., 40., 40., 40., 40., 40., 40., 40. /) 
713  REAL(r_std), SAVE, DIMENSION(nparts) :: LC = &    !! Lignine/C ratio of the different plant parts (0-1, unitless)
714       & (/ 0.22, 0.35, 0.35, 0.35, 0.35, 0.22, 0.22, 0.22 /)
715
716  ! 3. Coefficients of equations
717
718  REAL(r_std), SAVE :: metabolic_ref_frac = 0.85    !! used by litter and soilcarbon (0-1, unitless)
719  REAL(r_std), SAVE :: metabolic_LN_ratio = 0.018   !! (0-1, unitless)   
720  REAL(r_std), SAVE :: tau_metabolic = 0.066        !!
721  REAL(r_std), SAVE :: tau_struct = 0.245           !!
722  REAL(r_std), SAVE :: soil_Q10 = 0.69              !!= ln 2
723  REAL(r_std), SAVE :: tsoil_ref = 30.              !!
724  REAL(r_std), SAVE :: litter_struct_coef = 3.      !!
725  REAL(r_std), SAVE, DIMENSION(3) :: moist_coeff = (/ 1.1,  2.4,  0.29 /) !!
726
727
728
729  !
730  ! stomate_lpj.f90
731  !
732
733  ! 1. Scalar
734
735  REAL(r_std), SAVE :: frac_turnover_daily = 0.55  !! (0-1, unitless)
736
737
738
739  !
740  ! stomate_npp.f90
741  !
742
743  ! 1. Scalar
744
745  REAL(r_std), SAVE :: tax_max = 0.8 !! maximum fraction of allocatable biomass used
746                                     !! for maintenance respiration (0-1, unitless)
747
748
749
750  !
751  ! stomate_phenology.f90
752  !
753
754  ! 1. Scalar
755
756  LOGICAL, SAVE :: always_init = .FALSE.           !! take carbon from atmosphere if carbohydrate reserve too small? (true/false)
757  REAL(r_std), SAVE :: min_growthinit_time = 300.  !! minimum time since last beginning of a growing season (days)
758  REAL(r_std), SAVE :: moiavail_always_tree = 1.0  !! moisture availability above which moisture tendency doesn't matter
759                                                   !! (0-1, unitless)
760  REAL(r_std), SAVE :: moiavail_always_grass = 0.6 !! moisture availability above which moisture tendency doesn't matter
761                                                   !! (0-1, unitless)
762  REAL(r_std), SAVE :: t_always                    !! monthly temp. above which temp. tendency doesn't matter
763  REAL(r_std), SAVE :: t_always_add = 10.          !! monthly temp. above which temp. tendency doesn't matter (C)
764
765  ! 3. Coefficients of equations
766 
767  REAL(r_std), SAVE :: gddncd_ref = 603.           !!
768  REAL(r_std), SAVE :: gddncd_curve = 0.0091       !!
769  REAL(r_std), SAVE :: gddncd_offset = 64.         !!
770
771
772
773  !
774  ! stomate_prescribe.f90
775  !
776
777  ! 3. Coefficients of equations
778
779  REAL(r_std), SAVE :: bm_sapl_rescale = 40.       !!
780
781
782
783  !
784  ! stomate_resp.f90
785  !
786
787  ! 3. Coefficients of equations
788
789  REAL(r_std), SAVE :: maint_resp_min_vmax = 0.3   !!
790  REAL(r_std), SAVE :: maint_resp_coeff = 1.4      !!
791
792
793
794  !
795  ! stomate_soilcarbon.f90
796  !
797
798  ! 2. Arrays
799
800  ! 2.1 frac_carb_coefficients
801
802  REAL(r_std), SAVE :: frac_carb_ap = 0.004  !! from active pool: depends on clay content  (0-1, unitless)
803                                             !! corresponding to frac_carb(:,iactive,ipassive)
804  REAL(r_std), SAVE :: frac_carb_sa = 0.42   !! from slow pool (0-1, unitless)
805                                             !! corresponding to frac_carb(:,islow,iactive)
806  REAL(r_std), SAVE :: frac_carb_sp = 0.03   !! from slow pool (0-1, unitless)
807                                             !! corresponding to frac_carb(:,islow,ipassive)
808  REAL(r_std), SAVE :: frac_carb_pa = 0.45   !! from passive pool (0-1, unitless)
809                                             !! corresponding to frac_carb(:,ipassive,iactive)
810  REAL(r_std), SAVE :: frac_carb_ps = 0.0    !! from passive pool (0-1, unitless)
811                                             !! corresponding to frac_carb(:,ipassive,islow)
812
813  ! 3. Coefficients of equations
814
815  REAL(r_std), SAVE :: active_to_pass_clay_frac = 0.68  !! (0-1, unitless)
816  !! residence times in carbon pools (days)
817  REAL(r_std), SAVE :: carbon_tau_iactive = 0.149   !! residence times in active pool (days)
818  REAL(r_std), SAVE :: carbon_tau_islow = 5.48      !! residence times in slow pool (days)
819  REAL(r_std), SAVE :: carbon_tau_ipassive = 241.   !! residence times in passive pool (days)
820  REAL(r_std), SAVE, DIMENSION(3) :: flux_tot_coeff = (/ 1.2, 1.4, .75/)
821
822
823  !
824  ! stomate_turnover.f90
825  !
826
827  ! 3. Coefficients of equations
828
829  REAL(r_std), SAVE :: new_turnover_time_ref = 20. !!(days)
830  REAL(r_std), SAVE :: dt_turnover_time = 10.      !!(days)
831  REAL(r_std), SAVE :: leaf_age_crit_tref = 20.    !! (C)
832  REAL(r_std), SAVE, DIMENSION(3) :: leaf_age_crit_coeff = (/ 1.5, 0.75, 10./) !! (unitless)
833
834
835
836  !
837  ! stomate_vmax.f90
838  !
839 
840  ! 1. Scalar
841
842  REAL(r_std), SAVE :: vmax_offset = 0.3        !! offset (minimum relative vcmax)
843  REAL(r_std), SAVE :: leafage_firstmax = 0.03  !! leaf age at which vmax attains vcmax_opt
844                                                !! (in fraction of critical leaf age) (0-1, unitless)
845  REAL(r_std), SAVE :: leafage_lastmax = 0.5    !! leaf age at which vmax falls below vcmax_opt
846                                                !! (in fraction of critical leaf age) (0-1, unitless)
847  REAL(r_std), SAVE :: leafage_old = 1.         !! leaf age at which vmax attains its minimum
848                                                !! (in fraction of critical leaf age) (0-1, unitless)
849
850
851  !
852  ! stomate_season.f90
853  !
854
855  ! 1. Scalar
856
857  REAL(r_std), SAVE :: gppfrac_dormance = 0.2  !! maximal ratio GPP/GGP_max for dormance (0-1, unitless)
858  REAL(r_std), SAVE :: min_gpp_allowed = 0.3   !! minimum gpp considered as not "lowgpp" (gC.m^{-2}.year^{-1})
859  REAL(r_std), SAVE :: tau_climatology = 20.   !! tau for "climatologic variables (years)
860  REAL(r_std), SAVE :: hvc1 = 0.019            !! parameters for herbivore activity (unitless)
861  REAL(r_std), SAVE :: hvc2 = 1.38             !! parameters for herbivore activity (unitless)
862  REAL(r_std), SAVE :: leaf_frac_hvc = 0.33    !! parameters for herbivore activity (0-1, unitless)
863  REAL(r_std), SAVE :: tlong_ref_max = 303.1   !! maximum reference long term temperature (K)
864  REAL(r_std), SAVE :: tlong_ref_min = 253.1   !! minimum reference long term temperature (K)
865
866  ! 3. Coefficients of equations
867
868  REAL(r_std), SAVE :: ncd_max_year = 3.
869  REAL(r_std), SAVE :: gdd_threshold = 5.
870  REAL(r_std), SAVE :: green_age_ever = 2.
871  REAL(r_std), SAVE :: green_age_dec = 0.5
872
873
874
875 CONTAINS
876
877
878!! ================================================================================================================================
879!! SUBROUTINE   : activate_sub_models
880!!
881!>\BRIEF         This subroutine reads the flags in the configuration file to
882!! activate some sub-models like routing, irrigation, fire, herbivory, ... 
883!!
884!! DESCRIPTION  : None
885!!
886!! RECENT CHANGE(S): None
887!!
888!! MAIN OUTPUT VARIABLE(S): None
889!!
890!! REFERENCE(S) : None
891!!
892!! FLOWCHART    : None
893!! \n
894!_ ================================================================================================================================
895
896   SUBROUTINE activate_sub_models(active_flags)
897
898     IMPLICIT NONE
899
900     !! 0. Variables and parameters declaration
901
902     !! 0.1 Input variables
903
904     TYPE(control_type),INTENT(in) :: active_flags     !! What parts of the code are activated ?
905
906     !! 0.4 Local variables
907
908     LOGICAL, SAVE ::  first_call = .TRUE.             !! To keep first call trace (true/false)
909
910!_ ================================================================================================================================
911
912     IF (first_call) THEN
913
914        IF(active_flags%ok_sechiba .AND. active_flags%river_routing) THEN
915           
916           !Config Key   = DO_IRRIGATION
917           !Config Desc  = Should we compute an irrigation flux
918           !Config If    = RIVER_ROUTING
919           !Config Def   = n
920           !Config Help  = This parameters allows the user to ask the model
921           !Config         to compute an irigation flux. This performed for the
922           !Config         on very simple hypothesis. The idea is to have a good
923           !Config         map of irrigated areas and a simple function which estimates
924           !Config         the need to irrigate.
925           !Config Units = [FLAG]
926           CALL getin_p('DO_IRRIGATION', doirrigation)
927           !
928           !Config Key   = DO_FLOODPLAINS
929           !Config Desc  = Should we include floodplains
930           !Config If    = RIVER_ROUTING
931           !Config Def   = n
932           !Config Help  = This parameters allows the user to ask the model
933           !Config         to take into account the flood plains and return
934           !Config         the water into the soil moisture. It then can go
935           !Config         back to the atmopshere. This tried to simulate
936           !Config         internal deltas of rivers.
937           !Config Units = [FLAG]
938           CALL getin_p('DO_FLOODPLAINS', dofloodplains)
939       
940        ENDIF
941
942           
943        IF(active_flags%ok_stomate) THEN
944
945           !Config Key   = HERBIVORES
946           !Config Desc  = herbivores allowed?
947           !Config If    = OK_STOMATE
948           !Config Def   = n
949           !Config Help  = With this variable, you can determine
950           !Config         if herbivores are activated
951           !Config Units = [FLAG]
952           CALL getin_p('HERBIVORES', ok_herbivores)
953           !
954           !Config Key   = TREAT_EXPANSION
955           !Config Desc  = treat expansion of PFTs across a grid cell?
956           !Config If    = OK_STOMATE
957           !Config Def   = n
958           !Config Help  = With this variable, you can determine
959           !Config         whether we treat expansion of PFTs across a
960           !Config         grid cell.
961           !Config Units = [FLAG]
962           CALL getin_p('TREAT_EXPANSION', treat_expansion)
963           !
964           !Config Key   = LPJ_GAP_CONST_MORT
965           !Config Desc  = prescribe mortality if not using DGVM?
966           !Config If    = OK_STOMATE
967           !Config Def   = y
968           !Config Help  = set to TRUE if constant mortality is to be activated
969           !Config         ignored if DGVM=true!
970           !Config Units = [FLAG]
971           CALL getin_p('LPJ_GAP_CONST_MORT', lpj_gap_const_mort)
972           !
973           !Config Key   = HARVEST_AGRI
974           !Config Desc  = Harvest model for agricultural PFTs.
975           !Config If    = OK_STOMATE
976           !Config Def   = y
977           !Config Help  = Compute harvest above ground biomass for agriculture.
978           !Config         Change daily turnover.
979           !Config Units = [FLAG]
980           CALL getin_p('HARVEST_AGRI', harvest_agri)
981           !
982           !Config Key   = FIRE_DISABLE
983           !Config Desc  = no fire allowed
984           !Config If    = OK_STOMATE
985           !Config Def   = n
986           !Config Help  = With this variable, you can allow or not
987           !Config         the estimation of CO2 lost by fire
988           !Config Units = [FLAG]
989           CALL getin_p('FIRE_DISABLE', disable_fire)
990
991        ENDIF
992
993        !
994        ! Check consistency (see later)
995        !
996!!$        IF(.NOT.(ok_routing) .AND. (doirrigation .OR. dofloodplains)) THEN
997!!$           CALL ipslerr (2,'activate_sub_models', &
998!!$               &     'Problem :you tried to activate the irrigation and floodplains without activating the routing',&
999!!$               &     'Are you sure ?', &
1000!!$               &     '(check your parameters).')
1001!!$        ENDIF
1002       
1003!!$        IF(.NOT.(ok_stomate) .AND. (ok_herbivores .OR. treat_expansion .OR. lpj_gap_const_mort &
1004!!$            & .OR. harvest_agri .OR. disable_fire)) THEN
1005!!$          CALL ipslerr (2,'activate_sub_models', &
1006!!$               &     'Problem : try to activate the following options : herbivory, treat_expansion, fire,',&
1007!!$               &     'harvest_agri and constant mortality without stomate activated.',&
1008!!$               &     '(check your parameters).')
1009!!$        ENDIF
1010           
1011        first_call =.FALSE.
1012
1013     ENDIF
1014
1015   END SUBROUTINE activate_sub_models
1016!
1017!=
1018!
1019
1020!! ================================================================================================================================
1021!! SUBROUTINE   : veget_config
1022!!
1023!>\BRIEF         This subroutine reads the flags controlling the configuration for
1024!! the vegetation : impose_veg, veget_mpa, lai_map, etc...       
1025!!
1026!! DESCRIPTION  : None
1027!!
1028!! RECENT CHANGE(S): None
1029!!
1030!! MAIN OUTPUT VARIABLE(S):
1031!!
1032!! REFERENCE(S) :
1033!!
1034!! FLOWCHART    :
1035!! \n
1036!_ ================================================================================================================================
1037
1038   SUBROUTINE veget_config
1039
1040     IMPLICIT NONE
1041
1042     !! 0. Variables and parameters declaration
1043
1044     !! 0.4 Local variables 
1045
1046     LOGICAL, SAVE ::  first_call = .TRUE.        !! To keep first call trace (true/false) 
1047
1048!_ ================================================================================================================================
1049     
1050     IF (first_call) THEN 
1051
1052        !Config Key   = AGRICULTURE
1053        !Config Desc  = agriculture allowed?
1054        !Config If    = OK_SECHIBA or OK_STOMATE
1055        !Config Def   = y
1056        !Config Help  = With this variable, you can determine
1057        !Config         whether agriculture is allowed
1058        !Config Units = [FLAG]
1059        CALL getin_p('AGRICULTURE', agriculture)
1060        !
1061        !Config Key   = IMPOSE_VEG
1062        !Config Desc  = Should the vegetation be prescribed ?
1063        !Config If    = OK_SECHIBA or OK_STOMATE
1064        !Config Def   = n
1065        !Config Help  = This flag allows the user to impose a vegetation distribution
1066        !Config         and its characteristics. It is espacially interesting for 0D
1067        !Config         simulations. On the globe it does not make too much sense as
1068        !Config         it imposes the same vegetation everywhere
1069        !Config Units = [FLAG]
1070        CALL getin_p('IMPOSE_VEG', impveg)
1071
1072        IF(impveg) THEN
1073           !Config Key   = IMPOSE_SOILT
1074           !Config Desc  = Should the soil type be prescribed ?
1075           !Config Def   = n
1076           !Config If    = IMPOSE_VEG
1077           !Config Help  = This flag allows the user to impose a soil type distribution.
1078           !Config         It is espacially interesting for 0D
1079           !Config         simulations. On the globe it does not make too much sense as
1080           !Config         it imposes the same soil everywhere
1081           !Config Units = [FLAG]
1082           CALL getin_p('IMPOSE_SOILT', impsoilt)     
1083        ENDIF
1084
1085        !Config Key   = LAI_MAP
1086        !Config Desc  = Read the LAI map
1087        !Config If    = OK_SECHIBA or OK_STOMATE
1088        !Config Def   = n
1089        !Config Help  = It is possible to read a 12 month LAI map which will
1090        !Config         then be interpolated to daily values as needed.
1091        !Config Units = [FLAG]
1092        CALL getin_p('LAI_MAP',read_lai)
1093
1094        IF(read_lai) THEN
1095           !Config Key   = SLOWPROC_LAI_OLD_INTERPOL
1096           !Config Desc  = Flag to use old "interpolation" of LAI
1097           !Config If    = LAI_MAP
1098           !Config Def   = n
1099           !Config Help  = If you want to recover the old (ie orchidee_1_2 branch)
1100           !Config         "interpolation" of LAI map.
1101           !Config Units = [FLAG]
1102           CALL getin_p('SLOWPROC_LAI_OLD_INTERPOL',old_lai)
1103        ENDIF
1104 
1105        !Config Key   = LAND_USE
1106        !Config Desc  = Read a land_use vegetation map
1107        !Config If    = OK_SECHIBA or OK_STOMATE
1108        !Config Def   = y
1109        !Config Help  = pft values are needed, max time axis is 293
1110        !Config Units = [FLAG]
1111        CALL getin_p('LAND_USE',land_use)
1112
1113        IF(land_use) THEN
1114           !Config Key   = VEGET_REINIT
1115           !Config Desc  = booleen to indicate that a new LAND USE file will be used.
1116           !Config If    = LAND_USE
1117           !Config Def   = y
1118           !Config Help  = The parameter is used to bypass veget_year count
1119           !Config         and reinitialize it with VEGET_YEAR parameter.
1120           !Config         Then it is possible to change LAND USE file.
1121           !Config Units = [FLAG]
1122           CALL getin_p('VEGET_REINIT', veget_reinit)
1123           !
1124           !Config Key   = LAND_COVER_CHANGE
1125           !Config Desc  = treat land use modifications
1126           !Config If    = LAND_USE
1127           !Config Def   = n
1128           !Config Help  = With this variable, you can use a Land Use map
1129           !Config         to simulate anthropic modifications such as
1130           !Config         deforestation.
1131           !Config Units = [FLAG]
1132           CALL getin_p('LAND_COVER_CHANGE', lcchange)
1133           !
1134           !Config Key   = VEGET_YEAR
1135           !Config Desc  = Year of the land_use vegetation map to be read
1136           !Config If    = LAND_USE
1137           !Config Def   = 1
1138           !Config Help  = First year for landuse vegetation (2D map by pft).
1139           !Config         If VEGET_YEAR is set to 0, this means there is no time axis.
1140           !Config Units = [FLAG]
1141           CALL getin_p('VEGET_YEAR', veget_year_orig)
1142        ENDIF
1143
1144        IF(.NOT. impveg .AND. .NOT. land_use) THEN
1145           !Config Key   = SLOWPROC_VEGET_OLD_INTERPOL
1146           !Config Desc  = Flag to use old "interpolation" of vegetation map.
1147           !Config If    = NOT(IMPOSE_VEG) and NOT(LAND_USE)
1148           !Config Def   = n
1149           !Config Help  = If you want to recover the old (ie orchidee_1_2 branch)
1150           !Config         "interpolation" of vegetation map.
1151           !Config Units = [FLAG]
1152           CALL getin_p('SLOWPROC_VEGET_OLD_INTERPOL',old_veget)
1153         ENDIF 
1154
1155         !
1156         ! Check consistency
1157         !
1158         ! 1. You have to activate agriculture and land_use
1159         IF ( .NOT. agriculture .AND. land_use ) THEN
1160            CALL ipslerr (2,'veget_config', &
1161                 &     'Problem with agriculture desactivated and Land Use activated.',&
1162                 &     'Are you sure ?', &
1163                 &     '(check your parameters).')
1164         ENDIF
1165
1166
1167        first_call = .FALSE.
1168
1169     ENDIF
1170
1171!!$        ! DS : Add warning in case of a wrong configuration (need to be discussed)
1172!!$        ! 2.
1173!!$        IF (.NOT.(read_lai) .AND. old_lai) THEN
1174!!$           CALL ipslerr (2,'veget_config', &
1175!!$               &     'Problem with lai_map desactivated and old_lai activated.',&
1176!!$               &     'Are you sure ?', &
1177!!$               &     '(check your parameters).')
1178!!$        ENDIF
1179!!$   
1180!!$        ! 3.
1181!!$        IF ((impveg .OR. land_use) .AND. old_veget) THEN
1182!!$           CALL ipslerr (2,'veget_config', &
1183!!$                &     'Problem : try to use the old interpolation with a land use map or in impose_veg.',&
1184!!$                &     'Are you sure ?', &
1185!!$                &     '(check your parameters).')
1186!!$        ENDIF
1187!!$
1188!!$        ! 4.
1189!!$        IF ( .NOT.(impveg) .AND. impsoilt) THEN
1190!!$           CALL ipslerr (2,'veget_config', &
1191!!$               &     'Problem : try to activate impose_soilt without activating impose_veg.',&
1192!!$               &     'Are you sure ?', &
1193!!$               &     '(check your parameters).')
1194!!$        ENDIF
1195!!$
1196!!$        ! 5.
1197!!$        IF (.NOT.(land_use) .AND. (veget_reinit)) THEN
1198!!$           CALL ipslerr (2,'veget_config', &
1199!!$                &     'Problem : try to use a land_use map without activating land_use.',&
1200!!$                &     'Are you sure ?', &
1201!!$                &     '(check your parameters).')       
1202!!$        ENDIF
1203!!$
1204!!$        ! 6.
1205!!$        IF (.NOT.(land_use) .AND. lcchange) THEN
1206!!$           CALL ipslerr (2,'veget_config', &
1207!!$                &     'Problem : lcchange is activated without activating land_use.',&
1208!!$                &     'Are you sure ?', &
1209!!$                &     '(check your parameters).')       
1210!!$        ENDIF
1211           
1212   END SUBROUTINE veget_config
1213!
1214!=
1215!
1216
1217!! ================================================================================================================================
1218!! SUBROUTINE   : veget_config
1219!!
1220!>\BRIEF         This subroutine reads in the configuration file the imposed values of the parameters for all SECHIBA modules. 
1221!!
1222!! DESCRIPTION  : None
1223!!
1224!! RECENT CHANGE(S): None
1225!!
1226!! MAIN OUTPUT VARIABLE(S):
1227!!
1228!! REFERENCE(S) :
1229!!
1230!! FLOWCHART    :
1231!! \n
1232!_ ================================================================================================================================
1233
1234   SUBROUTINE config_sechiba_parameters
1235
1236     IMPLICIT NONE
1237
1238     !! 0. Variables and parameters declaration
1239
1240     !! 0.4 Local variables
1241     
1242     LOGICAL, SAVE ::  first_call = .TRUE.    !! To keep first call trace (true/false)
1243
1244!_ ================================================================================================================================
1245     
1246     IF(first_call) THEN 
1247       
1248        ! Global : parameters used by many modules
1249        !
1250        !Config Key   = MAXMASS_GLACIER
1251        !Config Desc  = The maximum mass of a glacier
1252        !Config If    = OK_SECHIBA or OK_CWRR
1253        !Config Def   = 3000.
1254        !Config Help  =
1255        !Config Units = [kg/m^2] 
1256        CALL getin_p('MAXMASS_GLACIER',maxmass_glacier)
1257        !
1258        !Config Key   = SNOWCRI
1259        !Config Desc  = Sets the amount above which only sublimation occures
1260        !Config If    = OK_SECHIBA or OK_CWRR
1261        !Config Def   = 1.5
1262        !Config Help  =
1263        !Config Units = [kg/m^2] 
1264        CALL getin_p('SNOWCRI',snowcri)
1265        !
1266        !Config Key   = SECHIBA_QSINT
1267        !Config Desc  = Interception reservoir coefficient
1268        !Config If    = OK_SECHIBA
1269        !Config Def   = 0.1
1270        !Config Help  = Transforms leaf area index into size of interception reservoir
1271        !Config         for slowproc_derivvar or stomate
1272        !Config Units = [m]
1273        CALL getin_p('SECHIBA_QSINT',qsintcst)
1274        !
1275        !Config Key   = HYDROL_SOIL_DEPTH
1276        !Config Desc  = Total depth of soil reservoir
1277        !Config If    = OK_SECHIBA
1278        !Config Def   = 4.
1279        !Config Help  =
1280        !Config Units = [m]
1281        CALL getin_p("HYDROL_SOIL_DEPTH",dpu_cste)
1282        !
1283        !
1284        !Config Key   = MIN_WIND
1285        !Config Desc  = Minimum wind speed
1286        !Config If    = OK_SECHIBA
1287        !Config Def   = 0.1
1288        !Config Help  =
1289        !Config Units = [m/s]
1290        CALL getin_p('MIN_WIND',min_wind)
1291        !
1292        !Config Key   = MAX_SNOW_AGE
1293        !Config Desc  = Maximum period of snow aging
1294        !Config If    = OK_SECHIBA
1295        !Config Def   = 50.
1296        !Config Help  =
1297        !Config Units = [days?]
1298        CALL getin_p('MAX_SNOW_AGE',max_snow_age)
1299        !
1300        !Config Key   = SNOW_TRANS
1301        !Config Desc  = Transformation time constant for snow
1302        !Config If    = OK_SECHIBA
1303        !Config Def   = 0.3
1304        !Config Help  =
1305        !Config Units = [m]   
1306        CALL getin_p('SNOW_TRANS',snow_trans)
1307        !
1308        !Config Key   = MX_EAU_EAU
1309        !Config Desc  = Maximum quantity of water
1310        !Config If    = OK_SECHIBA
1311        !Config Def   = 150.
1312        !Config Help  =
1313        !Config Units = [kg/m^3] 
1314        CALL getin_p('MX_EAU_EAU',mx_eau_eau)
1315        !-
1316        ! condveg
1317        !-
1318        !
1319        !Config Key   = Z0_OVER_HEIGHT
1320        !Config Desc  = to get z0 from height
1321        !Config If    = OK_SECHIBA
1322        !Config Def   = 1/16.
1323        !Config Help  =
1324        !Config Units = [-]   
1325        CALL getin_p('Z0_OVER_HEIGHT',z0_over_height)
1326        !
1327        !Config Key   = HEIGHT_DISPLACEMENT
1328        !Config Desc  = Magic number which relates the height to the displacement height.
1329        !Config If    = OK_SECHIBA
1330        !Config Def   = 0.75
1331        !Config Help  =
1332        !Config Units = [m] 
1333        CALL getin_p('HEIGHT_DISPLACEMENT',height_displacement)
1334        !
1335        !Config Key   = Z0_BARE
1336        !Config Desc  = bare soil roughness length
1337        !Config If    = OK_SECHIBA
1338        !Config Def   = 0.01
1339        !Config Help  =
1340        !Config Units = [m]   
1341        CALL getin_p('Z0_BARE',z0_bare)
1342        !
1343        !Config Key   = Z0_ICE
1344        !Config Desc  = ice roughness length
1345        !Config If    = OK_SECHIBA
1346        !Config Def   = 0.001
1347        !Config Help  =
1348        !Config Units = [m]   
1349        CALL getin_p('Z0_ICE',z0_ice)
1350        !
1351        !Config Key   = TCST_SNOWA
1352        !Config Desc  = Time constant of the albedo decay of snow
1353        !Config If    = OK_SECHIBA
1354        !Config Def   = 5.0
1355        !Config Help  =
1356        !Config Units = [days]
1357        CALL getin_p('TCST_SNOWA',tcst_snowa)
1358        !
1359        !Config Key   = SNOWCRI_ALB
1360        !Config Desc  = Critical value for computation of snow albedo
1361        !Config If    = OK_SECHIBA
1362        !Config Def   = 10.
1363        !Config Help  =
1364        !Config Units = [kg/m^2] 
1365        CALL getin_p('SNOWCRI_ALB',snowcri_alb)
1366        !
1367        !
1368        !Config Key   = VIS_DRY
1369        !Config Desc  = The correspondance table for the soil color numbers and their albedo
1370        !Config If    = OK_SECHIBA
1371        !Config Def   = 0.24, 0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.27
1372        !Config Help  =
1373        !Config Units = [-] 
1374        CALL getin_p('VIS_DRY',vis_dry)
1375        !
1376        !Config Key   = NIR_DRY
1377        !Config Desc  = The correspondance table for the soil color numbers and their albedo
1378        !Config If    = OK_SECHIBA
1379        !Config Def   = 0.48, 0.44, 0.40, 0.36, 0.32, 0.28, 0.24, 0.20, 0.55
1380        !Config Help  =
1381        !Config Units = [-]   
1382        CALL getin_p('NIR_DRY',nir_dry)
1383        !
1384        !Config Key   = VIS_WET
1385        !Config Desc  = The correspondance table for the soil color numbers and their albedo
1386        !Config If    = OK_SECHIBA 
1387        !Config Def   = 0.12, 0.11, 0.10, 0.09, 0.08, 0.07, 0.06, 0.05, 0.15
1388        !Config Help  =
1389        !Config Units = [-]   
1390        CALL getin_p('VIS_WET',vis_wet)
1391        !
1392        !Config Key   = NIR_WET
1393        !Config Desc  = The correspondance table for the soil color numbers and their albedo
1394        !Config If    = OK_SECHIBA
1395        !Config Def   = 0.24, 0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.31
1396        !Config Help  =
1397        !Config Units = [-]   
1398        CALL getin_p('NIR_WET',nir_wet)
1399        !
1400        !Config Key   = ALBSOIL_VIS
1401        !Config Desc  =
1402        !Config If    = OK_SECHIBA
1403        !Config Def   = 0.18, 0.16, 0.16, 0.15, 0.12, 0.105, 0.09, 0.075, 0.25
1404        !Config Help  =
1405        !Config Units = [-] 
1406        CALL getin_p('ALBSOIL_VIS',albsoil_vis)
1407        !
1408        !Config Key   = ALBSOIL_NIR
1409        !Config Desc  =
1410        !Config If    = OK_SECHIBA
1411        !Config Def   = 0.36, 0.34, 0.34, 0.33, 0.30, 0.25, 0.20, 0.15, 0.45
1412        !Config Help  =
1413        !Config Units = [-] 
1414        CALL getin_p('ALBSOIL_NIR',albsoil_nir)
1415        !-
1416        !
1417        !Config Key   = ALB_DEADLEAF
1418        !Config Desc  = albedo of dead leaves, VIS+NIR
1419        !Config If    = OK_SECHIBA
1420        !Config Def   = 0.12, 0.35
1421        !Config Help  =
1422        !Config Units = [-]     
1423        CALL getin_p('ALB_DEADLEAF',alb_deadleaf)
1424        !
1425        !Config Key   = ALB_ICE
1426        !Config Desc  = albedo of ice, VIS+NIR
1427        !Config If    = OK_SECHIBA
1428        !Config Def   = 0.60, 0.20
1429        !Config Help  =
1430        !Config Units = [-] 
1431        CALL getin_p('ALB_ICE',alb_ice)
1432        !
1433        ! Get the fixed snow albedo if needed
1434        !
1435        !Config Key   = CONDVEG_SNOWA
1436        !Config Desc  = The snow albedo used by SECHIBA
1437        !Config Def   = 1.E+20
1438        !Config if    = OK_SECHIBA
1439        !Config Help  = This option allows the user to impose a snow albedo.
1440        !Config         Default behaviour is to use the model of snow albedo
1441        !Config         developed by Chalita (1993).
1442        !Config Units = [-]
1443        CALL getin_p('CONDVEG_SNOWA',fixed_snow_albedo)
1444        !
1445        !Config Key   = ALB_BARE_MODEL
1446        !Config Desc  = Switch bare soil albedo dependent (if TRUE) on soil wetness
1447        !Config Def   = n
1448        !Config if    = OK_SECHIBA
1449        !Config Help  = If TRUE, the model for bare soil albedo is the old formulation.
1450        !Config         Then it depend on the soil dry or wetness. If FALSE, it is the
1451        !Config         new computation that is taken, it is the mean of soil albedo.
1452        !Config Units = [FLAG]
1453        CALL getin_p('ALB_BARE_MODEL',alb_bare_model)
1454        !
1455        !Config Key   = Z0CDRAG_AVE
1456        !Config Desc  = Average method for z0
1457        !Config Def   = y
1458        !Config if    = OK_SECHIBA
1459        !Config Help  = If this flag is set to true (y) then the neutral Cdrag
1460        !Config         is averaged instead of the log(z0). This should be
1461        !Config         the prefered option. We still wish to keep the other
1462        !Config         option so we can come back if needed. If this is
1463        !Config         desired then one should set Z0CDRAG_AVE=n
1464        !Config Units = [FLAG]
1465        CALL getin_p('Z0CDRAG_AVE',z0cdrag_ave)
1466        !
1467        !Config Key   = IMPOSE_AZE
1468        !Config Desc  = Should the surface parameters be prescribed
1469        !Config Def   = n
1470        !Config if    = OK_SECHIBA
1471        !Config Help  = This flag allows the user to impose the surface parameters
1472        !Config         (Albedo Roughness and Emissivity). It is espacially interesting for 0D
1473        !Config         simulations. On the globe it does not make too much sense as
1474        !Config         it imposes the same vegetation everywhere
1475        !Config Units = [FLAG]
1476        CALL getin_p('IMPOSE_AZE',impaze)
1477        !
1478        IF(impaze) THEN
1479           !
1480           !Config Key   = CONDVEG_Z0
1481           !Config Desc  = Surface roughness
1482           !Config Def   = 0.15
1483           !Config If    = IMPOSE_AZE
1484           !Config Help  = Surface rougness to be used on the point if a 0-dim version
1485           !Config         of SECHIBA is used. Look at the description of the forcing 
1486           !Config         data for the correct value.
1487           !Config Units = [m]
1488           CALL getin_p('CONDVEG_Z0', z0_scal) 
1489           !
1490           !Config Key   = ROUGHHEIGHT
1491           !Config Desc  = Height to be added to the height of the first level
1492           !Config Def   = 0.0
1493           !Config If    = IMPOSE_AZE
1494           !Config Help  = ORCHIDEE assumes that the atmospheric level height is counted
1495           !Config         from the zero wind level. Thus to take into account the roughness
1496           !Config         of tall vegetation we need to correct this by a certain fraction
1497           !Config         of the vegetation height. This is called the roughness height in
1498           !Config         ORCHIDEE talk.
1499           !Config Units = [m]
1500           CALL getin_p('ROUGHHEIGHT', roughheight_scal)
1501           !
1502           !Config Key   = CONDVEG_ALBVIS
1503           !Config Desc  = SW visible albedo for the surface
1504           !Config Def   = 0.25
1505           !Config If    = IMPOSE_AZE
1506           !Config Help  = Surface albedo in visible wavelengths to be used
1507           !Config         on the point if a 0-dim version of SECHIBA is used.
1508           !Config         Look at the description of the forcing data for
1509           !Config         the correct value.
1510           !Config Units = [-]
1511           CALL getin_p('CONDVEG_ALBVIS', albedo_scal(ivis))
1512           !
1513           !Config Key   = CONDVEG_ALBNIR
1514           !Config Desc  = SW near infrared albedo for the surface
1515           !Config Def   = 0.25
1516           !Config If    = IMPOSE_AZE
1517           !Config Help  = Surface albedo in near infrared wavelengths to be used
1518           !Config         on the point if a 0-dim version of SECHIBA is used.
1519           !Config         Look at the description of the forcing data for
1520           !Config         the correct value.
1521           !Config Units = [-] 
1522           CALL getin_p('CONDVEG_ALBNIR', albedo_scal(inir))
1523           !
1524           !Config Key   = CONDVEG_EMIS
1525           !Config Desc  = Emissivity of the surface for LW radiation
1526           !Config Def   = 1.0
1527           !Config If    = IMPOSE_AZE
1528           !Config Help  = The surface emissivity used for compution the LE emission
1529           !Config         of the surface in a 0-dim version. Values range between
1530           !Config         0.97 and 1.. The GCM uses 0.98.
1531           !Config Units = [-]
1532           CALL getin_p('CONDVEG_EMIS', emis_scal)
1533        ENDIF
1534        !
1535        !-
1536        ! diffuco
1537        !-
1538        !
1539        !Config Key   = NLAI
1540        !Config Desc  = Number of LAI levels
1541        !Config If    = OK_SECHIBA
1542        !Config Def   = 20
1543        !Config Help  =
1544        !Config Units = [-] 
1545        CALL getin_p('NLAI',nlai)
1546        !
1547        !Config Key   = LAIMAX
1548        !Config Desc  = Maximum LAI
1549        !Config If    = OK_SECHIBA
1550        !Config Def   =
1551        !Config Help  =
1552        !Config Units = [m^2/m^2]   
1553        CALL getin_p('LAIMAX',laimax)
1554        !
1555        !Config Key   = XC4_1
1556        !Config Desc  = Factor in the first Collatz equation for C4 plants
1557        !Config If    = OK_SECHIBA
1558        !Config Def   = 0.83
1559        !Config Help  =
1560        !Config Units = [-]   
1561        CALL getin_p('XC4_1',xc4_1)
1562        !
1563        !Config Key   = XC4_2
1564        !Config Desc  = Factor in the second Collatz equation for C4 plants
1565        !Config If    = OK_SECHIBA
1566        !Config Def   = 0.93
1567        !Config Help  =
1568        !Config Units = [-]   
1569        CALL getin_p('XC4_2',xc4_2)
1570        !
1571        !Config Key   = DEW_VEG_POLY_COEFF
1572        !Config Desc  = coefficients of the polynome of degree 5 for the dew
1573        !Config If    = OK_SECHIBA
1574        !Config Def   = 0.887773, 0.205673, 0.110112, 0.014843, 0.000824, 0.000017
1575        !Config Help  =
1576        !Config Units = [-]   
1577        CALL getin_p('DEW_VEG_POLY_COEFF',dew_veg_poly_coeff)
1578        !-
1579        ! slowproc
1580        !-
1581        !
1582        !Config Key   = CLAYFRACTION_DEFAULT
1583        !Config Desc  = default fraction of clay
1584        !Config If    = OK_SECHIBA
1585        !Config Def   = 0.2
1586        !Config Help  =
1587        !Config Units = [-]   
1588        CALL getin_p('CLAYFRACTION_DEFAULT',clayfraction_default)
1589        !
1590        !Config Key   = MIN_VEGFRAC
1591        !Config Desc  = Minimal fraction of mesh a vegetation type can occupy
1592        !Config If    = OK_SECHIBA
1593        !Config Def   = 0.001
1594        !Config Help  =
1595        !Config Units = [-] 
1596        CALL getin_p('MIN_VEGFRAC',min_vegfrac)
1597        !
1598        !Config Key   = STEMPDIAG_BID
1599        !Config Desc  = only needed for an initial LAI if there is no restart file
1600        !Config If    = OK_SECHIBA
1601        !Config Def   = 280.
1602        !Config Help  =
1603        !Config Units = [K]
1604        CALL getin_p('STEMPDIAG_BID',stempdiag_bid)
1605        !
1606        !Config Key   = SOILTYPE_DEFAULT
1607        !Config Desc  = Default soil texture distribution in the following order : sand, loam and clay
1608        !Config If    = OK_SECHIBA
1609        !Config Def   = 0.0, 1.0, 0.0
1610        !Config Help  =
1611        !Config Units = [-]   
1612        CALL getin_p('SOILTYPE_DEFAULT',soiltype_default)
1613        !
1614        first_call =.FALSE.
1615       
1616     ENDIF
1617     
1618   END SUBROUTINE config_sechiba_parameters
1619!
1620!=
1621!
1622
1623!! ================================================================================================================================
1624!! SUBROUTINE   : config_co2_parameters
1625!!
1626!>\BRIEF        This subroutine reads in the configuration file all the parameters
1627!! needed when OK_CO2 is set to true. (ie : when the photosynthesis is activated)
1628!!
1629!! DESCRIPTION  : None
1630!!
1631!! RECENT CHANGE(S): None
1632!!
1633!! MAIN OUTPUT VARIABLE(S): None
1634!!
1635!! REFERENCE(S) :
1636!!
1637!! FLOWCHART    :
1638!! \n
1639!_ ================================================================================================================================
1640
1641   SUBROUTINE config_co2_parameters
1642     
1643     IMPLICIT NONE
1644
1645     !! 0. Variables and parameters declaration
1646
1647     !! 0.4 Local variables
1648     
1649     LOGICAL, SAVE ::  first_call = .TRUE.      !! To keep first call trace (true/false)
1650
1651!_ ================================================================================================================================
1652     
1653     IF(first_call) THEN
1654       
1655        !
1656        !Config Key   = LAI_LEVEL_DEPTH
1657        !Config Desc  =
1658        !Config If    = OK_CO2
1659        !Config Def   = 0.15
1660        !Config Help  =
1661        !Config Units = [-] 
1662        CALL getin_p('LAI_LEVEL_DEPTH',lai_level_depth)
1663        !
1664        !Config Key   = X1_COEF
1665        !Config Desc  = Multiplicative factor in the equation defining kt
1666        !Config If    = OK_CO2
1667        !Config Def   = 0.177
1668        !Config Help  = Multiplicative factor for calculating the pseudo first order rate constant
1669        !Config         of assimilation response to co2 kt
1670        !Config Units = [-] 
1671        CALL getin_p('X1_COEF',x1_coef)
1672        !
1673        !Config Key   = X1_Q10
1674        !Config Desc  = Exponential factor in the equation defining kt
1675        !Config If    = OK_CO2
1676        !Config Def   = 0.069
1677        !Config Help  =
1678        !Config Units = [-] 
1679        CALL getin_p('X1_Q10',x1_Q10)
1680        !
1681        !Config Key   = QUANTUM_YIELD
1682        !Config Desc  =
1683        !Config If    = OK_CO2
1684        !Config Def   = 0.092
1685        !Config Help  =
1686        !Config Units = [-]   
1687        CALL getin_p('QUANTUM_YIELD',quantum_yield)
1688        !
1689        !Config Key   = KT_COEF
1690        !Config Desc  = Multiplicative factor in the equation defining kt
1691        !Config If    = OK_CO2
1692        !Config Def   = 0.7
1693        !Config Help  =
1694        !Config Units = [-]   
1695        CALL getin_p('KT_COEF',kt_coef)
1696        !
1697        !Config Key   = KC_COEF
1698        !Config Desc  = Multiplicative factor for calculating Kc
1699        !Config If    = OK_CO2
1700        !Config Def   = 39.09
1701        !Config Help  = Multiplicative factor for calculating the Michaelis-Menten
1702        !Config         coefficient Kc 
1703        !Config Units = [-] 
1704        CALL getin_p('KC_COEF',kc_coef)
1705        !
1706        !Config Key   = KO_Q10
1707        !Config Desc  = Exponential factor for calculating Kc and Ko
1708        !Config If    = OK_CO2
1709        !Config Def   = 0.085
1710        !Config Help  = Exponential factor for calculating the Michaelis-Menten coefficients
1711        !Config         Kc and Ko
1712        !Config Units = [-] 
1713        CALL getin_p('KO_Q10',Ko_Q10)
1714        !
1715        !Config Key   = OA
1716        !Config Desc  = Intercellular concentration of O2
1717        !Config If    = OK_CO2
1718        !Config Def   = 210000.
1719        !Config Help  =
1720        !Config Units = [ppm] 
1721        CALL getin_p('OA',Oa)
1722        !
1723        !Config Key   = KO_COEF
1724        !Config Desc  = Multiplicative factor for calculating Ko
1725        !Config If    = OK_CO2
1726        !Config Def   = 2.412
1727        !Config Help  =
1728        !Config Units = [-] 
1729        CALL getin_p('KO_COEF',Ko_coef)
1730        !
1731        !Config Key   = CP_0
1732        !Config Desc  = Multiplicative factor for calculating the CO2 compensation point
1733        !Config If    = OK_CO2
1734        !Config Def   = 42.
1735        !Config Help  =
1736        !Config Units = [-] 
1737        CALL getin_p('CP_0',CP_0)
1738        !
1739        !Config Key   = CP_TEMP_COEF
1740        !Config Desc  = Exponential factor for calculating the CO2 compensation point
1741        !Config If    = OK_CO2
1742        !Config Def   = 9.46
1743        !Config Help  =
1744        !Config Units = [-] 
1745        CALL getin_p('CP_TEMP_COEF',cp_temp_coef)
1746        !
1747        !Config Key   = CP_TEMP_REF
1748        !Config Desc  = Reference temperature for the CO2 compensation point CP
1749        !Config If    = OK_CO2
1750        !Config Def   = 25.
1751        !Config Help  =
1752        !Config Units = [C] 
1753        CALL getin_p('CP_TEMP_REF',cp_temp_ref)
1754        !
1755        !Config Key   = RT_COEF
1756        !Config Desc  =
1757        !Config If    = OK_CO2
1758        !Config Def   = 0.8, 1.3
1759        !Config Help  =
1760        !Config Units = [-]   
1761        CALL getin_p('RT_COEF',rt_coef)
1762        !
1763        !Config Key   = VC_COEF
1764        !Config Desc  =
1765        !Config If    = OK_CO2
1766        !Config Def   = 0.39, 0.3
1767        !Config Help  =
1768        !Config Units = [-] 
1769        CALL getin_p('VC_COEF',vc_coef)
1770       
1771        first_call =.FALSE.
1772       
1773     ENDIF
1774     
1775   END SUBROUTINE config_co2_parameters
1776!
1777!=
1778!
1779
1780!! ================================================================================================================================
1781!! SUBROUTINE   : config_hydrolc_parameters
1782!!
1783!>\BRIEF        This subroutine reads in the configuration file all the parameters
1784!! needed when the Choisnel hydrology model is activated.
1785!!
1786!! DESCRIPTION  : None
1787!!
1788!! RECENT CHANGE(S): None
1789!!
1790!! MAIN OUTPUT VARIABLE(S):
1791!!
1792!! REFERENCE(S) :
1793!!
1794!! FLOWCHART    :
1795!! \n
1796!_ ================================================================================================================================
1797
1798   SUBROUTINE config_hydrolc_parameters
1799     
1800     IMPLICIT NONE
1801
1802    !! 0. Variables and parameters declaration
1803
1804    !! 0.4 Local variables
1805
1806     LOGICAL, SAVE ::  first_call = .TRUE.     !! To keep first call trace (true/false)
1807
1808!_ ================================================================================================================================
1809     
1810     IF(first_call) THEN 
1811        !
1812        !Config Key   = QWILT
1813        !Config Desc  = Wilting point
1814        !Config If    = OK_SECHIBA and .NOT.(OK_CWRR)
1815        !Config Def   = 5.0
1816        !Config Help  = Has a numerical role for the moment
1817        !Config Units = [-]
1818        CALL getin_p('QWILT',qwilt)
1819        !
1820        !Config Key   = MIN_RESDIS
1821        !Config Desc  = The minimal size we allow for the upper reservoir
1822        !Config If    = OK_SECHIBA and .NOT.(OK_CWRR)
1823        !Config Def   = 2.e-5
1824        !Config Help  =
1825        !Config Units = [m]
1826        CALL getin_p('MIN_RESDIS',min_resdis)
1827        !
1828        !Config Key   = MIN_DRAIN
1829        !Config Desc  = Diffusion constant for the slow regime
1830        !Config If    = OK_SECHIBA and .NOT.(OK_CWRR)
1831        !Config Def   = 0.001
1832        !Config Help  =
1833        !Config Units = [kg/m^2/dt]
1834        CALL getin_p('MIN_DRAIN',min_drain)
1835        !
1836        !Config Key   = MAX_DRAIN
1837        !Config Desc  = Diffusion constant for the fast regime
1838        !Config If    = OK_SECHIBA and .NOT.(OK_CWRR)
1839        !Config Def   = 0.1
1840        !Config Help  =
1841        !Config Units = [kg/m^2/dt]
1842        CALL getin_p('MAX_DRAIN',max_drain)
1843        !
1844        !Config Key   = EXP_DRAIN
1845        !Config Desc  = The exponential in the diffusion law
1846        !Config If    = OK_SECHIBA and .NOT.(OK_CWRR)
1847        !Config Def   = 1.5
1848        !Config Help  =
1849        !Config Units = [-]
1850        CALL getin_p('EXP_DRAIN',exp_drain)
1851        !
1852        !Config Key   = RSOL_CSTE
1853        !Config Desc  = Constant in the computation of resistance for bare  soil evaporation
1854        !Config If    = OK_SECHIBA and .NOT.(OK_CWRR)
1855        !Config Def   = 33.E3
1856        !Config Help  =
1857        !Config Units = [s/m^2]
1858        CALL getin_p('RSOL_CSTE',rsol_cste)
1859        !
1860        !Config Key   = HCRIT_LITTER
1861        !Config Desc  = Scaling depth for litter humidity
1862        !Config If    = OK_SECHIBA and .NOT.(OK_CWRR)
1863        !Config Def   = 0.08
1864        !Config Help  =
1865        !Config Units = [m]
1866        CALL getin_p('HCRIT_LITTER',hcrit_litter)
1867        !
1868        !Config Key   = HYDROL_OK_HDIFF
1869        !Config Desc  = do horizontal diffusion?
1870        !Config If    = OK_SECHIBA and .NOT.(OK_CWRR) 
1871        !Config Def   = n
1872        !Config Help  = If TRUE, then water can diffuse horizontally between
1873        !Config         the PFTs' water reservoirs.
1874        !Config Units = [FLAG]
1875        CALL getin_p('HYDROL_OK_HDIFF',ok_hdiff)         
1876
1877        first_call =.FALSE.
1878       
1879     ENDIF
1880     
1881   END SUBROUTINE config_hydrolc_parameters
1882   
1883!
1884!=
1885!
1886
1887!! ================================================================================================================================
1888!! SUBROUTINE   : config_hydrol_cwrr_parameters
1889!!
1890!>\BRIEF        This subroutine reads in the configuration file all the parameters
1891!! needed when the 11-layers hydrology model is activated.
1892!!
1893!! DESCRIPTION  : None
1894!!
1895!! RECENT CHANGE(S): None
1896!!
1897!! MAIN OUTPUT VARIABLE(S):
1898!!
1899!! REFERENCE(S) :
1900!!
1901!! FLOWCHART    :
1902!! \n
1903!_ ================================================================================================================================
1904
1905   SUBROUTINE config_hydrol_cwrr_parameters
1906     
1907     IMPLICIT NONE
1908
1909     !! 0. Variables and parameters declaration
1910
1911     !! 0.4 Local variables   
1912
1913     LOGICAL, SAVE ::  first_call = .TRUE.       !! To keep first call trace (true/false)
1914
1915!_ ================================================================================================================================
1916     
1917     IF (first_call) THEN
1918
1919        !
1920        !Config Key   = W_TIME
1921        !Config Desc  = Time weighting for discretisation
1922        !Config If    = OK_CWRR
1923        !Config Def   = 1.
1924        !Config Help  =
1925        !Config Units = [-]
1926        CALL getin_p('W_TIME',w_time)
1927        !
1928        !Config Key   = NVAN
1929        !Config Desc  = Van genuchten coefficient n
1930        !Config If    = OK_CWRR
1931        !Config Def   = 1.89, 1.56, 1.31
1932        !Config Help  =
1933        !Config Units = [-]
1934        CALL getin_p('NVAN',nvan)
1935        !
1936        !Config Key   = AVAN
1937        !Config Desc  = Van genuchten coefficient a
1938        !Config If    = OK_CWRR
1939        !Config Def   = 0.0075, 0.0036, 0.0019
1940        !Config Help  =
1941        !Config Units = [1/mm] 
1942        CALL getin_p('AVAN',avan)
1943        !
1944        !Config Key   = MCR
1945        !Config Desc  = Residual soil water content
1946        !Config If    = OK_CWRR
1947        !Config Def   = 0.065, 0.078, 0.095
1948        !Config Help  =
1949        !Config Units = [mm] 
1950        CALL getin_p('MCR',mcr)
1951        !
1952        !Config Key   = MCS
1953        !Config Desc  = Saturated soil water content
1954        !Config If    = OK_CWRR
1955        !Config Def   = 0.41, 0.43, 0.41
1956        !Config Help  =
1957        !Config Units = [-] 
1958        CALL getin_p('MCS',mcs)     
1959        !
1960        !Config Key   = KS
1961        !Config Desc  = Hydraulic conductivity Saturation
1962        !Config If    = OK_CWRR
1963        !Config Def   = 1060.8, 249.6, 62.4
1964        !Config Help  =
1965        !Config Units = [mm/d]   
1966        CALL getin_p('KS',ks)
1967        !
1968        !Config Key   = PCENT
1969        !Config Desc  = Soil moisture above which transpir is max
1970        !Config If    = OK_CWRR
1971        !Config Def   = 0.5, 0.5, 0.5
1972        !Config Help  =
1973        !Config Units = [-]   
1974        CALL getin_p('PCENT',pcent)
1975        !
1976        !Config Key   = FREE_DRAIN_MAX
1977        !Config Desc  = Max value of the permeability coeff at the bottom of the soil
1978        !Config If    = OK_CWRR
1979        !Config Def   = 1.0, 1.0, 1.0
1980        !Config Help  =
1981        !Config Units = [-]   
1982        CALL getin_p('FREE_DRAIN_MAX',free_drain_max)
1983        !
1984        !Config Key   = MCF
1985        !Config Desc  = Volumetric water content field capacity
1986        !Config If    = OK_CWRR
1987        !Config Def   = 0.32, 0.32, 0.32
1988        !Config Help  =
1989        !Config Units = [-]   
1990        CALL getin_p('MCF',mcf)
1991        !
1992        !Config Key   = MCW
1993        !Config Desc  = Volumetric water content Wilting pt
1994        !Config If    = OK_CWRR
1995        !Config Def   = 0.10, 0.10, 0.10
1996        !Config Help  =
1997        !Config Units = [-]   
1998        CALL getin_p('MCW',mcw)
1999        !
2000        !Config Key   = MC_AWET
2001        !Config Desc  = Vol. wat. cont. above which albedo is cst
2002        !Config If    = OK_CWRR
2003        !Config Def   = 0.25, 0.25, 0.25
2004        !Config Help  =
2005        !Config Units = [-]   
2006        CALL getin_p('MC_AWET',mc_awet)
2007        !
2008        !Config Key   = MC_ADRY
2009        !Config Desc  = Vol. wat. cont. below which albedo is cst
2010        !Config If    = OK_CWRR
2011        !Config Def   = 0.1, 0.1, 0.1
2012        !Config Help  =
2013        !Config Units = [-]   
2014        CALL getin_p('MC_ADRY',mc_adry)
2015         
2016        first_call =.FALSE.
2017       
2018     ENDIF
2019
2020   END SUBROUTINE config_hydrol_cwrr_parameters
2021!
2022!=
2023!
2024
2025!! ================================================================================================================================
2026!! SUBROUTINE   : config_routing_parameters
2027!!
2028!>\BRIEF        This subroutine reads in the configuration file all the parameters
2029!! needed when the routing is activated.
2030!!
2031!! DESCRIPTION  : None
2032!!
2033!! RECENT CHANGE(S): None
2034!!
2035!! MAIN OUTPUT VARIABLE(S):
2036!!
2037!! REFERENCE(S) :
2038!!
2039!! FLOWCHART    :
2040!! \n
2041!_ ================================================================================================================================
2042
2043   SUBROUTINE config_routing_parameters
2044     
2045     IMPLICIT NONE
2046     
2047     !! 0. Variables and parameters declaration
2048     
2049     !! 0.4 Local variables
2050
2051     LOGICAL, SAVE ::  first_call = .TRUE.    !! To keep first call trace (true/false)
2052
2053!_ ================================================================================================================================
2054     
2055     IF(first_call) THEN
2056        !
2057        !Config Key   = CROP_COEF
2058        !Config Desc  = Parameter for the Kassel irrigation parametrization linked to the crops
2059        !Config If    = OK_ROUTING
2060        !Config Def   = 1.5
2061        !Config Help  = Empirical crop coefficient dependent on vegetation characteristics
2062        !Config         according to Kassel irrigation parametrization.
2063        !Config         When potential transpiration is used this coefficient has another interpretation
2064        !Config Units = [-] 
2065        CALL getin_p('CROP_COEF',crop_coef)
2066       
2067        first_call =.FALSE.
2068       
2069     ENDIF
2070     
2071   END SUBROUTINE config_routing_parameters
2072!
2073!=
2074!
2075
2076!! ================================================================================================================================
2077!! SUBROUTINE   : config_stomate_parameters
2078!!
2079!>\BRIEF        This subroutine reads in the configuration file all the parameters
2080!! needed when stomate is activated (ie : when OK_STOMATE is set to true).
2081!!
2082!! DESCRIPTION  : None
2083!!
2084!! RECENT CHANGE(S): None
2085!!
2086!! MAIN OUTPUT VARIABLE(S):
2087!!
2088!! REFERENCE(S) :
2089!!
2090!! FLOWCHART    :
2091!! \n
2092!_ ================================================================================================================================
2093
2094   SUBROUTINE config_stomate_parameters
2095     
2096    IMPLICIT NONE
2097   
2098    !! 0. Variables and parameters declaration
2099
2100    !! 0.4 Local variables   
2101
2102    LOGICAL, SAVE ::  first_call = .TRUE.  !! To keep first call trace (true/false)
2103
2104!_ ================================================================================================================================
2105   
2106    IF(first_call) THEN
2107       !-
2108       ! constraints_parameters
2109       !-
2110       !
2111       !Config Key   = TOO_LONG
2112       !Config Desc  = longest sustainable time without regeneration (vernalization)
2113       !Config If    = OK_STOMATE
2114       !Config Def   = 5.
2115       !Config Help  =
2116       !Config Units = [days]   
2117       CALL getin_p('TOO_LONG',too_long)
2118
2119       !-
2120       ! fire parameters
2121       !-
2122       !
2123       !Config Key   = TAU_FIRE
2124       !Config Desc  = Time scale for memory of the fire index (days). Validated for one year in the DGVM.
2125       !Config If    = OK_STOMATE
2126       !Config Def   = 30.
2127       !Config Help  =
2128       !Config Units = [days]   
2129       CALL getin_p('TAU_FIRE',tau_fire)
2130       !
2131       !Config Key   = LITTER_CRIT
2132       !Config Desc  = Critical litter quantity for fire
2133       !Config If    = OK_STOMATE
2134       !Config Def   = 200.
2135       !Config Help  =
2136       !Config Units = [gC/m^2] 
2137       CALL getin_p('LITTER_CRIT',litter_crit)
2138       !
2139       !Config Key   = FIRE_RESIST_STRUCT
2140       !Config Desc  =
2141       !Config If    = OK_STOMATE
2142       !Config Def   = 0.5
2143       !Config Help  =
2144       !Config Units = [-] 
2145       CALL getin_p('FIRE_RESIST_STRUCT',fire_resist_struct)
2146       !
2147       !
2148       !Config Key   = CO2FRAC
2149       !Config Desc  = What fraction of a burned plant compartment goes into the atmosphere
2150       !Config If    = OK_STOMATE
2151       !Config Def   = 0.95, 0.95, 0., 0.3, 0., 0., 0.95, 0.95
2152       !Config Help  =
2153       !Config Units = [-] 
2154       CALL getin_p('CO2FRAC',co2frac)
2155       !
2156       !Config Key   = BCFRAC_COEFF
2157       !Config Desc  =
2158       !Config If    = OK_STOMATE
2159       !Config Def   = 0.3, 1.3, 88.2
2160       !Config Help  =
2161       !Config Units = [-] 
2162       CALL getin_p('BCFRAC_COEFF',bcfrac_coeff)
2163       !
2164       !Config Key   = FIREFRAC_COEFF
2165       !Config Desc  =
2166       !Config If    = OK_STOMATE
2167       !Config Def   = 0.45, 0.8, 0.6, 0.13
2168       !Config Help  =
2169       !Config Units = [-]   
2170       CALL getin_p('FIREFRAC_COEFF',firefrac_coeff)
2171
2172       !-
2173       ! gap parameters (+ lpj_const_mort)
2174       !-
2175       !
2176       !Config Key   = AVAILABILITY_FACT
2177       !Config Desc  =
2178       !Config If    = OK_STOMATE
2179       !Config Def   = 0.1
2180       !Config Help  =
2181       !Config Units = [-]   
2182       CALL getin_p('AVAILABILITY_FACT', availability_fact) 
2183       !
2184       !Config Key   = REF_GREFF
2185       !Config Desc  =
2186       !Config If    = OK_STOMATE
2187       !Config Def   = 0.035
2188       !Config Help  =
2189       !Config Units = [1/year] 
2190       CALL getin_p('REF_GREFF',ref_greff)
2191       !-
2192       ! allocation parameters
2193       !-
2194       !
2195       !Config Key   = OK_MINRES
2196       !Config Desc  = Do we try to reach a minimum reservoir even if we are severely stressed?
2197       !Config If    = OK_STOMATE
2198       !Config Def   = y
2199       !Config Help  =
2200       !Config Units = [FLAG]
2201       CALL getin_p('OK_MINRES',ok_minres)
2202       !
2203       !Config Key   = TAU_LEAFINIT
2204       !Config Desc  = time to attain the initial foliage using the carbohydrate reserve
2205       !Config If    = OK_STOMATE
2206       !Config Def   = 10.
2207       !Config Help  =
2208       !Config Units = [days] 
2209       CALL getin_p('TAU_LEAFINIT', tau_leafinit)
2210       !
2211       !Config Key   = RESERVE_TIME_TREE
2212       !Config Desc  = maximum time during which reserve is used (trees)
2213       !Config If    = OK_STOMATE
2214       !Config Def   = 30.
2215       !Config Help  =
2216       !Config Units = [days]   
2217       CALL getin_p('RESERVE_TIME_TREE',reserve_time_tree)
2218       !
2219       !Config Key   = RESERVE_TIME_GRASS
2220       !Config Desc  = maximum time during which reserve is used (grasses)
2221       !Config If    = OK_STOMATE
2222       !Config Def   = 20.
2223       !Config Help  =
2224       !Config Units = [days]   
2225       CALL getin_p('RESERVE_TIME_GRASS',reserve_time_grass)
2226       !
2227       !Config Key   = R0
2228       !Config Desc  = Standard root allocation
2229       !Config If    = OK_STOMATE
2230       !Config Def   = 0.3
2231       !Config Help  =
2232       !Config Units = [-] 
2233       CALL getin_p('R0',R0)
2234       !
2235       !Config Key   = S0
2236       !Config Desc  = Standard sapwood allocation
2237       !Config If    = OK_STOMATE
2238       !Config Def   = 0.3
2239       !Config Help  =
2240       !Config Units = [-]   
2241       CALL getin_p('S0',S0)
2242       !
2243       !Config Key   = F_FRUIT
2244       !Config Desc  = Standard fruit allocation
2245       !Config If    = OK_STOMATE
2246       !Config Def   = 0.1
2247       !Config Help  =
2248       !Config Units = [-]   
2249       CALL getin_p('F_FRUIT',f_fruit)
2250       !
2251       !Config Key   = ALLOC_SAP_ABOVE_GRASS
2252       !Config Desc  = fraction of sapwood allocation above ground
2253       !Config If    = OK_STOMATE
2254       !Config Def   = 1.0
2255       !Config Help  =
2256       !Config Units = [-]   
2257       CALL getin_p('ALLOC_SAP_ABOVE_GRASS',alloc_sap_above_grass)
2258       !
2259       !Config Key   = MIN_LTOLSR
2260       !Config Desc  = extrema of leaf allocation fraction
2261       !Config If    = OK_STOMATE
2262       !Config Def   = 0.2
2263       !Config Help  =
2264       !Config Units = [-]   
2265       CALL getin_p('MIN_LTOLSR',min_LtoLSR)
2266       !
2267       !Config Key   = MAX_LTOLSR
2268       !Config Desc  = extrema of leaf allocation fraction
2269       !Config If    = OK_STOMATE
2270       !Config Def   = 0.5
2271       !Config Help  =
2272       !Config Units = [-]   
2273       CALL getin_p('MAX_LTOLSR',max_LtoLSR)
2274       !
2275       !Config Key   = Z_NITROGEN
2276       !Config Desc  = scaling depth for nitrogen limitation
2277       !Config If    = OK_STOMATE
2278       !Config Def   = 0.2
2279       !Config Help  =
2280       !Config Units = [m] 
2281       CALL getin_p('Z_NITROGEN',z_nitrogen)
2282       !
2283       !Config Key   = LAI_MAX_TO_HAPPY
2284       !Config Desc  =
2285       !Config If    = OK_STOMATE
2286       !Config Def   = 0.5
2287       !Config Help  =
2288       !Config Units = [-] 
2289       CALL getin_p('LAI_MAX_TO_HAPPY',lai_max_to_happy)
2290       !
2291       !Config Key   = NLIM_TREF
2292       !Config Desc  =
2293       !Config If    = OK_STOMATE
2294       !Config Def   = 25.
2295       !Config Help  =
2296       !Config Units = [C] 
2297       CALL getin_p('NLIM_TREF',Nlim_tref) 
2298 
2299       !-
2300       ! data parameters
2301       !-
2302       !
2303       !Config Key   = PIPE_TUNE1
2304       !Config Desc  = crown area = pipe_tune1. stem diameter**(1.6) (Reinicke's theory)
2305       !Config If    = OK_STOMATE
2306       !Config Def   = 100.0
2307       !Config Help  =
2308       !Config Units = [-]   
2309       CALL getin_p('PIPE_TUNE1',pipe_tune1)
2310       !
2311       !Config Key   = PIPE_TUNE2
2312       !Config Desc  = height=pipe_tune2 * diameter**pipe_tune3
2313       !Config If    = OK_STOMATE
2314       !Config Def   = 40.0
2315       !Config Help  =
2316       !Config Units = [-]     
2317       CALL getin_p('PIPE_TUNE2',pipe_tune2) 
2318        !
2319       !Config Key   = PIPE_TUNE3
2320       !Config Desc  = height=pipe_tune2 * diameter**pipe_tune3
2321       !Config If    = OK_STOMATE
2322       !Config Def   = 0.5
2323       !Config Help  =
2324       !Config Units = [-]   
2325       CALL getin_p('PIPE_TUNE3',pipe_tune3)
2326       !
2327       !Config Key   = PIPE_TUNE4
2328       !Config Desc  = needed for stem diameter
2329       !Config If    = OK_STOMATE
2330       !Config Def   = 0.3
2331       !Config Help  =
2332       !Config Units = [-] 
2333       CALL getin_p('PIPE_TUNE4',pipe_tune4)
2334       !
2335       !Config Key   = PIPE_DENSITY
2336       !Config Desc  = Density
2337       !Config If    = OK_STOMATE
2338       !Config Def   = 2.e5
2339       !Config Help  =
2340       !Config Units = [-] 
2341       CALL getin_p('PIPE_DENSITY',pipe_density)
2342       !
2343       !Config Key   = PIPE_K1
2344       !Config Desc  =
2345       !Config If    = OK_STOMATE
2346       !Config Def   = 8.e3
2347       !Config Help  =
2348       !Config Units = [-]   
2349       CALL getin_p('PIPE_K1',pipe_k1)
2350       !
2351       !Config Key   = PIPE_TUNE_EXP_COEFF
2352       !Config Desc  = pipe tune exponential coeff
2353       !Config If    = OK_STOMATE
2354       !Config Def   = 1.6
2355       !Config Help  =
2356       !Config Units = [-]   
2357       CALL getin_p('PIPE_TUNE_EXP_COEFF',pipe_tune_exp_coeff)
2358       !
2359       !
2360       !Config Key   = PRECIP_CRIT
2361       !Config Desc  = minimum precip
2362       !Config If    = OK_STOMATE
2363       !Config Def   = 100.
2364       !Config Help  =
2365       !Config Units = [mm/year] 
2366       CALL getin_p('PRECIP_CRIT',precip_crit)
2367       !
2368       !Config Key   = GDD_CRIT_ESTAB
2369       !Config Desc  = minimum gdd for establishment of saplings
2370       !Config If    = OK_STOMATE
2371       !Config Def   = 150.
2372       !Config Help  =
2373       !Config Units = [-] 
2374       CALL getin_p('GDD_CRIT_ESTAB',gdd_crit_estab)
2375        !
2376       !Config Key   = FPC_CRIT
2377       !Config Desc  = critical fpc, needed for light competition and establishment
2378       !Config If    = OK_STOMATE
2379       !Config Def   = 0.95
2380       !Config Help  =
2381       !Config Units = [-] 
2382       CALL getin_p('FPC_CRIT',fpc_crit)
2383       !
2384       !Config Key   = ALPHA_GRASS
2385       !Config Desc  = sapling characteristics : alpha's
2386       !Config If    = OK_STOMATE
2387       !Config Def   = 0.5
2388       !Config Help  =
2389       !Config Units = [-]   
2390       CALL getin_p('ALPHA_GRASS',alpha_grass)
2391       !
2392       !Config Key   = ALPHA_TREE
2393       !Config Desc  = sapling characteristics : alpha's
2394       !Config If    = OK_STOMATE
2395       !Config Def   = 1.
2396       !Config Help  =
2397       !Config Units = [-]   
2398       CALL getin_p('ALPHA_TREE',alpha_tree)
2399       !-
2400       !
2401       !Config Key   = MASS_RATIO_HEART_SAP
2402       !Config Desc  = mass ratio (heartwood+sapwood)/sapwood
2403       !Config If    = OK_STOMATE
2404       !Config Def   = 3.
2405       !Config Help  =
2406       !Config Units = [-]   
2407       CALL getin_p('MASS_RATIO_HEART_SAP',mass_ratio_heart_sap)
2408       !
2409       !Config Key   = FRAC_GROWTHRESP
2410       !Config Desc  = fraction of GPP which is lost as growth respiration
2411       !Config If    = OK_STOMATE
2412       !Config Def   = 0.28
2413       !Config Help  =
2414       !Config Units = [-]
2415       CALL getin_p('FRAC_GROWTHRESP',frac_growthresp)
2416       !
2417       !Config Key   = TAU_HUM_MONTH
2418       !Config Desc  = time scales for phenology and other processes
2419       !Config If    = OK_STOMATE
2420       !Config Def   = 20.
2421       !Config Help  =
2422       !Config Units = [days] 
2423       CALL getin_p('TAU_HUM_MONTH',tau_hum_month)
2424       !
2425       !Config Key   = TAU_HUM_WEEK
2426       !Config Desc  = time scales for phenology and other processes
2427       !Config If    = OK_STOMATE
2428       !Config Def   = 7.
2429       !Config Help  =
2430       !Config Units = [days]   
2431       CALL getin_p('TAU_HUM_WEEK',tau_hum_week)
2432       !
2433       !Config Key   = TAU_T2M_MONTH
2434       !Config Desc  = time scales for phenology and other processes
2435       !Config If    = OK_STOMATE
2436       !Config Def   = 20.
2437       !Config Help  =
2438       !Config Units = [days]     
2439       CALL getin_p('TAU_T2M_MONTH',tau_t2m_month)
2440       !
2441       !Config Key   = TAU_T2M_WEEK
2442       !Config Desc  = time scales for phenology and other processes
2443       !Config If    = OK_STOMATE
2444       !Config Def   = 7.
2445       !Config Help  =
2446       !Config Units = [days]   
2447       CALL getin_p('TAU_T2M_WEEK',tau_t2m_week)
2448       !
2449       !Config Key   = TAU_TSOIL_MONTH
2450       !Config Desc  = time scales for phenology and other processes
2451       !Config If    = OK_STOMATE
2452       !Config Def   = 20.
2453       !Config Help  =
2454       !Config Units = [days]     
2455       CALL getin_p('TAU_TSOIL_MONTH',tau_tsoil_month)
2456       !
2457       !Config Key   = TAU_SOILHUM_MONTH
2458       !Config Desc  = time scales for phenology and other processes
2459       !Config If    = OK_STOMATE
2460       !Config Def   = 20.
2461       !Config Help  =
2462       !Config Units = [days]   
2463       CALL getin_p('TAU_SOILHUM_MONTH',tau_soilhum_month)
2464       !
2465       !Config Key   = TAU_GPP_WEEK
2466       !Config Desc  = time scales for phenology and other processes
2467       !Config If    = OK_STOMATE
2468       !Config Def   = 7.
2469       !Config Help  =
2470       !Config Units = [days]   
2471       CALL getin_p('TAU_GPP_WEEK',tau_gpp_week)
2472       !
2473       !Config Key   = TAU_GDD
2474       !Config Desc  = time scales for phenology and other processes
2475       !Config If    = OK_STOMATE
2476       !Config Def   = 40.
2477       !Config Help  =
2478       !Config Units = [days]   
2479       CALL getin_p('TAU_GDD',tau_gdd)
2480       !
2481       !Config Key   = TAU_NGD
2482       !Config Desc  = time scales for phenology and other processes
2483       !Config If    = OK_STOMATE
2484       !Config Def   = 50.
2485       !Config Help  =
2486       !Config Units = [days]   
2487       CALL getin_p('TAU_NGD',tau_ngd)
2488       !
2489       !Config Key   = COEFF_TAU_LONGTERM
2490       !Config Desc  = time scales for phenology and other processes
2491       !Config If    = OK_STOMATE
2492       !Config Def   = 3.
2493       !Config Help  =
2494       !Config Units = [days]   
2495       CALL getin_p('COEFF_TAU_LONGTERM',coeff_tau_longterm)
2496       !-
2497       !
2498       !Config Key   = BM_SAPL_CARBRES
2499       !Config Desc  =
2500       !Config If    = OK_STOMATE
2501       !Config Def   = 5.
2502       !Config Help  =
2503       !Config Units = [-]   
2504       CALL getin_p('BM_SAPL_CARBRES',bm_sapl_carbres)
2505       !
2506       !Config Key   = BM_SAPL_SAPABOVE
2507       !Config Desc  =
2508       !Config If    = OK_STOMATE
2509       !Config Def   = 0.5
2510       !Config Help  =
2511       !Config Units = [-]   
2512       CALL getin_p('BM_SAPL_SAPABOVE',bm_sapl_sapabove)
2513       !
2514       !Config Key   = BM_SAPL_HEARTABOVE
2515       !Config Desc  =
2516       !Config If    = OK_STOMATE
2517       !Config Def   = 2.
2518       !Config Help  =
2519       !Config Units = [-]   
2520       CALL getin_p('BM_SAPL_HEARTABOVE',bm_sapl_heartabove)
2521       !
2522       !Config Key   = BM_SAPL_HEARTBELOW
2523       !Config Desc  =
2524       !Config If    = OK_STOMATE
2525       !Config Def   = 2.
2526       !Config Help  =
2527       !Config Units = [-]   
2528       CALL getin_p('BM_SAPL_HEARTBELOW',bm_sapl_heartbelow)
2529       !
2530       !Config Key   = INIT_SAPL_MASS_LEAF_NAT
2531       !Config Desc  =
2532       !Config If    = OK_STOMATE
2533       !Config Def   = 0.1
2534       !Config Help  =
2535       !Config Units = [-]   
2536       CALL getin_p('INIT_SAPL_MASS_LEAF_NAT',init_sapl_mass_leaf_nat)
2537       !
2538       !Config Key   = INIT_SAPL_MASS_LEAF_AGRI
2539       !Config Desc  =
2540       !Config If    = OK_STOMATE
2541       !Config Def   = 1.
2542       !Config Help  =
2543       !Config Units = [-]   
2544       CALL getin_p('INIT_SAPL_MASS_LEAF_AGRI',init_sapl_mass_leaf_agri)
2545       !
2546       !Config Key   = INIT_SAPL_MASS_CARBRES
2547       !Config Desc  =
2548       !Config If    = OK_STOMATE
2549       !Config Def   = 5.
2550       !Config Help  =
2551       !Config Units = [-]   
2552       CALL getin_p('INIT_SAPL_MASS_CARBRES',init_sapl_mass_carbres)
2553       !
2554       !Config Key   = INIT_SAPL_MASS_ROOT
2555       !Config Desc  =
2556       !Config If    = OK_STOMATE
2557       !Config Def   = 0.1
2558       !Config Help  =
2559       !Config Units = [-]   
2560       CALL getin_p('INIT_SAPL_MASS_ROOT',init_sapl_mass_root)
2561       !
2562       !Config Key   = INIT_SAPL_MASS_FRUIT
2563       !Config Desc  =
2564       !Config If    = OK_STOMATE
2565       !Config Def   = 0.3
2566       !Config Help  =
2567       !Config Units = [-]   
2568       CALL getin_p('INIT_SAPL_MASS_FRUIT',init_sapl_mass_fruit)
2569       !
2570       !Config Key   = CN_SAPL_INIT
2571       !Config Desc  =
2572       !Config If    = OK_STOMATE
2573       !Config Def   = 0.5
2574       !Config Help  =
2575       !Config Units = [-]   
2576       CALL getin_p('CN_SAPL_INIT',cn_sapl_init)
2577       !
2578       !Config Key   = MIGRATE_TREE
2579       !Config Desc  =
2580       !Config If    = OK_STOMATE
2581       !Config Def   = 10000.
2582       !Config Help  =
2583       !Config Units = [m/year]   
2584       CALL getin_p('MIGRATE_TREE',migrate_tree)
2585       !
2586       !Config Key   = MIGRATE_GRASS
2587       !Config Desc  =
2588       !Config If    = OK_STOMATE
2589       !Config Def   = 10000.
2590       !Config Help  =
2591       !Config Units = [m/year]   
2592       CALL getin_p('MIGRATE_GRASS',migrate_grass)
2593       !
2594       !Config Key   = LAI_INITMIN_TREE
2595       !Config Desc  =
2596       !Config If    = OK_STOMATE
2597       !Config Def   = 0.3
2598       !Config Help  =
2599       !Config Units = [m^2/m^2] 
2600       CALL getin_p('LAI_INITMIN_TREE',lai_initmin_tree)
2601       !
2602       !Config Key   = LAI_INITMIN_GRASS
2603       !Config Desc  =
2604       !Config If    = OK_STOMATE
2605       !Config Def   = 0.1
2606       !Config Help  =
2607       !Config Units = [m^2/m^2]   
2608       CALL getin_p('LAI_INITMIN_GRASS',lai_initmin_grass)
2609       !
2610       !Config Key   = DIA_COEFF
2611       !Config Desc  =
2612       !Config If    = OK_STOMATE
2613       !Config Def   = 4., 0.5
2614       !Config Help  =
2615       !Config Units = [-]   
2616       CALL getin_p('DIA_COEFF',dia_coeff)
2617       !
2618       !Config Key   = MAXDIA_COEFF
2619       !Config Desc  =
2620       !Config If    = OK_STOMATE
2621       !Config Def   = 100., 0.01
2622       !Config Help  =
2623       !Config Units = [-]   
2624       CALL getin_p('MAXDIA_COEFF',maxdia_coeff)
2625       !
2626       !Config Key   = BM_SAPL_LEAF
2627       !Config Desc  =
2628       !Config If    = OK_STOMATE
2629       !Config Def   = 4., 4., 0.8, 5.
2630       !Config Help  =
2631       !Config Units = [-] 
2632       CALL getin_p('BM_SAPL_LEAF',bm_sapl_leaf)
2633
2634       !-
2635       ! litter parameters
2636       !-
2637       !
2638       !Config Key   = METABOLIC_REF_FRAC
2639       !Config Desc  =
2640       !Config If    = OK_STOMATE
2641       !Config Def   = 0.85 
2642       !Config Help  =
2643       !Config Units = [-]
2644       CALL getin_p('METABOLIC_REF_FRAC',metabolic_ref_frac)
2645       !
2646       !Config Key   = Z_DECOMP
2647       !Config Desc  = scaling depth for soil activity
2648       !Config If    = OK_STOMATE
2649       !Config Def   = 0.2
2650       !Config Help  =
2651       !Config Units = [m]   
2652       CALL getin_p('Z_DECOMP',z_decomp)
2653       !
2654       !Config Key   = CN
2655       !Config Desc  = C/N ratio
2656       !Config If    = OK_STOMATE
2657       !Config Def   = 40., 40., 40., 40., 40., 40., 40., 40.
2658       !Config Help  =
2659       !Config Units = [-] 
2660       CALL getin_p('CN',CN)
2661       !
2662       !Config Key   = LC
2663       !Config Desc  = Lignine/C ratio of the different plant parts
2664       !Config If    = OK_STOMATE
2665       !Config Def   = 0.22, 0.35, 0.35, 0.35, 0.35, 0.22, 0.22, 0.22
2666       !Config Help  =
2667       !Config Units = [-]   
2668       CALL getin_p('LC',LC)
2669       !
2670       !Config Key   = FRAC_SOIL_STRUCT_AA
2671       !Config Desc  = frac_soil(istructural,iactive,iabove)
2672       !Config If    = OK_STOMATE
2673       !Config Def   = 0.55
2674       !Config Help  =
2675       !Config Units = [-]
2676       CALL getin_p('FRAC_SOIL_STRUCT_AA',frac_soil_struct_aa)
2677       !
2678       !Config Key   = FRAC_SOIL_STRUCT_A
2679       !Config Desc  = frac_soil(istructural,iactive,ibelow)
2680       !Config If    = OK_STOMATE
2681       !Config Def   = 0.45
2682       !Config Help  =
2683       !Config Units = [-]
2684       CALL getin_p('FRAC_SOIL_STRUCT_AB',frac_soil_struct_ab)
2685       !
2686       !Config Key   = FRAC_SOIL_STRUCT_SA
2687       !Config Desc  = frac_soil(istructural,islow,iabove)
2688       !Config If    = OK_STOMATE
2689       !Config Def   = 0.7 
2690       !Config Help  =
2691       !Config Units = [-]   
2692       CALL getin_p('FRAC_SOIL_STRUCT_SA',frac_soil_struct_sa)
2693       !
2694       !Config Key   = FRAC_SOIL_STRUCT_SB
2695       !Config Desc  = frac_soil(istructural,islow,ibelow)
2696       !Config If    = OK_STOMATE
2697       !Config Def   = 0.7 
2698       !Config Help  =
2699       !Config Units = [-]   
2700       CALL getin_p('FRAC_SOIL_STRUCT_SB',frac_soil_struct_sb)
2701       !
2702       !Config Key   = FRAC_SOIL_METAB_AA
2703       !Config Desc  = frac_soil(imetabolic,iactive,iabove)
2704       !Config If    = OK_STOMATE
2705       !Config Def   = 0.45
2706       !Config Help  =
2707       !Config Units = [-]   
2708       CALL getin_p('FRAC_SOIL_METAB_AA',frac_soil_metab_aa)
2709       !
2710       !Config Key   = FRAC_SOIL_METAB_AB
2711       !Config Desc  = frac_soil(imetabolic,iactive,ibelow)
2712       !Config If    = OK_STOMATE
2713       !Config Def   = 0.45 
2714       !Config Help  =
2715       !Config Units = [-]   
2716       CALL getin_p('FRAC_SOIL_METAB_AB',frac_soil_metab_ab)
2717       !
2718       !
2719       !Config Key   = METABOLIC_LN_RATIO
2720       !Config Desc  =
2721       !Config If    = OK_STOMATE
2722       !Config Def   = 0.018 
2723       !Config Help  =
2724       !Config Units = [-]   
2725       CALL getin_p('METABOLIC_LN_RATIO',metabolic_LN_ratio) 
2726       !
2727       !Config Key   = TAU_METABOLIC
2728       !Config Desc  =
2729       !Config If    = OK_STOMATE
2730       !Config Def   = 0.066
2731       !Config Help  =
2732       !Config Units = [days]
2733       CALL getin_p('TAU_METABOLIC',tau_metabolic)
2734       !
2735       !Config Key   = TAU_STRUCT
2736       !Config Desc  =
2737       !Config If    = OK_STOMATE
2738       !Config Def   = 0.245
2739       !Config Help  =
2740       !Config Units = [days]
2741       CALL getin_p('TAU_STRUCT',tau_struct)
2742       !
2743       !Config Key   = SOIL_Q10
2744       !Config Desc  =
2745       !Config If    = OK_STOMATE
2746       !Config Def   = 0.69 (=ln2)
2747       !Config Help  =
2748       !Config Units = [-]
2749       CALL getin_p('SOIL_Q10',soil_Q10)
2750       !
2751       !Config Key   = TSOIL_REF
2752       !Config Desc  =
2753       !Config If    = OK_STOMATE
2754       !Config Def   = 30.
2755       !Config Help  =
2756       !Config Units = [C]   
2757       CALL getin_p('TSOIL_REF',tsoil_ref)
2758       !
2759       !Config Key   = LITTER_STRUCT_COEF
2760       !Config Desc  =
2761       !Config If    = OK_STOMATE
2762       !Config Def   = 3.
2763       !Config Help  =
2764       !Config Units = [-]   
2765       CALL getin_p('LITTER_STRUCT_COEF',litter_struct_coef)
2766       !
2767       !Config Key   = MOIST_COEFF
2768       !Config Desc  =
2769       !Config If    = OK_STOMATE
2770       !Config Def   = 1.1, 2.4, 0.29
2771       !Config Help  =
2772       !Config Units = [-]   
2773       CALL getin_p('MOIST_COEFF',moist_coeff)
2774
2775       !-
2776       ! lpj parameters
2777       !-
2778       !
2779       !Config Key   = FRAC_TURNOVER_DAILY
2780       !Config Desc  =
2781       !Config If    = OK_STOMATE
2782       !Config Def   = 0.55
2783       !Config Help  =
2784       !Config Units = [-]
2785       CALL getin_p('FRAC_TURNOVER_DAILY',frac_turnover_daily)   
2786
2787       !-
2788       ! npp parameters
2789       !-
2790       !
2791       !Config Key   = TAX_MAX
2792       !Config Desc  = maximum fraction of allocatable biomass used for maintenance respiration
2793       !Config If    = OK_STOMATE
2794       !Config Def   = 0.8
2795       !Config Help  =
2796       !Config Units = [-]   
2797       CALL getin_p('TAX_MAX',tax_max) 
2798
2799       !-
2800       ! phenology parameters
2801       !-
2802       !
2803       !Config Key   = ALWAYS_INIT
2804       !Config Desc  = take carbon from atmosphere if carbohydrate reserve too small?
2805       !Config If    = OK_STOMATE
2806       !Config Def   = n
2807       !Config Help  =
2808       !Config Units = [-]   
2809       CALL getin_p('ALWAYS_INIT',always_init)
2810       !
2811       !Config Key   = MIN_GROWTHINIT_TIME
2812       !Config Desc  = minimum time since last beginning of a growing season
2813       !Config If    = OK_STOMATE
2814       !Config Def   = 300.
2815       !Config Help  =
2816       !Config Units = [days] 
2817       CALL getin_p('MIN_GROWTHINIT_TIME',min_growthinit_time)
2818       !
2819       !Config Key   = MOIAVAIL_ALWAYS_TREE
2820       !Config Desc  = moisture availability above which moisture tendency doesn't matter
2821       !Config If    = OK_STOMATE
2822       !Config Def   = 1.0
2823       !Config Help  =
2824       !Config Units = [-]   
2825       CALL getin_p('MOIAVAIL_ALWAYS_TREE',moiavail_always_tree)
2826       !
2827       !Config Key   = MOIAVAIL_ALWAYS_GRASS
2828       !Config Desc  = moisture availability above which moisture tendency doesn't matter
2829       !Config If    = OK_STOMATE
2830       !Config Def   = 0.6
2831       !Config Help  =
2832       !Config Units = [-]   
2833       CALL getin_p('MOIAVAIL_ALWAYS_GRASS',moiavail_always_grass)
2834       !
2835       !Config Key   = T_ALWAYS_ADD
2836       !Config Desc  = monthly temp. above which temp. tendency doesn't matter
2837       !Config If    = OK_STOMATE
2838       !Config Def   = 10.
2839       !Config Help  =
2840       !Config Units = [C]   
2841       CALL getin_p('T_ALWAYS_ADD',t_always_add)
2842       !
2843       !
2844       !Config Key   = GDDNCD_REF
2845       !Config Desc  =
2846       !Config If    = OK_STOMATE
2847       !Config Def   = 603.
2848       !Config Help  =
2849       !Config Units = [-]   
2850       CALL getin_p('GDDNCD_REF',gddncd_ref)
2851       !
2852       !Config Key   = GDDNCD_CURVE
2853       !Config Desc  =
2854       !Config If    = OK_STOMATE
2855       !Config Def   = 0.0091
2856       !Config Help  =
2857       !Config Units = [-] 
2858       CALL getin_p('GDDNCD_CURVE',gddncd_curve)
2859       !
2860       !Config Key   = GDDNCD_OFFSET
2861       !Config Desc  =
2862       !Config If    = OK_STOMATE
2863       !Config Def   = 64.
2864       !Config Help  =
2865       !Config Units = [-] 
2866       CALL getin_p('GDDNCD_OFFSET',gddncd_offset)
2867       !-
2868       ! prescribe parameters
2869       !-
2870       !
2871       !Config Key   = BM_SAPL_RESCALE
2872       !Config Desc  =
2873       !Config If    = OK_STOMATE
2874       !Config Def   = 40.
2875       !Config Help  =
2876       !Config Units = [-] 
2877       CALL getin_p('BM_SAPL_RESCALE',bm_sapl_rescale)
2878
2879       !-
2880       ! respiration parameters
2881       !-
2882       !
2883       !Config Key   = MAINT_RESP_MIN_VMAX
2884       !Config Desc  =
2885       !Config If    = OK_STOMATE
2886       !Config Def   = 0.3
2887       !Config Help  =
2888       !Config Units = [-] 
2889       CALL getin_p('MAINT_RESP_MIN_VMAX',maint_resp_min_vmax) 
2890       !
2891       !Config Key   = MAINT_RESP_COEFF
2892       !Config Desc  =
2893       !Config If    = OK_STOMATE
2894       !Config Def   = 1.4
2895       !Config Help  =
2896       !Config Units = [-]
2897       CALL getin_p('MAINT_RESP_COEFF',maint_resp_coeff)
2898
2899       !-
2900       ! soilcarbon parameters
2901       !-
2902       !
2903       !Config Key   = FRAC_CARB_AP
2904       !Config Desc  = frac carb coefficients from active pool: depends on clay content
2905       !Config if    = OK_STOMATE
2906       !Config Def   = 0.004
2907       !Config Help  = fraction of the active pool going into the passive pool
2908       !Config Units = [-]
2909       CALL getin_p('FRAC_CARB_AP',frac_carb_ap) 
2910       !
2911       !Config Key   = FRAC_CARB_SA
2912       !Config Desc  = frac_carb_coefficients from slow pool
2913       !Config if    = OK_STOMATE
2914       !Config Def   = 0.42
2915       !Config Help  = fraction of the slow pool going into the active pool
2916       !Config Units = [-]
2917       CALL getin_p('FRAC_CARB_SA',frac_carb_sa)
2918       !
2919       !Config Key   = FRAC_CARB_SP
2920       !Config Desc  = frac_carb_coefficients from slow pool
2921       !Config if    = OK_STOMATE
2922       !Config Def   = 0.03
2923       !Config Help  = fraction of the slow pool going into the passive pool
2924       !Config Units = [-]
2925       CALL getin_p('FRAC_CARB_SP',frac_carb_sp)
2926       !
2927       !Config Key   = FRAC_CARB_PA
2928       !Config Desc  = frac_carb_coefficients from passive pool
2929       !Config if    = OK_STOMATE
2930       !Config Def   = 0.45
2931       !Config Help  = fraction of the passive pool going into the active pool
2932       !Config Units = [-]
2933       CALL getin_p('FRAC_CARB_PA',frac_carb_pa)
2934       !
2935       !Config Key   = FRAC_CARB_PS
2936       !Config Desc  = frac_carb_coefficients from passive pool
2937       !Config if    = OK_STOMATE
2938       !Config Def   = 0.0
2939       !Config Help  = fraction of the passive pool going into the slow pool
2940       !Config Units = [-]
2941       CALL getin_p('FRAC_CARB_PS',frac_carb_ps)
2942       !
2943       !Config Key   = ACTIVE_TO_PASS_CLAY_FRAC
2944       !Config Desc  =
2945       !Config if    = OK_STOMATE
2946       !Config Def   = 0.68 
2947       !Config Help  =
2948       !Config Units = [-]
2949       CALL getin_p('ACTIVE_TO_PASS_CLAY_FRAC',active_to_pass_clay_frac)
2950       !
2951       !Config Key   = CARBON_TAU_IACTIVE
2952       !Config Desc  = residence times in carbon pools
2953       !Config if    = OK_STOMATE
2954       !Config Def   = 0.149
2955       !Config Help  =
2956       !Config Units =  [days]
2957       CALL getin_p('CARBON_TAU_IACTIVE',carbon_tau_iactive)
2958       !
2959       !Config Key   = CARBON_TAU_ISLOW
2960       !Config Desc  = residence times in carbon pools
2961       !Config if    = OK_STOMATE
2962       !Config Def   = 5.48
2963       !Config Help  =
2964       !Config Units = [days]
2965       CALL getin_p('CARBON_TAU_ISLOW',carbon_tau_islow)
2966       !
2967       !Config Key   = CARBON_TAU_IPASSIVE
2968       !Config Desc  = residence times in carbon pools
2969       !Config if    = OK_STOMATE
2970       !Config Def   = 241.
2971       !Config Help  = residence time in the passive pool
2972       !Config Units = [days]
2973       CALL getin_p('CARBON_TAU_IPASSIVE',carbon_tau_ipassive)
2974       !
2975       !Config Key   = FLUX_TOT_COEFF
2976       !Config Desc  =
2977       !Config if    = OK_STOMATE
2978       !Config Def   = 1.2, 1.4,.75
2979       !Config Help  =
2980       !Config Units = [days]
2981       CALL getin_p('FLUX_TOT_COEFF',flux_tot_coeff)
2982
2983       !-
2984       ! turnover parameters
2985       !-
2986       !
2987       !Config Key   = NEW_TURNOVER_TIME_REF
2988       !Config Desc  =
2989       !Config If    = OK_STOMATE
2990       !Config Def   = 20.
2991       !Config Help  =
2992       !Config Units = [days] 
2993       CALL getin_p('NEW_TURNOVER_TIME_REF',new_turnover_time_ref)
2994       !
2995       !Config Key   = DT_TURNOVER_TIME
2996       !Config Desc  =
2997       !Config If    = OK_STOMATE
2998       !Config Def   = 10.
2999       !Config Help  =
3000       !Config Units = [days] 
3001       CALL getin_p('DT_TURNOVER_TIME',dt_turnover_time)
3002       !
3003       !Config Key   = LEAF_AGE_CRIT_TREF
3004       !Config Desc  =
3005       !Config If    = OK_STOMATE
3006       !Config Def   = 20.
3007       !Config Help  =
3008       !Config Units = [days] 
3009       CALL getin_p('LEAF_AGE_CRIT_TREF',leaf_age_crit_tref)
3010       !
3011       !Config Key   = LEAF_AGE_CRIT_COEFF
3012       !Config Desc  =
3013       !Config If    = OK_STOMATE
3014       !Config Def   = 1.5, 0.75, 10.
3015       !Config Help  =
3016       !Config Units = [-]
3017       CALL getin_p('LEAF_AGE_CRIT_COEFF',leaf_age_crit_coeff)
3018
3019       !-
3020       ! vmax parameters
3021       !-
3022       !
3023       !Config Key   = VMAX_OFFSET
3024       !Config Desc  = offset (minimum relative vcmax)
3025       !Config If    = OK_STOMATE
3026       !Config Def   = 0.3
3027       !Config Help  = offset (minimum vcmax/vmax_opt)
3028       !Config Units = [-] 
3029       CALL getin_p('VMAX_OFFSET',vmax_offset)
3030       !
3031       !Config Key   = LEAFAGE_FIRSTMAX
3032       !Config Desc  = leaf age at which vmax attains vcmax_opt (in fraction of critical leaf age)
3033       !Config If    = OK_STOMATE
3034       !Config Def   = 0.03
3035       !Config Help  = relative leaf age at which vmax attains vcmax_opt
3036       !Config Units = [-]
3037       CALL getin_p('LEAFAGE_FIRSTMAX',leafage_firstmax)
3038       !
3039       !Config Key   = LEAFAGE_LASTMAX
3040       !Config Desc  = leaf age at which vmax falls below vcmax_opt (in fraction of critical leaf age)
3041       !Config If    = OK_STOMATE
3042       !Config Def   = 0.5
3043       !Config Help  = relative leaf age at which vmax falls below vcmax_opt
3044       !Config Units = [-] 
3045       CALL getin_p('LEAFAGE_LASTMAX',leafage_lastmax)
3046       !
3047       !Config Key   = LEAFAGE_OLD
3048       !Config Desc  = leaf age at which vmax attains its minimum (in fraction of critical leaf age)
3049       !Config If    = OK_STOMATE
3050       !Config Def   = 1.
3051       !Config Help  = relative leaf age at which vmax attains its minimum
3052       !Config Units = [-] 
3053       CALL getin_p('LEAFAGE_OLD',leafage_old)
3054
3055       !-
3056       ! season parameters
3057       !-
3058       !
3059       !Config Key   = GPPFRAC_DORMANCE
3060       !Config Desc  = rapport maximal GPP/GGP_max pour dormance
3061       !Config If    = OK_STOMATE
3062       !Config Def   = 0.2
3063       !Config Help  =
3064       !Config Units = [-]
3065       CALL getin_p('GPPFRAC_DORMANCE',gppfrac_dormance)
3066       !
3067       !Config Key   = MIN_GPP_ALLOWED
3068       !Config Desc  = minimum gpp considered as not "lowgpp"
3069       !Config If    = OK_STOMATE
3070       !Config Def   = 0.3
3071       !Config Help  =
3072       !Config Units = [gC/m^2/year]
3073       CALL getin_p('MIN_GPP_ALLOWED',min_gpp_allowed)
3074       !
3075       !Config Key   = TAU_CLIMATOLOGY
3076       !Config Desc  = tau for "climatologic variables
3077       !Config If    = OK_STOMATE
3078       !Config Def   = 20
3079       !Config Help  =
3080       !Config Units = [days]
3081       CALL getin_p('TAU_CLIMATOLOGY',tau_climatology)
3082       !
3083       !Config Key   = HVC1
3084       !Config Desc  = parameters for herbivore activity
3085       !Config If    = OK_STOMATE
3086       !Config Def   = 0.019
3087       !Config Help  =
3088       !Config Units = [-] 
3089       CALL getin_p('HVC1',hvc1)
3090       !
3091       !Config Key   = HVC2
3092       !Config Desc  = parameters for herbivore activity
3093       !Config If    = OK_STOMATE
3094       !Config Def   = 1.38
3095       !Config Help  =
3096       !Config Units = [-] 
3097       CALL getin_p('HVC2',hvc2)
3098       !
3099       !Config Key   = LEAF_FRAC_HVC
3100       !Config Desc  = parameters for herbivore activity
3101       !Config If    = OK_STOMATE
3102       !Config Def   = 0.33
3103       !Config Help  =
3104       !Config Units = [-]
3105       CALL getin_p('LEAF_FRAC_HVC',leaf_frac_hvc)
3106       !
3107       !Config Key   = TLONG_REF_MAX
3108       !Config Desc  = maximum reference long term temperature
3109       !Config If    = OK_STOMATE
3110       !Config Def   = 303.1
3111       !Config Help  =
3112       !Config Units = [K] 
3113       CALL getin_p('TLONG_REF_MAX',tlong_ref_max)
3114       !
3115       !Config Key   = TLONG_REF_MIN
3116       !Config Desc  = minimum reference long term temperature
3117       !Config If    = OK_STOMATE
3118       !Config Def   = 253.1
3119       !Config Help  =
3120       !Config Units = [K] 
3121       CALL getin_p('TLONG_REF_MIN',tlong_ref_min)
3122       !
3123       !Config Key   = NCD_MAX_YEAR
3124       !Config Desc  =
3125       !Config If    = OK_STOMATE
3126       !Config Def   = 3.
3127       !Config Help  = NCD : Number of Chilling Days
3128       !Config Units = [days]
3129       CALL getin_p('NCD_MAX_YEAR',ncd_max_year)
3130       !
3131       !Config Key   = GDD_THRESHOLD
3132       !Config Desc  =
3133       !Config If    = OK_STOMATE
3134       !Config Def   = 5.
3135       !Config Help  = GDD : Growing-Degree-Day
3136       !Config Units = [days]
3137       CALL getin_p('GDD_THRESHOLD',gdd_threshold)
3138       !
3139       !Config Key   = GREEN_AGE_EVER
3140       !Config Desc  =
3141       !Config If    = OK_STOMATE
3142       !Config Def   = 2.
3143       !Config Help  =
3144       !Config Units = [-] 
3145       CALL getin_p('GREEN_AGE_EVER',green_age_ever)
3146       !
3147       !Config Key   = GREEN_AGE_DEC
3148       !Config Desc  =
3149       !Config If    = OK_STOMATE
3150       !Config Def   = 0.5
3151       !Config Help  =
3152       !Config Units = [-]
3153       CALL getin_p('GREEN_AGE_DEC',green_age_dec)
3154       
3155       first_call = .FALSE.
3156       
3157    ENDIF
3158   
3159  END SUBROUTINE config_stomate_parameters
3160!
3161!=
3162!
3163
3164!! ================================================================================================================================
3165!! SUBROUTINE   : config_dgvm_parameters
3166!!
3167!>\BRIEF        This subroutine reads in the configuration file all the parameters
3168!! needed when the DGVM model is activated (ie : when ok_dgvm is set to true).
3169!!
3170!! DESCRIPTION  : None
3171!!
3172!! RECENT CHANGE(S): None
3173!!
3174!! MAIN OUTPUT VARIABLE(S):
3175!!
3176!! REFERENCE(S) :
3177!!
3178!! FLOWCHART    :
3179!! \n
3180!_ ================================================================================================================================
3181
3182  SUBROUTINE config_dgvm_parameters   
3183   
3184    IMPLICIT NONE
3185   
3186    !! 0. Variables and parameters declaration
3187
3188    !! 0.4 Local variables
3189
3190    LOGICAL, SAVE ::  first_call = .TRUE.         !! To keep first call trace (true/false)
3191
3192!_ ================================================================================================================================   
3193
3194    IF(first_call) THEN
3195 
3196       !-
3197       ! establish parameters
3198       !-
3199       !
3200       !Config Key   = ESTAB_MAX_TREE
3201       !Config Desc  = Maximum tree establishment rate
3202       !Config If    = OK_DGVM
3203       !Config Def   = 0.12
3204       !Config Help  =
3205       !Config Units = [-]   
3206       CALL getin_p('ESTAB_MAX_TREE',estab_max_tree)
3207       !
3208       !Config Key   = ESTAB_MAX_GRASS
3209       !Config Desc  = Maximum grass establishment rate
3210       !Config If    = OK_DGVM
3211       !Config Def   = 0.12
3212       !Config Help  =
3213       !Config Units = [-] 
3214       CALL getin_p('ESTAB_MAX_GRASS',estab_max_grass)
3215       !
3216       !Config Key   = ESTABLISH_SCAL_FACT
3217       !Config Desc  =
3218       !Config If    = OK_DGVM
3219       !Config Def   = 5.
3220       !Config Help  =
3221       !Config Units = [-]
3222       CALL getin_p('ESTABLISH_SCAL_FACT',establish_scal_fact)
3223       !
3224       !Config Key   = MAX_TREE_COVERAGE
3225       !Config Desc  =
3226       !Config If    = OK_DGVM
3227       !Config Def   = 0.98
3228       !Config Help  =
3229       !Config Units = [-]
3230       CALL getin_p('MAX_TREE_COVERAGE',max_tree_coverage)
3231       !
3232       !Config Key   = IND_0_ESTAB
3233       !Config Desc  =
3234       !Config If    = OK_DGVM
3235       !Config Def   = 0.2
3236       !Config Help  =
3237       !Config Units = [-] 
3238       CALL getin_p('IND_0_ESTAB',ind_0_estab)
3239
3240       !-
3241       ! light parameters
3242       !-
3243       !
3244       !Config Key   = ANNUAL_INCREASE
3245       !Config Desc  = for diagnosis of fpc increase, compare today's fpc to last year's maximum (T) or to fpc of last time step (F)?
3246       !Config If    = OK_DGVM
3247       !Config Def   = y
3248       !Config Help  =
3249       !Config Units = [FLAG]
3250       CALL getin_p('ANNUAL_INCREASE',annual_increase)
3251       !
3252       !Config Key   = MIN_COVER
3253       !Config Desc  = For trees, minimum fraction of crown area occupied
3254       !Config If    = OK_DGVM
3255       !Config Def   = 0.05
3256       !Config Help  =
3257       !Config Units = [-] 
3258       CALL getin_p('MIN_COVER',min_cover)
3259
3260       !-
3261       ! pftinout parameters
3262       !
3263       !Config Key   = IND_0
3264       !Config Desc  = initial density of individuals
3265       !Config If    = OK_DGVM
3266       !Config Def   = 0.02
3267       !Config Help  =
3268       !Config Units = [-] 
3269       CALL getin_p('IND_0',ind_0)
3270       !
3271       !Config Key   = MIN_AVAIL
3272       !Config Desc  = minimum availability
3273       !Config If    = OK_DGVM
3274       !Config Def   = 0.01
3275       !Config Help  =
3276       !Config Units = [-] 
3277       CALL getin_p('MIN_AVAIL',min_avail)
3278       !
3279       !Config Key   = RIP_TIME_MIN
3280       !Config Desc  =
3281       !Config If    = OK_DGVM
3282       !Config Def   = 1.25
3283       !Config Help  =
3284       !Config Units = [year] 
3285       CALL getin_p('RIP_TIME_MIN',RIP_time_min)
3286       !
3287       !Config Key   = NPP_LONGTERM_INIT
3288       !Config Desc  =
3289       !Config If    = OK_DGVM
3290       !Config Def   = 10.
3291       !Config Help  =
3292       !Config Units = [gC/m^2/year]
3293       CALL getin_p('NPP_LONGTERM_INIT',npp_longterm_init)
3294       !
3295       !Config Key   = EVERYWHERE_INIT
3296       !Config Desc  =
3297       !Config If    = OK_DGVM
3298       !Config Def   = 0.05
3299       !Config Help  =
3300       !Config Units = [-]
3301       CALL getin_p('EVERYWHERE_INIT',everywhere_init)
3302       
3303       first_call = .FALSE.
3304       
3305    ENDIF
3306   
3307   
3308  END SUBROUTINE config_dgvm_parameters
3309
3310
3311END MODULE constantes
Note: See TracBrowser for help on using the repository browser.