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

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

Add labels for the new externalized parameters. Replace 1000 by mille in the code

File size: 71.1 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  ! Nathalie, introduction d'un albedo moyen, VIS+NIR
511  ! Les valeurs suivantes correspondent a la moyenne des valeurs initiales
512  !  REAL(stnd), DIMENSION(classnb) :: albsoil_vis = (/0.18, 0.165, 0.15, 0.135, 0.12, 0.105, 0.09, 0.075, 0.21/)
513  !  REAL(stnd), DIMENSION(classnb) :: albsoil_nir = (/0.36, 0.33, 0.30, 0.27, 0.24, 0.21, 0.18, 0.15, 0.43/)
514  ! les valeurs retenues accentuent le contraste entre equateur et Sahara.
515  ! On diminue aussi l'albedo des deserts (tous sauf Sahara)
516  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/)
517  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/) 
518
519
520                               !-------------!
521                               ! diffuco.f90 !
522                               !-------------!
523
524  ! 1. Scalar
525
526  INTEGER(i_std), SAVE        :: nlai = 20 ! dimension de tableau
527  ! used in diffuco_trans
528  REAL(r_std), SAVE                :: laimax = 12.
529  REAL(r_std), SAVE                :: xc4_1 = .83
530  REAL(r_std), SAVE                :: xc4_2 = .93
531  ! Set to .TRUE. if you want q_cdrag coming from GCM
532  LOGICAL,SAVE :: ldq_cdrag_from_gcm = .FALSE.
533
534  ! 2; Arrays
535
536  ! 3. Coefficients of equations
537
538  REAL(r_std), SAVE      :: lai_level_depth = .15
539  REAL(r_std), SAVE      :: x1_coef =  0.177
540  REAL(r_std), SAVE      :: x1_Q10 =  0.069
541  REAL(r_std), SAVE      :: quantum_yield =  0.092
542  REAL(r_std), SAVE      :: kt_coef = 0.7     
543  REAL(r_std), SAVE      :: kc_coef = 39.09
544  REAL(r_std), SAVE      :: Ko_Q10 = .085
545  REAL(r_std), SAVE      :: Oa = 210000.
546  REAL(r_std), SAVE      :: Ko_coef =  2.412
547  REAL(r_std), SAVE      :: CP_0 = 42.
548  REAL(r_std), SAVE      :: CP_temp_coef = 9.46 
549  REAL(r_std), SAVE      :: CP_temp_ref = 25.
550  !
551  REAL(r_std), SAVE, DIMENSION(2)  :: rt_coef = (/ 0.8, 1.3 /) 
552  REAL(r_std), SAVE, DIMENSION(2)  :: vc_coef = (/ 0.39, 0.3 /)
553  !
554  ! coefficients of the polynome of degree 5 used inthe equation of coeff_dew_veg
555  REAL(r_std), SAVE, DIMENSION(6)     :: dew_veg_poly_coeff = &
556  & (/ 0.887773, 0.205673, 0.110112, 0.014843,  0.000824,  0.000017 /) 
557
558
559
560                              !-------------!
561                              ! hydrolc.f90 !
562                              !-------------!
563
564  ! 1. Scalar
565
566  !
567  ! Wilting point (Has a numerical role for the moment)
568  REAL(r_std),SAVE :: qwilt = 5.0
569  ! The minimal size we allow for the upper reservoir (m)
570  REAL(r_std),SAVE :: min_resdis = 2.e-5
571  !-
572  ! Diffusion constant for the slow regime
573  ! (This is for the diffusion between reservoirs)
574  REAL(r_std),SAVE :: min_drain = 0.001
575  ! Diffusion constant for the fast regime
576  REAL(r_std),SAVE :: max_drain = 0.1
577  ! The exponential in the diffusion law
578  REAL(r_std),SAVE :: exp_drain = 1.5
579  !-
580  ! Constant in the computation of resistance for bare  soil evaporation
581  REAL(r_std),SAVE :: rsol_cste = 33.E3
582  ! Scaling depth for litter humidity (m)
583  !SZ changed this according to SP from 0.03 to 0.08, 080806
584  REAL(r_std),SAVE :: hcrit_litter=0.08_r_std
585  ! do horizontal diffusion?
586  LOGICAL, SAVE    :: ok_hdiff  = .FALSE.
587
588
589                              !-------------!
590                              ! hydrol.f90  !
591                              !-------------!
592
593
594  ! 1. Scalar
595
596  ! Allowed moisture above mcs (boundary conditions)
597  REAL(r_std), SAVE                :: dmcs = 0.002     
598  ! Allowed moisture below mcr (boundary conditions)
599  REAL(r_std), SAVE                :: dmcr = 0.002 
600
601  ! 2. Arrays
602 
603  !-
604  ! externalise w_time (some bug in hydrol)
605  ! Time weighting for discretisation
606  REAL(r_std),SAVE :: w_time = un
607  !-
608  ! Van genuchten coefficient n
609  REAL(r_std),SAVE,DIMENSION(nstm) :: nvan = (/ 1.89_r_std, 1.56_r_std, 1.31_r_std /)
610  ! Van genuchten coefficient a (mm^{-1})
611  REAL(r_std),SAVE,DIMENSION(nstm) :: avan = (/ 0.0075_r_std, 0.0036_r_std, 0.0019_r_std /) 
612  !-
613  ! Residual soil water content
614  REAL(r_std),SAVE,DIMENSION(nstm) :: mcr = (/ 0.065_r_std, 0.078_r_std, 0.095_r_std /)
615  ! Saturated soil water content
616  REAL(r_std),SAVE,DIMENSION(nstm) :: mcs = (/ 0.41_r_std, 0.43_r_std, 0.41_r_std /)
617  !-
618  ! dpu must be constant over the different soil types
619  ! Hydraulic conductivity Saturation (mm/d)
620  REAL(r_std),SAVE,DIMENSION(nstm) :: ks = (/ 1060.8_r_std, 249.6_r_std, 62.4_r_std /)
621  ! Soil moisture above which transpir is max
622  REAL(r_std),SAVE,DIMENSION(nstm) :: pcent = (/ 0.5_r_std, 0.5_r_std, 0.5_r_std /)
623  ! Max value of the permeability coeff at the bottom of the soil
624  REAL(r_std),SAVE,DIMENSION(nstm) :: free_drain_max = (/ 1.0_r_std, 1.0_r_std, 1.0_r_std /)
625  !-
626  ! Volumetric water content field capacity
627  REAL(r_std),SAVE,DIMENSION(nstm) :: mcf = (/ 0.32_r_std, 0.32_r_std, 0.32_r_std /)
628  ! Volumetric water content Wilting pt
629  REAL(r_std),SAVE,DIMENSION(nstm) :: mcw = (/ 0.10_r_std, 0.10_r_std, 0.10_r_std /)
630  ! Vol. wat. cont. above which albedo is cst
631  REAL(r_std),SAVE,DIMENSION(nstm) :: mc_awet = (/ 0.25_r_std, 0.25_r_std, 0.25_r_std /)
632  ! Vol. wat. cont. below which albedo is cst
633  REAL(r_std),SAVE,DIMENSION(nstm) :: mc_adry = (/ 0.1_r_std, 0.1_r_std, 0.1_r_std /)
634
635
636 
637                              !-------------!
638                              ! routing.f90 !
639                              !-------------!
640
641  ! 1. Scalar
642
643  ! Parameter for the Kassel irrigation parametrization linked to the crops
644  REAL(r_std), SAVE          :: crop_coef = 1.5
645
646
647
648                              !--------------!
649                              ! slowproc.f90 !
650                              !--------------!
651
652
653  ! 1. Scalar
654
655  REAL(r_std), SAVE          :: clayfraction_default = 0.2
656  ! Minimal fraction of mesh a vegetation type can occupy
657  REAL(r_std),SAVE :: min_vegfrac=0.001
658  ! Value for frac_nobio for tests in 0-dim simulations
659  ! laisser ca tant qu'il n'y a que de la glace (pas de lacs)
660  !DS : used in slowproc
661  REAL(r_std),SAVE :: frac_nobio_fixed_test_1 = 0.0
662  ! first year for landuse
663  INTEGER(i_std) , SAVE  :: veget_year_orig = 0
664  ! DS which is the default value? I found also  :: veget_year_orig=282
665  ! only needed for an initial LAI if there is no restart file
666  REAL(r_std), SAVE :: stempdiag_bid = 280. 
667
668  ! 2. Arrays
669
670  ! Default soil texture distribution in the following order :
671  !    sand, loam and clay
672  REAL(r_std),SAVE, DIMENSION(nstm) :: soiltype_default = (/ 0.0, 1.0, 0.0 /)
673
674
675
676
677                           !-----------------------------!
678                           !  STOMATE AND LPJ PARAMETERS !
679                           !-----------------------------!
680
681  !-
682  ! stomate_alloc
683  !-
684  REAL(r_std), PARAMETER  ::  max_possible_lai = 10. 
685  REAL(r_std), PARAMETER  ::  Nlim_Q10 = 10. 
686  !-
687  ! stomate_litter
688  !-
689  REAL(r_std), PARAMETER    :: Q10 = 10.
690  !
691
692! DS 31/03/2011 test new organization
693! List of Externalized Parameters by modules
694
695
696                              !----------------------!
697                              ! lpj_constraints.f90  !
698                              !----------------------!
699
700 
701  ! 1. Scalar
702
703  ! longest sustainable time without regeneration (vernalization)
704  REAL(r_std), SAVE  :: too_long = 5.
705
706
707                              !--------------------!
708                              ! lpj_establish.f90  !
709                              !--------------------!
710
711  ! 1. Scalar
712  ! Maximum tree establishment rate
713  REAL(r_std),SAVE :: estab_max_tree = 0.12
714  ! Maximum grass establishment rate
715  REAL(r_std),SAVE :: estab_max_grass = 0.12 
716 
717  ! 3. Coefficients of equations
718
719  REAL(r_std), SAVE      :: establish_scal_fact = 15.
720  REAL(r_std), SAVE      :: fpc_crit_max = .075
721  REAL(r_std), SAVE      :: fpc_crit_min= .05 
722
723
724                              !---------------!
725                              ! lpj_fire.f90  !
726                              !---------------!
727
728  ! 1. Scalar
729
730  ! Time scale for memory of the fire index (days). Validated for one year in the DGVM.
731  REAL(r_std), SAVE  :: tau_fire = 30. 
732  ! Critical litter quantity for fire
733  REAL(r_std), SAVE  :: litter_crit = 200.
734
735  ! 2. Arrays
736
737  ! What fraction of a burned plant compartment goes into the atmosphere
738  !   (rest into litter)
739  REAL(r_std), SAVE, DIMENSION(nparts) :: co2frac = (/ .95, .95, 0., 0.3, 0., 0., .95, .95 /)
740
741
742  ! 3. Coefficients of equations
743
744  REAL(r_std), SAVE, DIMENSION(3) :: bcfrac_coeff = (/ .3,  1.3,  88.2 /) 
745  REAL(r_std), SAVE, DIMENSION(4)  :: firefrac_coeff = (/ 0.45, 0.8, 0.6, 0.13 /)
746
747
748                              !--------------!
749                              ! lpj_gap.f90  !
750                              !--------------!
751
752  ! 1. Scalar
753! DS 15/06/2011 : the name of the parameter constant_mortality was replaced by its keyword 
754!!$  ! which kind of mortality
755!!$  LOGICAL, SAVE          :: constant_mortality = .TRUE.
756
757  ! 3. Coefficients of equations
758
759  REAL(r_std), SAVE      ::  availability_fact = 0.02
760  REAL(r_std), SAVE      ::  vigour_ref = 0.17
761  REAL(r_std), SAVE      ::  vigour_coeff = 70.
762
763
764                              !----------------!
765                              ! lpj_light.f90  !
766                              !----------------!
767
768  ! 1. Scalar
769 
770  ! maximum total number of grass individuals in a closed canopy
771  REAL(r_std), SAVE  :: grass_mercy = 0.01
772  ! minimum fraction of trees that survive even in a closed canopy
773  REAL(r_std), SAVE  :: tree_mercy = 0.01
774  ! for diagnosis of fpc increase, compare today's fpc to last year's maximum (T) or
775  ! to fpc of last time step (F)?
776  LOGICAL, SAVE     :: annual_increase = .TRUE.
777  ! For trees, minimum fraction of crown area occupied
778  ! (due to its branches etc.)
779  ! This means that only a small fraction of its crown area
780  ! can be invaded by other trees.
781  REAL(r_std),SAVE :: min_cover = 0.05 
782
783
784                              !------------------!
785                              ! lpj_pftinout.f90 !
786                              !------------------!
787
788  ! 1. Scalar
789
790  ! minimum availability
791  REAL(r_std), SAVE  :: min_avail = 0.01
792  ! initial density of individuals
793  REAL(r_std),SAVE :: ind_0 = 0.02
794
795  ! 2. Arrays
796
797  ! 3. Coefficients of equations
798 
799  REAL(r_std), SAVE      :: RIP_time_min = 1.25
800  REAL(r_std), SAVE      :: npp_longterm_init = 10. 
801  REAL(r_std), SAVE      :: everywhere_init = 0.05
802
803
804
805                              !-------------------!
806                              ! stomate_alloc.f90 !
807                              !-------------------!
808
809  ! 1. Scalar
810
811  ! Do we try to reach a minimum reservoir even if we are severely stressed?
812  LOGICAL, SAVE                                        :: ok_minres = .TRUE.
813  ! time (d) to attain the initial foliage using the carbohydrate reserve
814  REAL(r_std), SAVE                                     :: tau_leafinit = 10.
815  ! maximum time (d) during which reserve is used (trees)
816  REAL(r_std), SAVE                                     :: reserve_time_tree = 30.
817  ! maximum time (d) during which reserve is used (grasses)
818  REAL(r_std), SAVE                                     :: reserve_time_grass = 20.
819  ! Standard root allocation
820  REAL(r_std), SAVE                                     :: R0 = 0.3
821  ! Standard sapwood allocation
822  REAL(r_std), SAVE                                     :: S0 = 0.3
823  ! only used in stomate_alloc
824  ! Standard leaf allocation
825  REAL(r_std), SAVE                                    ::  L0 
826  ! Standard fruit allocation
827  REAL(r_std), SAVE                                     :: f_fruit = 0.1
828  ! fraction of sapwood allocation above ground (SHOULD BE CALCULATED !!!!)
829  REAL(r_std), SAVE                                     :: alloc_sap_above_tree = 0.5
830  REAL(r_std), SAVE                                     :: alloc_sap_above_grass = 1.0
831  ! extrema of leaf allocation fraction
832  REAL(r_std), SAVE                                     :: min_LtoLSR = 0.2
833  REAL(r_std), SAVE                                     :: max_LtoLSR = 0.5
834  ! scaling depth for nitrogen limitation (m)
835  REAL(r_std), SAVE                                     :: z_nitrogen = 0.2
836
837
838  ! 2. Arrays
839 
840
841  ! 3. Coefficients of equations
842
843  REAL(r_std), SAVE  :: lai_max_to_happy = 0.5 
844  REAL(r_std), SAVE  ::  Nlim_tref = 25.
845
846
847                              !------------------!
848                              ! stomate_data.f90 !
849                              !------------------!
850  ! 1. Scalar
851
852  !
853  ! 1.1 Parameters for the pipe model
854  !
855  ! crown area = pipe_tune1. stem diameter**(1.6) (Reinicke's theory)
856  REAL(r_std),SAVE :: pipe_tune1 = 100.0
857  ! height=pipe_tune2 * diameter**pipe_tune3
858  REAL(r_std),SAVE :: pipe_tune2 = 40.0
859  REAL(r_std),SAVE :: pipe_tune3 = 0.5
860  ! needed for stem diameter
861  REAL(r_std),SAVE :: pipe_tune4 = 0.3
862  ! Density
863  REAL(r_std),SAVE :: pipe_density = 2.e5
864  ! one more SAVE
865  REAL(r_std),SAVE :: pipe_k1 = 8.e3
866  ! pipe tune exponential coeff
867  REAL(r_std), SAVE      :: pipe_tune_exp_coeff = 1.6 
868
869  !
870  !  1.2 climatic parameters
871  !
872  ! minimum precip, in mm/year
873  REAL(r_std),SAVE :: precip_crit = 100.
874  ! minimum gdd for establishment of saplings
875  REAL(r_std),SAVE :: gdd_crit_estab = 150.
876  ! critical fpc, needed for light competition and establishment
877  REAL(r_std),SAVE :: fpc_crit = 0.95
878
879  !
880  ! 1.3 sapling characteristics
881  !
882  ! alpha's : ?
883  REAL(r_std),SAVE :: alpha_grass = .5
884  REAL(r_std),SAVE :: alpha_tree = 1.
885  ! mass ratio (heartwood+sapwood)/sapwood
886  REAL(r_std), SAVE  :: mass_ratio_heart_sap = 3.
887  ! fraction of GPP which is lost as growth respiration
888  REAL(r_std),SAVE :: frac_growthresp = 0.28 
889
890  !
891  ! 1.4  time scales for phenology and other processes (in days)
892  !
893  REAL(r_std), SAVE    ::  tau_hum_month = 20.           
894  REAL(r_std), SAVE    ::  tau_hum_week = 7.
895  REAL(r_std), SAVE    ::  tau_t2m_month = 20.           
896  REAL(r_std), SAVE    ::  tau_t2m_week = 7.
897  REAL(r_std), SAVE    ::  tau_tsoil_month = 20.         
898  REAL(r_std), SAVE    ::  tau_soilhum_month = 20.       
899  REAL(r_std), SAVE    ::  tau_gpp_week = 7.
900  REAL(r_std), SAVE    ::  tau_gdd = 40.
901  REAL(r_std), SAVE    ::  tau_ngd = 50.
902  REAL(r_std), SAVE    ::  coeff_tau_longterm = 3.
903  REAL(r_std), SAVE    ::  tau_longterm 
904
905  ! 3. Coefficients of equations
906
907  REAL(r_std), SAVE  :: bm_sapl_carbres = 5.
908  REAL(r_std), SAVE  :: bm_sapl_sapabove = 0.5
909  REAL(r_std), SAVE  :: bm_sapl_heartabove = 2.
910  REAL(r_std), SAVE  :: bm_sapl_heartbelow = 2.
911  REAL(r_std), SAVE  :: init_sapl_mass_leaf_nat = 0.1
912  REAL(r_std), SAVE  :: init_sapl_mass_leaf_agri = 1.
913  REAL(r_std), SAVE  :: init_sapl_mass_carbres = 5.
914  REAL(r_std), SAVE  :: init_sapl_mass_root = 0.1
915  REAL(r_std), SAVE  :: init_sapl_mass_fruit = 0.3
916  REAL(r_std), SAVE  :: cn_sapl_init = 0.5
917  REAL(r_std), SAVE  :: migrate_tree = 10.*1.E3
918  REAL(r_std), SAVE  :: migrate_grass = 10.*1.E3
919  REAL(r_std), SAVE  :: lai_initmin_tree = 0.3
920  REAL(r_std), SAVE  :: lai_initmin_grass = 0.1
921  REAL(r_std), SAVE, DIMENSION(2)  :: dia_coeff = (/ 4., 0.5 /)
922  REAL(r_std), SAVE, DIMENSION(2)  :: maxdia_coeff =(/ 100., 0.01/)
923  REAL(r_std), SAVE, DIMENSION(4)  :: bm_sapl_leaf = (/ 4., 4., .8, 5./)
924
925
926
927                              !--------------------!
928                              ! stomate_litter.f90 !
929                              !--------------------!
930
931
932  ! 1. Scalar
933
934  ! scaling depth for soil activity (m)
935  REAL(r_std), SAVE    :: z_decomp = 0.2
936
937  ! 2. Arrays
938
939  ! C/N ratio
940  REAL(r_std), SAVE, DIMENSION(nparts) :: CN = 40.0 
941  ! Lignine/C ratio of the different plant parts
942  REAL(r_std), SAVE, DIMENSION(nparts) :: LC = (/ 0.22, 0.35, 0.35, 0.35, 0.35, 0.22, 0.22, 0.22 /)
943  ! corresponding to frac_soil(istructural,iactive,iabove)
944  REAL(r_std), SAVE      ::  frac_soil_struct_aa = .55
945  ! corresponding to frac_soil(istructural,iactive,ibelow)
946  REAL(r_std), SAVE      :: frac_soil_struct_ab = .45
947  ! corresponding to frac_soil(istructural,islow,iabove)
948  REAL(r_std), SAVE      ::  frac_soil_struct_sa = .7
949  ! corresponding to frac_soil(istructural,islow,ibelow)
950  REAL(r_std), SAVE      ::  frac_soil_struct_sb = .7
951  ! corresponding to frac_soil(imetabolic,iactive,iabove)
952  REAL(r_std), SAVE      ::  frac_soil_metab_aa = .45
953  ! corresponding to frac_soil(imetabolic,iactive,ibelow)
954  REAL(r_std), SAVE      ::  frac_soil_metab_ab = .45
955
956  ! 3. Coefficients of equations
957
958  REAL(r_std), SAVE      :: metabolic_ref_frac = 0.85  ! used by litter and soilcarbon
959  REAL(r_std), SAVE      :: metabolic_LN_ratio = 0.018   
960  REAL(r_std), SAVE      :: tau_metabolic = .066
961  REAL(r_std), SAVE      :: tau_struct = .245
962  REAL(r_std), SAVE      :: soil_Q10 = .69 != ln 2
963  REAL(r_std), SAVE      :: tsoil_ref = 30.
964  REAL(r_std), SAVE      :: litter_struct_coef = 3.
965  REAL(r_std), SAVE, DIMENSION(3)   :: moist_coeff = (/ 1.1,  2.4,  0.29 /)
966
967
968
969                             !-----------------!
970                             ! stomate_lpj.f90 !
971                             !-----------------!
972
973  ! 1. Scalar
974
975  REAL(r_std), SAVE    :: frac_turnover_daily = 0.55
976
977
978                             !-----------------!
979                             ! stomate_npp.f90 !
980                             !-----------------!
981
982  ! 1. Scalar
983
984  ! maximum fraction of allocatable biomass used for maintenance respiration
985  REAL(r_std), SAVE   :: tax_max = 0.8
986
987
988                             !-----------------------!
989                             ! stomate_phenology.f90 !
990                             !-----------------------!
991
992
993
994  ! 1. Scalar
995
996  ! take carbon from atmosphere if carbohydrate reserve too small?
997  LOGICAL, SAVE                                         :: always_init = .FALSE.
998  ! minimum time (d) since last beginning of a growing season
999  REAL(r_std), SAVE                                      :: min_growthinit_time = 300.
1000  ! moisture availability above which moisture tendency doesn't matter
1001  REAL(r_std), SAVE                                   :: moiavail_always_tree = 1.0
1002  REAL(r_std), SAVE                                   :: moiavail_always_grass = 0.6
1003  ! monthly temp. above which temp. tendency doesn't matter
1004  REAL(r_std), SAVE                                   ::  t_always
1005  REAL(r_std), SAVE                                   ::  t_always_add = 10.
1006
1007  ! 3. Coefficients of equations
1008 
1009  REAL(r_std), SAVE      :: gddncd_ref = 603.
1010  REAL(r_std), SAVE      :: gddncd_curve = 0.0091
1011  REAL(r_std), SAVE      :: gddncd_offset = 64.
1012
1013
1014
1015
1016                             !-----------------------!
1017                             ! stomate_prescribe.f90 !
1018                             !-----------------------!
1019
1020  ! 3. Coefficients of equations
1021
1022  REAL(r_std), SAVE      :: cn_tree = 4.
1023  REAL(r_std), SAVE      :: bm_sapl_rescale = 40.
1024
1025
1026
1027                             !------------------!
1028                             ! stomate_resp.f90 !
1029                             !------------------!
1030
1031  ! 3. Coefficients of equations
1032
1033  REAL(r_std), SAVE      :: maint_resp_min_vmax = 0.3 
1034  REAL(r_std), SAVE      :: maint_resp_coeff = 1.4
1035
1036
1037
1038                             !------------------------!
1039                             ! stomate_soilcarbon.f90 !
1040                             !------------------------!
1041
1042  ! 2. Arrays
1043
1044  ! frac_carb_coefficients
1045  ! from active pool: depends on clay content
1046  ! correspnding to  frac_carb(:,iactive,iactive)
1047  REAL(r_std), SAVE      :: frac_carb_aa = 0.0
1048  ! correspnding to  frac_carb(:,iactive,ipassive)
1049  REAL(r_std), SAVE      :: frac_carb_ap = 0.004
1050  !frac_carb(;;iactive,islow) is computed in stomate_soilcarbon.f90
1051  !-
1052  ! from slow pool
1053  ! correspnding to  frac_carb(:,islow,islow)
1054  REAL(r_std), SAVE      :: frac_carb_ss = 0.0 
1055  ! correspnding to  frac_carb(:,islow,iactive)
1056  REAL(r_std), SAVE      :: frac_carb_sa = .42
1057  ! correspnding to  frac_carb(:,islow,ipassive)
1058  REAL(r_std), SAVE      :: frac_carb_sp = .03
1059  !-
1060  ! from passive pool
1061  ! correspnding to  frac_carb(:,ipassive,ipassive)
1062  REAL(r_std), SAVE      :: frac_carb_pp = .0
1063  ! correspnding to  frac_carb(:,ipassive,iactive)
1064  REAL(r_std), SAVE      :: frac_carb_pa = .45
1065  ! correspnding to  frac_carb(:,ipassive,islow)
1066  REAL(r_std), SAVE      :: frac_carb_ps = .0
1067
1068
1069  ! 3. Coefficients of equations
1070
1071  REAL(r_std), SAVE      :: active_to_pass_clay_frac = .68 
1072  !residence times in carbon pools (days)
1073  REAL(r_std), SAVE      :: carbon_tau_iactive = .149
1074  REAL(r_std), SAVE      :: carbon_tau_islow = 5.48
1075  REAL(r_std), SAVE      :: carbon_tau_ipassive = 241.
1076  !
1077  REAL(r_std), SAVE, DIMENSION(3) :: flux_tot_coeff = (/ 1.2, 1.4, .75/)
1078
1079
1080
1081                             !----------------------!
1082                             ! stomate_turnover.f90 !
1083                             !----------------------!
1084
1085  ! 3.Coefficients of equations
1086
1087  REAL(r_std), SAVE      ::  new_turnover_time_ref = 20.
1088  REAL(r_std), SAVE      ::  dt_turnover_time = 10. 
1089  REAL(r_std), SAVE      :: leaf_age_crit_tref = 20.
1090  REAL(r_std), SAVE, DIMENSION(3)   :: leaf_age_crit_coeff = (/ 1.5, 0.75, 10./)
1091
1092
1093
1094
1095                             !------------------!
1096                             ! stomate_vmax.f90 !
1097                             !------------------!
1098
1099  ! 1. Scalar
1100
1101  ! offset (minimum relative vcmax)
1102  REAL(r_std), SAVE                                      :: vmax_offset = 0.3
1103  ! leaf age at which vmax attains vcmax_opt (in fraction of critical leaf age)
1104  REAL(r_std), SAVE                                      :: leafage_firstmax = 0.03
1105  ! leaf age at which vmax falls below vcmax_opt (in fraction of critical leaf age)
1106  REAL(r_std), SAVE                                      :: leafage_lastmax = 0.5
1107  ! leaf age at which vmax attains its minimum (in fraction of critical leaf age)
1108  REAL(r_std), SAVE                                      :: leafage_old = 1.
1109
1110
1111
1112                             !--------------------!
1113                             ! stomate_season.f90 !
1114                             !--------------------!
1115
1116
1117  ! 1. Scalar
1118
1119  ! rapport maximal GPP/GGP_max pour dormance
1120  REAL(r_std), SAVE                                  :: gppfrac_dormance = 0.2
1121  ! minimum gpp considered as not "lowgpp"
1122  REAL(r_std), SAVE                                  :: min_gpp_allowed = 0.3
1123  ! tau (year) for "climatologic variables
1124  REAL(r_std), SAVE                                  :: tau_climatology = 20
1125  ! parameters for herbivore activity
1126  REAL(r_std), SAVE                                  :: hvc1 = 0.019
1127  REAL(r_std), SAVE                                  :: hvc2 = 1.38
1128  REAL(r_std), SAVE                                  :: leaf_frac_hvc =.33
1129  ! maximum reference long term temperature (K)
1130  REAL(r_std),SAVE :: tlong_ref_max = 303.1
1131  ! minimum reference long term temperature (K)
1132  REAL(r_std),SAVE :: tlong_ref_min = 253.1
1133
1134  ! 3. Coefficients of equations
1135
1136  REAL(r_std), SAVE  :: ncd_max_year = 3.
1137  REAL(r_std), SAVE  :: gdd_threshold = 5.
1138  REAL(r_std), SAVE  :: green_age_ever = 2.
1139  REAL(r_std), SAVE  :: green_age_dec = 0.5
1140
1141
1142
1143 CONTAINS
1144
1145   SUBROUTINE activate_sub_models(ok_sechiba,ok_routing, ok_stomate)
1146
1147     IMPLICIT NONE
1148     ! first call
1149     LOGICAL, SAVE ::  first_call = .TRUE.   
1150     ! input
1151     LOGICAL, INTENT(in) :: ok_sechiba
1152     LOGICAL, INTENT(in) :: ok_routing
1153     LOGICAL, INTENT(in) :: ok_stomate   
1154
1155     IF (first_call) THEN
1156
1157        IF(ok_sechiba .AND. ok_routing) THEN
1158           
1159           !Config Key  = DO_IRRIGATION
1160           !Config Desc = Should we compute an irrigation flux
1161           !Config Def  = FALSE
1162           !Config Help = This parameters allows the user to ask the model
1163           !Config        to compute an irigation flux. This performed for the
1164           !Config        on very simple hypothesis. The idea is to have a good
1165           !Config        map of irrigated areas and a simple function which estimates
1166           !Config        the need to irrigate.
1167           CALL getin_p('DO_IRRIGATION', doirrigation)
1168           !
1169           !Config Key  = DO_FLOODPLAINS
1170           !Config Desc = Should we include floodplains
1171           !Config Def  = FALSE
1172           !Config Help = This parameters allows the user to ask the model
1173           !Config        to take into account the flood plains and return
1174           !Config        the water into the soil moisture. It then can go
1175           !Config        back to the atmopshere. This tried to simulate
1176           !Config        internal deltas of rivers.
1177           CALL getin_p('DO_FLOODPLAINS', dofloodplains)
1178       
1179        ENDIF
1180
1181           
1182        IF(ok_stomate) THEN
1183
1184           !Config  Key  = HERBIVORES
1185           !Config  Desc = herbivores allowed?
1186           !Config  Def  = n
1187           !Config  Help = With this variable, you can determine
1188           !Config         if herbivores are activated
1189           CALL getin_p('HERBIVORES', ok_herbivores)
1190           !
1191           !Config  Key  = TREAT_EXPANSION
1192           !Config  Desc = treat expansion of PFTs across a grid cell?
1193           !Config  Def  = n
1194           !Config  Help = With this variable, you can determine
1195           !Config         whether we treat expansion of PFTs across a
1196           !Config         grid cell.
1197           CALL getin_p('TREAT_EXPANSION', treat_expansion)
1198           !
1199           !Config Key  = LPJ_GAP_CONST_MORT
1200           !Config Desc = prescribe mortality if not using DGVM?
1201           !Config Def  = y
1202           !Config Help = set to TRUE if constant mortality is to be activated
1203           !              ignored if DGVM=true!
1204           CALL getin('LPJ_GAP_CONST_MORT', lpj_gap_const_mort)
1205           !
1206           !Config  Key  = HARVEST_AGRI
1207           !Config  Desc = Harvert model for agricol PFTs.
1208           !Config  Def  = y
1209           !Config  Help = Compute harvest above ground biomass for agriculture.
1210           !Config         Change daily turnover.
1211           CALL getin_p('HARVEST_AGRI', harvest_agri)
1212           !
1213           !Config  Key  = FIRE_DISABLE
1214           !Config  Desc = no fire allowed
1215           !Config  Def  = n
1216           !Config  Help = With this variable, you can allow or not
1217           !Config         the estimation of CO2 lost by fire
1218           CALL getin_p('FIRE_DISABLE', disable_fire)
1219
1220        ENDIF
1221
1222        !
1223        ! Check consistency (see later)
1224        !
1225!!$        IF(.NOT.(ok_routing) .AND. (doirrigation .OR. dofloodplains)) THEN
1226!!$           CALL ipslerr (2,'activate_sub_models', &
1227!!$               &     'Problem :you tried to activate the irrigation and floodplains without activating the routing',&
1228!!$               &     'Are you sure ?', &
1229!!$               &     '(check your parameters).')
1230!!$        ENDIF
1231       
1232!!$        IF(.NOT.(ok_stomate) .AND. (ok_herbivores .OR. treat_expansion .OR. lpj_gap_const_mort &
1233!!$            & .OR. harvest_agri .OR. disable_fire)) THEN
1234!!$          CALL ipslerr (2,'activate_sub_models', &
1235!!$               &     'Problem : try to activate the following options : herbivory, treat_expansion, fire,',&
1236!!$               &     'harvest_agri and constant mortality without stomate activated.',&
1237!!$               &     '(check your parameters).')
1238!!$        ENDIF
1239           
1240        first_call =.FALSE.
1241
1242     ENDIF
1243
1244   END SUBROUTINE activate_sub_models
1245!
1246!=
1247!
1248   SUBROUTINE veget_config
1249
1250     ! DS : this subroutine reads the flags previously in slowproc.f90 . As these parameters
1251     !      let the user to configure the vegetation, it is called veget_config.
1252     
1253     IMPLICIT NONE
1254
1255     ! first call
1256     LOGICAL, SAVE ::  first_call = .TRUE.   
1257     
1258     IF (first_call) THEN 
1259
1260        !Config  Key  = AGRICULTURE
1261        !Config  Desc = agriculture allowed?
1262        !Config  Def  = y
1263        !Config  Help = With this variable, you can determine
1264        !Config         whether agriculture is allowed
1265        !
1266        CALL getin_p('AGRICULTURE', agriculture)
1267        !
1268        !Config Key  = IMPOSE_VEG
1269        !Config Desc = Should the vegetation be prescribed
1270        !Config Def  = n
1271        !Config Help = This flag allows the user to impose a vegetation distribution
1272        !Config        and its characterisitcs. It is espacially interesting for 0D
1273        !Config        simulations. On the globe it does not make too much sense as
1274        !Config        it imposes the same vegetation everywhere
1275        !
1276        CALL getin_p('IMPOSE_VEG', impveg)
1277
1278        IF(impveg) THEN
1279           !Config Key  = IMPOSE_SOILT
1280           !Config Desc = Should the soil typ be prescribed
1281           !Config Def  = n
1282           !Config If   = IMPOSE_VEG
1283           !Config Help = This flag allows the user to impose a soil type distribution.
1284           !Config        It is espacially interesting for 0D
1285           !Config        simulations. On the globe it does not make too much sense as
1286           !Config        it imposes the same soil everywhere
1287           CALL getin_p('IMPOSE_SOILT', impsoilt)     
1288        ENDIF
1289
1290        !Config Key  = LAI_MAP
1291        !Config Desc = Read the LAI map
1292        !Config Def  = n
1293        !Config Help = It is possible to read a 12 month LAI map which will
1294        !Config        then be interpolated to daily values as needed.
1295        CALL getin_p('LAI_MAP',read_lai)
1296
1297        IF(read_lai) THEN
1298           !Config Key  = SLOWPROC_LAI_OLD_INTERPOL
1299           !Config Desc = Flag to use old "interpolation" of LAI
1300           !Config If   = LAI_MAP
1301           !Config Def  = FALSE
1302           !Config Help = If you want to recover the old (ie orchidee_1_2 branch)
1303           !Config        "interpolation" of LAI map.
1304           CALL getin_p('SLOWPROC_LAI_OLD_INTERPOL',old_lai)
1305        ENDIF
1306 
1307        !
1308        !Config Key  = LAND_USE
1309        !Config Desc = Read a land_use vegetation map
1310        !Config Def  = n
1311        !Config Help = pft values are needed, max time axis is 293
1312        CALL getin_p('LAND_USE',land_use)
1313
1314        IF(land_use) THEN
1315           !Config Key  = VEGET_REINIT
1316           !Config Desc = booleen to indicate that a new LAND USE file will be used.
1317           !Config If   = LAND_USE
1318           !Config Def  = n
1319           !Config Help = The parameter is used to bypass veget_year count
1320           !Config Help   and reinitialize it with VEGET_YEAR parameter.
1321           !Config Help   Then it is possible to change LAND USE file.
1322           CALL getin_p('VEGET_REINIT', veget_reinit)
1323           !
1324           !Config  Key  = LAND_COVER_CHANGE
1325           !Config  Desc = treat land use modifications
1326           !Config  If   = LAND_USE
1327           !Config  Def  = y
1328           !Config  Help = With this variable, you can use a Land Use map
1329           !Config         to simulate anthropic modifications such as
1330           !Config         deforestation.
1331           CALL getin_p('LAND_COVER_CHANGE', lcchange)
1332           !
1333           !Config Key  = VEGET_YEAR
1334           !Config Desc = Year of the land_use vegetation map to be read (0 == NO TIME AXIS)
1335           !Config If   = LAND_USE
1336           !Config Def  = 282
1337           !Config Help = First year for landuse vegetation (2D map by pft).
1338           !Config Help   If VEGET_YEAR == 0, this means there is no time axis.
1339           CALL getin_p('VEGET_YEAR', veget_year_orig)
1340        ENDIF
1341
1342        IF(.NOT. impveg .AND. .NOT. land_use) THEN
1343           !Config Key  = SLOWPROC_VEGET_OLD_INTERPOL
1344           !Config Desc = Flag to use old "interpolation" of vegetation map.
1345           !Config If   = NOT IMPOSE_VEG and NOT LAND_USE
1346           !Config Def  = FALSE
1347           !Config Help = If you want to recover the old (ie orchidee_1_2 branch)
1348           !Config        "interpolation" of vegetation map.
1349           CALL getin_p('SLOWPROC_VEGET_OLD_INTERPOL',old_veget)
1350         ENDIF 
1351
1352         !
1353         ! Check consistency
1354         !
1355         ! 1. You have to activate agriculture and land_use
1356         IF ( .NOT. agriculture .AND. land_use ) THEN
1357            CALL ipslerr (2,'veget_config', &
1358                 &     'Problem with agriculture desactivated and Land Use activated.',&
1359                 &     'Are you sure ?', &
1360                 &     '(check your parameters).')
1361         ENDIF
1362
1363
1364        first_call = .FALSE.
1365
1366     ENDIF
1367
1368!!$        ! DS : Add warning in case of a wrong configuration (need to be discussed)
1369!!$        ! 2.
1370!!$        IF (.NOT.(read_lai) .AND. old_lai) THEN
1371!!$           CALL ipslerr (2,'veget_config', &
1372!!$               &     'Problem with lai_map desactivated and old_lai activated.',&
1373!!$               &     'Are you sure ?', &
1374!!$               &     '(check your parameters).')
1375!!$        ENDIF
1376!!$   
1377!!$        ! 3.
1378!!$        IF ((impveg .OR. land_use) .AND. old_veget) THEN
1379!!$           CALL ipslerr (2,'veget_config', &
1380!!$                &     'Problem : try to use the old interpolation with a land use map or in impose_veg.',&
1381!!$                &     'Are you sure ?', &
1382!!$                &     '(check your parameters).')
1383!!$        ENDIF
1384!!$
1385!!$        ! 4.
1386!!$        IF ( .NOT.(impveg) .AND. impsoilt) THEN
1387!!$           CALL ipslerr (2,'veget_config', &
1388!!$               &     'Problem : try to activate impose_soilt without activating impose_veg.',&
1389!!$               &     'Are you sure ?', &
1390!!$               &     '(check your parameters).')
1391!!$        ENDIF
1392!!$
1393!!$        ! 5.
1394!!$        IF (.NOT.(land_use) .AND. (veget_reinit)) THEN
1395!!$           CALL ipslerr (2,'veget_config', &
1396!!$                &     'Problem : try to use a land_use map without activating land_use.',&
1397!!$                &     'Are you sure ?', &
1398!!$                &     '(check your parameters).')       
1399!!$        ENDIF
1400!!$
1401!!$        ! 6.
1402!!$        IF (.NOT.(land_use) .AND. lcchange) THEN
1403!!$           CALL ipslerr (2,'veget_config', &
1404!!$                &     'Problem : lcchange is activated without activating land_use.',&
1405!!$                &     'Are you sure ?', &
1406!!$                &     '(check your parameters).')       
1407!!$        ENDIF
1408           
1409   END SUBROUTINE veget_config
1410!
1411!=
1412!
1413   SUBROUTINE getin_sechiba_parameters
1414
1415     IMPLICIT NONE
1416     ! first call
1417     LOGICAL, SAVE ::  first_call = .TRUE.
1418     
1419     IF(first_call) THEN 
1420       
1421        ! Global
1422        ! DS by global I mean the parameters used by two or more modules
1423        ! Example : the common parameters for both hydrology models
1424        CALL getin_p('MAXMASS_GLACIER',maxmass_glacier)
1425        CALL getin_p('SNOWCRI',snowcri)
1426        !
1427        !Interception reservoir coefficient
1428        !Config  Key  = 'SECHIBA_QSINT'
1429        !Config  Desc = Interception reservoir coefficient
1430        !Config  Def  = 0.1
1431        !Config  Help = Transforms leaf area index into size of interception reservoir
1432        !Config         for slowproc_derivvar or stomate
1433        CALL getin_p('SECHIBA_QSINT', qsintcst)
1434        !
1435        !Config Key  = HYDROL_SOIL_DEPTH
1436        !Config Desc = Total depth of soil reservoir
1437        !Config Def  = 2.
1438        CALL getin_p("HYDROL_SOIL_DEPTH", dpu_cste)
1439        !
1440        CALL getin_p('MIN_WIND',min_wind)
1441        CALL getin_p('MAX_SNOW_AGE',max_snow_age)
1442        CALL getin_p('SNOW_TRANS',snow_trans)
1443        CALL getin_p('MX_EAU_EAU',mx_eau_eau)
1444        !-
1445        ! condveg
1446        CALL getin_p('Z0_OVER_HEIGHT',z0_over_height)
1447        CALL getin_p('HEIGHT_DISPLACEMENT',height_displacement)
1448        CALL getin_p('Z0_BARE',z0_bare)
1449        CALL getin_p('Z0_ICE',z0_ice)
1450        CALL getin_p('TCST_SNOWA',tcst_snowa)
1451        CALL getin_p('SNOWCRI_ALB',snowcri_alb)
1452        !
1453        CALL getin_p('VIS_DRY',vis_dry)
1454        CALL getin_p('NIR_DRY',nir_dry)
1455        CALL getin_p('VIS_WET',vis_wet)
1456        CALL getin_p('NIR_WET',nir_wet)
1457        CALL getin_p('ALBSOIL_VIS',albsoil_vis)
1458        CALL getin_p('ALBSOIL_NIR',albsoil_nir)
1459        !-
1460        CALL getin_p('ALB_DEADLEAF',alb_deadleaf)
1461        CALL getin_p('ALB_ICE',alb_ice)
1462        !
1463        ! Get the fixed snow albedo if needed
1464        !
1465        !Config Key  = CONDVEG_SNOWA
1466        !Config Desc = The snow albedo used by SECHIBA
1467        !Config Def  = DEF
1468        !Config Help = This option allows the user to impose a snow albedo.
1469        !Config        Default behaviour is to use the model of snow albedo
1470        !Config        developed by Chalita (1993).
1471        CALL getin_p('CONDVEG_SNOWA', fixed_snow_albedo)
1472        !
1473        !Config Key  = ALB_BARE_MODEL
1474        !Config Desc = Switch bare soil albedo dependent (if TRUE) on soil wetness
1475        !Config Def  = FALSE
1476        !Config Help = If TRUE, the model for bare soil albedo is the old formulation.
1477        !Config        Then it depend on the soil dry or wetness. If FALSE, it is the
1478        !Config        new computation that is taken, it is the mean of soil albedo.
1479        CALL getin_p('ALB_BARE_MODEL', alb_bare_model)
1480        !
1481        !Config Key  = Z0CDRAG_AVE
1482        !Config Desc = Average method for z0
1483        !Config Def  = y
1484        !Config Help = If this flag is set to true (y) then the neutral Cdrag
1485        !Config        is averaged instead of the log(z0). This should be
1486        !Config        the prefered option. We still wish to keep the other
1487        !Config        option so we can come back if needed. If this is
1488        !Config        desired then one should set Z0CDRAG_AVE=n
1489        CALL getin_p('Z0CDRAG_AVE', z0cdrag_ave)
1490        !
1491        !Config Key  = IMPOSE_AZE
1492        !Config Desc = Should the surface parameters be prescribed
1493        !Config Def  = n
1494        !Config Help = This flag allows the user to impose the surface parameters
1495        !Config        (Albedo Roughness and Emissivity). It is espacially interesting for 0D
1496        !Config        simulations. On the globe it does not make too much sense as
1497        !Config        it imposes the same vegetation everywhere
1498        CALL getin_p('IMPOSE_AZE', impaze)
1499        !
1500        IF(impaze) THEN
1501           !
1502           !Config Key  = CONDVEG_Z0
1503           !Config Desc = Surface roughness (m)
1504           !Config Def  = 0.15
1505           !Config If   = IMPOSE_AZE
1506           !Config Help = Surface rougness to be used on the point if a 0-dim version
1507           !Config        of SECHIBA is used. Look at the description of the forcing 
1508           !Config        data for the correct value.
1509           CALL getin_p('CONDVEG_Z0', z0_scal) 
1510           !
1511           !Config Key  = ROUGHHEIGHT
1512           !Config Desc = Height to be added to the height of the first level (m)
1513           !Config Def  = 0.0
1514           !Config If   = IMPOSE_AZE
1515           !Config Help = ORCHIDEE assumes that the atmospheric level height is counted
1516           !Config        from the zero wind level. Thus to take into account the roughness
1517           !Config        of tall vegetation we need to correct this by a certain fraction
1518           !Config        of the vegetation height. This is called the roughness height in
1519           !Config        ORCHIDEE talk.
1520           CALL getin_p('ROUGHHEIGHT', roughheight_scal)
1521           !
1522           !Config Key  = CONDVEG_ALBVIS
1523           !Config Desc = SW visible albedo for the surface
1524           !Config Def  = 0.25
1525           !Config If   = IMPOSE_AZE
1526           !Config Help = Surface albedo in visible wavelengths to be used
1527           !Config        on the point if a 0-dim version of SECHIBA is used.
1528           !Config        Look at the description of the forcing data for
1529           !Config        the correct value.
1530           CALL getin_p('CONDVEG_ALBVIS', albedo_scal(ivis))
1531           !
1532           !Config Key  = CONDVEG_ALBNIR
1533           !Config Desc = SW near infrared albedo for the surface
1534           !Config Def  = 0.25
1535           !Config If   = IMPOSE_AZE
1536           !Config Help = Surface albedo in near infrared wavelengths to be used
1537           !Config        on the point if a 0-dim version of SECHIBA is used.
1538           !Config        Look at the description of the forcing data for
1539           !Config        the correct value.
1540           CALL getin_p('CONDVEG_ALBNIR', albedo_scal(inir))
1541           !
1542           !Config Key  = CONDVEG_EMIS
1543           !Config Desc = Emissivity of the surface for LW radiation
1544           !Config Def  = 1.0
1545           !Config If   = IMPOSE_AZE
1546           !Config Help = The surface emissivity used for compution the LE emission
1547           !Config        of the surface in a 0-dim version. Values range between
1548           !Config        0.97 and 1.. The GCM uses 0.98.
1549           CALL getin_p('CONDVEG_EMIS', emis_scal)
1550        ENDIF
1551        !
1552        !-
1553        ! diffuco
1554        ! DS the rest of diffuco parameters are only read when ok_co2 is set to TRUE
1555        CALL getin_p('NLAI',nlai)
1556        CALL getin_p('LAIMAX',laimax)
1557        CALL getin_p('XC4_1',xc4_1)
1558        CALL getin_p('XC4_2',xc4_2)
1559        CALL getin_p('DEW_VEG_POLY_COEFF',dew_veg_poly_coeff)
1560        !-
1561        ! slowproc
1562        CALL getin_p('CLAYFRACTION_DEFAULT',clayfraction_default)
1563        CALL getin_p('MIN_VEGFRAC',min_vegfrac)
1564        CALL getin_p('SOILTYPE_DEFAULT',soiltype_default)
1565        !
1566        first_call =.FALSE.
1567       
1568     ENDIF
1569     
1570   END SUBROUTINE getin_sechiba_parameters
1571!
1572!=
1573!
1574   ! Subroutine called only if ok_co2 is activated
1575   ! only for diffuco_trans_co2
1576   
1577   SUBROUTINE getin_co2_parameters
1578     
1579     IMPLICIT NONE
1580     
1581     LOGICAL, SAVE ::  first_call = .TRUE.
1582     
1583     IF(first_call) THEN
1584       
1585        CALL getin_p('LAI_LEVEL_DEPTH',lai_level_depth)
1586        CALL getin_p('X1_COEF',x1_coef)
1587        CALL getin_p('X1_Q10',x1_Q10)
1588        CALL getin_p('QUANTUM_YIELD',quantum_yield)
1589        CALL getin_p('KT_COEF',kt_coef)
1590        CALL getin_p('KC_COEF',kc_coef)
1591        CALL getin_p('KO_Q10',Ko_Q10)
1592        CALL getin_p('OA',Oa)
1593        CALL getin_p('KO_COEF',Ko_coef)
1594        CALL getin_p('CP_0',CP_0)
1595        CALL getin_p('CP_TEMP_COEF',cp_temp_coef)
1596        CALL getin_p('CP_TEMP_REF',cp_temp_ref)
1597        CALL getin_p('RT_COEF',rt_coef)
1598        CALL getin_p('VC_COEF',vc_coef)
1599       
1600        first_call =.FALSE.
1601       
1602     ENDIF
1603     
1604   END SUBROUTINE getin_co2_parameters
1605!
1606!=
1607!
1608   SUBROUTINE getin_hydrolc_parameters
1609     
1610     LOGICAL, SAVE ::  first_call = .TRUE.
1611     
1612     IF(first_call) THEN
1613       
1614        CALL getin_p('QWILT',qwilt)
1615        CALL getin_p('MIN_RESDIS',min_resdis)
1616        CALL getin_p('MIN_DRAIN',min_drain)
1617        CALL getin_p('MAX_DRAIN',max_drain)
1618        CALL getin_p('EXP_DRAIN',exp_drain)
1619        CALL getin_p('RSOL_CSTE',rsol_cste)
1620        CALL getin_p('HCRIT_LITTER',hcrit_litter)
1621        !
1622        !Config  Key  = HYDROL_OK_HDIFF
1623        !Config  Desc = do horizontal diffusion?
1624        !Config  Def  = n
1625        !Config  Help = If TRUE, then water can diffuse horizontally between
1626        !Config         the PFTs' water reservoirs.
1627        CALL getin_p('HYDROL_OK_HDIFF',ok_hdiff)         
1628
1629        first_call =.FALSE.
1630       
1631     ENDIF
1632     
1633   END SUBROUTINE getin_hydrolc_parameters
1634   
1635!
1636!=
1637!
1638   ! Subroutine called only if hydrol_cwrr is activated
1639   
1640   SUBROUTINE getin_hydrol_cwrr_parameters
1641     
1642     IMPLICIT NONE
1643     
1644     LOGICAL, SAVE ::  first_call = .TRUE.
1645     
1646     IF (first_call) THEN
1647       
1648        CALL getin_p('W_TIME',w_time)
1649        CALL getin_p('NVAN',nvan)   
1650        CALL getin_p('AVAN',avan)
1651        CALL getin_p('MCR',mcr)
1652        CALL getin_p('MCS',mcs)
1653        CALL getin_p('KS',ks)
1654        CALL getin_p('PCENT',pcent)
1655        CALL getin_p('FREE_DRAIN_MAX',free_drain_max)
1656        CALL getin_p('MCF',mcf)
1657        CALL getin_p('MCW',mcw)
1658        CALL getin_p('MC_AWET',mc_awet)
1659         
1660        first_call =.FALSE.
1661       
1662     ENDIF
1663
1664   END SUBROUTINE getin_hydrol_cwrr_parameters
1665!
1666!=
1667!
1668   SUBROUTINE getin_routing_parameters
1669     
1670     IMPLICIT NONE
1671     
1672     LOGICAL, SAVE ::  first_call = .TRUE.
1673     
1674     IF(first_call) THEN
1675       
1676        CALL getin_p('CROP_COEF',crop_coef)
1677       
1678        first_call =.FALSE.
1679       
1680     ENDIF
1681     
1682   END SUBROUTINE getin_routing_parameters
1683!
1684!=
1685!
1686   SUBROUTINE getin_stomate_parameters
1687     
1688    IMPLICIT NONE
1689   
1690    LOGICAL, SAVE ::  first_call = .TRUE.
1691   
1692    IF(first_call) THEN
1693       
1694       ! constraints_parameters
1695       CALL getin_p('TOO_LONG',too_long)
1696       !-
1697       ! fire parameters
1698       CALL getin_p('TAU_FIRE',tau_fire)
1699       CALL getin_p('LITTER_CRIT',litter_crit)
1700       CALL getin_p('CO2FRAC',co2frac)
1701       CALL getin_p('BCFRAC_COEFF',bcfrac_coeff)
1702       CALL getin_p('FIREFRAC_COEFF',firefrac_coeff)
1703       !-
1704       ! gap parameters (+ lpj_const_mort)
1705       CALL getin_p('AVAILABILITY_FACT', availability_fact) 
1706       CALL getin_p('VIGOUR_REF',vigour_ref)
1707       CALL getin_p('VIGOUR_COEFF',vigour_coeff) 
1708       !-
1709       ! allocation parameters
1710       CALL getin_p('OK_MINRES',ok_minres)
1711       CALL getin_p('TAU_LEAFINIT', tau_leafinit)
1712       CALL getin_p('RESERVE_TIME_TREE',reserve_time_tree)
1713       CALL getin_p('RESERVE_TIME_GRASS',reserve_time_grass)
1714       CALL getin_p('R0',R0)
1715       CALL getin_p('S0',S0)
1716       CALL getin_p('F_FRUIT',f_fruit)
1717       CALL getin_p('ALLOC_SAP_ABOVE_TREE',alloc_sap_above_tree)
1718       CALL getin_p('ALLOC_SAP_ABOVE_GRASS',alloc_sap_above_grass)
1719       CALL getin_p('MIN_LTOLSR',min_LtoLSR)
1720       CALL getin_p('MAX_LTOLSR',max_LtoLSR)
1721       CALL getin_p('Z_NITROGEN',z_nitrogen)
1722       CALL getin_p('LAI_MAX_TO_HAPPY',lai_max_to_happy)
1723       CALL getin_p('NLIM_TREF',Nlim_tref)   
1724       !-
1725       ! data parameters
1726       CALL getin_p('PIPE_TUNE1',pipe_tune1)
1727       CALL getin_p('PIPE_TUNE2',pipe_tune2)   
1728       CALL getin_p('PIPE_TUNE3',pipe_tune3)
1729       CALL getin_p('PIPE_TUNE4',pipe_tune4)
1730       CALL getin_p('PIPE_DENSITY',pipe_density)
1731       CALL getin_p('PIPE_K1',pipe_k1)
1732       CALL getin_p('PIPE_TUNE_EXP_COEFF',pipe_tune_exp_coeff)
1733       !
1734       CALL getin_p('PRECIP_CRIT',precip_crit)
1735       CALL getin_p('GDD_CRIT_ESTAB',gdd_crit_estab) 
1736       CALL getin_p('FPC_CRIT',fpc_crit)
1737       CALL getin_p('ALPHA_GRASS',alpha_grass)
1738       CALL getin_p('ALPHA_TREE',alpha_tree)
1739       !-
1740       CALL getin_p('MASS_RATIO_HEART_SAP',mass_ratio_heart_sap)
1741       CALL getin_p('FRAC_GROWTHRESP',frac_growthresp)
1742       CALL getin_p('TAU_HUM_MONTH',tau_hum_month)
1743       CALL getin_p('TAU_HUM_WEEK',tau_hum_week)
1744       CALL getin_p('TAU_T2M_MONTH',tau_t2m_month)
1745       CALL getin_p('TAU_T2M_WEEK',tau_t2m_week)
1746       CALL getin_p('TAU_TSOIL_MONTH',tau_tsoil_month)
1747       CALL getin_p('TAU_SOILHUM_MONTH',tau_soilhum_month)
1748       CALL getin_p('TAU_GPP_WEEK',tau_gpp_week)
1749       CALL getin_p('TAU_GDD',tau_gdd)
1750       CALL getin_p('TAU_NGD',tau_ngd)
1751       CALL getin_p('COEFF_TAU_LONGTERM',coeff_tau_longterm)
1752       !-
1753       CALL getin_p('BM_SAPL_CARBRES',bm_sapl_carbres)
1754       CALL getin_p('BM_SAPL_SAPABOVE',bm_sapl_sapabove)
1755       CALL getin_p('BM_SAPL_HEARTABOVE',bm_sapl_heartabove)
1756       CALL getin_p('BM_SAPL_HEARTBELOW',bm_sapl_heartbelow)
1757       CALL getin_p('INIT_SAPL_MASS_LEAF_NAT',init_sapl_mass_leaf_nat)
1758       CALL getin_p('INIT_SAPL_MASS_LEAF_AGRI',init_sapl_mass_leaf_agri)
1759       CALL getin_p('INIT_SAPL_MASS_CARBRES',init_sapl_mass_carbres)
1760       CALL getin_p('INIT_SAPL_MASS_ROOT',init_sapl_mass_root)
1761       CALL getin_p('INIT_SAPL_MASS_FRUIT',init_sapl_mass_fruit)
1762       CALL getin_p('CN_SAPL_INIT',cn_sapl_init)
1763       CALL getin_p('MIGRATE_TREE',migrate_tree)
1764       CALL getin_p('MIGRATE_GRASS',migrate_grass)
1765       CALL getin_p('MAXDIA_COEFF',maxdia_coeff)
1766       CALL getin_p('LAI_INITMIN_TREE',lai_initmin_tree)
1767       CALL getin_p('LAI_INITMIN_GRASS',lai_initmin_grass)
1768       CALL getin_p('DIA_COEFF',dia_coeff)
1769       CALL getin_p('MAXDIA_COEFF',maxdia_coeff)
1770       CALL getin_p('BM_SAPL_LEAF',bm_sapl_leaf)
1771       !-
1772       ! litter parameters
1773       CALL getin_p('METABOLIC_REF_FRAC',metabolic_ref_frac)
1774       CALL getin_p('Z_DECOMP',z_decomp)
1775       CALL getin_p('CN',CN)
1776       CALL getin_p('LC',LC)
1777       CALL getin_p('FRAC_SOIL_STRUCT_AA',frac_soil_struct_aa)
1778       CALL getin_p('FRAC_SOIL_STRUCT_AB',frac_soil_struct_ab)
1779       CALL getin_p('FRAC_SOIL_STRUCT_SA',frac_soil_struct_sa)
1780       CALL getin_p('FRAC_SOIL_STRUCT_SB',frac_soil_struct_sb)
1781       CALL getin_p('FRAC_SOIL_METAB_AA',frac_soil_metab_aa)
1782       CALL getin_p('FRAC_SOIL_METAB_AB',frac_soil_metab_ab)
1783       !
1784       CALL getin_p('METABOLIC_LN_RATIO',metabolic_LN_ratio)   
1785       CALL getin_p('TAU_METABOLIC',tau_metabolic)
1786       CALL getin_p('TAU_STRUCT',tau_struct)
1787       CALL getin_p('SOIL_Q10',soil_Q10)
1788       CALL getin_p('TSOIL_REF',tsoil_ref)
1789       CALL getin_p('LITTER_STRUCT_COEF',litter_struct_coef)
1790       CALL getin_p('MOIST_COEFF',moist_coeff)
1791       !-
1792       ! lpj parameters
1793       CALL getin_p('FRAC_TURNOVER_DAILY',frac_turnover_daily)   
1794       !-
1795       ! npp parameters
1796       CALL getin_p('TAX_MAX',tax_max) 
1797       !-
1798       ! phenology parameters
1799       CALL getin_p('ALWAYS_INIT',always_init)
1800       CALL getin_p('MIN_GROWTHINIT_TIME',min_growthinit_time)
1801       CALL getin_p('MOIAVAIL_ALWAYS_TREE',moiavail_always_tree)
1802       CALL getin_p('MOIAVAIL_ALWAYS_GRASS',moiavail_always_grass)
1803       CALL getin_p('T_ALWAYS_ADD',t_always_add)
1804       !
1805       CALL getin_p('GDDNCD_REF',gddncd_ref)
1806       CALL getin_p('GDDNCD_CURVE',gddncd_curve)
1807       CALL getin_p('GDDNCD_OFFSET',gddncd_offset)
1808       !-
1809       ! prescribe parameters
1810       CALL getin_p('CN_TREE',cn_tree)
1811       CALL getin_p('BM_SAPL_RESCALE',bm_sapl_rescale)
1812       !-
1813       ! respiration parameters
1814       CALL getin_p('MAINT_RESP_MIN_VMAX',maint_resp_min_vmax) 
1815       CALL getin_p('MAINT_RESP_COEFF',maint_resp_coeff)
1816       !-
1817       ! soilcarbon parameters 
1818       !-
1819       !
1820       !Config  Key  = FRAC_CARB_AA
1821       !Config  Desc = frac carb coefficients from active pool: depends on clay content
1822       !Config  if  = OK_STOMATE
1823       !Config  Def  = 0.0
1824       !Config  Help = fraction of the active pool going to the active pool
1825       !Config  Units = NONE
1826       CALL getin_p('FRAC_CARB_AA',frac_carb_aa)
1827       !
1828       !Config  Key  = FRAC_CARB_AP
1829       !Config  Desc = frac carb coefficients from active pool: depends on clay content
1830       !Config  if  = OK_STOMATE
1831       !Config  Def  = 0.004
1832       !Config  Help = fraction of the active pool going to the passive pool
1833       !Config  Units = NONE
1834       CALL getin_p('FRAC_CARB_AP',frac_carb_ap) 
1835       !
1836       !Config  Key  = FRAC_CARB_SS
1837       !Config  Desc = frac_carb_coefficients from slow pool
1838       !Config  if  = OK_STOMATE
1839       !Config  Def  = 0.0
1840       !Config  Help = fraction of the slow pool going to the slow pool
1841       !Config  Units = NONE
1842       CALL getin_p('FRAC_CARB_SS',frac_carb_ss)
1843       !
1844       !Config  Key  = FRAC_CARB_SA
1845       !Config  Desc = frac_carb_coefficients from slow pool
1846       !Config  if  = OK_STOMATE
1847       !Config  Def  = 0.42
1848       !Config  Help = fraction of the slow pool going to the active pool
1849       !Config  Units = NONE
1850       CALL getin_p('FRAC_CARB_SA',frac_carb_sa)
1851       !
1852       !Config  Key  = FRAC_CARB_SP
1853       !Config  Desc = frac_carb_coefficients from slow pool
1854       !Config  if  = OK_STOMATE
1855       !Config  Def  =  0.03
1856       !Config  Help = fraction of the slow pool going to the passive pool
1857       !Config  Units = NONE
1858       CALL getin_p('FRAC_CARB_SP',frac_carb_sp)
1859       !
1860       !Config  Key  = FRAC_CARB_PP
1861       !Config  Desc = frac_carb_coefficients from passive pool
1862       !Config  if  = OK_STOMATE
1863       !Config  Def  = 0.0
1864       !Config  Help = fraction of the passive pool going to the passive pool
1865       !Config  Units = NONE
1866       CALL getin_p('FRAC_CARB_PP',frac_carb_pp)
1867       !
1868       !Config  Key  = FRAC_CARB_PA
1869       !Config  Desc = frac_carb_coefficients from passive pool
1870       !Config  if  = OK_STOMATE
1871       !Config  Def  = 0.45
1872       !Config  Help = fraction of the passive pool going to the passive pool
1873       !Config  Units = NONE
1874       CALL getin_p('FRAC_CARB_PA',frac_carb_pa)
1875       !
1876       !Config  Key  = FRAC_CARB_PS
1877       !Config  Desc = frac_carb_coefficients from passive pool
1878       !Config  if  = OK_STOMATE
1879       !Config  Def  = 0.0
1880       !Config  Help = fraction of the passive pool going to the passive pool
1881       !Config  Units = NONE
1882       CALL getin_p('FRAC_CARB_PS',frac_carb_ps)
1883       !
1884       !Config  Key  = ACTIVE_TO_PASS_CLAY_FRAC
1885       !Config  Desc =
1886       !Config  if  = OK_STOMATE
1887       !Config  Def  =  .68 
1888       !Config  Help =
1889       !Config  Units = NONE
1890       CALL getin_p('ACTIVE_TO_PASS_CLAY_FRAC',active_to_pass_clay_frac)
1891       !
1892       !Config  Key  = CARBON_TAU_IACTIVE
1893       !Config  Desc = residence times in carbon pools
1894       !Config  if  = OK_STOMATE
1895       !Config  Def  =  0.149
1896       !Config  Help =
1897       !Config  Units = days (d)
1898       CALL getin_p('CARBON_TAU_IACTIVE',carbon_tau_iactive)
1899       !
1900       !Config  Key  = CARBON_TAU_ISLOW
1901       !Config  Desc = residence times in carbon pools
1902       !Config  if  = OK_STOMATE
1903       !Config  Def  =  5.48
1904       !Config  Help =
1905       !Config  Units = days (d)
1906       CALL getin_p('CARBON_TAU_ISLOW',carbon_tau_islow)
1907       !
1908       !Config  Key  = CARBON_TAU_IPASSIVE
1909       !Config  Desc = residence times in carbon pools
1910       !Config  if  = OK_STOMATE
1911       !Config  Def  =  241.
1912       !Config  Help =
1913       !Config  Units = days (d)
1914       CALL getin_p('CARBON_TAU_IPASSIVE',carbon_tau_ipassive)
1915       !
1916       !Config  Key  = FLUX_TOT_COEFF
1917       !Config  Desc =
1918       !Config  if  = OK_STOMATE
1919       !Config  Def  = 1.2, 1.4,.75
1920       !Config  Help =
1921       !Config  Units =
1922       CALL getin_p('FLUX_TOT_COEFF',flux_tot_coeff)
1923       !-
1924       ! turnover parameters
1925       !-
1926       CALL getin_p('NEW_TURNOVER_TIME_REF',new_turnover_time_ref)
1927       CALL getin_p('DT_TURNOVER_TIME',dt_turnover_time)
1928       CALL getin_p('LEAF_AGE_CRIT_TREF',leaf_age_crit_tref)
1929       CALL getin_p('LEAF_AGE_CRIT_COEFF',leaf_age_crit_coeff)
1930       !-
1931       ! vmax parameters
1932       CALL getin_p('VMAX_OFFSET',vmax_offset)
1933       CALL getin_p('LEAFAGE_FIRSTMAX',leafage_firstmax)
1934       CALL getin_p('LEAFAGE_LASTMAX',leafage_lastmax)
1935       CALL getin_p('LEAFAGE_OLD',leafage_old)
1936       !-
1937       ! season parameters
1938       CALL getin_p('GPPFRAC_DORMANCE',gppfrac_dormance)
1939       CALL getin_p('MIN_GPP_ALLOWED',min_gpp_allowed)
1940       CALL getin_p('TAU_CLIMATOLOGY',tau_climatology)
1941       CALL getin_p('HVC1',hvc1)
1942       CALL getin_p('HVC2',hvc2)
1943       CALL getin_p('LEAF_FRAC_HVC',leaf_frac_hvc)
1944       !
1945       CALL getin_p('TLONG_REF_MAX',tlong_ref_max)
1946       CALL getin_p('TLONG_REF_MIN',tlong_ref_min)
1947       !
1948       CALL getin_p('NCD_MAX_YEAR',ncd_max_year)
1949       CALL getin_p('GDD_THRESHOLD',gdd_threshold)
1950       CALL getin_p('GREEN_AGE_EVER',green_age_ever)
1951       CALL getin_p('GREEN_AGE_DEC',green_age_dec)
1952       
1953       first_call = .FALSE.
1954       
1955    ENDIF
1956   
1957  END SUBROUTINE getin_stomate_parameters
1958!
1959!=
1960!
1961  SUBROUTINE getin_dgvm_parameters   
1962   
1963    IMPLICIT NONE
1964   
1965    LOGICAL, SAVE ::  first_call = .TRUE.
1966   
1967    IF(first_call) THEN
1968       
1969       ! establish parameters
1970       CALL getin_p('ESTAB_MAX_TREE',estab_max_tree)
1971       CALL getin_p('ESTAB_MAX_GRASS',estab_max_grass)
1972       CALL getin_p('ESTABLISH_SCAL_FACT',establish_scal_fact)
1973       CALL getin_p('FPC_CRIT_MAX',fpc_crit_max)
1974       CALL getin_p('FPC_CRIT_MIN',fpc_crit_min)
1975       !-
1976       ! light parameters
1977       CALL getin_p('GRASS_MERCY',grass_mercy)
1978       CALL getin_p('TREE_MERCY',tree_mercy)
1979       CALL getin_p('ANNUAL_INCREASE',annual_increase)
1980       CALL getin_p('MIN_COVER',min_cover)
1981       !-
1982       ! pftinout parameters
1983       CALL getin_p('IND_0',ind_0)
1984       CALL getin_p('MIN_AVAIL',min_avail)
1985       CALL getin_p('RIP_TIME_MIN',RIP_time_min)
1986       CALL getin_p('NPP_LONGTERM_INIT',npp_longterm_init)
1987       CALL getin_p('EVERYWHERE_INIT',everywhere_init)
1988       
1989       first_call = .FALSE.
1990       
1991    ENDIF
1992   
1993   
1994  END SUBROUTINE getin_dgvm_parameters
1995
1996
1997!--------------------
1998END MODULE constantes
Note: See TracBrowser for help on using the repository browser.