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

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

Move pipe_tune_exp_coeff in getin_stomate_parameters (this parameter is used even if dgvm is not activated, in stomate prescribe)

File size: 45.7 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 ioipsl
11!-
12  IMPLICIT NONE
13!-
14
15!-------------------------
16!  ORCHIDEE CONSTANTS
17!------------------------
18
19  !----------------
20  ! Global
21  !----------------
22
23  ! Unit for output messages
24  INTEGER(i_std), SAVE :: numout = 6
25  !-
26  ! To set for more printing
27  LOGICAL,SAVE :: long_print = .FALSE.
28  !-
29  ! One of the most frequent problems is a temperature out of range
30  ! we provide here a way to catch that in the calling procedure. (JP)
31  LOGICAL,PARAMETER :: diag_qsat = .TRUE.
32
33!!$  ! One of the most frequent problems is a temperature out of range
34!!$  ! we provide here a way to catch that in the calling procedure. (JP)
35!!$  LOGICAL,SAVE :: diag_qsat = .TRUE.
36
37  !-
38  ! Selects the type of output for the model.
39  ! Value is read from run.def in intersurf_history.
40  LOGICAL           :: almaoutput
41
42  !-
43  ! One day in seconds
44  REAL(r_std),SAVE :: one_day
45  ! One year in seconds
46  REAL(r_std),SAVE :: one_year
47
48  ! undef integer for integer arrays
49  INTEGER(i_std), PARAMETER :: undef_integer = 999999999
50
51  ! Specific value if no restart value
52  REAL(r_std),SAVE :: val_exp = 999999.
53
54  ! Special value for stomate
55  REAL(r_std),PARAMETER :: undef = -9999.
56
57  ! Epsilon to detect a near zero floating point
58  REAL(r_std),PARAMETER :: min_sechiba = 1.E-8_r_std
59  ! The undef value used in SECHIBA
60  REAL(r_std),PARAMETER :: undef_sechiba = 1.E+20_r_std
61
62  ! Epsilon to detect a near zero floating point
63  REAL(r_std),PARAMETER :: min_stomate = 1.E-8_r_std
64  ! some large value (for stomate)
65  REAL(r_std),PARAMETER :: large_value = 1.E33_r_std
66
67  !-
68  TYPE control_type
69    LOGICAL :: river_routing
70    LOGICAL :: hydrol_cwrr
71    LOGICAL :: ok_sechiba
72    LOGICAL :: ok_co2
73    LOGICAL :: ok_stomate
74    LOGICAL :: ok_dgvm
75    LOGICAL :: stomate_watchout
76    LOGICAL :: ok_pheno
77  END TYPE control_type
78
79  ! Flags that (de)activate parts of the model
80  TYPE(control_type),SAVE :: control
81  !-
82
83!---------------------------------------
84!  DIMENSIONING AND INDICES PARAMETERS
85!---------------------------------------
86
87  !----------------
88  ! qsat_moisture
89  !----------------
90  ! Number of other surface types: land ice (lakes,cities, ...)
91  INTEGER(i_std),PARAMETER :: nnobio=1
92  !-
93  ! Index for land ice (see nnobio)
94  INTEGER(i_std),PARAMETER :: iice = 1
95
96  !-------
97  ! Soil
98  !-------
99  ! Number of soil level
100  INTEGER(i_std),PARAMETER :: ngrnd=7
101  !-
102  ! Number of diagnostic levels in the soil
103  INTEGER(i_std),PARAMETER :: nbdl=11
104  !MM : if you want to compare hydrology variables with old TAG 1.6 and lower,
105  !     you must set the Number of diagnostic levels in the soil to 6 :
106  !  INTEGER(i_std),PARAMETER :: nbdl=6
107  !-
108  ! Number of levels in CWRR
109  INTEGER(i_std),PARAMETER :: nslm=11
110  !-
111  ! Number of soil types
112  INTEGER(i_std),PARAMETER :: nstm = 3
113  !-
114  ! Dimensioning parameter for the soil color numbers and their albedo
115  INTEGER(i_std), PARAMETER :: classnb = 9
116
117  !-
118  ! Diagnostic variables
119  !-
120  ! The lower limit of the layer on which soil moisture (relative)
121  ! and temperature are going to be diagnosed.
122  ! These variables are made for transfering the information
123  ! to the biogeophyical processes modelled in STOMATE.
124  !-
125  REAL(r_std),DIMENSION(nbdl),SAVE :: diaglev 
126
127  !-----------------
128  ! STOMATE - LPJ
129  !-----------------
130
131  ! NV080800 Name of STOMATE forcing file
132  CHARACTER(LEN=100) :: stomate_forcing_name='NONE'
133  !-
134  ! NV080800 Name of soil forcing file
135  CHARACTER(LEN=100) :: stomate_Cforcing_name='NONE'
136  !-
137  INTEGER(i_std),SAVE :: forcing_id
138  !-
139  ! leaf age discretisation ( 1 = no discretisation )
140  INTEGER(i_std),PARAMETER :: nleafages = 4
141  !
142  !----------------------------
143  ! litter fractions: indices
144  !----------------------------
145  INTEGER(i_std),PARAMETER :: ileaf = 1
146  INTEGER(i_std),PARAMETER :: isapabove = 2
147  INTEGER(i_std),PARAMETER :: isapbelow = 3
148  INTEGER(i_std),PARAMETER :: iheartabove = 4
149  INTEGER(i_std),PARAMETER :: iheartbelow = 5
150  INTEGER(i_std),PARAMETER :: iroot = 6
151  INTEGER(i_std),PARAMETER :: ifruit = 7
152  INTEGER(i_std),PARAMETER :: icarbres = 8
153  INTEGER(i_std),PARAMETER :: nparts = 8
154  !
155  !-------------------------------------
156  ! indices for assimilation parameters
157  !-------------------------------------
158  INTEGER(i_std),PARAMETER :: itmin = 1
159  INTEGER(i_std),PARAMETER :: itopt = 2
160  INTEGER(i_std),PARAMETER :: itmax = 3
161  INTEGER(i_std),PARAMETER :: ivcmax = 4
162  INTEGER(i_std),PARAMETER :: ivjmax = 5
163  INTEGER(i_std),PARAMETER :: npco2 = 5
164  !-
165  !------------------------------------------
166  ! trees and litter: indices for the parts of heart- and sapwood above
167  !   and below the ground
168  !-----------------------------------------
169  INTEGER(i_std),PARAMETER :: iabove = 1
170  INTEGER(i_std),PARAMETER :: ibelow = 2
171  INTEGER(i_std),PARAMETER :: nlevs = 2
172  !-
173  !---------------------------------------------------
174  ! litter: indices for metabolic and structural part
175  !--------------------------------------------------
176  INTEGER(i_std),PARAMETER :: imetabolic = 1
177  INTEGER(i_std),PARAMETER :: istructural = 2
178  INTEGER(i_std),PARAMETER :: nlitt = 2
179  !
180  !-----------------------
181  ! carbon pools: indices
182  !-----------------------
183  INTEGER(i_std),PARAMETER :: iactive = 1
184  INTEGER(i_std),PARAMETER :: islow = 2
185  INTEGER(i_std),PARAMETER :: ipassive = 3
186  INTEGER(i_std),PARAMETER :: ncarb = 3
187
188
189!------------------------------
190!  MATH AND PHYSICS CONSTANTS
191!------------------------------
192
193  !------------------------------------
194  ! 1 . Maths and numerical constants
195  !------------------------------------
196  ! pi
197  REAL(r_std), PARAMETER :: pi = 4.*ATAN(1.)
198  ! e
199  REAL(r_std),PARAMETER :: euler = 2.71828182846
200  !-
201  ! Integer constant set to zero
202  INTEGER(i_std), PARAMETER :: zero_int = 0
203  !-
204  ! Numerical constant set to 0
205  REAL(r_std),PARAMETER :: zero = 0._r_std
206  ! Numerical constant set to 1/2
207  REAL(r_std),PARAMETER :: undemi = 0.5_r_std
208  ! Numerical constant set to 1
209  REAL(r_std),PARAMETER :: un = 1._r_std
210  ! Numerical constant set to -1
211  REAL(r_std),PARAMETER :: moins_un = -1._r_std
212  ! Numerical constant set to 2
213  REAL(r_std),PARAMETER :: deux = 2._r_std
214  ! Numerical constant set to 3
215  REAL(r_std),PARAMETER :: trois = 3._r_std
216  ! Numerical constant set to 4
217  REAL(r_std),PARAMETER :: quatre = 4._r_std
218  ! Numerical constant set to 5
219  REAL(r_std),PARAMETER :: cinq = 5._r_std
220  ! Numerical constant set to 6
221  REAL(r_std),PARAMETER :: six = 6._r_std
222  ! Numerical constant set to 8
223  REAL(r_std),PARAMETER :: huit = 8._r_std
224  ! Numerical constant set to 1000
225  REAL(r_std),PARAMETER :: mille = 1000._r_std
226
227  !---------------
228  ! 2 . Physics
229  !---------------
230  !
231  ! radius of the Earth (m)
232  REAL(r_std), PARAMETER :: R_Earth = 6378000.
233  ! standard pressure
234  REAL(r_std), PARAMETER :: pb_std = 1013. 
235  !-
236  ! Freezing point
237  REAL(r_std),PARAMETER :: ZeroCelsius = 273.15
238  !-
239  ! 0 degre Celsius in degre Kelvin
240  REAL(r_std),PARAMETER :: tp_00=273.15
241  !-
242  ! Latent heat of sublimation
243  REAL(r_std),PARAMETER :: chalsu0 = 2.8345E06
244  ! Latent heat of evaporation
245  REAL(r_std),PARAMETER :: chalev0 = 2.5008E06
246  ! Latent heat of fusion
247  REAL(r_std),PARAMETER :: chalfu0 = chalsu0-chalev0
248  !-
249  ! Stefan-Boltzman constant
250  REAL(r_std),PARAMETER :: c_stefan = 5.6697E-8
251  ! Specific heat of air
252  REAL(r_std),PARAMETER :: cp_air = 1004.675
253  ! Constante molere
254  REAL(r_std),PARAMETER :: cte_molr = 287.05
255  ! Kappa
256  REAL(r_std),PARAMETER :: kappa = cte_molr/cp_air
257  ! in -- Kg/mole
258  REAL(r_std),PARAMETER :: msmlr_air = 28.964E-03
259  ! in -- Kg/mole
260  REAL(r_std),PARAMETER :: msmlr_h2o = 18.02E-03
261  !-
262  REAL(r_std),PARAMETER :: cp_h2o = &
263  & cp_air*(quatre*msmlr_air)/( 3.5_r_std*msmlr_h2o)
264  !-
265  REAL(r_std),PARAMETER :: cte_molr_h2o = cte_molr/quatre
266  !-
267  REAL(r_std),PARAMETER :: retv = msmlr_air/msmlr_h2o-un
268  !-
269  REAL(r_std),PARAMETER :: rvtmp2 = cp_h2o/cp_air-un
270  !-
271  REAL(r_std),PARAMETER :: cepdu2 = (0.1_r_std) **2
272  !-
273  ! Van Karmann Constante
274  REAL(r_std),PARAMETER :: ct_karman = 0.35_r_std
275  !-
276  ! g acceleration
277  REAL(r_std),PARAMETER :: cte_grav = 9.80665_r_std
278  !-
279  ! Transform pascal into hectopascal
280  REAL(r_std),PARAMETER :: pa_par_hpa = 100._r_std
281
282      !-------------------------------------
283      ! 2.1. Climatic constantes
284      !-------------------------------------
285      !
286      !$$ To externalise or not ?
287      !
288      ! Constantes of the Louis scheme
289      REAL(r_std),PARAMETER :: cb = cinq
290      REAL(r_std),PARAMETER :: cc = cinq
291      REAL(r_std),PARAMETER :: cd = cinq
292      !-
293      ! Constant in the computation of surface resistance
294      REAL(r_std),PARAMETER :: rayt_cste = 125.
295      !-
296      ! DS :both used in diffuco.f90
297      ! Constant in the computation of surface resistance
298      REAL(r_std),PARAMETER :: defc_plus=23.E-3
299      ! Constant in the computation of surface resistance
300      REAL(r_std),PARAMETER :: defc_mult=1.5
301
302      !-----------------------------------------
303      ! 2.2 Soil thermodynamics constants
304      !-----------------------------------------
305      !
306      ! Average Thermal Conductivity of soils
307      REAL(r_std),PARAMETER :: so_cond = 1.5396
308      ! Average Heat capacity of soils
309      REAL(r_std),PARAMETER :: so_capa = 2.0514e+6
310      !-
311      ! Values taken from : PIELKE,'MESOSCALE METEOROLOGICAL MODELING',P.384
312      ! Dry soil heat capacity was decreased and conductivity increased.
313      !-
314      ! To externalise ?
315      ! Dry soil Heat capacity of soils
316      !*REAL(r_std),PARAMETER :: so_capa_dry = 1.35e+6
317      REAL(r_std),PARAMETER :: so_capa_dry = 1.80e+6
318      ! Dry soil Thermal Conductivity of soils
319      !*REAL(r_std),PARAMETER :: so_cond_dry = 0.28
320      REAL(r_std),PARAMETER :: so_cond_dry = 0.40
321      !-
322      ! Wet soil Heat capacity of soils
323      REAL(r_std),PARAMETER :: so_capa_wet = 3.03e+6
324      ! Wet soil Thermal Conductivity of soils
325      REAL(r_std),PARAMETER :: so_cond_wet = 1.89
326      !-
327      ! Thermal Conductivity of snow
328      REAL(r_std),PARAMETER :: sn_cond = 0.3
329      ! Snow density for the soil thermodynamics
330      REAL(r_std),PARAMETER :: sn_dens = 330.0
331      ! Heat capacity for snow
332      REAL(r_std),PARAMETER :: sn_capa = 2100.0_r_std*sn_dens
333
334
335!-----------------------------------------------
336!----------------------------------------------
337! SCALAR PARAMETERS EXTERNALIZED
338!----------------------------------------------
339!-----------------------------------------------
340!------------------------------------------
341!  SECHIBA, SOIL AND VEGETATION parameters
342!-----------------------------------------
343
344  !!---------------------------------------
345  !! Parameters for soil type distribution
346  !!---------------------------------------
347  !
348  ! Default soil texture distribution in the following order :
349  !    sand, loam and clay
350  REAL(r_std),SAVE, DIMENSION(nstm) :: soiltype_default = (/ 0.0, 1.0, 0.0 /)
351
352  !!----------------------------------------
353  !! Constantes from the Choisnel hydrology
354  !!----------------------------------------
355  !
356  ! Wilting point (Has a numerical role for the moment)
357  REAL(r_std),SAVE :: qwilt = 5.0
358  ! Total depth of soil reservoir (for hydrolc)
359  REAL(r_std),SAVE :: dpu_cste =  deux
360  ! The minimal size we allow for the upper reservoir (m)
361  REAL(r_std),SAVE :: min_resdis = 2.e-5
362  !-
363  ! Diffusion constant for the slow regime
364  ! (This is for the diffusion between reservoirs)
365  REAL(r_std),SAVE :: min_drain = 0.001
366  ! Diffusion constant for the fast regime
367  REAL(r_std),SAVE :: max_drain = 0.1
368  ! The exponential in the diffusion law
369  REAL(r_std),SAVE :: exp_drain = 1.5
370  !-
371  ! Transforms leaf area index into size of interception reservoir
372  REAL(r_std),SAVE      :: qsintcst = 0.1
373  ! Maximum quantity of water (Kg/M3)
374  REAL(r_std),SAVE :: mx_eau_eau = 150.
375  !-
376  ! Constant in the computation of resistance for bare  soil evaporation
377  REAL(r_std),SAVE :: rsol_cste = 33.E3
378  ! Scaling depth for litter humidity (m)
379  !SZ changed this according to SP from 0.03 to 0.08, 080806
380  REAL(r_std),SAVE :: hcrit_litter=0.08_r_std
381
382  !!---------------------------------------------------
383  !! Specific parameters for the CWRR hydrology module
384  !!---------------------------------------------------
385  !
386!!$ DS To externalise ?
387!!$ advice of MM : to put in hydrol
388  ! CWRR linearisation
389  INTEGER(i_std),PARAMETER :: imin = 1
390  ! number of interval for CWRR
391  INTEGER(i_std),PARAMETER :: nbint = 100
392  ! number of points for CWRR
393  INTEGER(i_std),PARAMETER :: imax = nbint+1
394  !-
395  ! externalise w_time (some bug in hydrol)
396  ! Time weighting for discretisation
397  REAL(r_std),SAVE :: w_time = un
398  !-
399  ! Van genuchten coefficient n
400  REAL(r_std),SAVE,DIMENSION(nstm) :: nvan = (/ 1.89_r_std, 1.56_r_std, 1.31_r_std /)
401  ! Van genuchten coefficient a (mm^{-1})
402  REAL(r_std),SAVE,DIMENSION(nstm) :: avan = (/ 0.0075_r_std, 0.0036_r_std, 0.0019_r_std /) 
403  !-
404  ! Residual soil water content
405  REAL(r_std),SAVE,DIMENSION(nstm) :: mcr = (/ 0.065_r_std, 0.078_r_std, 0.095_r_std /)
406  ! Saturated soil water content
407  REAL(r_std),SAVE,DIMENSION(nstm) :: mcs = (/ 0.41_r_std, 0.43_r_std, 0.41_r_std /)
408  ! Total depth of soil reservoir (m)
409  REAL(r_std),SAVE,DIMENSION(nstm) :: dpu =  (/ 2.0_r_std, 2.0_r_std, 2.0_r_std /)
410  !-
411  ! dpu must be constant over the different soil types
412  ! Hydraulic conductivity Saturation (mm/d)
413  REAL(r_std),SAVE,DIMENSION(nstm) :: ks = (/ 1060.8_r_std, 249.6_r_std, 62.4_r_std /)
414  ! Soil moisture above which transpir is max
415  REAL(r_std),SAVE,DIMENSION(nstm) :: pcent = (/ 0.5_r_std, 0.5_r_std, 0.5_r_std /)
416  ! Max value of the permeability coeff at the bottom of the soil
417  REAL(r_std),SAVE,DIMENSION(nstm) :: free_drain_max = (/ 1.0_r_std, 1.0_r_std, 1.0_r_std /)
418  !-
419  ! Volumetric water content field capacity
420  REAL(r_std),SAVE,DIMENSION(nstm) :: mcf = (/ 0.32_r_std, 0.32_r_std, 0.32_r_std /)
421  ! Volumetric water content Wilting pt
422  REAL(r_std),SAVE,DIMENSION(nstm) :: mcw = (/ 0.10_r_std, 0.10_r_std, 0.10_r_std /)
423  ! Vol. wat. cont. above which albedo is cst
424  REAL(r_std),SAVE,DIMENSION(nstm) :: mc_awet = (/ 0.25_r_std, 0.25_r_std, 0.25_r_std /)
425  ! Vol. wat. cont. below which albedo is cst
426  REAL(r_std),SAVE,DIMENSION(nstm) :: mc_adry = (/ 0.1_r_std, 0.1_r_std, 0.1_r_std /)
427
428
429  !!-----------------------------------------------------
430  !! Vegetation parameters (previously in constantes_veg)
431  !!-----------------------------------------------------
432  !
433  ! Value for frac_nobio for tests in 0-dim simulations
434  ! laisser ca tant qu'il n'y a que de la glace (pas de lacs)
435  !DS : used in slowproc
436  REAL(r_std),SAVE :: frac_nobio_fixed_test_1 = 0.0
437  !-
438  ! Is veget_ori array stored in restart file
439!!$ DS: Where is it used ?
440  !  LOGICAL,PARAMETER :: ldveget_ori_on_restart = .TRUE.
441  !-
442  ! Set to .TRUE. if you want q_cdrag coming from GCM
443  ! used in diffuco
444  LOGICAL,SAVE :: ldq_cdrag_from_gcm = .FALSE.
445  !-
446  ! allow agricultural PFTs
447  LOGICAL,SAVE :: agriculture = .TRUE.
448  !-
449  ! The maximum mass (kg/m^2) of a glacier.
450  REAL(r_std),SAVE :: maxmass_glacier = 3000.
451  !-
452  ! Minimal fraction of mesh a vegetation type can occupy
453  REAL(r_std),SAVE :: min_vegfrac=0.001
454  !-
455!!$ DS not used in the code ?
456  ! Limit of air temperature for snow
457  REAL(r_std),SAVE :: tsnow=273.
458  !-
459  ! Sets the amount above which only sublimation occures [Kg/m^2]
460  REAL(r_std),SAVE :: snowcri=1.5
461  ! Critical value for computation of snow albedo [Kg/m^2]
462  REAL(r_std),SAVE :: snowcri_alb=10.
463  ! Lower limit of snow amount
464  REAL(r_std),SAVE :: sneige
465  !-
466  ! The minimum wind
467  REAL(r_std),SAVE :: min_wind = 0.1
468  ! bare soil roughness length (m)
469  REAL(r_std),SAVE :: z0_bare = 0.01
470  ! ice roughness length (m)
471  REAL(r_std),SAVE :: z0_ice = 0.001
472  !-
473  ! Time constant of the albedo decay of snow
474  REAL(r_std),SAVE :: tcst_snowa = cinq
475  ! Maximum period of snow aging
476  REAL(r_std),SAVE :: max_snow_age = 50._r_std
477  ! Transformation time constant for snow (m)
478  REAL(r_std),SAVE :: snow_trans = 0.3_r_std
479  !-
480  ! albedo of dead leaves, VIS+NIR
481  REAL(r_std),DIMENSION(2),SAVE :: alb_deadleaf = (/ .12, .35/)
482  ! albedo of ice, VIS+NIR
483  REAL(r_std),DIMENSION(2),SAVE :: alb_ice = (/ .60, .20/)
484
485  !!--------------------------------
486  !!  SECHIBA specific parameters
487  !!--------------------------------
488  !
489  !-
490  ! condveg
491  !-
492  ! to get z0 from height
493  REAL(r_std), SAVE  :: z0_over_height = un/16.
494  ! Magic number which relates the height to the displacement height.
495  REAL(r_std), SAVE  :: height_displacement = 0.75
496  !-
497  ! diffuco
498  !-
499  INTEGER(i_std), SAVE        :: nlai = 20 ! dimension de tableau
500  ! used in diffuco_trans
501  REAL(r_std), SAVE                :: laimax = 12.
502  REAL(r_std), SAVE                :: xc4_1 = .83
503  REAL(r_std), SAVE                :: xc4_2 = .93
504  !-
505  ! hydrol.
506  !-
507  ! Allowed moisture above mcs (boundary conditions)
508  REAL(r_std), SAVE                :: dmcs = 0.002     
509  ! Allowed moisture below mcr (boundary conditions)
510  REAL(r_std), SAVE                :: dmcr = 0.002 
511  !-
512  ! routing
513  !-
514  ! Parameter for the Kassel irrigation parametrization linked to the crops
515  REAL(r_std), SAVE          :: crop_coef = 1.5
516  !-
517  ! slowproc
518  !-
519  REAL(r_std), SAVE          :: clayfraction_default = 0.2
520 
521!-----------------------------
522!  STOMATE AND LPJ PARAMETERS
523!-----------------------------
524  !
525  !-
526  ! lpj_constraints
527  !-
528  ! longest sustainable time without regeneration (vernalization)
529  REAL(r_std), SAVE  :: too_long = 5.
530  !
531  !-
532  ! lpj_fire
533  !-
534  ! Time scale for memory of the fire index (days). Validated for one year in the DGVM.
535  REAL(r_std), SAVE  :: tau_fire = 30. 
536  ! Critical litter quantity for fire
537  REAL(r_std), SAVE  :: litter_crit = 200.
538  !
539  !-
540  ! lpj_light
541  !-
542  ! maximum total number of grass individuals in a closed canopy
543  REAL(r_std), SAVE  :: grass_mercy = 0.01
544  ! minimum fraction of trees that survive even in a closed canopy
545  REAL(r_std), SAVE  :: tree_mercy = 0.01
546  ! for diagnosis of fpc increase, compare today's fpc to last year's maximum (T) or
547  ! to fpc of last time step (F)?
548  LOGICAL, SAVE     :: annual_increase = .TRUE.
549  !
550  !-
551  ! lpj_pftinout
552  !-
553  ! minimum availability
554  REAL(r_std), SAVE  :: min_avail = 0.01
555  !
556  !-
557  ! stomate_alloc
558  !-
559  ! Do we try to reach a minimum reservoir even if we are severely stressed?
560  LOGICAL, SAVE                                        :: ok_minres = .TRUE.
561  ! time (d) to attain the initial foliage using the carbohydrate reserve
562  REAL(r_std), SAVE                                     :: tau_leafinit = 10.
563  ! maximum time (d) during which reserve is used (trees)
564  REAL(r_std), SAVE                                     :: reserve_time_tree = 30.
565  ! maximum time (d) during which reserve is used (grasses)
566  REAL(r_std), SAVE                                     :: reserve_time_grass = 20.
567  ! Standard root allocation
568  REAL(r_std), SAVE                                     :: R0 = 0.3
569  ! Standard sapwood allocation
570  REAL(r_std), SAVE                                     :: S0 = 0.3
571  ! only used in stomate_alloc
572  ! Standard leaf allocation
573  REAL(r_std), SAVE                                    ::  L0 
574  ! Standard fruit allocation
575  REAL(r_std), SAVE                                     :: f_fruit = 0.1
576  ! fraction of sapwood allocation above ground (SHOULD BE CALCULATED !!!!)
577  REAL(r_std), SAVE                                     :: alloc_sap_above_tree = 0.5
578  REAL(r_std), SAVE                                     :: alloc_sap_above_grass = 1.0
579  ! extrema of leaf allocation fraction
580  REAL(r_std), SAVE                                     :: min_LtoLSR = 0.2
581  REAL(r_std), SAVE                                     :: max_LtoLSR = 0.5
582  ! scaling depth for nitrogen limitation (m)
583  REAL(r_std), SAVE                                     :: z_nitrogen = 0.2
584  !
585  !-
586  ! stomate_data
587  !-
588  !!-------------------------------
589  !! Parameters for the pipe model
590  !!------------------------------
591  !-
592  ! crown area = pipe_tune1. stem diameter**(1.6) (Reinicke's theory)
593  REAL(r_std),SAVE :: pipe_tune1 = 100.0
594  ! height=pipe_tune2 * diameter**pipe_tune3
595  REAL(r_std),SAVE :: pipe_tune2 = 40.0
596  REAL(r_std),SAVE :: pipe_tune3 = 0.5
597  ! needed for stem diameter
598  REAL(r_std),SAVE :: pipe_tune4 = 0.3
599  ! Density
600  REAL(r_std),SAVE :: pipe_density = 2.e5
601  ! one more SAVE
602  REAL(r_std),SAVE :: pipe_k1 = 8.e3
603  !
604  !-
605  ! Maximum tree establishment rate
606  REAL(r_std),SAVE :: estab_max_tree = 0.12
607  ! Maximum grass establishment rate
608  REAL(r_std),SAVE :: estab_max_grass = 0.12
609  ! initial density of individuals
610  REAL(r_std),SAVE :: ind_0 = 0.02
611  ! For trees, minimum fraction of crown area occupied
612  ! (due to its branches etc.)
613  ! This means that only a small fraction of its crown area
614  ! can be invaded by other trees.
615  REAL(r_std),SAVE :: min_cover = 0.05 
616  !-
617  ! alpha's : ?
618  REAL(r_std),SAVE :: alpha_grass = .5
619  REAL(r_std),SAVE :: alpha_tree = 1.
620  !-
621  ! maximum reference long term temperature (K)
622  REAL(r_std),SAVE :: tlong_ref_max = 303.1
623  ! minimum reference long term temperature (K)
624  REAL(r_std),SAVE :: tlong_ref_min = 253.1
625  !
626  !! LOGICAL
627  !-
628  ! Do we treat PFT expansion across a grid point after introduction?
629  ! default = .FALSE.
630  LOGICAL,SAVE :: treat_expansion = .FALSE.
631  !
632  ! herbivores?
633  LOGICAL,SAVE :: ok_herbivores = .FALSE.
634  !
635  ! harvesting ?
636  LOGICAL,SAVE :: harvest_agri = .TRUE.
637  !!----------------------
638  !! climatic parameters
639  !!---------------------
640  !
641  ! minimum precip, in mm/year
642  REAL(r_std),SAVE :: precip_crit = 100.
643  ! minimum gdd for establishment of saplings
644  REAL(r_std),SAVE :: gdd_crit_estab = 150.
645  ! critical fpc, needed for light competition and establishment
646  REAL(r_std),SAVE :: fpc_crit = 0.95
647  !-
648  ! fraction of GPP which is lost as growth respiration
649  REAL(r_std),SAVE :: frac_growthresp = 0.28
650  !
651  !-
652  ! mass ratio (heartwood+sapwood)/sapwood
653  REAL(r_std), SAVE  :: mass_ratio_heart_sap = 3.
654  !
655  !!---------------------------------------------------------
656  ! time scales for phenology and other processes (in days)
657  !!---------------------------------------------------------
658  !
659  REAL(r_std), SAVE    ::  tau_hum_month = 20.           
660  REAL(r_std), SAVE    ::  tau_hum_week = 7.
661  REAL(r_std), SAVE    ::  tau_t2m_month = 20.           
662  REAL(r_std), SAVE    ::  tau_t2m_week = 7.
663  REAL(r_std), SAVE    ::  tau_tsoil_month = 20.         
664  REAL(r_std), SAVE    ::  tau_soilhum_month = 20.       
665  REAL(r_std), SAVE    ::  tau_gpp_week = 7.
666  REAL(r_std), SAVE    ::  tau_gdd = 40.
667  REAL(r_std), SAVE    ::  tau_ngd = 50.
668  REAL(r_std), SAVE    ::  coeff_tau_longterm = 3.
669  ! used in stomate_data and in stomate_season
670  REAL(r_std), SAVE    ::  tau_longterm 
671  !
672  !-
673  ! stomate_litter
674  !-
675  ! scaling depth for soil activity (m)
676  REAL(r_std), SAVE    :: z_decomp = 0.2
677  !
678  !-
679  ! stomate_lpj
680  !-
681  REAL(r_std), SAVE    :: frac_turnover_daily = 0.55
682  !
683  !-
684  ! stomate_npp
685  !-
686  ! maximum fraction of allocatable biomass used for maintenance respiration
687  REAL(r_std), SAVE   :: tax_max = 0.8
688  !
689  !-
690  ! stomate_phenology
691  !-
692  ! take carbon from atmosphere if carbohydrate reserve too small?
693  LOGICAL, SAVE                                         :: always_init = .FALSE.
694  ! minimum time (d) since last beginning of a growing season
695  REAL(r_std), SAVE                                      :: min_growthinit_time = 300.
696  ! moisture availability above which moisture tendency doesn't matter
697  REAL(r_std), SAVE                                   :: moiavail_always_tree = 1.0
698  REAL(r_std), SAVE                                   :: moiavail_always_grass = 0.6
699  ! monthly temp. above which temp. tendency doesn't matter
700  REAL(r_std), SAVE                                   ::  t_always
701  REAL(r_std), SAVE                                   ::  t_always_add = 10.
702  !
703  !-
704  ! stomate_season
705  !-
706  ! rapport maximal GPP/GGP_max pour dormance
707  REAL(r_std), SAVE                                  :: gppfrac_dormance = 0.2
708  ! minimum gpp considered as not "lowgpp"
709  REAL(r_std), SAVE                                  :: min_gpp_allowed = 0.3
710  ! tau (year) for "climatologic variables
711  REAL(r_std), SAVE                                  :: tau_climatology = 20
712  ! parameters for herbivore activity
713  REAL(r_std), SAVE                                  :: hvc1 = 0.019
714  REAL(r_std), SAVE                                  :: hvc2 = 1.38
715  REAL(r_std), SAVE                                  :: leaf_frac_hvc =.33
716  !
717  !-
718  ! stomate_vmax
719  !-
720  ! offset (minimum relative vcmax)
721  REAL(r_std), SAVE                                      :: vmax_offset = 0.3
722  ! leaf age at which vmax attains vcmax_opt (in fraction of critical leaf age)
723  REAL(r_std), SAVE                                      :: leafage_firstmax = 0.03
724  ! leaf age at which vmax falls below vcmax_opt (in fraction of critical leaf age)
725  REAL(r_std), SAVE                                      :: leafage_lastmax = 0.5
726  ! leaf age at which vmax attains its minimum (in fraction of critical leaf age)
727  REAL(r_std), SAVE                                      :: leafage_old = 1.
728
729
730!--------------------------
731!--------------------------
732! ARRAYS-PARAMETERS
733!--------------------------
734!--------------------------
735  !-
736  ! condveg
737  !-
738  !   The correspondance table for the soil color numbers and their albedo
739  !
740  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/)
741  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/) 
742  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/) 
743  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/)
744  !   
745  ! Nathalie, introduction d'un albedo moyen, VIS+NIR
746  ! Les valeurs suivantes correspondent a la moyenne des valeurs initiales
747  !  REAL(stnd), DIMENSION(classnb) :: albsoil_vis = (/0.18, 0.165, 0.15, 0.135, 0.12, 0.105, 0.09, 0.075, 0.21/)
748  !  REAL(stnd), DIMENSION(classnb) :: albsoil_nir = (/0.36, 0.33, 0.30, 0.27, 0.24, 0.21, 0.18, 0.15, 0.43/)
749  ! les valeurs retenues accentuent le contraste entre equateur et Sahara.
750  ! On diminue aussi l'albedo des deserts (tous sauf Sahara)
751  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/)
752  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/)
753
754  !-
755  ! lpj_fire
756  !-
757
758  ! What fraction of a burned plant compartment goes into the atmosphere
759  !   (rest into litter)
760  REAL(r_std), SAVE, DIMENSION(nparts) :: co2frac = (/ .95, .95, 0., 0.3, 0., 0., .95, .95 /)
761
762  !-
763  ! stomate_litter
764  !-
765
766  ! C/N ratio
767  REAL(r_std), SAVE, DIMENSION(nparts) :: CN = 40.0 
768  ! Lignine/C ratio of the different plant parts
769  REAL(r_std), SAVE, DIMENSION(nparts) :: LC = (/ 0.22, 0.35, 0.35, 0.35, 0.35, 0.22, 0.22, 0.22 /)
770  ! corresponding to frac_soil(istructural,iactive,iabove)
771  REAL(r_std), SAVE      ::  frac_soil_struct_aa = .55
772  ! corresponding to frac_soil(istructural,iactive,ibelow)
773  REAL(r_std), SAVE      :: frac_soil_struct_ab = .45
774  ! corresponding to frac_soil(istructural,islow,iabove)
775  REAL(r_std), SAVE      ::  frac_soil_struct_sa = .7
776  ! corresponding to frac_soil(istructural,islow,ibelow)
777  REAL(r_std), SAVE      ::  frac_soil_struct_sb = .7
778  ! corresponding to frac_soil(imetabolic,iactive,iabove)
779  REAL(r_std), SAVE      ::  frac_soil_metab_aa = .45
780  ! corresponding to frac_soil(imetabolic,iactive,ibelow)
781  REAL(r_std), SAVE      ::  frac_soil_metab_ab = .45
782  !-
783  ! stomate_soilcarbon
784  !-
785  ! frac_carb_coefficients
786  ! from active pool: depends on clay content
787  ! correspnding to  frac_carb(:,iactive,iactive)
788  REAL(r_std), SAVE      :: frac_carb_aa = 0.0
789  ! correspnding to  frac_carb(:,iactive,ipassive)
790  REAL(r_std), SAVE      :: frac_carb_ap = 0.004
791  !frac_carb(;;iactive,islow) is computed in stomate_soilcarbon.f90
792  !-
793  ! from slow pool
794  ! correspnding to  frac_carb(:,islow,islow)
795  REAL(r_std), SAVE      :: frac_carb_ss = 0.0 
796  ! correspnding to  frac_carb(:,islow,iactive)
797  REAL(r_std), SAVE      :: frac_carb_sa = .42
798  ! correspnding to  frac_carb(:,islow,ipassive)
799  REAL(r_std), SAVE      :: frac_carb_sp = .03
800  !-
801  ! from passive pool
802  ! correspnding to  frac_carb(:,ipassive,ipassive)
803  REAL(r_std), SAVE      :: frac_carb_pp = .0
804  ! correspnding to  frac_carb(:,ipassive,iactive)
805  REAL(r_std), SAVE      :: frac_carb_pa = .45
806  ! correspnding to  frac_carb(:,ipassive,islow)
807  REAL(r_std), SAVE      :: frac_carb_ps = .0
808 
809
810!----------------------------------------
811!---------------------------------------
812! COEFFICIENTS OF EQUATIONS
813!-------------------------------------
814!---------------------------------------
815
816  !---------
817  ! SECHIBA
818  !---------
819  !-
820  ! diffuco
821  !-
822  REAL(r_std),PARAMETER :: Tetens_1 = 0.622   
823  REAL(r_std),PARAMETER :: Tetens_2 = 0.378
824  REAL(r_std),PARAMETER :: std_ci_frac = 0.667
825  REAL(r_std),PARAMETER :: alpha_j = 0.8855
826  REAL(r_std),PARAMETER :: curve_assim = 0.7
827  REAL(r_std),PARAMETER :: WJ_coeff1 = 4.5
828  REAL(r_std),PARAMETER :: WJ_coeff2 = 10.5
829  REAL(r_std),PARAMETER :: Vc_to_Rd_ratio = 0.011
830  REAL(r_std),PARAMETER :: O2toCO2_stoechio = 1.6
831  REAL(r_std),PARAMETER :: mmol_to_m_1 = 0.0244
832  REAL(r_std),PARAMETER  :: RG_to_PAR = 0.5 
833  REAL(r_std),PARAMETER  :: W_to_mmol = 4.6 ! W_to_mmol * RG_to_PAR = 2.3
834  !
835  REAL(r_std), SAVE      :: lai_level_depth = .15
836  REAL(r_std), SAVE      :: x1_coef =  0.177
837  REAL(r_std), SAVE      :: x1_Q10 =  0.069
838  REAL(r_std), SAVE      :: quantum_yield =  0.092
839  REAL(r_std), SAVE      :: kt_coef = 0.7     
840  REAL(r_std), SAVE      :: kc_coef = 39.09
841  REAL(r_std), SAVE      :: Ko_Q10 = .085
842  REAL(r_std), SAVE      :: Oa = 210000.
843  REAL(r_std), SAVE      :: Ko_coef =  2.412
844  REAL(r_std), SAVE      :: CP_0 = 42.
845  REAL(r_std), SAVE      :: CP_temp_coef = 9.46 
846  REAL(r_std), SAVE      :: CP_temp_ref = 25.
847  !
848  REAL(r_std), SAVE, DIMENSION(2)  :: rt_coef = (/ 0.8, 1.3 /) 
849  REAL(r_std), SAVE, DIMENSION(2)  :: vc_coef = (/ 0.39, 0.3 /)
850  !
851  ! coefficients of the polynome of degree 5 used inthe equation of coeff_dew_veg
852  REAL(r_std), SAVE, DIMENSION(6)     :: dew_veg_poly_coeff = &
853  & (/ 0.887773, 0.205673, 0.110112, 0.014843,  0.000824,  0.000017 /) 
854 
855  !---------
856  ! LPJ
857  !---------
858  !-
859  ! lpj_crown
860  !-
861  REAL(r_std), SAVE      :: pipe_tune_exp_coeff = 1.6 
862  !
863  !-
864  ! lpj_establish
865  !-
866  REAL(r_std), SAVE      :: establish_scal_fact = 15.
867  REAL(r_std), SAVE      :: fpc_crit_max = .075
868  REAL(r_std), SAVE      :: fpc_crit_min= .05 
869  !
870  !-
871  ! lpj_fire
872  !-
873  REAL(r_std), SAVE, DIMENSION(3) :: bcfrac_coeff = (/ .3,  1.3,  88.2 /) 
874  REAL(r_std), SAVE, DIMENSION(4)  :: firefrac_coeff = (/ 0.45, 0.8, 0.6, 0.13 /)
875  !
876  !-
877  ! lpj_gap
878  !-
879  REAL(r_std), SAVE      ::  availability_fact = 0.02
880  REAL(r_std), SAVE      ::  vigour_ref = 0.17
881  REAL(r_std), SAVE      ::  vigour_coeff = 70. 
882  !-
883  ! lpj_pftinout
884  !-
885  REAL(r_std), SAVE      :: RIP_time_min = 1.25
886  REAL(r_std), SAVE      :: npp_longterm_init = 10. 
887  REAL(r_std), SAVE      :: everywhere_init = 0.05
888  !
889
890  !---------
891  ! STOMATE
892  !---------
893  !-
894  ! stomate_alloc
895  !-
896  REAL(r_std), PARAMETER  ::  max_possible_lai = 10. 
897  REAL(r_std), PARAMETER  ::  Nlim_Q10 = 10. 
898  !
899  REAL(r_std), SAVE      :: lai_max_to_happy = 0.5 
900  REAL(r_std), SAVE  ::  Nlim_tref = 25.
901  !
902  !-
903  ! stomate_data
904  !-
905  REAL(r_std), SAVE  :: bm_sapl_carbres = 5.
906  REAL(r_std), SAVE  :: bm_sapl_sapabove = 0.5
907  REAL(r_std), SAVE  :: bm_sapl_heartabove = 2.
908  REAL(r_std), SAVE  :: bm_sapl_heartbelow = 2.
909  REAL(r_std), SAVE  :: init_sapl_mass_leaf_nat = 0.1
910  REAL(r_std), SAVE  :: init_sapl_mass_leaf_agri = 1.
911  REAL(r_std), SAVE  :: init_sapl_mass_carbres = 5.
912  REAL(r_std), SAVE  :: init_sapl_mass_root = 0.1
913  REAL(r_std), SAVE  :: init_sapl_mass_fruit = 0.3
914  REAL(r_std), SAVE  :: cn_sapl_init = 0.5
915  REAL(r_std), SAVE  :: migrate_tree = 10.*1.E3
916  REAL(r_std), SAVE  :: migrate_grass = 10.*1.E3
917  REAL(r_std), SAVE  :: lai_initmin_tree = 0.3
918  REAL(r_std), SAVE  :: lai_initmin_grass = 0.1
919  REAL(r_std), SAVE, DIMENSION(2)  :: dia_coeff = (/ 4., 0.5 /)
920  REAL(r_std), SAVE, DIMENSION(2)  :: maxdia_coeff =(/ 100., 0.01/)
921  REAL(r_std), SAVE, DIMENSION(4)  :: bm_sapl_leaf = (/ 4., 4., .8, 5./)
922  !
923  !-
924  ! stomate_litter
925  !-
926  REAL(r_std), PARAMETER    :: Q10 = 10.
927  !
928  REAL(r_std), SAVE      :: metabolic_ref_frac = 0.85
929  REAL(r_std), SAVE      :: metabolic_LN_ratio = 0.018   
930  REAL(r_std), SAVE      :: tau_metabolic = .066
931  REAL(r_std), SAVE      :: tau_struct = .245
932  REAL(r_std), SAVE      :: soil_Q10 = .69 != ln 2
933  REAL(r_std), SAVE      :: tsoil_ref = 30.
934  REAL(r_std), SAVE      :: litter_struct_coef = 3.
935  REAL(r_std), SAVE, DIMENSION(3)   :: moist_coeff = (/ 1.1,  2.4,  0.29 /)
936  !
937  !-
938  ! stomate_phenology
939  !-
940  REAL(r_std), SAVE      :: gddncd_ref = 603.
941  REAL(r_std), SAVE      :: gddncd_curve = 0.0091
942  REAL(r_std), SAVE      :: gddncd_offset = 64.
943  !
944  !-
945  ! stomate_prescribe
946  !-
947  REAL(r_std), SAVE      :: cn_tree = 4.
948  REAL(r_std), SAVE      :: bm_sapl_rescale = 40.
949  !
950  !-
951  ! stomate_resp
952  !-
953  REAL(r_std), SAVE      :: maint_resp_min_vmax = 0.3 
954  REAL(r_std), SAVE      :: maint_resp_coeff = 1.4
955  !
956  !-
957  ! stomate_season
958  !-
959  REAL(r_std), SAVE  :: ncd_max_year = 3.
960  REAL(r_std), SAVE  :: gdd_threshold = 5.
961  REAL(r_std), SAVE  :: green_age_ever = 2.
962  REAL(r_std), SAVE  :: green_age_dec = 0.5
963  !-
964  ! stomate_soilcarbon
965  !-
966  REAL(r_std), SAVE      :: active_to_pass_clay_frac = .68 
967  !residence times in carbon pools (days)
968  REAL(r_std), SAVE      :: carbon_tau_iactive = .149
969  REAL(r_std), SAVE      :: carbon_tau_islow = 5.48
970  REAL(r_std), SAVE      :: carbon_tau_ipassive = 241.
971  !
972  REAL(r_std), SAVE, DIMENSION(3) :: flux_tot_coeff = (/ 1.2, 1.4, .75/)
973  !
974  !-
975  ! stomate_turnover
976  !-
977  REAL(r_std), SAVE      ::  new_turnover_time_ref = 20.
978  REAL(r_std), SAVE      ::  dt_turnover_time = 10. 
979  REAL(r_std), SAVE      :: leaf_age_crit_tref = 20.
980  REAL(r_std), SAVE, DIMENSION(3)   :: leaf_age_crit_coeff = (/ 1.5, 0.75, 10./)
981
982!**************************************************************
983
984 CONTAINS
985
986 ! Subroutine called for getin the new parameters values used in sechiba
987 !
988 SUBROUTINE getin_sechiba_parameters
989
990  IMPLICIT NONE
991  ! first call
992  LOGICAL, SAVE ::  first_call = .TRUE.
993
994  IF(first_call) THEN 
995
996!!$   CALL getin('DIAG_QSAT',diag_qsat)
997   
998   CALL getin('QWILT',qwilt)
999   CALL getin('MIN_RESDIS',min_resdis)
1000   CALL getin('MIN_DRAIN',min_drain)
1001   CALL getin('MAX_DRAIN',max_drain)
1002   CALL getin('EXP_DRAIN',exp_drain)
1003   CALL getin('MX_EAU_EAU',mx_eau_eau)
1004   CALL getin('RSOL_CSTE',rsol_cste)
1005   CALL getin('HCRIT_LITTER',hcrit_litter)
1006   !-
1007   CALL getin('SOILTYPE_DEFAULT',soiltype_default)
1008   !-
1009   CALL getin('MAXMASS_GLACIER',maxmass_glacier)
1010   CALL getin('MIN_VEGFRAC',min_vegfrac)
1011   !-
1012   CALL getin('SNOWCRI',snowcri)
1013   !-
1014   CALL getin('SNOWCRI_ALB',snowcri_alb)
1015   CALL getin('MIN_WIND',min_wind)
1016   CALL getin('Z0_BARE',z0_bare)
1017   CALL getin('Z0_ICE',z0_ice)
1018   CALL getin('TCST_SNOWA',tcst_snowa)
1019   CALL getin('MAX_SNOW_AGE',max_snow_age)
1020   CALL getin('SNOW_TRANS',snow_trans)
1021   CALL getin('ALB_DEADLEAF',alb_deadleaf)
1022   CALL getin('ALB_ICE',alb_ice)
1023   !-
1024   CALL getin('Z0_OVER_HEIGHT',z0_over_height)
1025   CALL getin('HEIGHT_DISPLACEMENT',height_displacement)
1026   !-
1027   CALL getin('NLAI',nlai)
1028   CALL getin('LAIMAX',laimax)
1029   CALL getin('XC4_1',xc4_1)
1030   CALL getin('XC4_2',xc4_2)
1031   !-
1032   CALL getin('DMCS',dmcs)
1033   CALL getin('DMCR',dmcr)
1034   !-
1035   CALL getin('VIS_DRY',vis_dry)
1036   CALL getin('NIR_DRY',nir_dry)
1037   CALL getin('VIS_WET',vis_wet)
1038   CALL getin('NIR_WET',nir_wet)
1039   CALL getin('ALBSOIL_VIS',albsoil_vis)
1040   CALL getin('ALBSOIL_NIR',albsoil_nir)
1041   !-
1042   CALL getin('CLAYFRACTION_DEFAULT',clayfraction_default)
1043   !
1044   CALL getin('DEW_VEG_POLY_COEFF',dew_veg_poly_coeff)
1045
1046   first_call =.FALSE.
1047
1048  ENDIF
1049
1050  END SUBROUTINE getin_sechiba_parameters
1051
1052!*********************************************************
1053
1054  ! Subroutine called only if river_routing is activated
1055
1056  SUBROUTINE getin_routing_parameters
1057
1058  IMPLICIT NONE
1059
1060  LOGICAL, SAVE ::  first_call = .TRUE.
1061
1062  IF(first_call) THEN
1063
1064     CALL getin('CROP_COEF',crop_coef)
1065
1066     first_call =.FALSE.
1067
1068  ENDIF   
1069
1070  END SUBROUTINE getin_routing_parameters 
1071
1072!*******************************************************
1073
1074  ! Subroutine called only if hydrol_cwrr is activated
1075
1076  SUBROUTINE getin_hydrol_cwrr_parameters
1077
1078  IMPLICIT NONE
1079
1080  LOGICAL, SAVE ::  first_call = .TRUE.
1081
1082    IF(first_call) THEN
1083
1084       CALL getin('W_TIME',w_time)
1085       CALL getin('NVAN',nvan)   
1086       CALL getin('AVAN',avan)
1087       CALL getin('MCR',mcr)
1088       CALL getin('MCS',mcs)
1089       CALL getin('KS',ks)
1090       CALL getin('PCENT',pcent)
1091       CALL getin('FREE_DRAIN_MAX',free_drain_max)
1092       CALL getin('MCF',mcf)
1093       CALL getin('MCW',mcw)
1094       CALL getin('MC_AWET',mc_awet)
1095
1096       first_call =.FALSE.
1097 
1098    ENDIF
1099
1100  END SUBROUTINE getin_hydrol_cwrr_parameters
1101!--------------------------------------------
1102
1103  ! Subroutine called only if ok_co2 is activated
1104  ! only for diffuco_trans_co2
1105
1106  SUBROUTINE getin_co2_parameters
1107
1108  IMPLICIT NONE
1109
1110  LOGICAL, SAVE ::  first_call = .TRUE.
1111
1112    IF(first_call) THEN
1113
1114       CALL getin('LAI_LEVEL_DEPTH',lai_level_depth)
1115       CALL getin('X1_COEF',x1_coef)
1116       CALL getin('X1_Q10',x1_Q10)
1117       CALL getin('QUANTUM_YIELD',quantum_yield)
1118       CALL getin('KT_COEF',kt_coef)
1119       CALL getin('KC_COEF',kc_coef)
1120       CALL getin('KO_Q10',Ko_Q10)
1121       CALL getin('OA',Oa)
1122       CALL getin('KO_COEF',Ko_coef)
1123       CALL getin('CP_0',CP_0)
1124       CALL getin('CP_TEMP_COEF',cp_temp_coef)
1125       CALL getin('CP_TEMP_REF',cp_temp_ref)
1126       CALL getin('RT_COEF',rt_coef)
1127       CALL getin('VC_COEF',vc_coef)
1128
1129       first_call =.FALSE.
1130
1131   ENDIF
1132
1133  END SUBROUTINE getin_co2_parameters
1134
1135!**********************************************************
1136
1137  ! Subroutine called only if stomate is activated
1138
1139  SUBROUTINE getin_stomate_parameters
1140
1141    IMPLICIT NONE
1142
1143    LOGICAL, SAVE ::  first_call = .TRUE.
1144
1145    IF(first_call) THEN
1146   
1147       CALL getin('TOO_LONG',too_long)
1148       !-
1149       CALL getin('TAU_FIRE',tau_fire)
1150       CALL getin('LITTER_CRIT',litter_crit)
1151       !-
1152       CALL getin('OK_MINRES',ok_minres)
1153       CALL getin('TAU_LEAFINIT', tau_leafinit)
1154       CALL getin('RESERVE_TIME_TREE',reserve_time_tree)
1155       CALL getin('RESERVE_TIME_GRASS',reserve_time_grass)
1156       CALL getin('R0',R0)
1157       CALL getin('S0',S0)
1158       CALL getin('F_FRUIT',f_fruit)
1159       CALL getin('ALLOC_SAP_ABOVE_TREE',alloc_sap_above_tree)
1160       CALL getin('ALLOC_SAP_ABOVE_GRASS',alloc_sap_above_grass)
1161       CALL getin('MIN_LTOLSR',min_LtoLSR)
1162       CALL getin('MAX_LTOLSR',max_LtoLSR)
1163       CALL getin('Z_NITROGEN',z_nitrogen)
1164       !-
1165       CALL getin('PIPE_TUNE_EXP_COEFF',pipe_tune_exp_coeff)
1166       CALL getin('PIPE_TUNE1',pipe_tune1)
1167       CALL getin('PIPE_TUNE2',pipe_tune2)   
1168       CALL getin('PIPE_TUNE3',pipe_tune3)
1169       CALL getin('PIPE_TUNE4',pipe_tune4)
1170       CALL getin('PIPE_DENSITY',pipe_density)
1171       CALL getin('PIPE_K1',pipe_k1)
1172       CALL getin('ESTAB_MAX_TREE',estab_max_tree)
1173       CALL getin('ESTAB_MAX_GRASS',estab_max_grass)
1174       CALL getin('IND_0',ind_0)
1175       CALL getin('MIN_COVER',min_cover)
1176       CALL getin('PRECIP_CRIT',precip_crit)
1177       CALL getin('GDD_CRIT_ESTAB',gdd_crit_estab) 
1178       CALL getin('FPC_CRIT',fpc_crit)
1179       CALL getin('FRAC_GROWTHRESP',frac_growthresp)
1180       CALL getin('ALPHA_GRASS',alpha_grass)
1181       CALL getin('ALPHA_TREE',alpha_tree)
1182       CALL getin('TLONG_REF_MAX',tlong_ref_max)
1183       CALL getin('TLONG_REF_MIN',tlong_ref_min)
1184       !-
1185       CALL getin('MASS_RATIO_HEART_SAP',mass_ratio_heart_sap)
1186       CALL getin('TAU_HUM_MONTH',tau_hum_month)
1187       CALL getin('TAU_HUM_WEEK',tau_hum_week)
1188       CALL getin('TAU_T2M_MONTH',tau_t2m_month)
1189       CALL getin('TAU_T2M_WEEK',tau_t2m_week)
1190       CALL getin('TAU_TSOIL_MONTH',tau_tsoil_month)
1191       CALL getin('TAU_SOILHUM_MONTH',tau_soilhum_month)
1192       CALL getin('TAU_GPP_WEEK',tau_gpp_week)
1193       CALL getin('TAU_GDD',tau_gdd)
1194       CALL getin('TAU_NGD',tau_ngd)
1195       CALL getin('COEFF_TAU_LONGTERM',coeff_tau_longterm)
1196       !
1197       CALL getin('FRAC_TURNOVER_DAILY',frac_turnover_daily)
1198       !-
1199       CALL getin('Z_DECOMP',z_decomp)
1200       !-
1201       CALL getin('TAX_MAX',tax_max)
1202       !-
1203       CALL getin('ALWAYS_INIT',always_init)
1204       CALL getin('MIN_GROWTHINIT_TIME',min_growthinit_time)
1205       CALL getin('MOIAVAIL_ALWAYS_TREE',moiavail_always_tree)
1206       CALL getin('MOIAVAIL_ALWAYS_GRASS',moiavail_always_grass)
1207       CALL getin('T_ALWAYS_ADD',t_always_add)
1208       !-
1209       CALL getin('VMAX_OFFSET',vmax_offset)
1210       CALL getin('LEAFAGE_FIRSTMAX',leafage_firstmax)
1211       CALL getin('LEAFAGE_LASTMAX',leafage_lastmax)
1212       CALL getin('LEAFAGE_OLD',leafage_old)
1213       !-
1214       CALL getin('GPPFRAC_DORMANCE',gppfrac_dormance)
1215       CALL getin('MIN_GPP_ALLOWED',min_gpp_allowed)
1216       CALL getin('TAU_CLIMATOLOGY',tau_climatology)
1217       CALL getin('HVC1',hvc1)
1218       CALL getin('HVC2',hvc2)
1219       CALL getin('LEAF_FRAC_HVC',leaf_frac_hvc)
1220       !-
1221       CALL getin('CO2FRAC',co2frac)
1222       CALL getin('CN',CN)
1223       CALL getin('LC',LC)
1224       !-
1225       CALL getin('FRAC_SOIL_STRUCT_AA',frac_soil_struct_aa)
1226       CALL getin('FRAC_SOIL_STRUCT_AB',frac_soil_struct_ab)
1227       CALL getin('FRAC_SOIL_STRUCT_SA',frac_soil_struct_sa)
1228       CALL getin('FRAC_SOIL_STRUCT_SB',frac_soil_struct_sb)
1229       CALL getin('FRAC_SOIL_METAB_AA',frac_soil_metab_aa)
1230       CALL getin('FRAC_SOIL_METAB_AB',frac_soil_metab_ab)
1231       !-
1232       CALL getin('FRAC_CARB_AA',frac_carb_aa)
1233       CALL getin('FRAC_CARB_AP',frac_carb_ap)   
1234       CALL getin('FRAC_CARB_SS',frac_carb_ss)
1235       CALL getin('FRAC_CARB_SA',frac_carb_sa)
1236       CALL getin('FRAC_CARB_SP',frac_carb_sp)
1237       CALL getin('FRAC_CARB_PP',frac_carb_pp)
1238       CALL getin('FRAC_CARB_PA',frac_carb_pa)
1239       CALL getin('FRAC_CARB_PS',frac_carb_ps)
1240
1241       !---------------------------------------
1242       ! COEFFICIENTS OF EQUATIONS
1243       !-------------------------------------
1244       !
1245       !-
1246       CALL getin('BCFRAC_COEFF',bcfrac_coeff)
1247       CALL getin('FIREFRAC_COEFF',firefrac_coeff)
1248       !-
1249       CALL getin('AVAILABILITY_FACT', availability_fact) 
1250       CALL getin('VIGOUR_REF',vigour_ref)
1251       CALL getin('VIGOUR_COEFF',vigour_coeff)
1252       !-
1253       CALL getin('RIP_TIME_MIN',RIP_time_min)
1254       CALL getin('NPP_LONGTERM_INIT',npp_longterm_init)
1255       CALL getin('EVERYWHERE_INIT',everywhere_init)
1256       !
1257       !-
1258       CALL getin('LAI_MAX_TO_HAPPY',lai_max_to_happy)
1259       CALL getin('NLIM_TREF',Nlim_tref)   
1260       !-
1261       CALL getin('BM_SAPL_CARBRES',bm_sapl_carbres)
1262       CALL getin('BM_SAPL_SAPABOVE',bm_sapl_sapabove)
1263       CALL getin('BM_SAPL_HEARTABOVE',bm_sapl_heartabove)
1264       CALL getin('BM_SAPL_HEARTBELOW',bm_sapl_heartbelow)
1265       CALL getin('INIT_SAPL_MASS_LEAF_NAT',init_sapl_mass_leaf_nat)
1266       CALL getin('INIT_SAPL_MASS_LEAF_AGRI',init_sapl_mass_leaf_agri)
1267       CALL getin('INIT_SAPL_MASS_CARBRES',init_sapl_mass_carbres)
1268       CALL getin('INIT_SAPL_MASS_ROOT',init_sapl_mass_root)
1269       CALL getin('INIT_SAPL_MASS_FRUIT',init_sapl_mass_fruit)
1270       CALL getin('CN_SAPL_INIT',cn_sapl_init)
1271       CALL getin('MIGRATE_TREE',migrate_tree)
1272       CALL getin('MIGRATE_GRASS',migrate_grass)
1273       CALL getin('MAXDIA_COEFF',maxdia_coeff)
1274       CALL getin('LAI_INITMIN_TREE',lai_initmin_tree)
1275       CALL getin('LAI_INITMIN_GRASS',lai_initmin_grass)
1276       CALL getin('DIA_COEFF',dia_coeff)
1277       CALL getin('MAXDIA_COEFF',maxdia_coeff)
1278       CALL getin('BM_SAPL_LEAF',bm_sapl_leaf)
1279       !-
1280       CALL getin('METABOLIC_REF_FRAC',metabolic_ref_frac)
1281       CALL getin('METABOLIC_LN_RATIO',metabolic_LN_ratio)   
1282       CALL getin('TAU_METABOLIC',tau_metabolic)
1283       CALL getin('TAU_STRUCT',tau_struct)
1284       CALL getin('SOIL_Q10',soil_Q10)
1285       CALL getin('TSOIL_REF',tsoil_ref)
1286       CALL getin('LITTER_STRUCT_COEF',litter_struct_coef)
1287       CALL getin('MOIST_COEFF',moist_coeff)
1288       !-
1289       CALL getin('GDDNCD_REF',gddncd_ref)
1290       CALL getin('GDDNCD_CURVE',gddncd_curve)
1291       CALL getin('GDDNCD_OFFSET',gddncd_offset)
1292       !-
1293       CALL getin('CN_TREE',cn_tree)
1294       CALL getin('BM_SAPL_RESCALE',bm_sapl_rescale)
1295       !-
1296       CALL getin('MAINT_RESP_MIN_VMAX',maint_resp_min_vmax) 
1297       CALL getin('MAINT_RESP_COEFF',maint_resp_coeff)
1298       !-
1299       CALL getin('NCD_MAX_YEAR',ncd_max_year)
1300       CALL getin('GDD_THRESHOLD',gdd_threshold)
1301       CALL getin('GREEN_AGE_EVER',green_age_ever)
1302       CALL getin('GREEN_AGE_DEC',green_age_dec)
1303       !-
1304       CALL getin('ACTIVE_TO_PASS_CLAY_FRAC',active_to_pass_clay_frac)
1305       CALL getin('CARBON_TAU_IACTIVE',carbon_tau_iactive)
1306       CALL getin('CARBON_TAU_ISLOW',carbon_tau_islow)
1307       CALL getin('CARBON_TAU_IPASSIVE',carbon_tau_ipassive)
1308       CALL getin('FLUX_TOT_COEFF',flux_tot_coeff)
1309       !-
1310       CALL getin('NEW_TURNOVER_TIME_REF',new_turnover_time_ref)
1311       CALL getin('DT_TURNOVER_TIME',dt_turnover_time)
1312       CALL getin('LEAF_AGE_CRIT_TREF',leaf_age_crit_tref)
1313       CALL getin('LEAF_AGE_CRIT_COEFF',leaf_age_crit_coeff)
1314
1315       first_call = .FALSE.
1316
1317    ENDIF
1318
1319 END SUBROUTINE getin_stomate_parameters
1320
1321!******************************************
1322
1323 SUBROUTINE getin_dgvm_parameters   
1324   
1325   IMPLICIT NONE
1326
1327    LOGICAL, SAVE ::  first_call = .TRUE.
1328
1329    IF(first_call) THEN
1330
1331          CALL getin('ESTABLISH_SCAL_FACT',establish_scal_fact)
1332          CALL getin('FPC_CRIT_MAX',fpc_crit_max)
1333          CALL getin('FPC_CRIT_MIN',fpc_crit_min)
1334          !
1335          CALL getin('GRASS_MERCY',grass_mercy)
1336          CALL getin('TREE_MERCY',tree_mercy)
1337          CALL getin('ANNUAL_INCREASE',annual_increase)
1338          !
1339          CALL getin('MIN_AVAIL',min_avail)
1340          CALL getin('RIP_TIME_MIN',RIP_time_min)
1341          CALL getin('NPP_LONGTERM_INIT',npp_longterm_init)
1342          CALL getin('EVERYWHERE_INIT',everywhere_init)
1343
1344          first_call = .FALSE.
1345       
1346     ENDIF
1347
1348
1349   END SUBROUTINE getin_dgvm_parameters
1350
1351!--------------------
1352END MODULE constantes
Note: See TracBrowser for help on using the repository browser.