source: branches/ORCHIDEE_EXT/ORCHIDEE/src_parameters/constantes.f90 @ 471

Last change on this file since 471 was 471, checked in by didier.solyga, 13 years ago

Correct wrong loops in slowproc (wrong algorithm and wrong vectorisation). Replace the differents ok_sechiba, ok_stomate, etc by a structure control_type for simplifying the routines

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