source: tags/ORCHIDEE_2_0/ORCHIDEE/src_parameters/constantes.f90 @ 6392

Last change on this file since 6392 was 6392, checked in by josefine.ghattas, 5 years ago

Added new option for downregulation parametrization. Set DOWNREGULATION_CO2_NEW=y in run.def to activate. This option will be availble for configurations IPSLCM66.1.11 and later.

IF both DOWNREGULATION_CO2 and DOWNREGULATION_CO2_NEW are true, then DOWNREGULATION_CO2 will be set to false.

See ticket #641

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