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

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

Externalized stemdiag_bid. Synchronize intersurf.f90 and stomate.f90 with revisions 351 and 352 of the trunk

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 = 2.71828182846 !or euler = EXP(1.)
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(ok_sechiba,ok_routing, ok_stomate)
1140
1141     IMPLICIT NONE
1142     ! first call
1143     LOGICAL, SAVE ::  first_call = .TRUE.   
1144     ! input
1145     LOGICAL, INTENT(in) :: ok_sechiba
1146     LOGICAL, INTENT(in) :: ok_routing
1147     LOGICAL, INTENT(in) :: ok_stomate   
1148
1149     IF (first_call) THEN
1150
1151        IF(ok_sechiba .AND. ok_routing) THEN
1152           
1153           !Config Key  = DO_IRRIGATION
1154           !Config Desc = Should we compute an irrigation flux
1155           !Config Def  = FALSE
1156           !Config Help = This parameters allows the user to ask the model
1157           !Config        to compute an irigation flux. This performed for the
1158           !Config        on very simple hypothesis. The idea is to have a good
1159           !Config        map of irrigated areas and a simple function which estimates
1160           !Config        the need to irrigate.
1161           CALL getin_p('DO_IRRIGATION', doirrigation)
1162           !
1163           !Config Key  = DO_FLOODPLAINS
1164           !Config Desc = Should we include floodplains
1165           !Config Def  = FALSE
1166           !Config Help = This parameters allows the user to ask the model
1167           !Config        to take into account the flood plains and return
1168           !Config        the water into the soil moisture. It then can go
1169           !Config        back to the atmopshere. This tried to simulate
1170           !Config        internal deltas of rivers.
1171           CALL getin_p('DO_FLOODPLAINS', dofloodplains)
1172       
1173        ENDIF
1174
1175           
1176        IF(ok_stomate) THEN
1177
1178           !Config  Key  = HERBIVORES
1179           !Config  Desc = herbivores allowed?
1180           !Config  Def  = n
1181           !Config  Help = With this variable, you can determine
1182           !Config         if herbivores are activated
1183           CALL getin_p('HERBIVORES', ok_herbivores)
1184           !
1185           !Config  Key  = TREAT_EXPANSION
1186           !Config  Desc = treat expansion of PFTs across a grid cell?
1187           !Config  Def  = n
1188           !Config  Help = With this variable, you can determine
1189           !Config         whether we treat expansion of PFTs across a
1190           !Config         grid cell.
1191           CALL getin_p('TREAT_EXPANSION', treat_expansion)
1192           !
1193           !Config Key  = LPJ_GAP_CONST_MORT
1194           !Config Desc = prescribe mortality if not using DGVM?
1195           !Config Def  = y
1196           !Config Help = set to TRUE if constant mortality is to be activated
1197           !              ignored if DGVM=true!
1198           CALL getin('LPJ_GAP_CONST_MORT', lpj_gap_const_mort)
1199           !
1200           !Config  Key  = HARVEST_AGRI
1201           !Config  Desc = Harvert model for agricol PFTs.
1202           !Config  Def  = y
1203           !Config  Help = Compute harvest above ground biomass for agriculture.
1204           !Config         Change daily turnover.
1205           CALL getin_p('HARVEST_AGRI', harvest_agri)
1206           !
1207           !Config  Key  = FIRE_DISABLE
1208           !Config  Desc = no fire allowed
1209           !Config  Def  = n
1210           !Config  Help = With this variable, you can allow or not
1211           !Config         the estimation of CO2 lost by fire
1212           CALL getin_p('FIRE_DISABLE', disable_fire)
1213
1214        ENDIF
1215
1216        !
1217        ! Check consistency (see later)
1218        !
1219!!$        IF(.NOT.(ok_routing) .AND. (doirrigation .OR. dofloodplains)) THEN
1220!!$           CALL ipslerr (2,'activate_sub_models', &
1221!!$               &     'Problem :you tried to activate the irrigation and floodplains without activating the routing',&
1222!!$               &     'Are you sure ?', &
1223!!$               &     '(check your parameters).')
1224!!$        ENDIF
1225       
1226!!$        IF(.NOT.(ok_stomate) .AND. (ok_herbivores .OR. treat_expansion .OR. lpj_gap_const_mort &
1227!!$            & .OR. harvest_agri .OR. disable_fire)) THEN
1228!!$          CALL ipslerr (2,'activate_sub_models', &
1229!!$               &     'Problem : try to activate the following options : herbivory, treat_expansion, fire,',&
1230!!$               &     'harvest_agri and constant mortality without stomate activated.',&
1231!!$               &     '(check your parameters).')
1232!!$        ENDIF
1233           
1234        first_call =.FALSE.
1235
1236     ENDIF
1237
1238   END SUBROUTINE activate_sub_models
1239!
1240!=
1241!
1242   SUBROUTINE veget_config
1243
1244     ! DS : this subroutine reads the flags previously in slowproc.f90 . As these parameters
1245     !      let the user to configure the vegetation, it is called veget_config.
1246     
1247     IMPLICIT NONE
1248
1249     ! first call
1250     LOGICAL, SAVE ::  first_call = .TRUE.   
1251     
1252     IF (first_call) THEN 
1253
1254        !Config  Key  = AGRICULTURE
1255        !Config  Desc = agriculture allowed?
1256        !Config  Def  = y
1257        !Config  Help = With this variable, you can determine
1258        !Config         whether agriculture is allowed
1259        !
1260        CALL getin_p('AGRICULTURE', agriculture)
1261        !
1262        !Config Key  = IMPOSE_VEG
1263        !Config Desc = Should the vegetation be prescribed
1264        !Config Def  = n
1265        !Config Help = This flag allows the user to impose a vegetation distribution
1266        !Config        and its characterisitcs. It is espacially interesting for 0D
1267        !Config        simulations. On the globe it does not make too much sense as
1268        !Config        it imposes the same vegetation everywhere
1269        !
1270        CALL getin_p('IMPOSE_VEG', impveg)
1271
1272        IF(impveg) THEN
1273           !Config Key  = IMPOSE_SOILT
1274           !Config Desc = Should the soil typ be prescribed
1275           !Config Def  = n
1276           !Config If   = IMPOSE_VEG
1277           !Config Help = This flag allows the user to impose a soil type distribution.
1278           !Config        It is espacially interesting for 0D
1279           !Config        simulations. On the globe it does not make too much sense as
1280           !Config        it imposes the same soil everywhere
1281           CALL getin_p('IMPOSE_SOILT', impsoilt)     
1282        ENDIF
1283
1284        !Config Key  = LAI_MAP
1285        !Config Desc = Read the LAI map
1286        !Config Def  = n
1287        !Config Help = It is possible to read a 12 month LAI map which will
1288        !Config        then be interpolated to daily values as needed.
1289        CALL getin_p('LAI_MAP',read_lai)
1290
1291        IF(read_lai) THEN
1292           !Config Key  = SLOWPROC_LAI_OLD_INTERPOL
1293           !Config Desc = Flag to use old "interpolation" of LAI
1294           !Config If   = LAI_MAP
1295           !Config Def  = FALSE
1296           !Config Help = If you want to recover the old (ie orchidee_1_2 branch)
1297           !Config        "interpolation" of LAI map.
1298           CALL getin_p('SLOWPROC_LAI_OLD_INTERPOL',old_lai)
1299        ENDIF
1300 
1301        !
1302        !Config Key  = LAND_USE
1303        !Config Desc = Read a land_use vegetation map
1304        !Config Def  = n
1305        !Config Help = pft values are needed, max time axis is 293
1306        CALL getin_p('LAND_USE',land_use)
1307
1308        IF(land_use) THEN
1309           !Config Key  = VEGET_REINIT
1310           !Config Desc = booleen to indicate that a new LAND USE file will be used.
1311           !Config If   = LAND_USE
1312           !Config Def  = n
1313           !Config Help = The parameter is used to bypass veget_year count
1314           !Config Help   and reinitialize it with VEGET_YEAR parameter.
1315           !Config Help   Then it is possible to change LAND USE file.
1316           CALL getin_p('VEGET_REINIT', veget_reinit)
1317           !
1318           !Config  Key  = LAND_COVER_CHANGE
1319           !Config  Desc = treat land use modifications
1320           !Config  If   = LAND_USE
1321           !Config  Def  = y
1322           !Config  Help = With this variable, you can use a Land Use map
1323           !Config         to simulate anthropic modifications such as
1324           !Config         deforestation.
1325           CALL getin_p('LAND_COVER_CHANGE', lcchange)
1326           !
1327           !Config Key  = VEGET_YEAR
1328           !Config Desc = Year of the land_use vegetation map to be read (0 == NO TIME AXIS)
1329           !Config If   = LAND_USE
1330           !Config Def  = 282
1331           !Config Help = First year for landuse vegetation (2D map by pft).
1332           !Config Help   If VEGET_YEAR == 0, this means there is no time axis.
1333           CALL getin_p('VEGET_YEAR', veget_year_orig)
1334        ENDIF
1335
1336        IF(.NOT. impveg .AND. .NOT. land_use) THEN
1337           !Config Key  = SLOWPROC_VEGET_OLD_INTERPOL
1338           !Config Desc = Flag to use old "interpolation" of vegetation map.
1339           !Config If   = NOT IMPOSE_VEG and NOT LAND_USE
1340           !Config Def  = FALSE
1341           !Config Help = If you want to recover the old (ie orchidee_1_2 branch)
1342           !Config        "interpolation" of vegetation map.
1343           CALL getin_p('SLOWPROC_VEGET_OLD_INTERPOL',old_veget)
1344         ENDIF 
1345
1346         !
1347         ! Check consistency
1348         !
1349         ! 1. You have to activate agriculture and land_use
1350         IF ( .NOT. agriculture .AND. land_use ) THEN
1351            CALL ipslerr (2,'veget_config', &
1352                 &     'Problem with agriculture desactivated and Land Use activated.',&
1353                 &     'Are you sure ?', &
1354                 &     '(check your parameters).')
1355         ENDIF
1356
1357
1358        first_call = .FALSE.
1359
1360     ENDIF
1361
1362!!$        ! DS : Add warning in case of a wrong configuration (need to be discussed)
1363!!$        ! 2.
1364!!$        IF (.NOT.(read_lai) .AND. old_lai) THEN
1365!!$           CALL ipslerr (2,'veget_config', &
1366!!$               &     'Problem with lai_map desactivated and old_lai activated.',&
1367!!$               &     'Are you sure ?', &
1368!!$               &     '(check your parameters).')
1369!!$        ENDIF
1370!!$   
1371!!$        ! 3.
1372!!$        IF ((impveg .OR. land_use) .AND. old_veget) THEN
1373!!$           CALL ipslerr (2,'veget_config', &
1374!!$                &     'Problem : try to use the old interpolation with a land use map or in impose_veg.',&
1375!!$                &     'Are you sure ?', &
1376!!$                &     '(check your parameters).')
1377!!$        ENDIF
1378!!$
1379!!$        ! 4.
1380!!$        IF ( .NOT.(impveg) .AND. impsoilt) THEN
1381!!$           CALL ipslerr (2,'veget_config', &
1382!!$               &     'Problem : try to activate impose_soilt without activating impose_veg.',&
1383!!$               &     'Are you sure ?', &
1384!!$               &     '(check your parameters).')
1385!!$        ENDIF
1386!!$
1387!!$        ! 5.
1388!!$        IF (.NOT.(land_use) .AND. (veget_reinit)) THEN
1389!!$           CALL ipslerr (2,'veget_config', &
1390!!$                &     'Problem : try to use a land_use map without activating land_use.',&
1391!!$                &     'Are you sure ?', &
1392!!$                &     '(check your parameters).')       
1393!!$        ENDIF
1394!!$
1395!!$        ! 6.
1396!!$        IF (.NOT.(land_use) .AND. lcchange) THEN
1397!!$           CALL ipslerr (2,'veget_config', &
1398!!$                &     'Problem : lcchange is activated without activating land_use.',&
1399!!$                &     'Are you sure ?', &
1400!!$                &     '(check your parameters).')       
1401!!$        ENDIF
1402           
1403   END SUBROUTINE veget_config
1404!
1405!=
1406!
1407   SUBROUTINE getin_sechiba_parameters
1408
1409     IMPLICIT NONE
1410     ! first call
1411     LOGICAL, SAVE ::  first_call = .TRUE.
1412     
1413     IF(first_call) THEN 
1414       
1415        ! Global : parameters used by many modules
1416        !
1417        !Config Key  = MAXMASS_GLACIER
1418        !Config Desc =
1419        !Config If   = OK_SECHIBA or OK_CWRR
1420        !Config Def  =  3000.
1421        !Config Help =
1422        !Config Units = [Kg/m^2] 
1423        CALL getin_p('MAXMASS_GLACIER',maxmass_glacier)
1424        !
1425        !Config Key  = SNOWCRI
1426        !Config Desc =
1427        !Config If   = OK_SECHIBA or OK_CWRR
1428        !Config Def  = 1.5
1429        !Config Help =
1430        !Config Units = [Kg/m^2] 
1431        CALL getin_p('SNOWCRI',snowcri)
1432        !
1433        !Interception reservoir coefficient
1434        !Config  Key  = SECHIBA_QSINT
1435        !Config  Desc = Interception reservoir coefficient
1436        !Config  If   = OK_SECHIBA
1437        !Config  Def  = 0.1
1438        !Config  Help = Transforms leaf area index into size of interception reservoir
1439        !Config         for slowproc_derivvar or stomate
1440        !Config Units = meters [m]
1441        CALL getin_p('SECHIBA_QSINT', qsintcst)
1442        !
1443        !Config Key  = HYDROL_SOIL_DEPTH
1444        !Config Desc = Total depth of soil reservoir
1445        !Config  If   = OK_SECHIBA
1446        !Config Def  = 2.
1447        !Config  Help =
1448        !Config Units = meters [m]
1449        CALL getin_p("HYDROL_SOIL_DEPTH", dpu_cste)
1450        !
1451        !
1452        !Config Key  = MIN_WIND
1453        !Config Desc =
1454        !Config If   = OK_SECHIBA
1455        !Config Def  = 0.1
1456        !Config Help =
1457        !Config Units = [m/s] ?   
1458        CALL getin_p('MIN_WIND',min_wind)
1459        !
1460        !Config Key  = MAX_SNOW_AGE
1461        !Config Desc = Maximum period of snow aging
1462        !Config If   = OK_SECHIBA
1463        !Config Def  = 50.
1464        !Config Help =
1465        !Config Units =   
1466        CALL getin_p('MAX_SNOW_AGE',max_snow_age)
1467        !
1468        !Config Key  = SNOW_TRANS
1469        !Config Desc =
1470        !Config If   = OK_SECHIBA
1471        !Config Def  = 0.3
1472        !Config Help =
1473        !Config Units = meters [m]   
1474        CALL getin_p('SNOW_TRANS',snow_trans)
1475        !
1476        !Config Key  = MX_EAU_EAU
1477        !Config Desc =
1478        !Config If   = OK_SECHIBA
1479        !Config Def  = 150.
1480        !Config Help =
1481        !Config Units = [Kg/M3] 
1482        CALL getin_p('MX_EAU_EAU',mx_eau_eau)
1483        !-
1484        ! condveg
1485        !-
1486        !
1487        !Config Key  = Z0_OVER_HEIGHT
1488        !Config Desc = to get z0 from height
1489        !Config If   = OK_SECHIBA
1490        !Config Def  =  1/16.
1491        !Config Help =
1492        !Config Units =   
1493        CALL getin_p('Z0_OVER_HEIGHT',z0_over_height)
1494        !
1495        !Config Key  = HEIGHT_DISPLACEMENT
1496        !Config Desc = Magic number which relates the height to the displacement height.
1497        !Config If   = OK_SECHIBA
1498        !Config Def  = 0.75
1499        !Config Help =
1500        !Config Units =   
1501        CALL getin_p('HEIGHT_DISPLACEMENT',height_displacement)
1502        !
1503        !Config Key  = Z0_BARE
1504        !Config Desc = bare soil roughness length
1505        !Config If   = OK_SECHIBA
1506        !Config Def  = 0.01
1507        !Config Help =
1508        !Config Units = Meters (m)   
1509        CALL getin_p('Z0_BARE',z0_bare)
1510        !
1511        !Config Key  = Z0_ICE
1512        !Config Desc = ice roughness length
1513        !Config If   = OK_SECHIBA
1514        !Config Def  = 0.001
1515        !Config Help =
1516        !Config Units = Meters (m)   
1517        CALL getin_p('Z0_ICE',z0_ice)
1518        !
1519        !Config Key  = TCST_SNOWA
1520        !Config Desc = Time constant of the albedo decay of snow
1521        !Config If   = OK_SECHIBA
1522        !Config Def  = 5.0
1523        !Config Help =
1524        !Config Units = days [d] ? 
1525        CALL getin_p('TCST_SNOWA',tcst_snowa)
1526        !
1527        !Config Key  = SNOWCRI_ALB
1528        !Config Desc = Critical value for computation of snow albedo
1529        !Config If   = OK_SECHIBA
1530        !Config Def  = 10.
1531        !Config Help =
1532        !Config Units = [Kg/m^2] 
1533        CALL getin_p('SNOWCRI_ALB',snowcri_alb)
1534        !
1535        !
1536        !Config Key  = VIS_DRY
1537        !Config Desc = The correspondance table for the soil color numbers and their albedo
1538        !Config If   = OK_SECHIBA
1539        !Config Def  = 0.24, 0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.27
1540        !Config Help =
1541        !Config Units =   
1542        CALL getin_p('VIS_DRY',vis_dry)
1543        !
1544        !Config Key  = NIR_DRY
1545        !Config Desc = The correspondance table for the soil color numbers and their albedo
1546        !Config If   = OK_SECHIBA
1547        !Config Def  = 0.48, 0.44, 0.40, 0.36, 0.32, 0.28, 0.24, 0.20, 0.55
1548        !Config Help =
1549        !Config Units =   
1550        CALL getin_p('NIR_DRY',nir_dry)
1551        !
1552        !Config Key  = VIS_WET
1553        !Config Desc = The correspondance table for the soil color numbers and their albedo
1554        !Config If   = 0.12, 0.11, 0.10, 0.09, 0.08, 0.07, 0.06, 0.05, 0.15
1555        !Config Def  =
1556        !Config Help =
1557        !Config Units =   
1558        CALL getin_p('VIS_WET',vis_wet)
1559        !
1560        !Config Key  = NIR_WET
1561        !Config Desc = The correspondance table for the soil color numbers and their albedo
1562        !Config If   = OK_SECHIBA
1563        !Config Def  = 0.24, 0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.31
1564        !Config Help =
1565        !Config Units =   
1566        CALL getin_p('NIR_WET',nir_wet)
1567        !
1568        !Config Key  = ALBSOIL_VIS
1569        !Config Desc =
1570        !Config If   = OK_SECHIBA
1571        !Config Def  = 0.18, 0.16, 0.16, 0.15, 0.12, 0.105, 0.09, 0.075, 0.25
1572        !Config Help =
1573        !Config Units = NONE 
1574        CALL getin_p('ALBSOIL_VIS',albsoil_vis)
1575        !
1576        !Config Key  = ALBSOIL_NIR
1577        !Config Desc =
1578        !Config If   = OK_SECHIBA
1579        !Config Def  = 0.36, 0.34, 0.34, 0.33, 0.30, 0.25, 0.20, 0.15, 0.45
1580        !Config Help =
1581        !Config Units = NONE 
1582        CALL getin_p('ALBSOIL_NIR',albsoil_nir)
1583        !-
1584        !
1585        !Config Key  = ALB_DEADLEAF
1586        !Config Desc = albedo of dead leaves, VIS+NIR
1587        !Config If   = OK_SECHIBA
1588        !Config Def  = 0.12, 0.35
1589        !Config Help =
1590        !Config Units =   
1591        CALL getin_p('ALB_DEADLEAF',alb_deadleaf)
1592        !
1593        !Config Key  = ALB_ICE
1594        !Config Desc = albedo of ice, VIS+NIR
1595        !Config If   =  OK_SECHIBA
1596        !Config Def  = 0.60, 0.20
1597        !Config Help =
1598        !Config Units = NONE 
1599        CALL getin_p('ALB_ICE',alb_ice)
1600        !
1601        ! Get the fixed snow albedo if needed
1602        !
1603        !Config Key  = CONDVEG_SNOWA
1604        !Config Desc = The snow albedo used by SECHIBA
1605        !Config Def  = DEF
1606        !Config Help = This option allows the user to impose a snow albedo.
1607        !Config        Default behaviour is to use the model of snow albedo
1608        !Config        developed by Chalita (1993).
1609        CALL getin_p('CONDVEG_SNOWA', fixed_snow_albedo)
1610        !
1611        !Config Key  = ALB_BARE_MODEL
1612        !Config Desc = Switch bare soil albedo dependent (if TRUE) on soil wetness
1613        !Config Def  = FALSE
1614        !Config Help = If TRUE, the model for bare soil albedo is the old formulation.
1615        !Config        Then it depend on the soil dry or wetness. If FALSE, it is the
1616        !Config        new computation that is taken, it is the mean of soil albedo.
1617        CALL getin_p('ALB_BARE_MODEL', alb_bare_model)
1618        !
1619        !Config Key  = Z0CDRAG_AVE
1620        !Config Desc = Average method for z0
1621        !Config Def  = y
1622        !Config Help = If this flag is set to true (y) then the neutral Cdrag
1623        !Config        is averaged instead of the log(z0). This should be
1624        !Config        the prefered option. We still wish to keep the other
1625        !Config        option so we can come back if needed. If this is
1626        !Config        desired then one should set Z0CDRAG_AVE=n
1627        CALL getin_p('Z0CDRAG_AVE', z0cdrag_ave)
1628        !
1629        !Config Key  = IMPOSE_AZE
1630        !Config Desc = Should the surface parameters be prescribed
1631        !Config Def  = n
1632        !Config Help = This flag allows the user to impose the surface parameters
1633        !Config        (Albedo Roughness and Emissivity). It is espacially interesting for 0D
1634        !Config        simulations. On the globe it does not make too much sense as
1635        !Config        it imposes the same vegetation everywhere
1636        CALL getin_p('IMPOSE_AZE', impaze)
1637        !
1638        IF(impaze) THEN
1639           !
1640           !Config Key  = CONDVEG_Z0
1641           !Config Desc = Surface roughness (m)
1642           !Config Def  = 0.15
1643           !Config If   = IMPOSE_AZE
1644           !Config Help = Surface rougness to be used on the point if a 0-dim version
1645           !Config        of SECHIBA is used. Look at the description of the forcing 
1646           !Config        data for the correct value.
1647           CALL getin_p('CONDVEG_Z0', z0_scal) 
1648           !
1649           !Config Key  = ROUGHHEIGHT
1650           !Config Desc = Height to be added to the height of the first level (m)
1651           !Config Def  = 0.0
1652           !Config If   = IMPOSE_AZE
1653           !Config Help = ORCHIDEE assumes that the atmospheric level height is counted
1654           !Config        from the zero wind level. Thus to take into account the roughness
1655           !Config        of tall vegetation we need to correct this by a certain fraction
1656           !Config        of the vegetation height. This is called the roughness height in
1657           !Config        ORCHIDEE talk.
1658           CALL getin_p('ROUGHHEIGHT', roughheight_scal)
1659           !
1660           !Config Key  = CONDVEG_ALBVIS
1661           !Config Desc = SW visible albedo for the surface
1662           !Config Def  = 0.25
1663           !Config If   = IMPOSE_AZE
1664           !Config Help = Surface albedo in visible wavelengths to be used
1665           !Config        on the point if a 0-dim version of SECHIBA is used.
1666           !Config        Look at the description of the forcing data for
1667           !Config        the correct value.
1668           CALL getin_p('CONDVEG_ALBVIS', albedo_scal(ivis))
1669           !
1670           !Config Key  = CONDVEG_ALBNIR
1671           !Config Desc = SW near infrared albedo for the surface
1672           !Config Def  = 0.25
1673           !Config If   = IMPOSE_AZE
1674           !Config Help = Surface albedo in near infrared wavelengths to be used
1675           !Config        on the point if a 0-dim version of SECHIBA is used.
1676           !Config        Look at the description of the forcing data for
1677           !Config        the correct value.
1678           CALL getin_p('CONDVEG_ALBNIR', albedo_scal(inir))
1679           !
1680           !Config Key  = CONDVEG_EMIS
1681           !Config Desc = Emissivity of the surface for LW radiation
1682           !Config Def  = 1.0
1683           !Config If   = IMPOSE_AZE
1684           !Config Help = The surface emissivity used for compution the LE emission
1685           !Config        of the surface in a 0-dim version. Values range between
1686           !Config        0.97 and 1.. The GCM uses 0.98.
1687           CALL getin_p('CONDVEG_EMIS', emis_scal)
1688        ENDIF
1689        !
1690        !-
1691        ! diffuco
1692        !-
1693        !
1694        !Config Key  = NLAI
1695        !Config Desc =
1696        !Config If   = OK_SECHIBA
1697        !Config Def  = 20
1698        !Config Help = dimension of an array used in diffuco
1699        !Config Units = NONE 
1700        CALL getin_p('NLAI',nlai)
1701        !
1702        !Config Key  = LAIMAX
1703        !Config Desc =
1704        !Config If   = OK_SECHIBA
1705        !Config Def  =
1706        !Config Help =
1707        !Config Units =   
1708        CALL getin_p('LAIMAX',laimax)
1709        !
1710        !Config Key  = XC4_1
1711        !Config Desc =
1712        !Config If   = OK_SECHIBA
1713        !Config Def  = 0.83
1714        !Config Help =
1715        !Config Units =   
1716        CALL getin_p('XC4_1',xc4_1)
1717        !
1718        !Config Key  = XC4_2
1719        !Config Desc =
1720        !Config If   = OK_SECHIBA
1721        !Config Def  = 0.93
1722        !Config Help =
1723        !Config Units =   
1724        CALL getin_p('XC4_2',xc4_2)
1725        !
1726        !Config Key  = DEW_VEG_POLY_COEFF
1727        !Config Desc = coefficients of the polynome of degree 5 for the dew
1728        !Config If   = OK_SECHIBA
1729        !Config Def  = 0.887773, 0.205673, 0.110112, 0.014843,  0.000824,  0.000017
1730        !Config Help =
1731        !Config Units =   
1732        CALL getin_p('DEW_VEG_POLY_COEFF',dew_veg_poly_coeff)
1733        !-
1734        ! slowproc
1735        !-
1736        !
1737        !Config Key  = CLAYFRACTION_DEFAULT
1738        !Config Desc =
1739        !Config If   = OK_SECHIBA
1740        !Config Def  = 0.2
1741        !Config Help =
1742        !Config Units = NONE   
1743        CALL getin_p('CLAYFRACTION_DEFAULT',clayfraction_default)
1744        !
1745        !Config Key  = MIN_VEGFRAC
1746        !Config Desc = Minimal fraction of mesh a vegetation type can occupy
1747        !Config If   = OK_SECHIBA
1748        !Config Def  = 0.001
1749        !Config Help =
1750        !Config Units = NONE 
1751        CALL getin_p('MIN_VEGFRAC',min_vegfrac)
1752        !
1753        !Config Key  = STEMPDIAG_BID
1754        !Config Desc = only needed for an initial LAI if there is no restart file
1755        !Config If   = OK_SECHIBA
1756        !Config Def  = 280.
1757        !Config Help =
1758        !Config Units =
1759        CALL getin_p('STEMPDIAG_BID',stempdiag_bid)
1760        !
1761        !Config Key  = SOILTYPE_DEFAULT
1762        !Config Desc = Default soil texture distribution in the following order : sand, loam and clay
1763        !Config If   = OK_SECHIBA
1764        !Config Def  = 0.0, 1.0, 0.0
1765        !Config Help =
1766        !Config Units = NONE   
1767        CALL getin_p('SOILTYPE_DEFAULT',soiltype_default)
1768        !
1769        first_call =.FALSE.
1770       
1771     ENDIF
1772     
1773   END SUBROUTINE getin_sechiba_parameters
1774!
1775!=
1776!
1777   ! Subroutine called only if ok_co2 is activated
1778   ! only for diffuco_trans_co2
1779   
1780   SUBROUTINE getin_co2_parameters
1781     
1782     IMPLICIT NONE
1783     
1784     LOGICAL, SAVE ::  first_call = .TRUE.
1785     
1786     IF(first_call) THEN
1787       
1788        !
1789        !Config Key  = LAI_LEVEL_DEPTH
1790        !Config Desc =
1791        !Config If   = OK_CO2
1792        !Config Def  = 0.15
1793        !Config Help =
1794        !Config Units =   
1795        CALL getin_p('LAI_LEVEL_DEPTH',lai_level_depth)
1796        !
1797        !Config Key  = X1_COEF
1798        !Config Desc =
1799        !Config If   = OK_CO2
1800        !Config Def  = 0.177
1801        !Config Help =
1802        !Config Units =   
1803        CALL getin_p('X1_COEF',x1_coef)
1804        !
1805        !Config Key  = X1_Q10
1806        !Config Desc =
1807        !Config If   = OK_CO2
1808        !Config Def  = 0.069
1809        !Config Help =
1810        !Config Units =   
1811        CALL getin_p('X1_Q10',x1_Q10)
1812        !
1813        !Config Key  = QUANTUM_YIELD
1814        !Config Desc =
1815        !Config If   = OK_CO2
1816        !Config Def  = 0.092
1817        !Config Help =
1818        !Config Units =   
1819        CALL getin_p('QUANTUM_YIELD',quantum_yield)
1820        !
1821        !Config Key  = KT_COEF
1822        !Config Desc =
1823        !Config If   = OK_CO2
1824        !Config Def  = 0.7
1825        !Config Help =
1826        !Config Units =   
1827        CALL getin_p('KT_COEF',kt_coef)
1828        !
1829        !Config Key  = KC_COEF
1830        !Config Desc =
1831        !Config If   = OK_CO2
1832        !Config Def  = 39.09
1833        !Config Help =
1834        !Config Units =   
1835        CALL getin_p('KC_COEF',kc_coef)
1836        !
1837        !Config Key  = KO_Q10
1838        !Config Desc =
1839        !Config If   = OK_CO2
1840        !Config Def  = 0.085
1841        !Config Help =
1842        !Config Units =   
1843        CALL getin_p('KO_Q10',Ko_Q10)
1844        !
1845        !Config Key  = OA
1846        !Config Desc =
1847        !Config If   = OK_CO2
1848        !Config Def  = 210000.
1849        !Config Help =
1850        !Config Units =   
1851        CALL getin_p('OA',Oa)
1852        !
1853        !Config Key  = KO_COEF
1854        !Config Desc =
1855        !Config If   = OK_CO2
1856        !Config Def  = 2.412
1857        !Config Help =
1858        !Config Units =   
1859        CALL getin_p('KO_COEF',Ko_coef)
1860        !
1861        !Config Key  = CP_0
1862        !Config Desc =
1863        !Config If   = OK_CO2
1864        !Config Def  = 42.
1865        !Config Help =
1866        !Config Units =   
1867        CALL getin_p('CP_0',CP_0)
1868        !
1869        !Config Key  = CP_TEMP_COEF
1870        !Config Desc =
1871        !Config If   = OK_CO2
1872        !Config Def  = 9.46
1873        !Config Help =
1874        !Config Units =   
1875        CALL getin_p('CP_TEMP_COEF',cp_temp_coef)
1876        !
1877        !Config Key  = CP_TEMP_REF
1878        !Config Desc =
1879        !Config If   = OK_CO2
1880        !Config Def  =  25.
1881        !Config Help =
1882        !Config Units = degrees Celsius ? 
1883        CALL getin_p('CP_TEMP_REF',cp_temp_ref)
1884        !
1885        !Config Key  = RT_COEF
1886        !Config Desc =
1887        !Config If   = OK_CO2
1888        !Config Def  =  0.8, 1.3
1889        !Config Help =
1890        !Config Units =   
1891        CALL getin_p('RT_COEF',rt_coef)
1892        !
1893        !Config Key  = VC_COEF
1894        !Config Desc =
1895        !Config If   = OK_CO2
1896        !Config Def  = 0.39, 0.3
1897        !Config Help =
1898        !Config Units =   
1899        CALL getin_p('VC_COEF',vc_coef)
1900       
1901        first_call =.FALSE.
1902       
1903     ENDIF
1904     
1905   END SUBROUTINE getin_co2_parameters
1906!
1907!=
1908!
1909   SUBROUTINE getin_hydrolc_parameters
1910     
1911     LOGICAL, SAVE ::  first_call = .TRUE.
1912     
1913     IF(first_call) THEN 
1914        !
1915        !Config Key  = QWILT
1916        !Config Desc = Wilting point
1917        !Config If   = OK_SECHIBA and .NOT.(OK_CWRR)
1918        !Config Def  =  5.0
1919        !Config Help =
1920        !Config Units =
1921        CALL getin_p('QWILT',qwilt)
1922        !
1923        !Config Key  = MIN_RESDIS
1924        !Config Desc = The minimal size we allow for the upper reservoir
1925        !Config If   = OK_SECHIBA and .NOT.(OK_CWRR)
1926        !Config Def  = 2.e-5
1927        !Config Help =
1928        !Config Units = Meters (m)
1929        CALL getin_p('MIN_RESDIS',min_resdis)
1930        !
1931        !Config Key  = MIN_DRAIN
1932        !Config Desc = Diffusion constant for the slow regime
1933        !Config If   = OK_SECHIBA and .NOT.(OK_CWRR)
1934        !Config Def  = 0.001
1935        !Config Help =
1936        !Config Units =
1937        CALL getin_p('MIN_DRAIN',min_drain)
1938        !
1939        !Config Key  = MAX_DRAIN
1940        !Config Desc = Diffusion constant for the fast regime
1941        !Config If   = OK_SECHIBA and .NOT.(OK_CWRR)
1942        !Config Def  = 0.1
1943        !Config Help =
1944        !Config Units =
1945        CALL getin_p('MAX_DRAIN',max_drain)
1946        !
1947        !Config Key  = EXP_DRAIN
1948        !Config Desc = The exponential in the diffusion law
1949        !Config If   = OK_SECHIBA and .NOT.(OK_CWRR)
1950        !Config Def  = 1.5
1951        !Config Help =
1952        !Config Units =
1953        CALL getin_p('EXP_DRAIN',exp_drain)
1954        !
1955        !Config Key  = RSOL_CSTE
1956        !Config Desc = Constant in the computation of resistance for bare  soil evaporation
1957        !Config If   = OK_SECHIBA and .NOT.(OK_CWRR)
1958        !Config Def  = 33.E3
1959        !Config Help =
1960        !Config Units =
1961        CALL getin_p('RSOL_CSTE',rsol_cste)
1962        !
1963        !Config Key  = HCRIT_LITTER
1964        !Config Desc = Scaling depth for litter humidity (m)
1965        !Config If   = OK_SECHIBA and .NOT.(OK_CWRR)
1966        !Config Def  = 0.08
1967        !Config Help =
1968        !Config Units =
1969        CALL getin_p('HCRIT_LITTER',hcrit_litter)
1970        !
1971        !Config  Key  = HYDROL_OK_HDIFF
1972        !Config  Desc = do horizontal diffusion?
1973        !Config  Def  = n
1974        !Config  Help = If TRUE, then water can diffuse horizontally between
1975        !Config         the PFTs' water reservoirs.
1976        CALL getin_p('HYDROL_OK_HDIFF',ok_hdiff)         
1977
1978        first_call =.FALSE.
1979       
1980     ENDIF
1981     
1982   END SUBROUTINE getin_hydrolc_parameters
1983   
1984!
1985!=
1986!
1987   ! Subroutine called only if hydrol_cwrr is activated
1988   
1989   SUBROUTINE getin_hydrol_cwrr_parameters
1990     
1991     IMPLICIT NONE
1992     
1993     LOGICAL, SAVE ::  first_call = .TRUE.
1994     
1995     IF (first_call) THEN
1996
1997        !
1998        !Config Key  = W_TIME
1999        !Config Desc = Time weighting for discretisation
2000        !Config If   = OK_CWRR
2001        !Config Def  = 1.
2002        !Config Help =
2003        !Config Units =
2004        CALL getin_p('W_TIME',w_time)
2005        !
2006        !Config Key  = NVAN
2007        !Config Desc = Van genuchten coefficient n
2008        !Config If   = OK_CWRR
2009        !Config Def  = 1.89, 1.56, 1.31
2010        !Config Help =
2011        !Config Units =
2012        CALL getin_p('NVAN',nvan)
2013        !
2014        !Config Key  = AVAN
2015        !Config Desc = Van genuchten coefficient a (mm^{-1})
2016        !Config If   = OK_CWRR
2017        !Config Def  = 0.0075, 0.0036, 0.0019
2018        !Config Help =
2019        !Config Units = [1/mm] 
2020        CALL getin_p('AVAN',avan)
2021        !
2022        !Config Key  = MCR
2023        !Config Desc = Residual soil water content
2024        !Config If   = OK_CWRR
2025        !Config Def  = 0.065, 0.078, 0.095
2026        !Config Help =
2027        !Config Units =   
2028        CALL getin_p('MCR',mcr)
2029        !
2030        !Config Key  = MCS
2031        !Config Desc = Saturated soil water content
2032        !Config If   = OK_CWRR
2033        !Config Def  = 0.41, 0.43, 0.41
2034        !Config Help =
2035        !Config Units =   
2036        CALL getin_p('MCS',mcs)     
2037        !
2038        !Config Key  = KS
2039        !Config Desc = Hydraulic conductivity Saturation
2040        !Config If   = OK_CWRR
2041        !Config Def  = 1060.8, 249.6, 62.4
2042        !Config Help =
2043        !Config Units = [mm/d]   
2044        CALL getin_p('KS',ks)
2045        !
2046        !Config Key  = PCENT
2047        !Config Desc = Soil moisture above which transpir is max
2048        !Config If   = OK_CWRR
2049        !Config Def  =  0.5, 0.5, 0.5
2050        !Config Help =
2051        !Config Units =   
2052        CALL getin_p('PCENT',pcent)
2053        !
2054        !Config Key  = FREE_DRAIN_MAX
2055        !Config Desc = Max value of the permeability coeff at the bottom of the soil
2056        !Config If   = OK_CWRR
2057        !Config Def  =  1.0, 1.0, 1.0
2058        !Config Help =
2059        !Config Units =   
2060        CALL getin_p('FREE_DRAIN_MAX',free_drain_max)
2061        !
2062        !Config Key  = MCF
2063        !Config Desc = Volumetric water content field capacity
2064        !Config If   = OK_CWRR
2065        !Config Def  = 0.32, 0.32, 0.32
2066        !Config Help =
2067        !Config Units =   
2068        CALL getin_p('MCF',mcf)
2069        !
2070        !Config Key  = MCW
2071        !Config Desc = Volumetric water content Wilting pt
2072        !Config If   = OK_CWRR
2073        !Config Def  = 0.10, 0.10, 0.10
2074        !Config Help =
2075        !Config Units =   
2076        CALL getin_p('MCW',mcw)
2077        !
2078        !Config Key  = MC_AWET
2079        !Config Desc = Vol. wat. cont. above which albedo is cst
2080        !Config If   = OK_CWRR
2081        !Config Def  = 0.25, 0.25, 0.25
2082        !Config Help =
2083        !Config Units =   
2084        CALL getin_p('MC_AWET',mc_awet)
2085        !
2086        !Config Key  = MC_ADRY
2087        !Config Desc = Vol. wat. cont. below which albedo is cst
2088        !Config If   = OK_CWRR
2089        !Config Def  = 0.1, 0.1, 0.1
2090        !Config Help =
2091        !Config Units =   
2092        CALL getin_p('MC_ADRY',mc_adry)
2093         
2094        first_call =.FALSE.
2095       
2096     ENDIF
2097
2098   END SUBROUTINE getin_hydrol_cwrr_parameters
2099!
2100!=
2101!
2102   SUBROUTINE getin_routing_parameters
2103     
2104     IMPLICIT NONE
2105     
2106     LOGICAL, SAVE ::  first_call = .TRUE.
2107     
2108     IF(first_call) THEN
2109        !
2110        !Config Key  = CROP_COEF
2111        !Config Desc = Parameter for the Kassel irrigation parametrization linked to the crops
2112        !Config If   = OK_ROUTING
2113        !Config Def  = 1.5
2114        !Config Help =
2115        !Config Units =   
2116        CALL getin_p('CROP_COEF',crop_coef)
2117       
2118        first_call =.FALSE.
2119       
2120     ENDIF
2121     
2122   END SUBROUTINE getin_routing_parameters
2123!
2124!=
2125!
2126   SUBROUTINE getin_stomate_parameters
2127     
2128    IMPLICIT NONE
2129   
2130    LOGICAL, SAVE ::  first_call = .TRUE.
2131   
2132    IF(first_call) THEN
2133       !-
2134       ! constraints_parameters
2135       !-
2136       !
2137       !Config Key  = TOO_LONG
2138       !Config Desc = longest sustainable time without regeneration (vernalization)
2139       !Config If   = OK_STOMATE
2140       !Config Def  = 5.
2141       !Config Help =
2142       !Config Units = days (d)   
2143       CALL getin_p('TOO_LONG',too_long)
2144
2145       !-
2146       ! fire parameters
2147       !-
2148       !
2149       !Config Key  = TAU_FIRE
2150       !Config Desc = Time scale for memory of the fire index (days). Validated for one year in the DGVM.
2151       !Config If   = OK_STOMATE
2152       !Config Def  =
2153       !Config Help =
2154       !Config Units = days [d]   
2155       CALL getin_p('TAU_FIRE',tau_fire)
2156       !
2157       !Config Key  = LITTER_CRIT
2158       !Config Desc = Critical litter quantity for fire
2159       !Config If   = OK_STOMATE
2160       !Config Def  = 200.
2161       !Config Help =
2162       !Config Units =   
2163       CALL getin_p('LITTER_CRIT',litter_crit)
2164       !
2165       !Config Key  = CO2FRAC
2166       !Config Desc = What fraction of a burned plant compartment goes into the atmosphere
2167       !Config If   = OK_STOMATE
2168       !Config Def  = .95, .95, 0., 0.3, 0., 0., .95, .95
2169       !Config Help =
2170       !Config Units = NONE   
2171       CALL getin_p('CO2FRAC',co2frac)
2172       !
2173       !Config Key  = BCFRAC_COEFF
2174       !Config Desc =
2175       !Config If   = OK_STOMATE
2176       !Config Def  = 0.3,  1.3,  88.2
2177       !Config Help =
2178       !Config Units =   
2179       CALL getin_p('BCFRAC_COEFF',bcfrac_coeff)
2180       !
2181       !Config Key  = FIREFRAC_COEFF
2182       !Config Desc =
2183       !Config If   = OK_STOMATE
2184       !Config Def  = 0.45, 0.8, 0.6, 0.13
2185       !Config Help =
2186       !Config Units =   
2187       CALL getin_p('FIREFRAC_COEFF',firefrac_coeff)
2188
2189       !-
2190       ! gap parameters (+ lpj_const_mort)
2191       !-
2192       !
2193       !Config Key  = AVAILABILITY_FACT
2194       !Config Desc =
2195       !Config If   = OK_STOMATE
2196       !Config Def  = 0.02
2197       !Config Help =
2198       !Config Units =   
2199       CALL getin_p('AVAILABILITY_FACT', availability_fact) 
2200       !
2201       !Config Key  = VIGOUR_REF
2202       !Config Desc =
2203       !Config If   = OK_STOMATE
2204       !Config Def  = 0.17
2205       !Config Help =
2206       !Config Units =   
2207       CALL getin_p('VIGOUR_REF',vigour_ref)
2208       !
2209       !Config Key  = VIGOUR_COEFF
2210       !Config Desc =
2211       !Config If   = OK_STOMATE
2212       !Config Def  = 70.
2213       !Config Help =
2214       !Config Units =   
2215       CALL getin_p('VIGOUR_COEFF',vigour_coeff) 
2216
2217       !-
2218       ! allocation parameters
2219       !-
2220       !
2221       !Config Key  = OK_MINRES
2222       !Config Desc = Do we try to reach a minimum reservoir even if we are severely stressed?
2223       !Config If   = OK_STOMATE
2224       !Config Def  = y
2225       !Config Help =
2226       !Config Units = NONE   
2227       CALL getin_p('OK_MINRES',ok_minres)
2228       !
2229       !Config Key  = TAU_LEAFINIT
2230       !Config Desc = time to attain the initial foliage using the carbohydrate reserve
2231       !Config If   = OK_STOMATE
2232       !Config Def  =  10.
2233       !Config Help =
2234       !Config Units = dayd [d] 
2235       CALL getin_p('TAU_LEAFINIT', tau_leafinit)
2236       !
2237       !Config Key  = RESERVE_TIME_TREE
2238       !Config Desc = maximum time during which reserve is used (trees)
2239       !Config If   = OK_STOMATE
2240       !Config Def  = 30.
2241       !Config Help =
2242       !Config Units = dayd [d]   
2243       CALL getin_p('RESERVE_TIME_TREE',reserve_time_tree)
2244       !
2245       !Config Key  = RESERVE_TIME_GRASS
2246       !Config Desc = maximum time during which reserve is used (grasses)
2247       !Config If   = OK_STOMATE
2248       !Config Def  = 20.
2249       !Config Help =
2250       !Config Units = dayd [d]   
2251       CALL getin_p('RESERVE_TIME_GRASS',reserve_time_grass)
2252       !
2253       !Config Key  = R0
2254       !Config Desc = Standard root allocation
2255       !Config If   = OK_STOMATE
2256       !Config Def  = 0.3
2257       !Config Help =
2258       !Config Units =   
2259       CALL getin_p('R0',R0)
2260       !
2261       !Config Key  = S0
2262       !Config Desc = Standard sapwood allocation
2263       !Config If   = OK_STOMATE
2264       !Config Def  = 0.3
2265       !Config Help =
2266       !Config Units =   
2267       CALL getin_p('S0',S0)
2268       !
2269       !Config Key  = F_FRUIT
2270       !Config Desc = Standard fruit allocation
2271       !Config If   = OK_STOMATE
2272       !Config Def  = 0.1
2273       !Config Help =
2274       !Config Units =   
2275       CALL getin_p('F_FRUIT',f_fruit)
2276       !
2277       !Config Key  = ALLOC_SAP_ABOVE_TREE
2278       !Config Desc = fraction of sapwood allocation above ground
2279       !Config If   = OK_STOMATE
2280       !Config Def  = 0.5
2281       !Config Help =
2282       !Config Units = NONE 
2283       CALL getin_p('ALLOC_SAP_ABOVE_TREE',alloc_sap_above_tree)
2284       !
2285       !Config Key  = ALLOC_SAP_ABOVE_GRASS
2286       !Config Desc = fraction of sapwood allocation above ground
2287       !Config If   = OK_STOMATE
2288       !Config Def  = 1.0
2289       !Config Help =
2290       !Config Units = NONE   
2291       CALL getin_p('ALLOC_SAP_ABOVE_GRASS',alloc_sap_above_grass)
2292       !
2293       !Config Key  = MIN_LTOLSR
2294       !Config Desc = extrema of leaf allocation fraction
2295       !Config If   = OK_STOMATE
2296       !Config Def  = 0.2
2297       !Config Help =
2298       !Config Units = NONE   
2299       CALL getin_p('MIN_LTOLSR',min_LtoLSR)
2300       !
2301       !Config Key  = MAX_LTOLSR
2302       !Config Desc = extrema of leaf allocation fraction
2303       !Config If   = OK_STOMATE
2304       !Config Def  = 0.5
2305       !Config Help =
2306       !Config Units = NONE   
2307       CALL getin_p('MAX_LTOLSR',max_LtoLSR)
2308       !
2309       !Config Key  = Z_NITROGEN
2310       !Config Desc = scaling depth for nitrogen limitation
2311       !Config If   = OK_STOMATE
2312       !Config Def  = 0.2
2313       !Config Help =
2314       !Config Units = meters (m) 
2315       CALL getin_p('Z_NITROGEN',z_nitrogen)
2316       !
2317       !Config Key  = LAI_MAX_TO_HAPPY
2318       !Config Desc =
2319       !Config If   = OK_STOMATE
2320       !Config Def  = 0.5
2321       !Config Help =
2322       !Config Units =   
2323       CALL getin_p('LAI_MAX_TO_HAPPY',lai_max_to_happy)
2324       !
2325       !Config Key  = NLIM_TREF
2326       !Config Desc =
2327       !Config If   = OK_STOMATE
2328       !Config Def  = 25.
2329       !Config Help =
2330       !Config Units = Degrees Celsius [C] 
2331       CALL getin_p('NLIM_TREF',Nlim_tref) 
2332 
2333       !-
2334       ! data parameters
2335       !-
2336       !
2337       !Config Key  = PIPE_TUNE1
2338       !Config Desc = crown area = pipe_tune1. stem diameter**(1.6) (Reinicke's theory)
2339       !Config If   = OK_STOMATE
2340       !Config Def  = 100.0
2341       !Config Help =
2342       !Config Units =   
2343       CALL getin_p('PIPE_TUNE1',pipe_tune1)
2344       !
2345       !Config Key  = PIPE_TUNE2
2346       !Config Desc = height=pipe_tune2 * diameter**pipe_tune3
2347       !Config If   = OK_STOMATE
2348       !Config Def  = 40.0
2349       !Config Help =
2350       !Config Units =   
2351       CALL getin_p('PIPE_TUNE2',pipe_tune2) 
2352        !
2353       !Config Key  = PIPE_TUNE3
2354       !Config Desc = height=pipe_tune2 * diameter**pipe_tune3
2355       !Config If   = OK_STOMATE
2356       !Config Def  = 0.5
2357       !Config Help =
2358       !Config Units =   
2359       CALL getin_p('PIPE_TUNE3',pipe_tune3)
2360       !
2361       !Config Key  = PIPE_TUNE4
2362       !Config Desc = needed for stem diameter
2363       !Config If   = OK_STOMATE
2364       !Config Def  = 0.3
2365       !Config Help =
2366       !Config Units =   
2367       CALL getin_p('PIPE_TUNE4',pipe_tune4)
2368       !
2369       !Config Key  = PIPE_DENSITY
2370       !Config Desc = Density
2371       !Config If   = OK_STOMATE
2372       !Config Def  = 2.e5
2373       !Config Help =
2374       !Config Units =   
2375       CALL getin_p('PIPE_DENSITY',pipe_density)
2376       !
2377       !Config Key  = PIPE_K1
2378       !Config Desc =
2379       !Config If   = OK_STOMATE
2380       !Config Def  = 8.e3
2381       !Config Help =
2382       !Config Units =   
2383       CALL getin_p('PIPE_K1',pipe_k1)
2384       !
2385       !Config Key  = PIPE_TUNE_EXP_COEFF
2386       !Config Desc = pipe tune exponential coeff
2387       !Config If   = OK_STOMATE
2388       !Config Def  = 1.6
2389       !Config Help =
2390       !Config Units = NONE   
2391       CALL getin_p('PIPE_TUNE_EXP_COEFF',pipe_tune_exp_coeff)
2392       !
2393       !
2394       !Config Key  = PRECIP_CRIT
2395       !Config Desc = minimum precip
2396       !Config If   = OK_STOMATE
2397       !Config Def  = 100.
2398       !Config Help =
2399       !Config Units = [mm/year] 
2400       CALL getin_p('PRECIP_CRIT',precip_crit)
2401       !
2402       !Config Key  = GDD_CRIT_ESTAB
2403       !Config Desc = minimum gdd for establishment of saplings
2404       !Config If   = OK_STOMATE
2405       !Config Def  = 150.
2406       !Config Help =
2407       !Config Units =   
2408       CALL getin_p('GDD_CRIT_ESTAB',gdd_crit_estab)
2409        !
2410       !Config Key  = FPC_CRIT
2411       !Config Desc = critical fpc, needed for light competition and establishment
2412       !Config If   = OK_STOMATE
2413       !Config Def  = 0.95
2414       !Config Help =
2415       !Config Units =   
2416       CALL getin_p('FPC_CRIT',fpc_crit)
2417       !
2418       !Config Key  = ALPHA_GRASS
2419       !Config Desc = sapling characteristics : alpha's
2420       !Config If   = OK_STOMATE
2421       !Config Def  = 0.5
2422       !Config Help =
2423       !Config Units =   
2424       CALL getin_p('ALPHA_GRASS',alpha_grass)
2425       !
2426       !Config Key  = ALPHA_TREE
2427       !Config Desc = sapling characteristics : alpha's
2428       !Config If   = OK_STOMATE
2429       !Config Def  = 1.
2430       !Config Help =
2431       !Config Units =   
2432       CALL getin_p('ALPHA_TREE',alpha_tree)
2433       !-
2434       !
2435       !Config Key  = MASS_RATIO_HEART_SAP
2436       !Config Desc = mass ratio (heartwood+sapwood)/sapwood
2437       !Config If   = OK_STOMATE
2438       !Config Def  = 3.
2439       !Config Help =
2440       !Config Units = NONE   
2441       CALL getin_p('MASS_RATIO_HEART_SAP',mass_ratio_heart_sap)
2442       !
2443       !Config Key  = FRAC_GROWTHRESP
2444       !Config Desc = fraction of GPP which is lost as growth respiration
2445       !Config If   = OK_STOMATE
2446       !Config Def  = 0.28
2447       !Config Help =
2448       !Config Units = NONE 
2449       CALL getin_p('FRAC_GROWTHRESP',frac_growthresp)
2450       !
2451       !Config Key  = TAU_HUM_MONTH
2452       !Config Desc = time scales for phenology and other processes
2453       !Config If   = OK_STOMATE
2454       !Config Def  = 20.
2455       !Config Help =
2456       !Config Units = days [d] 
2457       CALL getin_p('TAU_HUM_MONTH',tau_hum_month)
2458       !
2459       !Config Key  = TAU_HUM_WEEK
2460       !Config Desc = time scales for phenology and other processes
2461       !Config If   = OK_STOMATE
2462       !Config Def  = 7.
2463       !Config Help =
2464       !Config Units = days [d]   
2465       CALL getin_p('TAU_HUM_WEEK',tau_hum_week)
2466       !
2467       !Config Key  = TAU_T2M_MONTH
2468       !Config Desc = time scales for phenology and other processes
2469       !Config If   = OK_STOMATE
2470       !Config Def  = 20.
2471       !Config Help =
2472       !Config Units =   
2473       CALL getin_p('TAU_T2M_MONTH',tau_t2m_month)
2474       !
2475       !Config Key  = TAU_T2M_WEEK
2476       !Config Desc = time scales for phenology and other processes
2477       !Config If   = OK_STOMATE
2478       !Config Def  = 7.
2479       !Config Help =
2480       !Config Units = days [d]   
2481       CALL getin_p('TAU_T2M_WEEK',tau_t2m_week)
2482       !
2483       !Config Key  = TAU_TSOIL_MONTH
2484       !Config Desc = time scales for phenology and other processes
2485       !Config If   = OK_STOMATE
2486       !Config Def  = 20.
2487       !Config Help =
2488       !Config Units =   
2489       CALL getin_p('TAU_TSOIL_MONTH',tau_tsoil_month)
2490       !
2491       !Config Key  = TAU_SOILHUM_MONTH
2492       !Config Desc = time scales for phenology and other processes
2493       !Config If   = OK_STOMATE
2494       !Config Def  = 20.
2495       !Config Help =
2496       !Config Units = days [d]   
2497       CALL getin_p('TAU_SOILHUM_MONTH',tau_soilhum_month)
2498       !
2499       !Config Key  = TAU_GPP_WEEK
2500       !Config Desc = time scales for phenology and other processes
2501       !Config If   = OK_STOMATE
2502       !Config Def  = 7.
2503       !Config Help =
2504       !Config Units = days [d]   
2505       CALL getin_p('TAU_GPP_WEEK',tau_gpp_week)
2506       !
2507       !Config Key  = TAU_GDD
2508       !Config Desc = time scales for phenology and other processes
2509       !Config If   = OK_STOMATE
2510       !Config Def  = 40.
2511       !Config Help =
2512       !Config Units = days [d]   
2513       CALL getin_p('TAU_GDD',tau_gdd)
2514       !
2515       !Config Key  = TAU_NGD
2516       !Config Desc = time scales for phenology and other processes
2517       !Config If   = OK_STOMATE
2518       !Config Def  = 50.
2519       !Config Help =
2520       !Config Units = days [d]   
2521       CALL getin_p('TAU_NGD',tau_ngd)
2522       !
2523       !Config Key  = COEFF_TAU_LONGTERM
2524       !Config Desc = time scales for phenology and other processes
2525       !Config If   = OK_STOMATE
2526       !Config Def  = 3.
2527       !Config Help =
2528       !Config Units = days [d]   
2529       CALL getin_p('COEFF_TAU_LONGTERM',coeff_tau_longterm)
2530       !-
2531       !
2532       !Config Key  = BM_SAPL_CARBRES
2533       !Config Desc =
2534       !Config If   = OK_STOMATE
2535       !Config Def  = 5.
2536       !Config Help =
2537       !Config Units =   
2538       CALL getin_p('BM_SAPL_CARBRES',bm_sapl_carbres)
2539       !
2540       !Config Key  = BM_SAPL_SAPABOVE
2541       !Config Desc =
2542       !Config If   = OK_STOMATE
2543       !Config Def  = 0.5
2544       !Config Help =
2545       !Config Units =   
2546       CALL getin_p('BM_SAPL_SAPABOVE',bm_sapl_sapabove)
2547       !
2548       !Config Key  = BM_SAPL_HEARTABOVE
2549       !Config Desc =
2550       !Config If   = OK_STOMATE
2551       !Config Def  = 2.
2552       !Config Help =
2553       !Config Units =   
2554       CALL getin_p('BM_SAPL_HEARTABOVE',bm_sapl_heartabove)
2555       !
2556       !Config Key  = BM_SAPL_HEARTBELOW
2557       !Config Desc =
2558       !Config If   = OK_STOMATE
2559       !Config Def  = 2.
2560       !Config Help =
2561       !Config Units =   
2562       CALL getin_p('BM_SAPL_HEARTBELOW',bm_sapl_heartbelow)
2563       !
2564       !Config Key  = INIT_SAPL_MASS_LEAF_NAT
2565       !Config Desc =
2566       !Config If   = OK_STOMATE
2567       !Config Def  = 0.1
2568       !Config Help =
2569       !Config Units =   
2570       CALL getin_p('INIT_SAPL_MASS_LEAF_NAT',init_sapl_mass_leaf_nat)
2571       !
2572       !Config Key  = INIT_SAPL_MASS_LEAF_AGRI
2573       !Config Desc =
2574       !Config If   = OK_STOMATE
2575       !Config Def  = 1.
2576       !Config Help =
2577       !Config Units =   
2578       CALL getin_p('INIT_SAPL_MASS_LEAF_AGRI',init_sapl_mass_leaf_agri)
2579       !
2580       !Config Key  = INIT_SAPL_MASS_CARBRES
2581       !Config Desc =
2582       !Config If   = OK_STOMATE
2583       !Config Def  = 5.
2584       !Config Help =
2585       !Config Units =   
2586       CALL getin_p('INIT_SAPL_MASS_CARBRES',init_sapl_mass_carbres)
2587       !
2588       !Config Key  = INIT_SAPL_MASS_ROOT
2589       !Config Desc =
2590       !Config If   = OK_STOMATE
2591       !Config Def  = 0.1
2592       !Config Help =
2593       !Config Units =   
2594       CALL getin_p('INIT_SAPL_MASS_ROOT',init_sapl_mass_root)
2595       !
2596       !Config Key  = INIT_SAPL_MASS_FRUIT
2597       !Config Desc =
2598       !Config If   = OK_STOMATE
2599       !Config Def  = 0.3
2600       !Config Help =
2601       !Config Units =   
2602       CALL getin_p('INIT_SAPL_MASS_FRUIT',init_sapl_mass_fruit)
2603       !
2604       !Config Key  = CN_SAPL_INIT
2605       !Config Desc =
2606       !Config If   = OK_STOMATE
2607       !Config Def  = 0.5
2608       !Config Help =
2609       !Config Units =   
2610       CALL getin_p('CN_SAPL_INIT',cn_sapl_init)
2611       !
2612       !Config Key  = MIGRATE_TREE
2613       !Config Desc =
2614       !Config If   = OK_STOMATE
2615       !Config Def  = 10.*1.E3
2616       !Config Help =
2617       !Config Units =   
2618       CALL getin_p('MIGRATE_TREE',migrate_tree)
2619       !
2620       !Config Key  = MIGRATE_GRASS
2621       !Config Desc =
2622       !Config If   = OK_STOMATE
2623       !Config Def  = 10.*1.E3
2624       !Config Help =
2625       !Config Units =   
2626       CALL getin_p('MIGRATE_GRASS',migrate_grass)
2627       !
2628       !Config Key  = LAI_INITMIN_TREE
2629       !Config Desc =
2630       !Config If   = OK_STOMATE
2631       !Config Def  = 0.3
2632       !Config Help =
2633       !Config Units =   
2634       CALL getin_p('LAI_INITMIN_TREE',lai_initmin_tree)
2635       !
2636       !Config Key  = LAI_INITMIN_GRASS
2637       !Config Desc =
2638       !Config If   = OK_STOMATE
2639       !Config Def  = 0.1
2640       !Config Help =
2641       !Config Units =   
2642       CALL getin_p('LAI_INITMIN_GRASS',lai_initmin_grass)
2643       !
2644       !Config Key  = DIA_COEFF
2645       !Config Desc =
2646       !Config If   = OK_STOMATE
2647       !Config Def  = 4., 0.5
2648       !Config Help =
2649       !Config Units =   
2650       CALL getin_p('DIA_COEFF',dia_coeff)
2651       !
2652       !Config Key  = MAXDIA_COEFF
2653       !Config Desc =
2654       !Config If   = OK_STOMATE
2655       !Config Def  = 100., 0.01
2656       !Config Help =
2657       !Config Units =   
2658       CALL getin_p('MAXDIA_COEFF',maxdia_coeff)
2659       !
2660       !Config Key  = BM_SAPL_LEAF
2661       !Config Desc =
2662       !Config If   = OK_STOMATE
2663       !Config Def  = 4., 4., .8, 5.
2664       !Config Help =
2665       !Config Units =   
2666       CALL getin_p('BM_SAPL_LEAF',bm_sapl_leaf)
2667
2668       !-
2669       ! litter parameters
2670       !-
2671       !
2672       !Config Key  = METABOLIC_REF_FRAC
2673       !Config Desc =
2674       !Config If   = OK_STOMATE
2675       !Config Def  = 0.85 
2676       !Config Help =
2677       !Config Units = NONE   
2678       CALL getin_p('METABOLIC_REF_FRAC',metabolic_ref_frac)
2679       !
2680       !Config Key  = Z_DECOMP
2681       !Config Desc = scaling depth for soil activity
2682       !Config If   = OK_STOMATE
2683       !Config Def  = 0.2
2684       !Config Help =
2685       !Config Units = meters [m]   
2686       CALL getin_p('Z_DECOMP',z_decomp)
2687       !
2688       !Config Key  = CN
2689       !Config Desc = C/N ratio
2690       !Config If   = OK_STOMATE
2691       !Config Def  = 40.,40.,40.,40.,40.,40.,40.,40.
2692       !Config Help =
2693       !Config Units = NONE 
2694       CALL getin_p('CN',CN)
2695       !
2696       !Config Key  = LC
2697       !Config Desc = Lignine/C ratio of the different plant parts
2698       !Config If   = OK_STOMATE
2699       !Config Def  = 0.22, 0.35, 0.35, 0.35, 0.35, 0.22, 0.22, 0.22
2700       !Config Help =
2701       !Config Units = NONE   
2702       CALL getin_p('LC',LC)
2703       !
2704       !Config Key  = FRAC_SOIL_STRUCT_AA
2705       !Config Desc = frac_soil(istructural,iactive,iabove)
2706       !Config If   = OK_STOMATE
2707       !Config Def  = 0.55
2708       !Config Help =
2709       !Config Units = NONE   
2710       CALL getin_p('FRAC_SOIL_STRUCT_AA',frac_soil_struct_aa)
2711       !
2712       !Config Key  = FRAC_SOIL_STRUCT_A
2713       !Config Desc = frac_soil(istructural,iactive,ibelow)
2714       !Config If   = OK_STOMATE
2715       !Config Def  = 0.45
2716       !Config Help =
2717       !Config Units = NONE   
2718       CALL getin_p('FRAC_SOIL_STRUCT_AB',frac_soil_struct_ab)
2719       !
2720       !Config Key  = FRAC_SOIL_STRUCT_SA
2721       !Config Desc = frac_soil(istructural,islow,iabove)
2722       !Config If   = OK_STOMATE
2723       !Config Def  = 0.7 
2724       !Config Help =
2725       !Config Units = NONE   
2726       CALL getin_p('FRAC_SOIL_STRUCT_SA',frac_soil_struct_sa)
2727       !
2728       !Config Key  = FRAC_SOIL_STRUCT_SB
2729       !Config Desc = frac_soil(istructural,islow,ibelow)
2730       !Config If   = OK_STOMATE
2731       !Config Def  = 0.7 
2732       !Config Help =
2733       !Config Units = NONE   
2734       CALL getin_p('FRAC_SOIL_STRUCT_SB',frac_soil_struct_sb)
2735       !
2736       !Config Key  = FRAC_SOIL_METAB_AA
2737       !Config Desc = frac_soil(imetabolic,iactive,iabove)
2738       !Config If   = OK_STOMATE
2739       !Config Def  = 0.45
2740       !Config Help =
2741       !Config Units = NONE   
2742       CALL getin_p('FRAC_SOIL_METAB_AA',frac_soil_metab_aa)
2743       !
2744       !Config Key  = FRAC_SOIL_METAB_AB
2745       !Config Desc = frac_soil(imetabolic,iactive,ibelow)
2746       !Config If   = OK_STOMATE
2747       !Config Def  = 0.45 
2748       !Config Help =
2749       !Config Units = NONE   
2750       CALL getin_p('FRAC_SOIL_METAB_AB',frac_soil_metab_ab)
2751       !
2752       !
2753       !Config Key  = METABOLIC_LN_RATIO
2754       !Config Desc =
2755       !Config If   = OK_STOMATE
2756       !Config Def  = 0.018 
2757       !Config Help =
2758       !Config Units =   
2759       CALL getin_p('METABOLIC_LN_RATIO',metabolic_LN_ratio) 
2760       !
2761       !Config Key  = TAU_METABOLIC
2762       !Config Desc =
2763       !Config If   = OK_STOMATE
2764       !Config Def  = 0.066
2765       !Config Help =
2766       !Config Units = days [d] ?   
2767       CALL getin_p('TAU_METABOLIC',tau_metabolic)
2768       !
2769       !Config Key  = TAU_STRUCT
2770       !Config Desc =
2771       !Config If   = OK_STOMATE
2772       !Config Def  = 0.245
2773       !Config Help =
2774       !Config Units = days [d] ?   
2775       CALL getin_p('TAU_STRUCT',tau_struct)
2776       !
2777       !Config Key  = SOIL_Q10
2778       !Config Desc =
2779       !Config If   = OK_STOMATE
2780       !Config Def  = .69 (=ln2)
2781       !Config Help =
2782       !Config Units =   
2783       CALL getin_p('SOIL_Q10',soil_Q10)
2784       !
2785       !Config Key  = TSOIL_REF
2786       !Config Desc =
2787       !Config If   = OK_STOMATE
2788       !Config Def  = 30.
2789       !Config Help =
2790       !Config Units = Celsius degrees [C]   
2791       CALL getin_p('TSOIL_REF',tsoil_ref)
2792       !
2793       !Config Key  = LITTER_STRUCT_COEF
2794       !Config Desc =
2795       !Config If   = OK_STOMATE
2796       !Config Def  = 3.
2797       !Config Help =
2798       !Config Units =   
2799       CALL getin_p('LITTER_STRUCT_COEF',litter_struct_coef)
2800       !
2801       !Config Key  = MOIST_COEFF
2802       !Config Desc =
2803       !Config If   = OK_STOMATE
2804       !Config Def  = 1.1, 2.4, 0.29
2805       !Config Help =
2806       !Config Units =   
2807       CALL getin_p('MOIST_COEFF',moist_coeff)
2808
2809       !-
2810       ! lpj parameters
2811       !-
2812       !
2813       !Config Key  = FRAC_TURNOVER_DAILY
2814       !Config Desc =
2815       !Config If   = OK_STOMATE
2816       !Config Def  = 0.55
2817       !Config Help =
2818       !Config Units = NONE 
2819       CALL getin_p('FRAC_TURNOVER_DAILY',frac_turnover_daily)   
2820
2821       !-
2822       ! npp parameters
2823       !-
2824       !
2825       !Config Key  = TAX_MAX
2826       !Config Desc = maximum fraction of allocatable biomass used for maintenance respiration
2827       !Config If   = OK_STOMATE
2828       !Config Def  = 0.8
2829       !Config Help =
2830       !Config Units = NONE   
2831       CALL getin_p('TAX_MAX',tax_max) 
2832
2833       !-
2834       ! phenology parameters
2835       !-
2836       !
2837       !Config Key  = ALWAYS_INIT
2838       !Config Desc = take carbon from atmosphere if carbohydrate reserve too small?
2839       !Config If   = OK_STOMATE
2840       !Config Def  = n
2841       !Config Help =
2842       !Config Units = NONE   
2843       CALL getin_p('ALWAYS_INIT',always_init)
2844       !
2845       !Config Key  = MIN_GROWTHINIT_TIME
2846       !Config Desc = minimum time since last beginning of a growing season
2847       !Config If   = OK_STOMATE
2848       !Config Def  = 300.
2849       !Config Help =
2850       !Config Units = days [d] 
2851       CALL getin_p('MIN_GROWTHINIT_TIME',min_growthinit_time)
2852       !
2853       !Config Key  = MOIAVAIL_ALWAYS_TREE
2854       !Config Desc = moisture availability above which moisture tendency doesn't matter
2855       !Config If   = OK_STOMATE
2856       !Config Def  = 1.0
2857       !Config Help =
2858       !Config Units =   
2859       CALL getin_p('MOIAVAIL_ALWAYS_TREE',moiavail_always_tree)
2860       !
2861       !Config Key  = MOIAVAIL_ALWAYS_GRASS
2862       !Config Desc = moisture availability above which moisture tendency doesn't matter
2863       !Config If   = OK_STOMATE
2864       !Config Def  = 0.6
2865       !Config Help =
2866       !Config Units =   
2867       CALL getin_p('MOIAVAIL_ALWAYS_GRASS',moiavail_always_grass)
2868       !
2869       !Config Key  = T_ALWAYS_ADD
2870       !Config Desc = monthly temp. above which temp. tendency doesn't matter
2871       !Config If   = OK_STOMATE
2872       !Config Def  = 10.
2873       !Config Help =
2874       !Config Units = Celsius degrees [C]   
2875       CALL getin_p('T_ALWAYS_ADD',t_always_add)
2876       !
2877       !
2878       !Config Key  = GDDNCD_REF
2879       !Config Desc =
2880       !Config If   = OK_STOMATE
2881       !Config Def  = 603.
2882       !Config Help =
2883       !Config Units =   
2884       CALL getin_p('GDDNCD_REF',gddncd_ref)
2885       !
2886       !Config Key  = GDDNCD_CURVE
2887       !Config Desc =
2888       !Config If   = OK_STOMATE
2889       !Config Def  = 0.0091
2890       !Config Help =
2891       !Config Units =   
2892       CALL getin_p('GDDNCD_CURVE',gddncd_curve)
2893       !
2894       !Config Key  = GDDNCD_OFFSET
2895       !Config Desc =
2896       !Config If   = OK_STOMATE
2897       !Config Def  = 64.
2898       !Config Help =
2899       !Config Units =   
2900       CALL getin_p('GDDNCD_OFFSET',gddncd_offset)
2901       !-
2902       ! prescribe parameters
2903       !-
2904       !
2905       !Config Key  = CN_TREE
2906       !Config Desc =
2907       !Config If   = OK_STOMATE
2908       !Config Def  = 4.
2909       !Config Help =
2910       !Config Units = 
2911       CALL getin_p('CN_TREE',cn_tree)
2912       !
2913       !Config Key  = BM_SAPL_RESCALE
2914       !Config Desc =
2915       !Config If   = OK_STOMATE
2916       !Config Def  = 40.
2917       !Config Help =
2918       !Config Units = 
2919       CALL getin_p('BM_SAPL_RESCALE',bm_sapl_rescale)
2920
2921       !-
2922       ! respiration parameters
2923       !-
2924       !
2925       !Config Key  = MAINT_RESP_MIN_VMAX
2926       !Config Desc =
2927       !Config If   = OK_STOMATE
2928       !Config Def  = 0.3
2929       !Config Help =
2930       !Config Units = 
2931       CALL getin_p('MAINT_RESP_MIN_VMAX',maint_resp_min_vmax) 
2932       !
2933       !Config Key  = MAINT_RESP_COEFF
2934       !Config Desc =
2935       !Config If   = OK_STOMATE
2936       !Config Def  = 1.4
2937       !Config Help =
2938       !Config Units = 
2939       CALL getin_p('MAINT_RESP_COEFF',maint_resp_coeff)
2940
2941       !-
2942       ! soilcarbon parameters
2943       !-
2944       !
2945       !Config Key  = FRAC_CARB_AA
2946       !Config Desc = frac carb coefficients from active pool: depends on clay content
2947       !Config if  = OK_STOMATE
2948       !Config Def  = 0.0
2949       !Config Help = fraction of the active pool going to the active pool
2950       !Config Units = NONE
2951       CALL getin_p('FRAC_CARB_AA',frac_carb_aa)
2952       !
2953       !Config Key  = FRAC_CARB_AP
2954       !Config Desc = frac carb coefficients from active pool: depends on clay content
2955       !Config if  = OK_STOMATE
2956       !Config Def  = 0.004
2957       !Config Help = fraction of the active pool going to the passive pool
2958       !Config Units = NONE
2959       CALL getin_p('FRAC_CARB_AP',frac_carb_ap) 
2960       !
2961       !Config Key  = FRAC_CARB_SS
2962       !Config Desc = frac_carb_coefficients from slow pool
2963       !Config if  = OK_STOMATE
2964       !Config Def  = 0.0
2965       !Config Help = fraction of the slow pool going to the slow pool
2966       !Config Units = NONE
2967       CALL getin_p('FRAC_CARB_SS',frac_carb_ss)
2968       !
2969       !Config Key  = FRAC_CARB_SA
2970       !Config Desc = frac_carb_coefficients from slow pool
2971       !Config if  = OK_STOMATE
2972       !Config Def  = 0.42
2973       !Config Help = fraction of the slow pool going to the active pool
2974       !Config Units = NONE
2975       CALL getin_p('FRAC_CARB_SA',frac_carb_sa)
2976       !
2977       !Config Key  = FRAC_CARB_SP
2978       !Config Desc = frac_carb_coefficients from slow pool
2979       !Config if  = OK_STOMATE
2980       !Config Def  =  0.03
2981       !Config Help = fraction of the slow pool going to the passive pool
2982       !Config Units = NONE
2983       CALL getin_p('FRAC_CARB_SP',frac_carb_sp)
2984       !
2985       !Config Key  = FRAC_CARB_PP
2986       !Config Desc = frac_carb_coefficients from passive pool
2987       !Config if  = OK_STOMATE
2988       !Config Def  = 0.0
2989       !Config Help = fraction of the passive pool going to the passive pool
2990       !Config Units = NONE
2991       CALL getin_p('FRAC_CARB_PP',frac_carb_pp)
2992       !
2993       !Config Key  = FRAC_CARB_PA
2994       !Config Desc = frac_carb_coefficients from passive pool
2995       !Config if  = OK_STOMATE
2996       !Config Def  = 0.45
2997       !Config Help = fraction of the passive pool going to the passive pool
2998       !Config Units = NONE
2999       CALL getin_p('FRAC_CARB_PA',frac_carb_pa)
3000       !
3001       !Config Key  = FRAC_CARB_PS
3002       !Config Desc = frac_carb_coefficients from passive pool
3003       !Config if  = OK_STOMATE
3004       !Config Def  = 0.0
3005       !Config Help = fraction of the passive pool going to the passive pool
3006       !Config Units = NONE
3007       CALL getin_p('FRAC_CARB_PS',frac_carb_ps)
3008       !
3009       !Config Key  = ACTIVE_TO_PASS_CLAY_FRAC
3010       !Config Desc =
3011       !Config if  = OK_STOMATE
3012       !Config Def  =  .68 
3013       !Config Help =
3014       !Config Units = NONE
3015       CALL getin_p('ACTIVE_TO_PASS_CLAY_FRAC',active_to_pass_clay_frac)
3016       !
3017       !Config Key  = CARBON_TAU_IACTIVE
3018       !Config Desc = residence times in carbon pools
3019       !Config if  = OK_STOMATE
3020       !Config Def  =  0.149
3021       !Config Help =
3022       !Config Units = days [d]
3023       CALL getin_p('CARBON_TAU_IACTIVE',carbon_tau_iactive)
3024       !
3025       !Config Key  = CARBON_TAU_ISLOW
3026       !Config Desc = residence times in carbon pools
3027       !Config if  = OK_STOMATE
3028       !Config Def  =  5.48
3029       !Config Help =
3030       !Config Units = days [d]
3031       CALL getin_p('CARBON_TAU_ISLOW',carbon_tau_islow)
3032       !
3033       !Config Key  = CARBON_TAU_IPASSIVE
3034       !Config Desc = residence times in carbon pools
3035       !Config if  = OK_STOMATE
3036       !Config Def  =  241.
3037       !Config Help =
3038       !Config Units = days [d]
3039       CALL getin_p('CARBON_TAU_IPASSIVE',carbon_tau_ipassive)
3040       !
3041       !Config Key  = FLUX_TOT_COEFF
3042       !Config Desc =
3043       !Config if  = OK_STOMATE
3044       !Config Def  = 1.2, 1.4,.75
3045       !Config Help =
3046       !Config Units = days [d]
3047       CALL getin_p('FLUX_TOT_COEFF',flux_tot_coeff)
3048
3049       !-
3050       ! turnover parameters
3051       !-
3052       !
3053       !Config Key  = NEW_TURNOVER_TIME_REF
3054       !Config Desc =
3055       !Config If   = OK_STOMATE
3056       !Config Def  = 20.
3057       !Config Help =
3058       !Config Units = 
3059       CALL getin_p('NEW_TURNOVER_TIME_REF',new_turnover_time_ref)
3060       !
3061       !Config Key  = DT_TURNOVER_TIME
3062       !Config Desc =
3063       !Config If   = OK_STOMATE
3064       !Config Def  = 10.
3065       !Config Help =
3066       !Config Units = 
3067       CALL getin_p('DT_TURNOVER_TIME',dt_turnover_time)
3068       !
3069       !Config Key  = LEAF_AGE_CRIT_TREF
3070       !Config Desc =
3071       !Config If   = OK_STOMATE
3072       !Config Def  = 20.
3073       !Config Help =
3074       !Config Units = 
3075       CALL getin_p('LEAF_AGE_CRIT_TREF',leaf_age_crit_tref)
3076       !
3077       !Config Key  = LEAF_AGE_CRIT_COEFF
3078       !Config Desc =
3079       !Config If   = OK_STOMATE
3080       !Config Def  = 1.5, 0.75, 10.
3081       !Config Help =
3082       !Config Units = 
3083       CALL getin_p('LEAF_AGE_CRIT_COEFF',leaf_age_crit_coeff)
3084
3085       !-
3086       ! vmax parameters
3087       !-
3088       !
3089       !Config Key  = VMAX_OFFSET
3090       !Config Desc = offset (minimum relative vcmax)
3091       !Config If   = OK_STOMATE
3092       !Config Def  = 0.3
3093       !Config Help =
3094       !Config Units = 
3095       CALL getin_p('VMAX_OFFSET',vmax_offset)
3096       !
3097       !Config Key  = LEAFAGE_FIRSTMAX
3098       !Config Desc = leaf age at which vmax attains vcmax_opt (in fraction of critical leaf age)
3099       !Config If   = OK_STOMATE
3100       !Config Def  = 0.03
3101       !Config Help =
3102       !Config Units = 
3103       CALL getin_p('LEAFAGE_FIRSTMAX',leafage_firstmax)
3104       !
3105       !Config Key  = LEAFAGE_LASTMAX
3106       !Config Desc = leaf age at which vmax falls below vcmax_opt (in fraction of critical leaf age)
3107       !Config If   = OK_STOMATE
3108       !Config Def  = 0.5
3109       !Config Help =
3110       !Config Units = 
3111       CALL getin_p('LEAFAGE_LASTMAX',leafage_lastmax)
3112       !
3113       !Config Key  = LEAFAGE_OLD
3114       !Config Desc = leaf age at which vmax attains its minimum (in fraction of critical leaf age)
3115       !Config If   = OK_STOMATE
3116       !Config Def  = 1.
3117       !Config Help =
3118       !Config Units = 
3119       CALL getin_p('LEAFAGE_OLD',leafage_old)
3120
3121       !-
3122       ! season parameters
3123       !-
3124       !
3125       !Config Key  = GPPFRAC_DORMANCE
3126       !Config Desc = rapport maximal GPP/GGP_max pour dormance
3127       !Config If   = OK_STOMATE
3128       !Config Def  = 0.2
3129       !Config Help =
3130       !Config Units = NONE
3131       CALL getin_p('GPPFRAC_DORMANCE',gppfrac_dormance)
3132       !
3133       !Config Key  = MIN_GPP_ALLOWED
3134       !Config Desc = minimum gpp considered as not "lowgpp"
3135       !Config If   = OK_STOMATE
3136       !Config Def  = 0.3
3137       !Config Help =
3138       !Config Units = 
3139       CALL getin_p('MIN_GPP_ALLOWED',min_gpp_allowed)
3140       !
3141       !Config Key  = TAU_CLIMATOLOGY
3142       !Config Desc = tau for "climatologic variables
3143       !Config If   = OK_STOMATE
3144       !Config Def  = 20
3145       !Config Help =
3146       !Config Units = year [y] ? 
3147       CALL getin_p('TAU_CLIMATOLOGY',tau_climatology)
3148       !
3149       !Config Key  = HVC1
3150       !Config Desc = parameters for herbivore activity
3151       !Config If   = OK_STOMATE
3152       !Config Def  = 0.019
3153       !Config Help =
3154       !Config Units = 
3155       CALL getin_p('HVC1',hvc1)
3156       !
3157       !Config Key  = HVC2
3158       !Config Desc = parameters for herbivore activity
3159       !Config If   = OK_STOMATE
3160       !Config Def  = 1.38
3161       !Config Help =
3162       !Config Units = 
3163       CALL getin_p('HVC2',hvc2)
3164       !
3165       !Config Key  = LEAF_FRAC_HVC
3166       !Config Desc = parameters for herbivore activity
3167       !Config If   = OK_STOMATE
3168       !Config Def  = 0.33
3169       !Config Help =
3170       !Config Units = 
3171       CALL getin_p('LEAF_FRAC_HVC',leaf_frac_hvc)
3172       !
3173       !Config Key  = TLONG_REF_MAX
3174       !Config Desc = maximum reference long term temperature
3175       !Config If   = OK_STOMATE
3176       !Config Def  = 303.1
3177       !Config Help =
3178       !Config Units = Kelvin [K] 
3179       CALL getin_p('TLONG_REF_MAX',tlong_ref_max)
3180       !
3181       !Config Key  = TLONG_REF_MIN
3182       !Config Desc = minimum reference long term temperature
3183       !Config If   = OK_STOMATE
3184       !Config Def  = 253.1
3185       !Config Help =
3186       !Config Units = Kelvin [K] 
3187       CALL getin_p('TLONG_REF_MIN',tlong_ref_min)
3188       !
3189       !Config Key  = NCD_MAX_YEAR
3190       !Config Desc =
3191       !Config If   = OK_STOMATE
3192       !Config Def  = 3.
3193       !Config Help =
3194       !Config Units = 
3195       CALL getin_p('NCD_MAX_YEAR',ncd_max_year)
3196       !
3197       !Config Key  = GDD_THRESHOLD
3198       !Config Desc =
3199       !Config If   = OK_STOMATE
3200       !Config Def  = 5.
3201       !Config Help =
3202       !Config Units = 
3203       CALL getin_p('GDD_THRESHOLD',gdd_threshold)
3204       !
3205       !Config Key  = GREEN_AGE_EVER
3206       !Config Desc =
3207       !Config If   = OK_STOMATE
3208       !Config Def  = 2.
3209       !Config Help =
3210       !Config Units = 
3211       CALL getin_p('GREEN_AGE_EVER',green_age_ever)
3212       !
3213       !Config Key  = GREEN_AGE_DEC
3214       !Config Desc =
3215       !Config If   = OK_STOMATE
3216       !Config Def  = 0.5
3217       !Config Help =
3218       !Config Units = 
3219       CALL getin_p('GREEN_AGE_DEC',green_age_dec)
3220       
3221       first_call = .FALSE.
3222       
3223    ENDIF
3224   
3225  END SUBROUTINE getin_stomate_parameters
3226!
3227!=
3228!
3229  SUBROUTINE getin_dgvm_parameters   
3230   
3231    IMPLICIT NONE
3232   
3233    LOGICAL, SAVE ::  first_call = .TRUE.
3234   
3235    IF(first_call) THEN
3236 
3237       !-
3238       ! establish parameters
3239       !-
3240       !
3241       !Config Key  = ESTAB_MAX_TREE
3242       !Config Desc = Maximum tree establishment rate
3243       !Config If   = OK_DGVM
3244       !Config Def  = 0.12
3245       !Config Help =
3246       !Config Units = 
3247       CALL getin_p('ESTAB_MAX_TREE',estab_max_tree)
3248       !
3249       !Config Key  = ESTAB_MAX_GRASS
3250       !Config Desc = Maximum grass establishment rate
3251       !Config If   = OK_DGVM
3252       !Config Def  = 0.12
3253       !Config Help =
3254       !Config Units = 
3255       CALL getin_p('ESTAB_MAX_GRASS',estab_max_grass)
3256       !
3257       !Config Key  = ESTABLISH_SCAL_FACT
3258       !Config Desc =
3259       !Config If   = OK_DGVM
3260       !Config Def  = 15.
3261       !Config Help =
3262       !Config Units = 
3263       CALL getin_p('ESTABLISH_SCAL_FACT',establish_scal_fact)
3264       !
3265       !Config Key  = FPC_CRIT_MAX
3266       !Config Desc =
3267       !Config If   = OK_DGVM
3268       !Config Def  = 0.075
3269       !Config Help =
3270       !Config Units = 
3271       CALL getin_p('FPC_CRIT_MAX',fpc_crit_max)
3272       !
3273       !Config Key  = FPC_CRIT_MIN
3274       !Config Desc =
3275       !Config If   = OK_DGVM
3276       !Config Def  = 0.05
3277       !Config Help =
3278       !Config Units = 
3279       CALL getin_p('FPC_CRIT_MIN',fpc_crit_min)
3280
3281       !-
3282       ! light parameters
3283       !-
3284       !
3285       !Config Key  = GRASS_MERCY
3286       !Config Desc = maximum total number of grass individuals in a closed canopy
3287       !Config If   = OK_DGVM
3288       !Config Def  = 0.01
3289       !Config Help =
3290       !Config Units = 
3291       CALL getin_p('GRASS_MERCY',grass_mercy)
3292       !
3293       !Config Key  = TREE_MERCY
3294       !Config Desc = minimum fraction of trees that survive even in a closed canopy
3295       !Config If   = OK_DGVM
3296       !Config Def  = 0.01
3297       !Config Help =
3298       !Config Units = 
3299       CALL getin_p('TREE_MERCY',tree_mercy)
3300       !
3301       !Config Key  = ANNUAL_INCREASE
3302       !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)?
3303       !Config If   = OK_DGVM
3304       !Config Def  = y
3305       !Config Help =
3306       !Config Units = NONE
3307       CALL getin_p('ANNUAL_INCREASE',annual_increase)
3308       !
3309       !Config Key  = MIN_COVER
3310       !Config Desc = For trees, minimum fraction of crown area occupied
3311       !Config If   = OK_DGVM
3312       !Config Def  = 0.05
3313       !Config Help =
3314       !Config Units = 
3315       CALL getin_p('MIN_COVER',min_cover)
3316
3317       !-
3318       ! pftinout parameters
3319       !-
3320       !
3321       !Config Key  = IND_0
3322       !Config Desc = initial density of individuals
3323       !Config If   = OK_DGVM
3324       !Config Def  = 0.02
3325       !Config Help =
3326       !Config Units = 
3327       CALL getin_p('IND_0',ind_0)
3328       !
3329       !Config Key  = MIN_AVAIL
3330       !Config Desc = minimum availability
3331       !Config If   = OK_DGVM
3332       !Config Def  = 0.01
3333       !Config Help =
3334       !Config Units = 
3335       CALL getin_p('MIN_AVAIL',min_avail)
3336       !
3337       !Config Key  = RIP_TIME_MIN
3338       !Config Desc =
3339       !Config If   = OK_DGVM
3340       !Config Def  = 1.25
3341       !Config Help =
3342       !Config Units = 
3343       CALL getin_p('RIP_TIME_MIN',RIP_time_min)
3344       !
3345       !Config Key  = NPP_LONGTERM_INIT
3346       !Config Desc =
3347       !Config If   = OK_DGVM
3348       !Config Def  = 10.
3349       !Config Help =
3350       !Config Units = 
3351       CALL getin_p('NPP_LONGTERM_INIT',npp_longterm_init)
3352       !
3353       !Config Key  = EVERYWHERE_INIT
3354       !Config Desc =
3355       !Config If   = OK_DGVM
3356       !Config Def  = 0.05
3357       !Config Help =
3358       !Config Units = 
3359       CALL getin_p('EVERYWHERE_INIT',everywhere_init)
3360       
3361       first_call = .FALSE.
3362       
3363    ENDIF
3364   
3365   
3366  END SUBROUTINE getin_dgvm_parameters
3367
3368
3369!--------------------
3370END MODULE constantes
Note: See TracBrowser for help on using the repository browser.