source: branches/ORCHIDEE_2_2/ORCHIDEE/src_parameters/constantes.f90 @ 7547

Last change on this file since 7547 was 7547, checked in by agnes.ducharne, 2 years ago

Create new flag IMPOSE_SLOPE to control the possibility to impose a uniform reinf_slope for surface runoff reinfiltration. orchidee.default is manually updated.

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