source: branches/publications/ORCHIDEE_gmd-2018-57/src_parameters/constantes.f90

Last change on this file was 4074, checked in by jan.polcher, 7 years ago

Convergence with Trunk version 4061 and in particular introduces the option FROZ_FRAC_CORR to reduce runoff over frozen soils.

  • Property svn:keywords set to Date Revision
File size: 69.5 KB
Line 
1! =================================================================================================================================
2! MODULE       : constantes
3!
4! CONTACT      : orchidee-help _at_ ipsl.jussieu.fr
5!
6! LICENCE      : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF        "constantes" module contains subroutines to initialize most of the exernalized parameters. This module
10!!              also make a use to the module constantes_var where the parameters are declared.
11!!
12!!\n DESCRIPTION: This module contains subroutines to initialize most of the exernalized parameters. This module
13!!                also make a use to the module constantes_var where the parameters are declared.\n
14!!                This module can be used to acces the subroutines and the constantes. The constantes declarations
15!!                can also be used seperatly with "USE constantes_var".
16!!
17!! RECENT CHANGE(S): Didier Solyga : This module contains now all the externalized parameters of ORCHIDEE
18!!                   listed by modules which are not pft-dependent 
19!!                   Josefine Ghattas 2013 : The declaration part has been extracted and moved to module constates_var
20!!
21!! REFERENCE(S) :
22!! - Louis, Jean-Francois (1979), A parametric model of vertical eddy fluxes in the atmosphere.
23!! Boundary Layer Meteorology, 187-202.
24!!
25!! SVN          :
26!! $HeadURL: $
27!! $Date$
28!! $Revision$
29!! \n
30!_ ================================================================================================================================
31
32MODULE constantes
33
34  USE constantes_var
35  USE defprec
36  USE ioipsl_para, ONLY : getin_p, ipslerr_p
37  USE mod_orchidee_para, ONLY : numout
38
39  IMPLICIT NONE
40
41CONTAINS
42
43
44!! ================================================================================================================================
45!! SUBROUTINE   : activate_sub_models
46!!
47!>\BRIEF         This subroutine reads the flags in the configuration file to
48!! activate some sub-models like routing, irrigation, fire, herbivory, ... 
49!!
50!! DESCRIPTION  : None
51!!
52!! RECENT CHANGE(S): None
53!!
54!! MAIN OUTPUT VARIABLE(S): None
55!!
56!! REFERENCE(S) : None
57!!
58!! FLOWCHART    : None
59!! \n
60!_ ================================================================================================================================
61
62  SUBROUTINE activate_sub_models()
63
64    IMPLICIT NONE
65
66    !! 0. Variables and parameters declaration
67
68    !! 0.4 Local variables
69
70    !_ ================================================================================================================================
71
72    IF (ok_stomate) THEN
73
74       !Config Key   = HERBIVORES
75       !Config Desc  = herbivores allowed?
76       !Config If    = OK_STOMATE
77       !Config Def   = n
78       !Config Help  = With this variable, you can determine
79       !Config         if herbivores are activated
80       !Config Units = [FLAG]
81       CALL getin_p('HERBIVORES', ok_herbivores)
82       !
83       !Config Key   = TREAT_EXPANSION
84       !Config Desc  = treat expansion of PFTs across a grid cell?
85       !Config If    = OK_STOMATE
86       !Config Def   = n
87       !Config Help  = With this variable, you can determine
88       !Config         whether we treat expansion of PFTs across a
89       !Config         grid cell.
90       !Config Units = [FLAG]
91       CALL getin_p('TREAT_EXPANSION', treat_expansion)
92
93       !Config Key   = LPJ_GAP_CONST_MORT
94       !Config Desc  = Constant mortality
95       !Config If    = OK_STOMATE AND NOT OK_DGVM
96       !Config Def   = y/n depending on OK_DGVM
97       !Config Help  = set to TRUE if constant mortality is to be activated
98       !Config         
99       !Config Units = [FLAG]
100
101       ! Set Default value different if DGVM is activated.
102       IF ( ok_dgvm ) THEN
103          lpj_gap_const_mort=.FALSE.
104       ELSE
105          lpj_gap_const_mort=.TRUE.
106       END IF
107       CALL getin_p('LPJ_GAP_CONST_MORT', lpj_gap_const_mort)
108
109       IF (ok_dgvm .AND. lpj_gap_const_mort) THEN
110          CALL ipslerr_p(1,"activate_sub_models","Both OK_DGVM and LPJ_GAP_CONST_MORT are activated.",&
111               "This combination is possible but unusual","The simulation will continue with these flags activated." )
112       END IF
113
114       !Config Key   = HARVEST_AGRI
115       !Config Desc  = Harvest model for agricultural PFTs.
116       !Config If    = OK_STOMATE
117       !Config Def   = y
118       !Config Help  = Compute harvest above ground biomass for agriculture.
119       !Config         Change daily turnover.
120       !Config Units = [FLAG]
121       CALL getin_p('HARVEST_AGRI', harvest_agri)
122       !
123       !Config Key   = FIRE_DISABLE
124       !Config Desc  = no fire allowed
125       !Config If    = OK_STOMATE
126       !Config Def   = n
127       !Config Help  = With this variable, you can allow or not
128       !Config         the estimation of CO2 lost by fire
129       !Config Units = [FLAG]
130       CALL getin_p('FIRE_DISABLE', disable_fire)
131       !
132       !Config Key   = SPINUP_ANALYTIC
133       !Config Desc  = Activation of the analytic resolution of the spinup.
134       !Config If    = OK_STOMATE
135       !Config Def   = n
136       !Config Help  = Activate this option if you want to solve the spinup by the Gauss-Jordan method.
137       !Config Units = BOOLEAN   
138       CALL getin_p('SPINUP_ANALYTIC',spinup_analytic)
139
140    ENDIF
141
142    !
143    ! Check consistency (see later)
144    !
145!!$        IF(.NOT.(ok_routing) .AND. (doirrigation .OR. dofloodplains)) THEN
146!!$           CALL ipslerr_p(2,'activate_sub_models', &
147!!$               &     'Problem :you tried to activate the irrigation and floodplains without activating the routing',&
148!!$               &     'Are you sure ?', &
149!!$               &     '(check your parameters).')
150!!$        ENDIF
151
152!!$        IF(.NOT.(ok_stomate) .AND. (ok_herbivores .OR. treat_expansion .OR. lpj_gap_const_mort &
153!!$            & .OR. harvest_agri .OR. disable_fire)) THEN
154!!$          CALL ipslerr_p(2,'activate_sub_models', &
155!!$               &     'Problem : try to activate the following options : herbivory, treat_expansion, fire,',&
156!!$               &     'harvest_agri and constant mortality without stomate activated.',&
157!!$               &     '(check your parameters).')
158!!$        ENDIF
159
160
161  END SUBROUTINE activate_sub_models
162
163!! ================================================================================================================================
164!! SUBROUTINE   : veget_config
165!!
166!>\BRIEF         This subroutine reads the flags controlling the configuration for
167!! the vegetation : impose_veg, veget_mpa, lai_map, etc...       
168!!
169!! DESCRIPTION  : None
170!!
171!! RECENT CHANGE(S): None
172!!
173!! MAIN OUTPUT VARIABLE(S):
174!!
175!! REFERENCE(S) :
176!!
177!! FLOWCHART    :
178!! \n
179!_ ================================================================================================================================
180
181  SUBROUTINE veget_config
182
183    IMPLICIT NONE
184
185    !! 0. Variables and parameters declaration
186
187    !! 0.4 Local variables 
188
189    !_ ================================================================================================================================
190
191    !Config Key   = AGRICULTURE
192    !Config Desc  = agriculture allowed?
193    !Config If    = OK_SECHIBA or OK_STOMATE
194    !Config Def   = y
195    !Config Help  = With this variable, you can determine
196    !Config         whether agriculture is allowed
197    !Config Units = [FLAG]
198    CALL getin_p('AGRICULTURE', agriculture)
199    !
200    !Config Key   = IMPOSE_VEG
201    !Config Desc  = Should the vegetation be prescribed ?
202    !Config If    = OK_SECHIBA or OK_STOMATE
203    !Config Def   = n
204    !Config Help  = This flag allows the user to impose a vegetation distribution
205    !Config         and its characteristics. It is espacially interesting for 0D
206    !Config         simulations. On the globe it does not make too much sense as
207    !Config         it imposes the same vegetation everywhere
208    !Config Units = [FLAG]
209    CALL getin_p('IMPOSE_VEG', impveg)
210
211    IF (impveg) THEN
212       !Config Key   = IMPOSE_SOILT
213       !Config Desc  = Should the soil type be prescribed ?
214       !Config Def   = n
215       !Config If    = IMPOSE_VEG
216       !Config Help  = This flag allows the user to impose a soil type distribution.
217       !Config         It is espacially interesting for 0D
218       !Config         simulations. On the globe it does not make too much sense as
219       !Config         it imposes the same soil everywhere
220       !Config Units = [FLAG]
221       CALL getin_p('IMPOSE_SOILT', impsoilt)     
222    ENDIF
223
224    !Config Key   = LAI_MAP
225    !Config Desc  = Read the LAI map
226    !Config If    = OK_SECHIBA or OK_STOMATE
227    !Config Def   = n
228    !Config Help  = It is possible to read a 12 month LAI map which will
229    !Config         then be interpolated to daily values as needed.
230    !Config Units = [FLAG]
231    CALL getin_p('LAI_MAP',read_lai)
232
233    !Config Key   = MAP_PFT_FORMAT
234    !Config Desc  = Read a land use vegetation map on PFT format
235    !Config If    = OK_SECHIBA or OK_STOMATE
236    !Config Def   = y
237    !Config Help  = pft values are needed, max time axis is 293
238    !Config Units = [FLAG]
239    CALL getin_p('MAP_PFT_FORMAT',map_pft_format)
240
241    IF(map_pft_format) THEN
242       !Config Key   = VEGET_REINIT
243       !Config Desc  = booleen to indicate that a new LAND USE file will be used.
244       !Config If    = MAP_PFT_FORMAT
245       !Config Def   = y
246       !Config Help  = The parameter is used to bypass veget_year count
247       !Config         and reinitialize it with VEGET_YEAR parameter.
248       !Config         Then it is possible to change LAND USE file.
249       !Config Units = [FLAG]
250       CALL getin_p('VEGET_REINIT', veget_reinit)
251       !
252       !Config Key   = VEGET_YEAR
253       !Config Desc  = Year of the vegetation map to be read
254       !Config If    = MAP_PFT_FORMAT
255       !Config Def   = 1
256       !Config Help  = First year for land use vegetation (2D map by pft).
257       !Config         If VEGET_YEAR is set to 0, this means there is no time axis.
258       !Config Units = [FLAG]
259       CALL getin_p('VEGET_YEAR', veget_year_orig)
260    ENDIF
261
262
263!!$        ! DS : Add warning in case of a wrong configuration (need to be discussed)
264!!$        ! 4.
265!!$        IF ( .NOT.(impveg) .AND. impsoilt) THEN
266!!$           CALL ipslerr_p(2,'veget_config', &
267!!$               &     'Problem : try to activate impose_soilt without activating impose_veg.',&
268!!$               &     'Are you sure ?', &
269!!$               &     '(check your parameters).')
270!!$        ENDIF
271!!$
272
273  END SUBROUTINE veget_config
274
275
276!! ================================================================================================================================
277!! SUBROUTINE   : veget_config
278!!
279!>\BRIEF         This subroutine reads in the configuration file the imposed values of the parameters for all SECHIBA modules. 
280!!
281!! DESCRIPTION  : None
282!!
283!! RECENT CHANGE(S): None
284!!
285!! MAIN OUTPUT VARIABLE(S):
286!!
287!! REFERENCE(S) :
288!!
289!! FLOWCHART    :
290!! \n
291!_ ================================================================================================================================
292
293  SUBROUTINE config_sechiba_parameters
294
295    IMPLICIT NONE
296
297    !! 0. Variables and parameters declaration
298
299    !! 0.4 Local variables
300
301    !_ ================================================================================================================================
302
303    ! Global : parameters used by many modules
304    CALL getin_p('TESTPFT',testpft)
305
306    !
307    !Config Key   = MAXMASS_SNOW
308    !Config Desc  = The maximum mass of a snow
309    !Config If    = OK_SECHIBA or HYDROL_CWRR
310    !Config Def   = 3000.
311    !Config Help  =
312    !Config Units = [kg/m^2] 
313    CALL getin_p('MAXMASS_SNOW',maxmass_snow)
314    !
315    !Config Key   = SNOWCRI
316    !Config Desc  = Sets the amount above which only sublimation occures
317    !Config If    = OK_SECHIBA or HYDROL_CWRR
318    !Config Def   = 1.5
319    !Config Help  =
320    !Config Units = [kg/m^2] 
321    CALL getin_p('SNOWCRI',snowcri)
322    !
323    !! Initialization of sneige
324    sneige = snowcri/mille
325    !
326    !Config Key   = MIN_WIND
327    !Config Desc  = Minimum wind speed
328    !Config If    = OK_SECHIBA
329    !Config Def   = 0.1
330    !Config Help  =
331    !Config Units = [m/s]
332    CALL getin_p('MIN_WIND',min_wind)
333    !
334    !Config Key   = MAX_SNOW_AGE
335    !Config Desc  = Maximum period of snow aging
336    !Config If    = OK_SECHIBA
337    !Config Def   = 50.
338    !Config Help  =
339    !Config Units = [days?]
340    CALL getin_p('MAX_SNOW_AGE',max_snow_age)
341    !
342    !Config Key   = SNOW_TRANS
343    !Config Desc  = Transformation time constant for snow
344    !Config If    = OK_SECHIBA
345    !Config Def   = 0.2
346    !Config Help  = optimized on 04/07/2016
347    !Config Units = [m]   
348    CALL getin_p('SNOW_TRANS',snow_trans)
349
350    !-
351    ! condveg
352    !-
353    !
354    !Config Key   = HEIGHT_DISPLACEMENT
355    !Config Desc  = Magic number which relates the height to the displacement height.
356    !Config If    = OK_SECHIBA
357    !Config Def   = 0.75
358    !Config Help  =
359    !Config Units = [m] 
360    CALL getin_p('HEIGHT_DISPLACEMENT',height_displacement)
361    !
362    !Config Key   = Z0_BARE
363    !Config Desc  = bare soil roughness length
364    !Config If    = OK_SECHIBA
365    !Config Def   = 0.01
366    !Config Help  =
367    !Config Units = [m]   
368    CALL getin_p('Z0_BARE',z0_bare)
369    !
370    !Config Key   = Z0_ICE
371    !Config Desc  = ice roughness length
372    !Config If    = OK_SECHIBA
373    !Config Def   = 0.001
374    !Config Help  =
375    !Config Units = [m]   
376    CALL getin_p('Z0_ICE',z0_ice)
377    !
378    !Config Key   = TCST_SNOWA
379    !Config Desc  = Time constant of the albedo decay of snow
380    !Config If    = OK_SECHIBA
381    !Config Def   = 10.0
382    !Config Help  = optimized on 04/07/2016
383    !Config Units = [days]
384    CALL getin_p('TCST_SNOWA',tcst_snowa)
385    !
386    !Config Key   = SNOWCRI_ALB
387    !Config Desc  = Critical value for computation of snow albedo
388    !Config If    = OK_SECHIBA
389    !Config Def   = 10.
390    !Config Help  =
391    !Config Units = [cm] 
392    CALL getin_p('SNOWCRI_ALB',snowcri_alb)
393    !
394    !
395    !Config Key   = VIS_DRY
396    !Config Desc  = The correspondance table for the soil color numbers and their albedo
397    !Config If    = OK_SECHIBA
398    !Config Def   = 0.24, 0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.27
399    !Config Help  =
400    !Config Units = [-] 
401    CALL getin_p('VIS_DRY',vis_dry)
402    !
403    !Config Key   = NIR_DRY
404    !Config Desc  = The correspondance table for the soil color numbers and their albedo
405    !Config If    = OK_SECHIBA
406    !Config Def   = 0.48, 0.44, 0.40, 0.36, 0.32, 0.28, 0.24, 0.20, 0.55
407    !Config Help  =
408    !Config Units = [-]   
409    CALL getin_p('NIR_DRY',nir_dry)
410    !
411    !Config Key   = VIS_WET
412    !Config Desc  = The correspondance table for the soil color numbers and their albedo
413    !Config If    = OK_SECHIBA 
414    !Config Def   = 0.12, 0.11, 0.10, 0.09, 0.08, 0.07, 0.06, 0.05, 0.15
415    !Config Help  =
416    !Config Units = [-]   
417    CALL getin_p('VIS_WET',vis_wet)
418    !
419    !Config Key   = NIR_WET
420    !Config Desc  = The correspondance table for the soil color numbers and their albedo
421    !Config If    = OK_SECHIBA
422    !Config Def   = 0.24, 0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.31
423    !Config Help  =
424    !Config Units = [-]   
425    CALL getin_p('NIR_WET',nir_wet)
426    !
427    !Config Key   = ALBSOIL_VIS
428    !Config Desc  =
429    !Config If    = OK_SECHIBA
430    !Config Def   = 0.18, 0.16, 0.16, 0.15, 0.12, 0.105, 0.09, 0.075, 0.25
431    !Config Help  =
432    !Config Units = [-] 
433    CALL getin_p('ALBSOIL_VIS',albsoil_vis)
434    !
435    !Config Key   = ALBSOIL_NIR
436    !Config Desc  =
437    !Config If    = OK_SECHIBA
438    !Config Def   = 0.36, 0.34, 0.34, 0.33, 0.30, 0.25, 0.20, 0.15, 0.45
439    !Config Help  =
440    !Config Units = [-] 
441    CALL getin_p('ALBSOIL_NIR',albsoil_nir)
442    !-
443    !
444    !Config Key   = ALB_DEADLEAF
445    !Config Desc  = albedo of dead leaves, VIS+NIR
446    !Config If    = OK_SECHIBA
447    !Config Def   = 0.12, 0.35
448    !Config Help  =
449    !Config Units = [-]     
450    CALL getin_p('ALB_DEADLEAF',alb_deadleaf)
451    !
452    !Config Key   = ALB_ICE
453    !Config Desc  = albedo of ice, VIS+NIR
454    !Config If    = OK_SECHIBA
455    !Config Def   = 0.60, 0.20
456    !Config Help  =
457    !Config Units = [-] 
458    CALL getin_p('ALB_ICE',alb_ice)
459    !
460    ! Get the fixed snow albedo if needed
461    !
462    !Config Key   = CONDVEG_SNOWA
463    !Config Desc  = The snow albedo used by SECHIBA
464    !Config Def   = 1.E+20
465    !Config if    = OK_SECHIBA
466    !Config Help  = This option allows the user to impose a snow albedo.
467    !Config         Default behaviour is to use the model of snow albedo
468    !Config         developed by Chalita (1993).
469    !Config Units = [-]
470    CALL getin_p('CONDVEG_SNOWA',fixed_snow_albedo)
471    !
472    !Config Key   = ALB_BARE_MODEL
473    !Config Desc  = Switch bare soil albedo dependent (if TRUE) on soil wetness
474    !Config Def   = n
475    !Config if    = OK_SECHIBA
476    !Config Help  = If TRUE, the model for bare soil albedo is the old formulation.
477    !Config         Then it depend on the soil dry or wetness. If FALSE, it is the
478    !Config         new computation that is taken, it is the mean of soil albedo.
479    !Config Units = [FLAG]
480    CALL getin_p('ALB_BARE_MODEL',alb_bare_model)
481    !
482    !Config Key   = ALB_BG_MODIS
483    !Config Desc  = Read bare soil albedo from file with background MODIS data
484    !Config Def   = n
485    !Config if    = OK_SECHIBA
486    !Config Help  = If TRUE, the bare soil albedo is read from file
487    !Config         based on background MODIS data. 
488    !Config         If FALSE, computaion depends on ALB_BARE_MODEL
489    !Config Units = [FLAG]
490    CALL getin_p('ALB_BG_MODIS',alb_bg_modis)
491    !
492    !Config Key   = IMPOSE_AZE
493    !Config Desc  = Should the surface parameters be prescribed
494    !Config Def   = n
495    !Config if    = OK_SECHIBA
496    !Config Help  = This flag allows the user to impose the surface parameters
497    !Config         (Albedo Roughness and Emissivity). It is espacially interesting for 0D
498    !Config         simulations. On the globe it does not make too much sense as
499    !Config         it imposes the same vegetation everywhere
500    !Config Units = [FLAG]
501    CALL getin_p('IMPOSE_AZE',impaze)
502    !
503    IF(impaze) THEN
504       !
505       !Config Key   = CONDVEG_Z0
506       !Config Desc  = Surface roughness
507       !Config Def   = 0.15
508       !Config If    = IMPOSE_AZE
509       !Config Help  = Surface rougness to be used on the point if a 0-dim version
510       !Config         of SECHIBA is used. Look at the description of the forcing 
511       !Config         data for the correct value.
512       !Config Units = [m]
513       CALL getin_p('CONDVEG_Z0', z0_scal) 
514       !
515       !Config Key   = ROUGHHEIGHT
516       !Config Desc  = Height to be added to the height of the first level
517       !Config Def   = 0.0
518       !Config If    = IMPOSE_AZE
519       !Config Help  = ORCHIDEE assumes that the atmospheric level height is counted
520       !Config         from the zero wind level. Thus to take into account the roughness
521       !Config         of tall vegetation we need to correct this by a certain fraction
522       !Config         of the vegetation height. This is called the roughness height in
523       !Config         ORCHIDEE talk.
524       !Config Units = [m]
525       CALL getin_p('ROUGHHEIGHT', roughheight_scal)
526       !
527       !Config Key   = CONDVEG_ALBVIS
528       !Config Desc  = SW visible albedo for the surface
529       !Config Def   = 0.25
530       !Config If    = IMPOSE_AZE
531       !Config Help  = Surface albedo in visible wavelengths to be used
532       !Config         on the point if a 0-dim version of SECHIBA is used.
533       !Config         Look at the description of the forcing data for
534       !Config         the correct value.
535       !Config Units = [-]
536       CALL getin_p('CONDVEG_ALBVIS', albedo_scal(ivis))
537       !
538       !Config Key   = CONDVEG_ALBNIR
539       !Config Desc  = SW near infrared albedo for the surface
540       !Config Def   = 0.25
541       !Config If    = IMPOSE_AZE
542       !Config Help  = Surface albedo in near infrared wavelengths to be used
543       !Config         on the point if a 0-dim version of SECHIBA is used.
544       !Config         Look at the description of the forcing data for
545       !Config         the correct value.
546       !Config Units = [-] 
547       CALL getin_p('CONDVEG_ALBNIR', albedo_scal(inir))
548       !
549       !Config Key   = CONDVEG_EMIS
550       !Config Desc  = Emissivity of the surface for LW radiation
551       !Config Def   = 1.0
552       !Config If    = IMPOSE_AZE
553       !Config Help  = The surface emissivity used for compution the LE emission
554       !Config         of the surface in a 0-dim version. Values range between
555       !Config         0.97 and 1.. The GCM uses 0.98.
556       !Config Units = [-]
557       CALL getin_p('CONDVEG_EMIS', emis_scal)
558    ENDIF
559
560    CALL getin_p('NEW_WATSTRESS',new_watstress)
561    IF(new_watstress) THEN
562       CALL getin_p('ALPHA_WATSTRESS',alpha_watstress)
563    ENDIF
564
565    !
566    !Config Key   = ROUGH_DYN
567    !Config Desc  = Account for a dynamic roughness height
568    !Config Def   = y
569    !Config if    = OK_SECHIBA
570    !Config Help  = If this flag is set to true (y) then the roughness
571    !Config         height is computed dynamically, varying with LAI
572    !Config Units = [FLAG]
573    CALL getin_p('ROUGH_DYN',rough_dyn)
574
575    IF ( rough_dyn ) THEN
576       !
577       !Config Key   = C1
578       !Config Desc  = Constant used in the formulation of the ratio of
579       !Config         the ratio of friction velocity to the wind speed
580       !Config         at the canopy top
581       !Config         See Ershadi et al. (2015) for more info
582       !Config Def   = 0.32
583       !Config If    = ROUGH_DYN
584       !Config Help  =
585       !Config Units = [-]
586       CALL getin_p('C1', c1)
587       !
588       !Config Key   = C2
589       !Config Desc  = Constant used in the formulation of the ratio of
590       !Config         the ratio of friction velocity to the wind speed
591       !Config         at the canopy top
592       !Config         See Ershadi et al. (2015) for more info
593       !Config Def   = 0.264
594       !Config If    = ROUGH_DYN
595       !Config Help  =
596       !Config Units = [-]
597       CALL getin_p('C2', c2)
598       !
599       !Config Key   = C3
600       !Config Desc  = Constant used in the formulation of the ratio of
601       !Config         the ratio of friction velocity to the wind speed
602       !Config         at the canopy top
603       !Config         See Ershadi et al. (2015) for more info
604       !Config Def   = 15.1
605       !Config If    = ROUGH_DYN
606       !Config Help  =
607       !Config Units = [-]
608       CALL getin_p('C3', c3)
609       !
610       !Config Key   = Cdrag_foliage
611       !Config Desc  = Drag coefficient of the foliage
612       !Config         See Ershadi et al. (2015) and Su et al. (2001)
613       !Config         for more info
614       !Config Def   = 0.2
615       !Config If    = ROUGH_DYN
616       !Config Help  =
617       !Config Units = [-]
618       CALL getin_p('CDRAG_FOLIAGE', Cdrag_foliage)
619       !
620       !Config Key   = Ct
621       !Config Desc  = Heat transfer coefficient of the leaf
622       !Config         See Ershadi et al. (2015) and Su et al. (2001)
623       !Config         for more info
624       !Config Def   = 0.01
625       !Config If    = ROUGH_DYN
626       !Config Help  =
627       !Config Units = [-]
628       CALL getin_p('CT', Ct)
629       !
630       !Config Key   = Prandtl
631       !Config Desc  = Prandtl number used in the calculation of Ct*
632       !Config         See Su et al. (2001) for more info
633       !Config Def   = 0.71
634       !Config If    = ROUGH_DYN
635       !Config Help  =
636       !Config Units = [-]
637       CALL getin_p('PRANDTL', Prandtl)
638    ENDIF
639    !-
640    ! Variables related to the explicitsnow module
641    !-
642    !Config Key = xansmax
643    !Config Desc = maximum snow albedo
644    !Config If = OK_SECHIBA
645    !Config Def = 0.85
646    !Config Help =
647    !Config Units = [-]
648    CALL getin_p('XANSMAX',xansmax)
649    !
650    !Config Key = xansmin
651    !Config Desc = minimum snow albedo
652    !Config If = OK_SECHIBA
653    !Config Def = 0.50
654    !Config Help =
655    !Config Units = [-]
656    CALL getin_p('XANSMIN',xansmin)
657    !
658    !Config Key = xans_todry
659    !Config Desc = albedo decay rate for the dry snow
660    !Config If = OK_SECHIBA
661    !Config Def = 0.008
662    !Config Help =
663    !Config Units = [S-1]
664    CALL getin_p('XANSDRY',xans_todry)
665    !
666    !Config Key = xans_t
667    !Config Desc = albedo decay rate for the wet snow
668    !Config If = OK_SECHIBA
669    !Config Def = 0.24
670    !Config Help =
671    !Config Units = [S-1]
672    CALL getin_p('XANS_T',xans_t)
673
674    !Config Key = xrhosmax
675    !Config Desc = maximum snow density
676    !Config If = OK_SECHIBA
677    !Config Def = 750
678    !Config Help =
679    !Config Units = [-]
680    CALL getin_p('XRHOSMAX',xrhosmax)
681    !
682    !Config Key = xwsnowholdmax1
683    !Config Desc = snow holding capacity 1
684    !Config If = OK_SECHIBA
685    !Config Def = 0.03
686    !Config Help =
687    !Config Units = [-]
688    CALL getin_p('XWSNOWHOLDMAX1',xwsnowholdmax1)
689    !
690    !Config Key = xwsnowholdmax2
691    !Config Desc = snow holding capacity 2
692    !Config If = OK_SECHIBA
693    !Config Def = 0.10
694    !Config Help =
695    !Config Units = [-]
696    CALL getin_p('XWSNOWHOLDMAX2',xwsnowholdmax2)
697    !
698    !Config Key = xsnowrhohold
699    !Config Desc = snow density
700    !Config If = OK_SECHIBA
701    !Config Def = 200.0
702    !Config Help =
703    !Config Units = [kg/m3]
704    CALL getin_p('XSNOWRHOHOLD',xsnowrhohold)
705    !
706    !Config Key = ZSNOWTHRMCOND1
707    !Config Desc = Thermal conductivity Coef 1
708    !Config If = OK_SECHIBA
709    !Config Def = 0.02
710    !Config Help =
711    !Config Units = [W/m/K]
712    CALL getin_p('ZSNOWTHRMCOND1',ZSNOWTHRMCOND1)
713    !
714    !Config Key = ZSNOWTHRMCOND2
715    !Config Desc = Thermal conductivity Coef 2
716    !Config If = OK_SECHIBA
717    !Config Def = 2.5E-6
718    !Config Help =
719    !Config Units = [W m5/(kg2 K)]
720    CALL getin_p('ZSNOWTHRMCOND2',ZSNOWTHRMCOND2)
721    !
722    !Config Key = ZSNOWTHRMCOND_AVAP
723    !Config Desc = Thermal conductivity Coef 1 water vapor
724    !Config If = OK_SECHIBA
725    !Config Def = -0.06023
726    !Config Help =
727    !Config Units = [W/m/K]
728    CALL getin_p('ZSNOWTHRMCOND_AVAP',ZSNOWTHRMCOND_AVAP)
729    !
730    !Config Key = ZSNOWTHRMCOND_BVAP
731    !Config Desc = Thermal conductivity Coef 2 water vapor
732    !Config If = OK_SECHIBA
733    !Config Def = -2.5425
734    !Config Help =
735    !Config Units = [W/m]
736    CALL getin_p('ZSNOWTHRMCOND_BVAP',ZSNOWTHRMCOND_BVAP)
737    !
738    !Config Key = ZSNOWTHRMCOND_CVAP
739    !Config Desc = Thermal conductivity Coef 3 water vapor
740    !Config If = OK_SECHIBA
741    !Config Def = -289.99
742    !Config Help =
743    !Config Units = [K]
744    CALL getin_p('ZSNOWTHRMCOND_CVAP',ZSNOWTHRMCOND_CVAP)
745
746    !Snow compaction factors
747    !Config Key = ZSNOWCMPCT_RHOD
748    !Config Desc = Snow compaction coefficent
749    !Config If = OK_SECHIBA
750    !Config Def = 150.0
751    !Config Help =
752    !Config Units = [kg/m3]
753    CALL getin_p('ZSNOWCMPCT_RHOD',ZSNOWCMPCT_RHOD)
754
755    !Config Key = ZSNOWCMPCT_ACM
756    !Config Desc = Coefficent for the thermal conductivity
757    !Config If = OK_SECHIBA
758    !Config Def = 2.8e-6
759    !Config Help =
760    !Config Units = [1/s]
761    CALL getin_p('ZSNOWCMPCT_ACM',ZSNOWCMPCT_ACM)
762
763    !Config Key = ZSNOWCMPCT_BCM
764    !Config Desc = Coefficent for the thermal conductivity
765    !Config If = OK_SECHIBA
766    !Config Def = 0.04
767    !Config Help =
768    !Config Units = [1/K]
769    CALL getin_p('ZSNOWCMPCT_BCM',ZSNOWCMPCT_BCM)
770
771    !Config Key = ZSNOWCMPCT_CCM
772    !Config Desc = Coefficent for the thermal conductivity
773    !Config If = OK_SECHIBA
774    !Config Def = 460.
775    !Config Help =
776    !Config Units = [m3/kg]
777    CALL getin_p('ZSNOWCMPCT_CCM',ZSNOWCMPCT_CCM)
778
779    !Config Key = ZSNOWCMPCT_V0
780    !Config Desc = Vapor coefficent for the thermal conductivity
781    !Config If = OK_SECHIBA
782    !Config Def = 3.7e7
783    !Config Help =
784    !Config Units = [Pa/s]
785    CALL getin_p('ZSNOWCMPCT_V0',ZSNOWCMPCT_V0)
786
787    !Config Key = ZSNOWCMPCT_VT
788    !Config Desc = Vapor coefficent for the thermal conductivity
789    !Config If = OK_SECHIBA
790    !Config Def = 0.081
791    !Config Help =
792    !Config Units = [1/K]
793    CALL getin_p('ZSNOWCMPCT_VT',ZSNOWCMPCT_VT)
794
795    !Config Key = ZSNOWCMPCT_VR
796    !Config Desc = Vapor coefficent for the thermal conductivity
797    !Config If = OK_SECHIBA
798    !Config Def = 0.018
799    !Config Help =
800    !Config Units = [m3/kg]
801    CALL getin_p('ZSNOWCMPCT_VR',ZSNOWCMPCT_VR)
802
803
804    !Surface resistance
805    !
806    !Config Key = CB
807    !Config Desc = Constant of the Louis scheme
808    !Config If = OK_SECHIBA
809    !Config Def = 5.0
810    !Config Help =
811    !Config Units = [-]
812    CALL getin_p('CB',cb)
813    !
814    !Config Key = CC
815    !Config Desc = Constant of the Louis scheme
816    !Config If = OK_SECHIBA
817    !Config Def = 5.0
818    !Config Help =
819    !Config Units = [-]
820    CALL getin_p('CC',cc)
821    !
822    !Config Key = CD
823    !Config Desc = Constant of the Louis scheme
824    !Config If = OK_SECHIBA
825    !Config Def = 5.0
826    !Config Help =
827    !Config Units = [-]
828    CALL getin_p('CD',cd)
829    !
830    !Config Key = RAYT_CSTE
831    !Config Desc = Constant in the computation of surface resistance 
832    !Config If = OK_SECHIBA
833    !Config Def = 125
834    !Config Help =
835    !Config Units = [W.m^{-2}]
836    CALL getin_p('RAYT_CSTE',rayt_cste)
837    !
838    !Config Key = DEFC_PLUS
839    !Config Desc = Constant in the computation of surface resistance 
840    !Config If = OK_SECHIBA
841    !Config Def = 23.E-3
842    !Config Help =
843    !Config Units = [K.W^{-1}]
844    CALL getin_p('DEFC_PLUS',defc_plus)
845    !
846    !Config Key = DEFC_MULT
847    !Config Desc = Constant in the computation of surface resistance 
848    !Config If = OK_SECHIBA
849    !Config Def = 1.5
850    !Config Help =
851    !Config Units = [K.W^{-1}]
852    CALL getin_p('DEFC_MULT',defc_mult)
853    !
854
855    !
856    !-
857    ! diffuco
858    !-
859    !
860    !Config Key   = NLAI
861    !Config Desc  = Number of LAI levels
862    !Config If    = OK_SECHIBA
863    !Config Def   = 20
864    !Config Help  =
865    !Config Units = [-] 
866    CALL getin_p('NLAI',nlai)
867    !
868    !Config Key   = LAIMAX
869    !Config Desc  = Maximum LAI
870    !Config If    = OK_SECHIBA
871    !Config Def   =
872    !Config Help  =
873    !Config Units = [m^2/m^2]   
874    CALL getin_p('LAIMAX',laimax)
875    !
876    !Config Key   = DEW_VEG_POLY_COEFF
877    !Config Desc  = coefficients of the polynome of degree 5 for the dew
878    !Config If    = OK_SECHIBA
879    !Config Def   = 0.887773, 0.205673, 0.110112, 0.014843, 0.000824, 0.000017
880    !Config Help  =
881    !Config Units = [-]   
882    CALL getin_p('DEW_VEG_POLY_COEFF',dew_veg_poly_coeff)
883    !
884    !Config Key   = DOWNREGULATION_CO2
885    !Config Desc  = Activation of CO2 downregulation
886    !Config If    = OK_SECHIBA
887    !Config Def   = n
888    !Config Help  =
889    !Config Units = [FLAG]   
890    CALL getin_p('DOWNREGULATION_CO2',downregulation_co2)
891    !
892    !Config Key   = DOWNREGULATION_CO2_BASELEVEL
893    !Config Desc  = CO2 base level
894    !Config If    = OK_SECHIBA
895    !Config Def   = 280.
896    !Config Help  =
897    !Config Units = [ppm]   
898    CALL getin_p('DOWNREGULATION_CO2_BASELEVEL',downregulation_co2_baselevel)
899
900   
901    !Config Key   = GB_REF
902    !Config Desc  = Leaf bulk boundary layer resistance
903    !Config If    = OK_CO2
904    !Config Def   = 1./25.
905    !Config Help  =
906    !Config Units = [s m-1]   
907    CALL getin_p('GB_REF',gb_ref)
908
909
910    !-
911    ! slowproc
912    !-
913    !
914    !Config Key   = CLAYFRACTION_DEFAULT
915    !Config Desc  = default fraction of clay
916    !Config If    = OK_SECHIBA
917    !Config Def   = 0.2
918    !Config Help  =
919    !Config Units = [-]   
920    CALL getin_p('CLAYFRACTION_DEFAULT',clayfraction_default)
921    !
922    !Config Key   = MIN_VEGFRAC
923    !Config Desc  = Minimal fraction of mesh a vegetation type can occupy
924    !Config If    = OK_SECHIBA
925    !Config Def   = 0.001
926    !Config Help  =
927    !Config Units = [-] 
928    CALL getin_p('MIN_VEGFRAC',min_vegfrac)
929    !
930    !Config Key   = STEMPDIAG_BID
931    !Config Desc  = only needed for an initial LAI if there is no restart file
932    !Config If    = OK_SECHIBA
933    !Config Def   = 280.
934    !Config Help  =
935    !Config Units = [K]
936    CALL getin_p('STEMPDIAG_BID',stempdiag_bid)
937    !
938
939  END SUBROUTINE config_sechiba_parameters
940
941
942!! ================================================================================================================================
943!! SUBROUTINE   : config_co2_parameters
944!!
945!>\BRIEF        This subroutine reads in the configuration file all the parameters
946!! needed when OK_CO2 is set to true. (ie : when the photosynthesis is activated)
947!!
948!! DESCRIPTION  : None
949!!
950!! RECENT CHANGE(S): None
951!!
952!! MAIN OUTPUT VARIABLE(S): None
953!!
954!! REFERENCE(S) :
955!!
956!! FLOWCHART    :
957!! \n
958!_ ================================================================================================================================
959
960  SUBROUTINE config_co2_parameters
961
962    IMPLICIT NONE
963
964    !! 0. Variables and parameters declaration
965
966    !! 0.4 Local variables
967
968    !_ ================================================================================================================================
969
970    !
971    !Config Key   = LAI_LEVEL_DEPTH
972    !Config Desc  =
973    !Config If    = OK_CO2
974    !Config Def   = 0.15
975    !Config Help  =
976    !Config Units = [-] 
977    CALL getin_p('LAI_LEVEL_DEPTH',lai_level_depth)
978    !
979    !Config Key   = Oi
980    !Config Desc  = Intercellular oxygen partial pressure
981    !Config If    = OK_CO2
982    !Config Def   = 210000.
983    !Config Help  = See Legend of Figure 6 of Yin et al. (2009)
984    !Config Units = [ubar] 
985    CALL getin_p('Oi',Oi)
986
987
988  END SUBROUTINE config_co2_parameters
989
990
991!! ================================================================================================================================
992!! SUBROUTINE   : config_stomate_parameters
993!!
994!>\BRIEF        This subroutine reads in the configuration file all the parameters
995!! needed when stomate is activated (ie : when OK_STOMATE is set to true).
996!!
997!! DESCRIPTION  : None
998!!
999!! RECENT CHANGE(S): None
1000!!
1001!! MAIN OUTPUT VARIABLE(S):
1002!!
1003!! REFERENCE(S) :
1004!!
1005!! FLOWCHART    :
1006!! \n
1007!_ ================================================================================================================================
1008
1009  SUBROUTINE config_stomate_parameters
1010
1011    IMPLICIT NONE
1012
1013    !! 0. Variables and parameters declaration
1014
1015    !! 0.4 Local variables   
1016
1017
1018    !_ ================================================================================================================================
1019
1020    !-
1021    ! constraints_parameters
1022    !-
1023    !
1024    !Config Key   = TOO_LONG
1025    !Config Desc  = longest sustainable time without regeneration (vernalization)
1026    !Config If    = OK_STOMATE
1027    !Config Def   = 5.
1028    !Config Help  =
1029    !Config Units = [days]   
1030    CALL getin_p('TOO_LONG',too_long)
1031
1032    !-
1033    ! fire parameters
1034    !-
1035    !
1036    !Config Key   = TAU_FIRE
1037    !Config Desc  = Time scale for memory of the fire index (days). Validated for one year in the DGVM.
1038    !Config If    = OK_STOMATE
1039    !Config Def   = 30.
1040    !Config Help  =
1041    !Config Units = [days]   
1042    CALL getin_p('TAU_FIRE',tau_fire)
1043    !
1044    !Config Key   = LITTER_CRIT
1045    !Config Desc  = Critical litter quantity for fire
1046    !Config If    = OK_STOMATE
1047    !Config Def   = 200.
1048    !Config Help  =
1049    !Config Units = [gC/m^2] 
1050    CALL getin_p('LITTER_CRIT',litter_crit)
1051    !
1052    !Config Key   = FIRE_RESIST_STRUCT
1053    !Config Desc  =
1054    !Config If    = OK_STOMATE
1055    !Config Def   = 0.5
1056    !Config Help  =
1057    !Config Units = [-] 
1058    CALL getin_p('FIRE_RESIST_STRUCT',fire_resist_struct)
1059    !
1060    !
1061    !Config Key   = CO2FRAC
1062    !Config Desc  = What fraction of a burned plant compartment goes into the atmosphere
1063    !Config If    = OK_STOMATE
1064    !Config Def   = 0.95, 0.95, 0., 0.3, 0., 0., 0.95, 0.95
1065    !Config Help  =
1066    !Config Units = [-] 
1067    CALL getin_p('CO2FRAC',co2frac)
1068    !
1069    !Config Key   = BCFRAC_COEFF
1070    !Config Desc  =
1071    !Config If    = OK_STOMATE
1072    !Config Def   = 0.3, 1.3, 88.2
1073    !Config Help  =
1074    !Config Units = [-] 
1075    CALL getin_p('BCFRAC_COEFF',bcfrac_coeff)
1076    !
1077    !Config Key   = FIREFRAC_COEFF
1078    !Config Desc  =
1079    !Config If    = OK_STOMATE
1080    !Config Def   = 0.45, 0.8, 0.6, 0.13
1081    !Config Help  =
1082    !Config Units = [-]   
1083    CALL getin_p('FIREFRAC_COEFF',firefrac_coeff)
1084
1085    !Config Key   = REF_GREFF
1086    !Config Desc  = Asymptotic maximum mortality rate
1087    !Config If    = OK_STOMATE
1088    !Config Def   = 0.035
1089    !Config Help  = Set asymptotic maximum mortality rate from Sitch 2003
1090    !Config         (they use 0.01) (year^{-1})
1091    !Config Units = [1/year] 
1092    CALL getin_p('REF_GREFF',ref_greff)
1093    !-
1094    ! allocation parameters
1095    !-
1096    !
1097    !Config Key   = OK_MINRES
1098    !Config Desc  = Do we try to reach a minimum reservoir even if we are severely stressed?
1099    !Config If    = OK_STOMATE
1100    !Config Def   = y
1101    !Config Help  =
1102    !Config Units = [FLAG]
1103    CALL getin_p('OK_MINRES',ok_minres)
1104    !
1105    !Config Key   = RESERVE_TIME_TREE
1106    !Config Desc  = maximum time during which reserve is used (trees)
1107    !Config If    = OK_STOMATE
1108    !Config Def   = 30.
1109    !Config Help  =
1110    !Config Units = [days]   
1111    CALL getin_p('RESERVE_TIME_TREE',reserve_time_tree)
1112    !
1113    !Config Key   = RESERVE_TIME_GRASS
1114    !Config Desc  = maximum time during which reserve is used (grasses)
1115    !Config If    = OK_STOMATE
1116    !Config Def   = 20.
1117    !Config Help  =
1118    !Config Units = [days]   
1119    CALL getin_p('RESERVE_TIME_GRASS',reserve_time_grass)
1120    !
1121    !Config Key   = F_FRUIT
1122    !Config Desc  = Standard fruit allocation
1123    !Config If    = OK_STOMATE
1124    !Config Def   = 0.1
1125    !Config Help  =
1126    !Config Units = [-]   
1127    CALL getin_p('F_FRUIT',f_fruit)
1128    !
1129    !Config Key   = ALLOC_SAP_ABOVE_GRASS
1130    !Config Desc  = fraction of sapwood allocation above ground
1131    !Config If    = OK_STOMATE
1132    !Config Def   = 1.0
1133    !Config Help  =
1134    !Config Units = [-]   
1135    CALL getin_p('ALLOC_SAP_ABOVE_GRASS',alloc_sap_above_grass)
1136    !
1137    !Config Key   = MIN_LTOLSR
1138    !Config Desc  = extrema of leaf allocation fraction
1139    !Config If    = OK_STOMATE
1140    !Config Def   = 0.2
1141    !Config Help  =
1142    !Config Units = [-]   
1143    CALL getin_p('MIN_LTOLSR',min_LtoLSR)
1144    !
1145    !Config Key   = MAX_LTOLSR
1146    !Config Desc  = extrema of leaf allocation fraction
1147    !Config If    = OK_STOMATE
1148    !Config Def   = 0.5
1149    !Config Help  =
1150    !Config Units = [-]   
1151    CALL getin_p('MAX_LTOLSR',max_LtoLSR)
1152    !
1153    !Config Key   = Z_NITROGEN
1154    !Config Desc  = scaling depth for nitrogen limitation
1155    !Config If    = OK_STOMATE
1156    !Config Def   = 0.2
1157    !Config Help  =
1158    !Config Units = [m] 
1159    CALL getin_p('Z_NITROGEN',z_nitrogen)
1160    !
1161    !Config Key   = NLIM_TREF
1162    !Config Desc  =
1163    !Config If    = OK_STOMATE
1164    !Config Def   = 25.
1165    !Config Help  =
1166    !Config Units = [C] 
1167    CALL getin_p('NLIM_TREF',Nlim_tref) 
1168
1169    !-
1170    ! data parameters
1171    !-
1172    !
1173    !Config Key   = PIPE_TUNE1
1174    !Config Desc  = crown area = pipe_tune1. stem diameter**(1.6) (Reinicke's theory)
1175    !Config If    = OK_STOMATE
1176    !Config Def   = 100.0
1177    !Config Help  =
1178    !Config Units = [-]   
1179    CALL getin_p('PIPE_TUNE1',pipe_tune1)
1180    !
1181    !Config Key   = PIPE_TUNE2
1182    !Config Desc  = height=pipe_tune2 * diameter**pipe_tune3
1183    !Config If    = OK_STOMATE
1184    !Config Def   = 40.0
1185    !Config Help  =
1186    !Config Units = [-]     
1187    CALL getin_p('PIPE_TUNE2',pipe_tune2) 
1188    !
1189    !Config Key   = PIPE_TUNE3
1190    !Config Desc  = height=pipe_tune2 * diameter**pipe_tune3
1191    !Config If    = OK_STOMATE
1192    !Config Def   = 0.5
1193    !Config Help  =
1194    !Config Units = [-]   
1195    CALL getin_p('PIPE_TUNE3',pipe_tune3)
1196    !
1197    !Config Key   = PIPE_TUNE4
1198    !Config Desc  = needed for stem diameter
1199    !Config If    = OK_STOMATE
1200    !Config Def   = 0.3
1201    !Config Help  =
1202    !Config Units = [-] 
1203    CALL getin_p('PIPE_TUNE4',pipe_tune4)
1204    !
1205    !Config Key   = PIPE_DENSITY
1206    !Config Desc  = Density
1207    !Config If    = OK_STOMATE
1208    !Config Def   = 2.e5
1209    !Config Help  =
1210    !Config Units = [-] 
1211    CALL getin_p('PIPE_DENSITY',pipe_density)
1212    !
1213    !Config Key   = PIPE_K1
1214    !Config Desc  =
1215    !Config If    = OK_STOMATE
1216    !Config Def   = 8.e3
1217    !Config Help  =
1218    !Config Units = [-]   
1219    CALL getin_p('PIPE_K1',pipe_k1)
1220    !
1221    !Config Key   = PIPE_TUNE_EXP_COEFF
1222    !Config Desc  = pipe tune exponential coeff
1223    !Config If    = OK_STOMATE
1224    !Config Def   = 1.6
1225    !Config Help  =
1226    !Config Units = [-]   
1227    CALL getin_p('PIPE_TUNE_EXP_COEFF',pipe_tune_exp_coeff)
1228    !
1229    !
1230    !Config Key   = PRECIP_CRIT
1231    !Config Desc  = minimum precip
1232    !Config If    = OK_STOMATE
1233    !Config Def   = 100.
1234    !Config Help  =
1235    !Config Units = [mm/year] 
1236    CALL getin_p('PRECIP_CRIT',precip_crit)
1237    !
1238    !Config Key   = GDD_CRIT_ESTAB
1239    !Config Desc  = minimum gdd for establishment of saplings
1240    !Config If    = OK_STOMATE
1241    !Config Def   = 150.
1242    !Config Help  =
1243    !Config Units = [-] 
1244    CALL getin_p('GDD_CRIT_ESTAB',gdd_crit_estab)
1245    !
1246    !Config Key   = FPC_CRIT
1247    !Config Desc  = critical fpc, needed for light competition and establishment
1248    !Config If    = OK_STOMATE
1249    !Config Def   = 0.95
1250    !Config Help  =
1251    !Config Units = [-] 
1252    CALL getin_p('FPC_CRIT',fpc_crit)
1253    !
1254    !Config Key   = ALPHA_GRASS
1255    !Config Desc  = sapling characteristics : alpha's
1256    !Config If    = OK_STOMATE
1257    !Config Def   = 0.5
1258    !Config Help  =
1259    !Config Units = [-]   
1260    CALL getin_p('ALPHA_GRASS',alpha_grass)
1261    !
1262    !Config Key   = ALPHA_TREE
1263    !Config Desc  = sapling characteristics : alpha's
1264    !Config If    = OK_STOMATE
1265    !Config Def   = 1.
1266    !Config Help  =
1267    !Config Units = [-]   
1268    CALL getin_p('ALPHA_TREE',alpha_tree)
1269    !-
1270    !
1271    !Config Key   = MASS_RATIO_HEART_SAP
1272    !Config Desc  = mass ratio (heartwood+sapwood)/sapwood
1273    !Config If    = OK_STOMATE
1274    !Config Def   = 3.
1275    !Config Help  =
1276    !Config Units = [-]   
1277    CALL getin_p('MASS_RATIO_HEART_SAP',mass_ratio_heart_sap)
1278    !
1279    !Config Key   = TAU_HUM_MONTH
1280    !Config Desc  = time scales for phenology and other processes
1281    !Config If    = OK_STOMATE
1282    !Config Def   = 20.
1283    !Config Help  =
1284    !Config Units = [days] 
1285    CALL getin_p('TAU_HUM_MONTH',tau_hum_month)
1286    !
1287    !Config Key   = TAU_HUM_WEEK
1288    !Config Desc  = time scales for phenology and other processes
1289    !Config If    = OK_STOMATE
1290    !Config Def   = 7.
1291    !Config Help  =
1292    !Config Units = [days]   
1293    CALL getin_p('TAU_HUM_WEEK',tau_hum_week)
1294    !
1295    !Config Key   = TAU_T2M_MONTH
1296    !Config Desc  = time scales for phenology and other processes
1297    !Config If    = OK_STOMATE
1298    !Config Def   = 20.
1299    !Config Help  =
1300    !Config Units = [days]     
1301    CALL getin_p('TAU_T2M_MONTH',tau_t2m_month)
1302    !
1303    !Config Key   = TAU_T2M_WEEK
1304    !Config Desc  = time scales for phenology and other processes
1305    !Config If    = OK_STOMATE
1306    !Config Def   = 7.
1307    !Config Help  =
1308    !Config Units = [days]   
1309    CALL getin_p('TAU_T2M_WEEK',tau_t2m_week)
1310    !
1311    !Config Key   = TAU_TSOIL_MONTH
1312    !Config Desc  = time scales for phenology and other processes
1313    !Config If    = OK_STOMATE
1314    !Config Def   = 20.
1315    !Config Help  =
1316    !Config Units = [days]     
1317    CALL getin_p('TAU_TSOIL_MONTH',tau_tsoil_month)
1318    !
1319    !Config Key   = TAU_SOILHUM_MONTH
1320    !Config Desc  = time scales for phenology and other processes
1321    !Config If    = OK_STOMATE
1322    !Config Def   = 20.
1323    !Config Help  =
1324    !Config Units = [days]   
1325    CALL getin_p('TAU_SOILHUM_MONTH',tau_soilhum_month)
1326    !
1327    !Config Key   = TAU_GPP_WEEK
1328    !Config Desc  = time scales for phenology and other processes
1329    !Config If    = OK_STOMATE
1330    !Config Def   = 7.
1331    !Config Help  =
1332    !Config Units = [days]   
1333    CALL getin_p('TAU_GPP_WEEK',tau_gpp_week)
1334    !
1335    !Config Key   = TAU_GDD
1336    !Config Desc  = time scales for phenology and other processes
1337    !Config If    = OK_STOMATE
1338    !Config Def   = 40.
1339    !Config Help  =
1340    !Config Units = [days]   
1341    CALL getin_p('TAU_GDD',tau_gdd)
1342    !
1343    !Config Key   = TAU_NGD
1344    !Config Desc  = time scales for phenology and other processes
1345    !Config If    = OK_STOMATE
1346    !Config Def   = 50.
1347    !Config Help  =
1348    !Config Units = [days]   
1349    CALL getin_p('TAU_NGD',tau_ngd)
1350    !
1351    !Config Key   = COEFF_TAU_LONGTERM
1352    !Config Desc  = time scales for phenology and other processes
1353    !Config If    = OK_STOMATE
1354    !Config Def   = 3.
1355    !Config Help  =
1356    !Config Units = [days]   
1357    CALL getin_p('COEFF_TAU_LONGTERM',coeff_tau_longterm)
1358    !-
1359    !
1360    !Config Key   = BM_SAPL_CARBRES
1361    !Config Desc  =
1362    !Config If    = OK_STOMATE
1363    !Config Def   = 5.
1364    !Config Help  =
1365    !Config Units = [-]   
1366    CALL getin_p('BM_SAPL_CARBRES',bm_sapl_carbres)
1367    !
1368    !Config Key   = BM_SAPL_SAPABOVE
1369    !Config Desc  =
1370    !Config If    = OK_STOMATE
1371    !Config Def   = 0.5
1372    !Config Help  =
1373    !Config Units = [-]   
1374    CALL getin_p('BM_SAPL_SAPABOVE',bm_sapl_sapabove)
1375    !
1376    !Config Key   = BM_SAPL_HEARTABOVE
1377    !Config Desc  =
1378    !Config If    = OK_STOMATE
1379    !Config Def   = 2.
1380    !Config Help  =
1381    !Config Units = [-]   
1382    CALL getin_p('BM_SAPL_HEARTABOVE',bm_sapl_heartabove)
1383    !
1384    !Config Key   = BM_SAPL_HEARTBELOW
1385    !Config Desc  =
1386    !Config If    = OK_STOMATE
1387    !Config Def   = 2.
1388    !Config Help  =
1389    !Config Units = [-]   
1390    CALL getin_p('BM_SAPL_HEARTBELOW',bm_sapl_heartbelow)
1391    !
1392    !Config Key   = INIT_SAPL_MASS_LEAF_NAT
1393    !Config Desc  =
1394    !Config If    = OK_STOMATE
1395    !Config Def   = 0.1
1396    !Config Help  =
1397    !Config Units = [-]   
1398    CALL getin_p('INIT_SAPL_MASS_LEAF_NAT',init_sapl_mass_leaf_nat)
1399    !
1400    !Config Key   = INIT_SAPL_MASS_LEAF_AGRI
1401    !Config Desc  =
1402    !Config If    = OK_STOMATE
1403    !Config Def   = 1.
1404    !Config Help  =
1405    !Config Units = [-]   
1406    CALL getin_p('INIT_SAPL_MASS_LEAF_AGRI',init_sapl_mass_leaf_agri)
1407    !
1408    !Config Key   = INIT_SAPL_MASS_CARBRES
1409    !Config Desc  =
1410    !Config If    = OK_STOMATE
1411    !Config Def   = 5.
1412    !Config Help  =
1413    !Config Units = [-]   
1414    CALL getin_p('INIT_SAPL_MASS_CARBRES',init_sapl_mass_carbres)
1415    !
1416    !Config Key   = INIT_SAPL_MASS_ROOT
1417    !Config Desc  =
1418    !Config If    = OK_STOMATE
1419    !Config Def   = 0.1
1420    !Config Help  =
1421    !Config Units = [-]   
1422    CALL getin_p('INIT_SAPL_MASS_ROOT',init_sapl_mass_root)
1423    !
1424    !Config Key   = INIT_SAPL_MASS_FRUIT
1425    !Config Desc  =
1426    !Config If    = OK_STOMATE
1427    !Config Def   = 0.3
1428    !Config Help  =
1429    !Config Units = [-]   
1430    CALL getin_p('INIT_SAPL_MASS_FRUIT',init_sapl_mass_fruit)
1431    !
1432    !Config Key   = CN_SAPL_INIT
1433    !Config Desc  =
1434    !Config If    = OK_STOMATE
1435    !Config Def   = 0.5
1436    !Config Help  =
1437    !Config Units = [-]   
1438    CALL getin_p('CN_SAPL_INIT',cn_sapl_init)
1439    !
1440    !Config Key   = MIGRATE_TREE
1441    !Config Desc  =
1442    !Config If    = OK_STOMATE
1443    !Config Def   = 10000.
1444    !Config Help  =
1445    !Config Units = [m/year]   
1446    CALL getin_p('MIGRATE_TREE',migrate_tree)
1447    !
1448    !Config Key   = MIGRATE_GRASS
1449    !Config Desc  =
1450    !Config If    = OK_STOMATE
1451    !Config Def   = 10000.
1452    !Config Help  =
1453    !Config Units = [m/year]   
1454    CALL getin_p('MIGRATE_GRASS',migrate_grass)
1455    !
1456    !Config Key   = LAI_INITMIN_TREE
1457    !Config Desc  =
1458    !Config If    = OK_STOMATE
1459    !Config Def   = 0.3
1460    !Config Help  =
1461    !Config Units = [m^2/m^2] 
1462    CALL getin_p('LAI_INITMIN_TREE',lai_initmin_tree)
1463    !
1464    !Config Key   = LAI_INITMIN_GRASS
1465    !Config Desc  =
1466    !Config If    = OK_STOMATE
1467    !Config Def   = 0.1
1468    !Config Help  =
1469    !Config Units = [m^2/m^2]   
1470    CALL getin_p('LAI_INITMIN_GRASS',lai_initmin_grass)
1471    !
1472    !Config Key   = DIA_COEFF
1473    !Config Desc  =
1474    !Config If    = OK_STOMATE
1475    !Config Def   = 4., 0.5
1476    !Config Help  =
1477    !Config Units = [-]   
1478    CALL getin_p('DIA_COEFF',dia_coeff)
1479    !
1480    !Config Key   = MAXDIA_COEFF
1481    !Config Desc  =
1482    !Config If    = OK_STOMATE
1483    !Config Def   = 100., 0.01
1484    !Config Help  =
1485    !Config Units = [-]   
1486    CALL getin_p('MAXDIA_COEFF',maxdia_coeff)
1487    !
1488    !Config Key   = BM_SAPL_LEAF
1489    !Config Desc  =
1490    !Config If    = OK_STOMATE
1491    !Config Def   = 4., 4., 0.8, 5.
1492    !Config Help  =
1493    !Config Units = [-] 
1494    CALL getin_p('BM_SAPL_LEAF',bm_sapl_leaf)
1495
1496    !-
1497    ! litter parameters
1498    !-
1499    !
1500    !Config Key   = METABOLIC_REF_FRAC
1501    !Config Desc  =
1502    !Config If    = OK_STOMATE
1503    !Config Def   = 0.85 
1504    !Config Help  =
1505    !Config Units = [-]
1506    CALL getin_p('METABOLIC_REF_FRAC',metabolic_ref_frac)
1507    !
1508    !Config Key   = Z_DECOMP
1509    !Config Desc  = scaling depth for soil activity
1510    !Config If    = OK_STOMATE
1511    !Config Def   = 0.2
1512    !Config Help  =
1513    !Config Units = [m]   
1514    CALL getin_p('Z_DECOMP',z_decomp)
1515    !
1516    !Config Key   = CN
1517    !Config Desc  = C/N ratio
1518    !Config If    = OK_STOMATE
1519    !Config Def   = 40., 40., 40., 40., 40., 40., 40., 40.
1520    !Config Help  =
1521    !Config Units = [-] 
1522    CALL getin_p('CN',CN)
1523    !
1524    !Config Key   = LC
1525    !Config Desc  = Lignine/C ratio of the different plant parts
1526    !Config If    = OK_STOMATE
1527    !Config Def   = 0.22, 0.35, 0.35, 0.35, 0.35, 0.22, 0.22, 0.22
1528    !Config Help  =
1529    !Config Units = [-]   
1530    CALL getin_p('LC',LC)
1531    !
1532    !Config Key   = FRAC_SOIL_STRUCT_AA
1533    !Config Desc  = frac_soil(istructural,iactive,iabove)
1534    !Config If    = OK_STOMATE
1535    !Config Def   = 0.55
1536    !Config Help  =
1537    !Config Units = [-]
1538    CALL getin_p('FRAC_SOIL_STRUCT_AA',frac_soil_struct_aa)
1539    !
1540    !Config Key   = FRAC_SOIL_STRUCT_A
1541    !Config Desc  = frac_soil(istructural,iactive,ibelow)
1542    !Config If    = OK_STOMATE
1543    !Config Def   = 0.45
1544    !Config Help  =
1545    !Config Units = [-]
1546    CALL getin_p('FRAC_SOIL_STRUCT_AB',frac_soil_struct_ab)
1547    !
1548    !Config Key   = FRAC_SOIL_STRUCT_SA
1549    !Config Desc  = frac_soil(istructural,islow,iabove)
1550    !Config If    = OK_STOMATE
1551    !Config Def   = 0.7 
1552    !Config Help  =
1553    !Config Units = [-]   
1554    CALL getin_p('FRAC_SOIL_STRUCT_SA',frac_soil_struct_sa)
1555    !
1556    !Config Key   = FRAC_SOIL_STRUCT_SB
1557    !Config Desc  = frac_soil(istructural,islow,ibelow)
1558    !Config If    = OK_STOMATE
1559    !Config Def   = 0.7 
1560    !Config Help  =
1561    !Config Units = [-]   
1562    CALL getin_p('FRAC_SOIL_STRUCT_SB',frac_soil_struct_sb)
1563    !
1564    !Config Key   = FRAC_SOIL_METAB_AA
1565    !Config Desc  = frac_soil(imetabolic,iactive,iabove)
1566    !Config If    = OK_STOMATE
1567    !Config Def   = 0.45
1568    !Config Help  =
1569    !Config Units = [-]   
1570    CALL getin_p('FRAC_SOIL_METAB_AA',frac_soil_metab_aa)
1571    !
1572    !Config Key   = FRAC_SOIL_METAB_AB
1573    !Config Desc  = frac_soil(imetabolic,iactive,ibelow)
1574    !Config If    = OK_STOMATE
1575    !Config Def   = 0.45 
1576    !Config Help  =
1577    !Config Units = [-]   
1578    CALL getin_p('FRAC_SOIL_METAB_AB',frac_soil_metab_ab)
1579    !
1580    !
1581    !Config Key   = METABOLIC_LN_RATIO
1582    !Config Desc  =
1583    !Config If    = OK_STOMATE
1584    !Config Def   = 0.018 
1585    !Config Help  =
1586    !Config Units = [-]   
1587    CALL getin_p('METABOLIC_LN_RATIO',metabolic_LN_ratio) 
1588    !
1589    !Config Key   = TAU_METABOLIC
1590    !Config Desc  =
1591    !Config If    = OK_STOMATE
1592    !Config Def   = 0.066
1593    !Config Help  =
1594    !Config Units = [days]
1595    CALL getin_p('TAU_METABOLIC',tau_metabolic)
1596    !
1597    !Config Key   = TAU_STRUCT
1598    !Config Desc  =
1599    !Config If    = OK_STOMATE
1600    !Config Def   = 0.245
1601    !Config Help  =
1602    !Config Units = [days]
1603    CALL getin_p('TAU_STRUCT',tau_struct)
1604    !
1605    !Config Key   = SOIL_Q10
1606    !Config Desc  =
1607    !Config If    = OK_STOMATE
1608    !Config Def   = 0.69 (=ln2)
1609    !Config Help  =
1610    !Config Units = [-]
1611    CALL getin_p('SOIL_Q10',soil_Q10)
1612    !
1613    !Config Key   = TSOIL_REF
1614    !Config Desc  =
1615    !Config If    = OK_STOMATE
1616    !Config Def   = 30.
1617    !Config Help  =
1618    !Config Units = [C]   
1619    CALL getin_p('TSOIL_REF',tsoil_ref)
1620    !
1621    !Config Key   = LITTER_STRUCT_COEF
1622    !Config Desc  =
1623    !Config If    = OK_STOMATE
1624    !Config Def   = 3.
1625    !Config Help  =
1626    !Config Units = [-]   
1627    CALL getin_p('LITTER_STRUCT_COEF',litter_struct_coef)
1628    !
1629    !Config Key   = MOIST_COEFF
1630    !Config Desc  =
1631    !Config If    = OK_STOMATE
1632    !Config Def   = 1.1, 2.4, 0.29
1633    !Config Help  =
1634    !Config Units = [-]   
1635    CALL getin_p('MOIST_COEFF',moist_coeff)
1636    !
1637    !Config Key   = MOISTCONT_MIN
1638    !Config Desc  = minimum soil wetness to limit the heterotrophic respiration
1639    !Config If    = OK_STOMATE
1640    !Config Def   = 0.25
1641    !Config Help  =
1642    !Config Units = [-]
1643    CALL getin_p('MOISTCONT_MIN',moistcont_min)
1644
1645    !-
1646    ! lpj parameters
1647    !-
1648    !
1649    !Config Key   = FRAC_TURNOVER_DAILY
1650    !Config Desc  =
1651    !Config If    = OK_STOMATE
1652    !Config Def   = 0.55
1653    !Config Help  =
1654    !Config Units = [-]
1655    CALL getin_p('FRAC_TURNOVER_DAILY',frac_turnover_daily)   
1656
1657    !-
1658    ! npp parameters
1659    !-
1660    !
1661    !Config Key   = TAX_MAX
1662    !Config Desc  = maximum fraction of allocatable biomass used for maintenance respiration
1663    !Config If    = OK_STOMATE
1664    !Config Def   = 0.8
1665    !Config Help  =
1666    !Config Units = [-]   
1667    CALL getin_p('TAX_MAX',tax_max) 
1668
1669    !-
1670    ! phenology parameters
1671    !-
1672    !
1673    !Config Key   = ALWAYS_INIT
1674    !Config Desc  = take carbon from atmosphere if carbohydrate reserve too small?
1675    !Config If    = OK_STOMATE
1676    !Config Def   = n
1677    !Config Help  =
1678    !Config Units = [-]   
1679    CALL getin_p('ALWAYS_INIT',always_init)
1680    !
1681    !Config Key   = MIN_GROWTHINIT_TIME
1682    !Config Desc  = minimum time since last beginning of a growing season
1683    !Config If    = OK_STOMATE
1684    !Config Def   = 300.
1685    !Config Help  =
1686    !Config Units = [days] 
1687    CALL getin_p('MIN_GROWTHINIT_TIME',min_growthinit_time)
1688    !
1689    !Config Key   = MOIAVAIL_ALWAYS_TREE
1690    !Config Desc  = moisture availability above which moisture tendency doesn't matter
1691    !Config If    = OK_STOMATE
1692    !Config Def   = 1.0
1693    !Config Help  =
1694    !Config Units = [-]   
1695    CALL getin_p('MOIAVAIL_ALWAYS_TREE',moiavail_always_tree)
1696    !
1697    !Config Key   = MOIAVAIL_ALWAYS_GRASS
1698    !Config Desc  = moisture availability above which moisture tendency doesn't matter
1699    !Config If    = OK_STOMATE
1700    !Config Def   = 0.6
1701    !Config Help  =
1702    !Config Units = [-]   
1703    CALL getin_p('MOIAVAIL_ALWAYS_GRASS',moiavail_always_grass)
1704    !
1705    !Config Key   = T_ALWAYS_ADD
1706    !Config Desc  = monthly temp. above which temp. tendency doesn't matter
1707    !Config If    = OK_STOMATE
1708    !Config Def   = 10.
1709    !Config Help  =
1710    !Config Units = [C]   
1711    CALL getin_p('T_ALWAYS_ADD',t_always_add)
1712    !
1713    !
1714    !Config Key   = GDDNCD_REF
1715    !Config Desc  =
1716    !Config If    = OK_STOMATE
1717    !Config Def   = 603.
1718    !Config Help  =
1719    !Config Units = [-]   
1720    CALL getin_p('GDDNCD_REF',gddncd_ref)
1721    !
1722    !Config Key   = GDDNCD_CURVE
1723    !Config Desc  =
1724    !Config If    = OK_STOMATE
1725    !Config Def   = 0.0091
1726    !Config Help  =
1727    !Config Units = [-] 
1728    CALL getin_p('GDDNCD_CURVE',gddncd_curve)
1729    !
1730    !Config Key   = GDDNCD_OFFSET
1731    !Config Desc  =
1732    !Config If    = OK_STOMATE
1733    !Config Def   = 64.
1734    !Config Help  =
1735    !Config Units = [-] 
1736    CALL getin_p('GDDNCD_OFFSET',gddncd_offset)
1737    !-
1738    ! prescribe parameters
1739    !-
1740    !
1741    !Config Key   = BM_SAPL_RESCALE
1742    !Config Desc  =
1743    !Config If    = OK_STOMATE
1744    !Config Def   = 40.
1745    !Config Help  =
1746    !Config Units = [-] 
1747    CALL getin_p('BM_SAPL_RESCALE',bm_sapl_rescale)
1748
1749    !-
1750    ! respiration parameters
1751    !-
1752    !
1753    !Config Key   = MAINT_RESP_MIN_VMAX
1754    !Config Desc  =
1755    !Config If    = OK_STOMATE
1756    !Config Def   = 0.3
1757    !Config Help  =
1758    !Config Units = [-] 
1759    CALL getin_p('MAINT_RESP_MIN_VMAX',maint_resp_min_vmax) 
1760    !
1761    !Config Key   = MAINT_RESP_COEFF
1762    !Config Desc  =
1763    !Config If    = OK_STOMATE
1764    !Config Def   = 1.4
1765    !Config Help  =
1766    !Config Units = [-]
1767    CALL getin_p('MAINT_RESP_COEFF',maint_resp_coeff)
1768
1769    !-
1770    ! soilcarbon parameters
1771    !-
1772    !
1773    !Config Key   = FRAC_CARB_AP
1774    !Config Desc  = frac carb coefficients from active pool: depends on clay content
1775    !Config if    = OK_STOMATE
1776    !Config Def   = 0.004
1777    !Config Help  = fraction of the active pool going into the passive pool
1778    !Config Units = [-]
1779    CALL getin_p('FRAC_CARB_AP',frac_carb_ap) 
1780    !
1781    !Config Key   = FRAC_CARB_SA
1782    !Config Desc  = frac_carb_coefficients from slow pool
1783    !Config if    = OK_STOMATE
1784    !Config Def   = 0.42
1785    !Config Help  = fraction of the slow pool going into the active pool
1786    !Config Units = [-]
1787    CALL getin_p('FRAC_CARB_SA',frac_carb_sa)
1788    !
1789    !Config Key   = FRAC_CARB_SP
1790    !Config Desc  = frac_carb_coefficients from slow pool
1791    !Config if    = OK_STOMATE
1792    !Config Def   = 0.03
1793    !Config Help  = fraction of the slow pool going into the passive pool
1794    !Config Units = [-]
1795    CALL getin_p('FRAC_CARB_SP',frac_carb_sp)
1796    !
1797    !Config Key   = FRAC_CARB_PA
1798    !Config Desc  = frac_carb_coefficients from passive pool
1799    !Config if    = OK_STOMATE
1800    !Config Def   = 0.45
1801    !Config Help  = fraction of the passive pool going into the active pool
1802    !Config Units = [-]
1803    CALL getin_p('FRAC_CARB_PA',frac_carb_pa)
1804    !
1805    !Config Key   = FRAC_CARB_PS
1806    !Config Desc  = frac_carb_coefficients from passive pool
1807    !Config if    = OK_STOMATE
1808    !Config Def   = 0.0
1809    !Config Help  = fraction of the passive pool going into the slow pool
1810    !Config Units = [-]
1811    CALL getin_p('FRAC_CARB_PS',frac_carb_ps)
1812    !
1813    !Config Key   = ACTIVE_TO_PASS_CLAY_FRAC
1814    !Config Desc  =
1815    !Config if    = OK_STOMATE
1816    !Config Def   = 0.68 
1817    !Config Help  =
1818    !Config Units = [-]
1819    CALL getin_p('ACTIVE_TO_PASS_CLAY_FRAC',active_to_pass_clay_frac)
1820    !
1821    !Config Key   = CARBON_TAU_IACTIVE
1822    !Config Desc  = residence times in carbon pools
1823    !Config if    = OK_STOMATE
1824    !Config Def   = 0.149
1825    !Config Help  =
1826    !Config Units =  [days]
1827    CALL getin_p('CARBON_TAU_IACTIVE',carbon_tau_iactive)
1828    !
1829    !Config Key   = CARBON_TAU_ISLOW
1830    !Config Desc  = residence times in carbon pools
1831    !Config if    = OK_STOMATE
1832    !Config Def   = 5.48
1833    !Config Help  =
1834    !Config Units = [days]
1835    CALL getin_p('CARBON_TAU_ISLOW',carbon_tau_islow)
1836    !
1837    !Config Key   = CARBON_TAU_IPASSIVE
1838    !Config Desc  = residence times in carbon pools
1839    !Config if    = OK_STOMATE
1840    !Config Def   = 241.
1841    !Config Help  = residence time in the passive pool
1842    !Config Units = [days]
1843    CALL getin_p('CARBON_TAU_IPASSIVE',carbon_tau_ipassive)
1844    !
1845    !Config Key   = FLUX_TOT_COEFF
1846    !Config Desc  =
1847    !Config if    = OK_STOMATE
1848    !Config Def   = 1.2, 1.4,.75
1849    !Config Help  =
1850    !Config Units = [days]
1851    CALL getin_p('FLUX_TOT_COEFF',flux_tot_coeff)
1852
1853    !-
1854    ! turnover parameters
1855    !-
1856    !
1857    !Config Key   = NEW_TURNOVER_TIME_REF
1858    !Config Desc  =
1859    !Config If    = OK_STOMATE
1860    !Config Def   = 20.
1861    !Config Help  =
1862    !Config Units = [days] 
1863    CALL getin_p('NEW_TURNOVER_TIME_REF',new_turnover_time_ref)
1864
1865    !Config Key   = LEAF_AGE_CRIT_TREF
1866    !Config Desc  =
1867    !Config If    = OK_STOMATE
1868    !Config Def   = 20.
1869    !Config Help  =
1870    !Config Units = [days] 
1871    CALL getin_p('LEAF_AGE_CRIT_TREF',leaf_age_crit_tref)
1872    !
1873    !Config Key   = LEAF_AGE_CRIT_COEFF
1874    !Config Desc  =
1875    !Config If    = OK_STOMATE
1876    !Config Def   = 1.5, 0.75, 10.
1877    !Config Help  =
1878    !Config Units = [-]
1879    CALL getin_p('LEAF_AGE_CRIT_COEFF',leaf_age_crit_coeff)
1880
1881    !-
1882    ! vmax parameters
1883    !-
1884    !
1885    !Config Key   = VMAX_OFFSET
1886    !Config Desc  = offset (minimum relative vcmax)
1887    !Config If    = OK_STOMATE
1888    !Config Def   = 0.3
1889    !Config Help  = offset (minimum vcmax/vmax_opt)
1890    !Config Units = [-] 
1891    CALL getin_p('VMAX_OFFSET',vmax_offset)
1892    !
1893    !Config Key   = LEAFAGE_FIRSTMAX
1894    !Config Desc  = leaf age at which vmax attains vcmax_opt (in fraction of critical leaf age)
1895    !Config If    = OK_STOMATE
1896    !Config Def   = 0.03
1897    !Config Help  = relative leaf age at which vmax attains vcmax_opt
1898    !Config Units = [-]
1899    CALL getin_p('LEAFAGE_FIRSTMAX',leafage_firstmax)
1900    !
1901    !Config Key   = LEAFAGE_LASTMAX
1902    !Config Desc  = leaf age at which vmax falls below vcmax_opt (in fraction of critical leaf age)
1903    !Config If    = OK_STOMATE
1904    !Config Def   = 0.5
1905    !Config Help  = relative leaf age at which vmax falls below vcmax_opt
1906    !Config Units = [-] 
1907    CALL getin_p('LEAFAGE_LASTMAX',leafage_lastmax)
1908    !
1909    !Config Key   = LEAFAGE_OLD
1910    !Config Desc  = leaf age at which vmax attains its minimum (in fraction of critical leaf age)
1911    !Config If    = OK_STOMATE
1912    !Config Def   = 1.
1913    !Config Help  = relative leaf age at which vmax attains its minimum
1914    !Config Units = [-] 
1915    CALL getin_p('LEAFAGE_OLD',leafage_old)
1916
1917    !-
1918    ! season parameters
1919    !-
1920    !
1921    !Config Key   = GPPFRAC_DORMANCE
1922    !Config Desc  = rapport maximal GPP/GGP_max pour dormance
1923    !Config If    = OK_STOMATE
1924    !Config Def   = 0.2
1925    !Config Help  =
1926    !Config Units = [-]
1927    CALL getin_p('GPPFRAC_DORMANCE',gppfrac_dormance)
1928    !
1929    !Config Key   = TAU_CLIMATOLOGY
1930    !Config Desc  = tau for "climatologic variables
1931    !Config If    = OK_STOMATE
1932    !Config Def   = 20
1933    !Config Help  =
1934    !Config Units = [days]
1935    CALL getin_p('TAU_CLIMATOLOGY',tau_climatology)
1936    !
1937    !Config Key   = HVC1
1938    !Config Desc  = parameters for herbivore activity
1939    !Config If    = OK_STOMATE
1940    !Config Def   = 0.019
1941    !Config Help  =
1942    !Config Units = [-] 
1943    CALL getin_p('HVC1',hvc1)
1944    !
1945    !Config Key   = HVC2
1946    !Config Desc  = parameters for herbivore activity
1947    !Config If    = OK_STOMATE
1948    !Config Def   = 1.38
1949    !Config Help  =
1950    !Config Units = [-] 
1951    CALL getin_p('HVC2',hvc2)
1952    !
1953    !Config Key   = LEAF_FRAC_HVC
1954    !Config Desc  = parameters for herbivore activity
1955    !Config If    = OK_STOMATE
1956    !Config Def   = 0.33
1957    !Config Help  =
1958    !Config Units = [-]
1959    CALL getin_p('LEAF_FRAC_HVC',leaf_frac_hvc)
1960    !
1961    !Config Key   = TLONG_REF_MAX
1962    !Config Desc  = maximum reference long term temperature
1963    !Config If    = OK_STOMATE
1964    !Config Def   = 303.1
1965    !Config Help  =
1966    !Config Units = [K] 
1967    CALL getin_p('TLONG_REF_MAX',tlong_ref_max)
1968    !
1969    !Config Key   = TLONG_REF_MIN
1970    !Config Desc  = minimum reference long term temperature
1971    !Config If    = OK_STOMATE
1972    !Config Def   = 253.1
1973    !Config Help  =
1974    !Config Units = [K] 
1975    CALL getin_p('TLONG_REF_MIN',tlong_ref_min)
1976    !
1977    !Config Key   = NCD_MAX_YEAR
1978    !Config Desc  =
1979    !Config If    = OK_STOMATE
1980    !Config Def   = 3.
1981    !Config Help  = NCD : Number of Chilling Days
1982    !Config Units = [days]
1983    CALL getin_p('NCD_MAX_YEAR',ncd_max_year)
1984    !
1985    !Config Key   = GDD_THRESHOLD
1986    !Config Desc  =
1987    !Config If    = OK_STOMATE
1988    !Config Def   = 5.
1989    !Config Help  = GDD : Growing-Degree-Day
1990    !Config Units = [days]
1991    CALL getin_p('GDD_THRESHOLD',gdd_threshold)
1992    !
1993    !Config Key   = GREEN_AGE_EVER
1994    !Config Desc  =
1995    !Config If    = OK_STOMATE
1996    !Config Def   = 2.
1997    !Config Help  =
1998    !Config Units = [-] 
1999    CALL getin_p('GREEN_AGE_EVER',green_age_ever)
2000    !
2001    !Config Key   = GREEN_AGE_DEC
2002    !Config Desc  =
2003    !Config If    = OK_STOMATE
2004    !Config Def   = 0.5
2005    !Config Help  =
2006    !Config Units = [-]
2007    CALL getin_p('GREEN_AGE_DEC',green_age_dec)
2008
2009  END SUBROUTINE config_stomate_parameters
2010
2011!! ================================================================================================================================
2012!! SUBROUTINE   : config_dgvm_parameters
2013!!
2014!>\BRIEF        This subroutine reads in the configuration file all the parameters
2015!! needed when the DGVM model is activated (ie : when ok_dgvm is set to true).
2016!!
2017!! DESCRIPTION  : None
2018!!
2019!! RECENT CHANGE(S): None
2020!!
2021!! MAIN OUTPUT VARIABLE(S):
2022!!
2023!! REFERENCE(S) :
2024!!
2025!! FLOWCHART    :
2026!! \n
2027!_ ================================================================================================================================
2028
2029  SUBROUTINE config_dgvm_parameters   
2030
2031    IMPLICIT NONE
2032
2033    !! 0. Variables and parameters declaration
2034
2035    !! 0.4 Local variables
2036
2037    !_ ================================================================================================================================   
2038
2039    !-
2040    ! establish parameters
2041    !-
2042    !
2043    !Config Key   = ESTAB_MAX_TREE
2044    !Config Desc  = Maximum tree establishment rate
2045    !Config If    = OK_DGVM
2046    !Config Def   = 0.12
2047    !Config Help  =
2048    !Config Units = [-]   
2049    CALL getin_p('ESTAB_MAX_TREE',estab_max_tree)
2050    !
2051    !Config Key   = ESTAB_MAX_GRASS
2052    !Config Desc  = Maximum grass establishment rate
2053    !Config If    = OK_DGVM
2054    !Config Def   = 0.12
2055    !Config Help  =
2056    !Config Units = [-] 
2057    CALL getin_p('ESTAB_MAX_GRASS',estab_max_grass)
2058    !
2059    !Config Key   = ESTABLISH_SCAL_FACT
2060    !Config Desc  =
2061    !Config If    = OK_DGVM
2062    !Config Def   = 5.
2063    !Config Help  =
2064    !Config Units = [-]
2065    CALL getin_p('ESTABLISH_SCAL_FACT',establish_scal_fact)
2066    !
2067    !Config Key   = MAX_TREE_COVERAGE
2068    !Config Desc  =
2069    !Config If    = OK_DGVM
2070    !Config Def   = 0.98
2071    !Config Help  =
2072    !Config Units = [-]
2073    CALL getin_p('MAX_TREE_COVERAGE',max_tree_coverage)
2074    !
2075    !Config Key   = IND_0_ESTAB
2076    !Config Desc  =
2077    !Config If    = OK_DGVM
2078    !Config Def   = 0.2
2079    !Config Help  =
2080    !Config Units = [-] 
2081    CALL getin_p('IND_0_ESTAB',ind_0_estab)
2082
2083    !-
2084    ! light parameters
2085    !-
2086    !
2087    !Config Key   = ANNUAL_INCREASE
2088    !Config Desc  = for diagnosis of fpc increase, compare today's fpc to last year's maximum (T) or to fpc of last time step (F)?
2089    !Config If    = OK_DGVM
2090    !Config Def   = y
2091    !Config Help  =
2092    !Config Units = [FLAG]
2093    CALL getin_p('ANNUAL_INCREASE',annual_increase)
2094    !
2095    !Config Key   = MIN_COVER
2096    !Config Desc  = For trees, minimum fraction of crown area occupied
2097    !Config If    = OK_DGVM
2098    !Config Def   = 0.05
2099    !Config Help  =
2100    !Config Units = [-] 
2101    CALL getin_p('MIN_COVER',min_cover)
2102
2103    !-
2104    ! pftinout parameters
2105    !
2106    !Config Key   = IND_0
2107    !Config Desc  = initial density of individuals
2108    !Config If    = OK_DGVM
2109    !Config Def   = 0.02
2110    !Config Help  =
2111    !Config Units = [-] 
2112    CALL getin_p('IND_0',ind_0)
2113    !
2114    !Config Key   = MIN_AVAIL
2115    !Config Desc  = minimum availability
2116    !Config If    = OK_DGVM
2117    !Config Def   = 0.01
2118    !Config Help  =
2119    !Config Units = [-] 
2120    CALL getin_p('MIN_AVAIL',min_avail)
2121    !
2122    !Config Key   = RIP_TIME_MIN
2123    !Config Desc  =
2124    !Config If    = OK_DGVM
2125    !Config Def   = 1.25
2126    !Config Help  =
2127    !Config Units = [year] 
2128    CALL getin_p('RIP_TIME_MIN',RIP_time_min)
2129    !
2130    !Config Key   = NPP_LONGTERM_INIT
2131    !Config Desc  =
2132    !Config If    = OK_DGVM
2133    !Config Def   = 10.
2134    !Config Help  =
2135    !Config Units = [gC/m^2/year]
2136    CALL getin_p('NPP_LONGTERM_INIT',npp_longterm_init)
2137    !
2138    !Config Key   = EVERYWHERE_INIT
2139    !Config Desc  =
2140    !Config If    = OK_DGVM
2141    !Config Def   = 0.05
2142    !Config Help  =
2143    !Config Units = [-]
2144    CALL getin_p('EVERYWHERE_INIT',everywhere_init)
2145
2146
2147  END SUBROUTINE config_dgvm_parameters
2148
2149
2150!! ================================================================================================================================
2151!! FUNCTION   : get_printlev
2152!!
2153!>\BRIEF        Read global PRINTLEV parmeter and local PRINTLEV_modname
2154!!
2155!! DESCRIPTION  : The first time this function is called the parameter PRINTLEV is read from run.def file.
2156!!                It is stored in the variable named printlev which is declared in constantes_var.f90. printlev
2157!!                can be accesed each module in ORCHIDEE which makes use of constantes_var module.
2158!!
2159!!                This function also reads the parameter PRINTLEV_modname for run.def file. modname is the
2160!!                intent(in) character string to this function. If the variable is set in run.def file, the corresponding
2161!!                value is returned. Otherwise the value of printlev is returnd as default.
2162!!
2163!! RECENT CHANGE(S): None
2164!!
2165!! MAIN OUTPUT VARIABLE(S): The local output level for the module set as intent(in) argument.
2166!!
2167!! REFERENCE(S) :
2168!!
2169!! FLOWCHART    :
2170!! \n
2171!_ ================================================================================================================================
2172
2173  FUNCTION get_printlev ( modname )
2174
2175    !! 0.1 Input arguments
2176    CHARACTER(LEN=*), INTENT(IN) :: modname
2177
2178    !! 0.2 Returned variable
2179    INTEGER       :: get_printlev
2180
2181    !! 0.3 Local variables
2182    LOGICAL, SAVE :: first=.TRUE.
2183
2184    !_ ================================================================================================================================
2185
2186    !! 1.0  Read the global PRINTLEV from run.def. This is only done at first call to this function.
2187    IF (first) THEN
2188       ! Set default value for printlev
2189       ! printlev is a public variable declared in constantes_var
2190       printlev=1
2191       !Config Key   = PRINTLEV
2192       !Config Desc  = Print level for text output
2193       !Config If    =
2194       !Config Help  = Possible values are:
2195       !Config         0    No output,
2196       !Config         1    Minimum writing for long simulations,
2197       !Config         2    More basic information for long simulations,
2198       !Config         3    First debug level,
2199       !Config         4    Higher debug level
2200       !Config Def   = 1
2201       !Config Units = [0, 1, 2, 3, 4]
2202       CALL getin_p('PRINTLEV',printlev)
2203       first=.FALSE.
2204
2205       !Config Key   = PRINTLEV_modname
2206       !Config Desc  = Specific print level of text output for the module "modname". Default as PRINTLEV.
2207       !Config Def   = 1
2208       !Config If    =
2209       !Config Help  = Use this option to activate a different level of text output
2210       !Config         for a specific module. This can be activated for several modules
2211       !Config         at the same time. Use for example PRINTLEV_sechiba.
2212       !Config Units = [0, 1, 2, 3, 4]
2213    END IF
2214
2215    ! Set default value as the standard printlev
2216    get_printlev=printlev
2217    ! Read optional value from run.def file
2218    CALL getin_p('PRINTLEV_'//modname, get_printlev)
2219
2220  END FUNCTION get_printlev
2221
2222
2223END MODULE constantes
Note: See TracBrowser for help on using the repository browser.