source: branches/publications/ORCHIDEE_gmd-2018-261/src_parameters/constantes.f90 @ 8787

Last change on this file since 8787 was 4998, checked in by nicolas.vuichard, 7 years ago

rev29012018

  • Property svn:keywords set to Date Revision
File size: 94.6 KB
Line 
1! =================================================================================================================================
2! MODULE       : constantes
3!
4! CONTACT      : orchidee-help _at_ ipsl.jussieu.fr
5!
6! LICENCE      : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF        "constantes" module contains subroutines to initialize most of the exernalized parameters. This module
10!!              also make a use to the module constantes_var where the parameters are declared.
11!!
12!!\n DESCRIPTION: This module contains subroutines to initialize most of the exernalized parameters. This module
13!!                also make a use to the module constantes_var where the parameters are declared.\n
14!!                This module can be used to acces the subroutines and the constantes. The constantes declarations
15!!                can also be used seperatly with "USE constantes_var".
16!!
17!! RECENT CHANGE(S): Didier Solyga : This module contains now all the externalized parameters of ORCHIDEE
18!!                   listed by modules which are not pft-dependent 
19!!                   Josefine Ghattas 2013 : The declaration part has been extracted and moved to module constates_var
20!!
21!! REFERENCE(S) :
22!! - Louis, Jean-Francois (1979), A parametric model of vertical eddy fluxes in the atmosphere.
23!! Boundary Layer Meteorology, 187-202.
24!!
25!! SVN          :
26!! $HeadURL: $
27!! $Date$
28!! $Revision$
29!! \n
30!_ ================================================================================================================================
31
32MODULE constantes
33
34  USE constantes_var
35  USE defprec
36  USE ioipsl_para, ONLY : getin_p, ipslerr_p
37  USE mod_orchidee_para, ONLY : numout
38
39  IMPLICIT NONE
40
41CONTAINS
42
43
44!! ================================================================================================================================
45!! SUBROUTINE   : activate_sub_models
46!!
47!>\BRIEF         This subroutine reads the flags in the configuration file to
48!! activate some sub-models like routing, irrigation, fire, herbivory, ... 
49!!
50!! DESCRIPTION  : None
51!!
52!! RECENT CHANGE(S): None
53!!
54!! MAIN OUTPUT VARIABLE(S): None
55!!
56!! REFERENCE(S) : None
57!!
58!! FLOWCHART    : None
59!! \n
60!_ ================================================================================================================================
61
62  SUBROUTINE activate_sub_models()
63
64    IMPLICIT NONE
65
66    !! 0. Variables and parameters declaration
67
68    !! 0.4 Local variables
69
70    !_ ================================================================================================================================
71
72    IF (ok_stomate) THEN
73
74       !Config Key   = HERBIVORES
75       !Config Desc  = herbivores allowed?
76       !Config If    = OK_STOMATE
77       !Config Def   = n
78       !Config Help  = With this variable, you can determine
79       !Config         if herbivores are activated
80       !Config Units = [FLAG]
81       CALL getin_p('HERBIVORES', ok_herbivores)
82       !
83       !Config Key   = TREAT_EXPANSION
84       !Config Desc  = treat expansion of PFTs across a grid cell?
85       !Config If    = OK_STOMATE
86       !Config Def   = n
87       !Config Help  = With this variable, you can determine
88       !Config         whether we treat expansion of PFTs across a
89       !Config         grid cell.
90       !Config Units = [FLAG]
91       CALL getin_p('TREAT_EXPANSION', treat_expansion)
92
93       !Config Key   = SLA_DYN
94       !Config Desc  = Account for a dynamic SLA
95       !Config Def   = n
96       !Config if    = OK_STOMATE
97       !Config Help  = If this flag is set to true (y) then the SLA
98       !Config         is computed dynamically, varying with leaf biomass
99       !Config Units = [FLAG]
100       CALL getin_p('SLA_DYN',sla_dyn)
101
102       !Config Key   = LPJ_GAP_CONST_MORT
103       !Config Desc  = Constant mortality
104       !Config If    = OK_STOMATE AND NOT OK_DGVM
105       !Config Def   = y/n depending on OK_DGVM
106       !Config Help  = set to TRUE if constant mortality is to be activated
107       !Config         
108       !Config Units = [FLAG]
109
110       ! Set Default value different if DGVM is activated.
111       IF ( ok_dgvm ) THEN
112          lpj_gap_const_mort=.FALSE.
113       ELSE
114          lpj_gap_const_mort=.TRUE.
115       END IF
116       CALL getin_p('LPJ_GAP_CONST_MORT', lpj_gap_const_mort)
117
118       IF (ok_dgvm .AND. lpj_gap_const_mort) THEN
119          CALL ipslerr_p(1,"activate_sub_models","Both OK_DGVM and LPJ_GAP_CONST_MORT are activated.",&
120               "This combination is possible but unusual","The simulation will continue with these flags activated." )
121       END IF
122
123       !Config Key   = HARVEST_AGRI
124       !Config Desc  = Harvest model for agricultural PFTs.
125       !Config If    = OK_STOMATE
126       !Config Def   = y
127       !Config Help  = Compute harvest above ground biomass for agriculture.
128       !Config         Change daily turnover.
129       !Config Units = [FLAG]
130       CALL getin_p('HARVEST_AGRI', harvest_agri)
131       !
132       !Config Key   = FIRE_DISABLE
133       !Config Desc  = no fire allowed
134       !Config If    = OK_STOMATE
135       !Config Def   = n
136       !Config Help  = With this variable, you can allow or not
137       !Config         the estimation of CO2 lost by fire
138       !Config Units = [FLAG]
139       CALL getin_p('FIRE_DISABLE', disable_fire)
140       !
141       !Config Key   = SPINUP_ANALYTIC
142       !Config Desc  = Activation of the analytic resolution of the spinup.
143       !Config If    = OK_STOMATE
144       !Config Def   = n
145       !Config Help  = Activate this option if you want to solve the spinup by the Gauss-Jordan method.
146       !Config Units = BOOLEAN   
147       CALL getin_p('SPINUP_ANALYTIC',spinup_analytic)
148
149    ENDIF
150
151    !
152    ! Check consistency (see later)
153    !
154!!$        IF(.NOT.(ok_routing) .AND. (doirrigation .OR. dofloodplains)) THEN
155!!$           CALL ipslerr_p(2,'activate_sub_models', &
156!!$               &     'Problem :you tried to activate the irrigation and floodplains without activating the routing',&
157!!$               &     'Are you sure ?', &
158!!$               &     '(check your parameters).')
159!!$        ENDIF
160
161!!$        IF(.NOT.(ok_stomate) .AND. (ok_herbivores .OR. treat_expansion .OR. lpj_gap_const_mort &
162!!$            & .OR. harvest_agri .OR. disable_fire)) THEN
163!!$          CALL ipslerr_p(2,'activate_sub_models', &
164!!$               &     'Problem : try to activate the following options : herbivory, treat_expansion, fire,',&
165!!$               &     'harvest_agri and constant mortality without stomate activated.',&
166!!$               &     '(check your parameters).')
167!!$        ENDIF
168
169
170  END SUBROUTINE activate_sub_models
171
172!! ================================================================================================================================
173!! SUBROUTINE   : veget_config
174!!
175!>\BRIEF         This subroutine reads the flags controlling the configuration for
176!! the vegetation : impose_veg, veget_mpa, lai_map, etc...       
177!!
178!! DESCRIPTION  : None
179!!
180!! RECENT CHANGE(S): None
181!!
182!! MAIN OUTPUT VARIABLE(S):
183!!
184!! REFERENCE(S) :
185!!
186!! FLOWCHART    :
187!! \n
188!_ ================================================================================================================================
189
190  SUBROUTINE veget_config
191
192    IMPLICIT NONE
193
194    !! 0. Variables and parameters declaration
195
196    !! 0.4 Local variables 
197
198    !_ ================================================================================================================================
199
200    !Config Key   = AGRICULTURE
201    !Config Desc  = agriculture allowed?
202    !Config If    = OK_SECHIBA or OK_STOMATE
203    !Config Def   = y
204    !Config Help  = With this variable, you can determine
205    !Config         whether agriculture is allowed
206    !Config Units = [FLAG]
207    CALL getin_p('AGRICULTURE', agriculture)
208    !
209    !Config Key   = IMPOSE_VEG
210    !Config Desc  = Should the vegetation be prescribed ?
211    !Config If    = OK_SECHIBA or OK_STOMATE
212    !Config Def   = n
213    !Config Help  = This flag allows the user to impose a vegetation distribution
214    !Config         and its characteristics. It is espacially interesting for 0D
215    !Config         simulations. On the globe it does not make too much sense as
216    !Config         it imposes the same vegetation everywhere
217    !Config Units = [FLAG]
218    CALL getin_p('IMPOSE_VEG', impveg)
219
220    IF (impveg) THEN
221       !Config Key   = IMPOSE_SOILT
222       !Config Desc  = Should the soil type be prescribed ?
223       !Config Def   = n
224       !Config If    = IMPOSE_VEG
225       !Config Help  = This flag allows the user to impose a soil type distribution.
226       !Config         It is espacially interesting for 0D
227       !Config         simulations. On the globe it does not make too much sense as
228       !Config         it imposes the same soil everywhere
229       !Config Units = [FLAG]
230       CALL getin_p('IMPOSE_SOILT', impsoilt)     
231    ENDIF
232
233    !Config Key   = IMPOSE_NINPUT_DEP
234    !Config Desc  = Should the N inputs be prescribed ?
235    !Config Def   = n
236    !Config If    = NOT IMPOSE_CN
237    !Config Help  = This flag allows the user to impose N inputs
238    !Config         It is espacially interesting for 0D
239    !Config         simulations. On the globe it does not make too much sense as
240    !Config         it imposes the same N inputs everywhere
241    !Config Units = [FLAG]
242    CALL getin_p('IMPOSE_NINPUT_DEP', impose_ninput_dep)     
243
244    !Config Key   = IMPOSE_NINPUT_FERT                                                     
245    !Config Desc  = Should the N inputs be prescribed ?                               
246    !Config Def   = n                                                                 
247    !Config If    = -                                                                 
248    !Config Help  = This flag allows the user to impose N inputs                     
249    !Config         It is espacially interesting for 0D                               
250    !Config         simulations. On the globe it does not make too much sense as     
251    !Config         it imposes the same N inputs everywhere                           
252    !Config Units = [FLAG]                                                           
253    CALL getin_p('IMPOSE_NINPUT_FERT', impose_ninput_fert)
254
255    !Config Key   = IMPOSE_NINPUT_MANURE                                                     
256    !Config Desc  = Should the N inputs be prescribed ?                               
257    !Config Def   = n                                                                 
258    !Config If    = -                                                                 
259    !Config Help  = This flag allows the user to impose N inputs                     
260    !Config         It is espacially interesting for 0D                               
261    !Config         simulations. On the globe it does not make too much sense as     
262    !Config         it imposes the same N inputs everywhere                           
263    !Config Units = [FLAG]                                                           
264    CALL getin_p('IMPOSE_NINPUT_MANURE', impose_ninput_manure)
265
266    !Config Key   = IMPOSE_NINPUT_BNF                                                     
267    !Config Desc  = Should the N inputs be prescribed ?                               
268    !Config Def   = n                                                                 
269    !Config If    = -                                                                 
270    !Config Help  = This flag allows the user to impose N inputs                     
271    !Config         It is espacially interesting for 0D                               
272    !Config         simulations. On the globe it does not make too much sense as     
273    !Config         it imposes the same N inputs everywhere                           
274    !Config Units = [FLAG]                                                           
275    CALL getin_p('IMPOSE_NINPUT_BNF', impose_ninput_bnf)
276       
277   
278    !Config Key   = LAI_MAP
279    !Config Desc  = Read the LAI map
280    !Config If    = OK_SECHIBA or OK_STOMATE
281    !Config Def   = n
282    !Config Help  = It is possible to read a 12 month LAI map which will
283    !Config         then be interpolated to daily values as needed.
284    !Config Units = [FLAG]
285    CALL getin_p('LAI_MAP',read_lai)
286
287    !Config Key   = MAP_PFT_FORMAT
288    !Config Desc  = Read a land use vegetation map on PFT format
289    !Config If    = OK_SECHIBA or OK_STOMATE
290    !Config Def   = y
291    !Config Help  = pft values are needed, max time axis is 293
292    !Config Units = [FLAG]
293    CALL getin_p('MAP_PFT_FORMAT',map_pft_format)
294
295    IF(map_pft_format) THEN
296       !Config Key   = VEGET_REINIT
297       !Config Desc  = booleen to indicate that a new LAND USE file will be used.
298       !Config If    = MAP_PFT_FORMAT
299       !Config Def   = y
300       !Config Help  = The parameter is used to bypass veget_year count
301       !Config         and reinitialize it with VEGET_YEAR parameter.
302       !Config         Then it is possible to change LAND USE file.
303       !Config Units = [FLAG]
304       CALL getin_p('VEGET_REINIT', veget_reinit)
305       !
306       !Config Key   = VEGET_YEAR
307       !Config Desc  = Year of the vegetation map to be read
308       !Config If    = MAP_PFT_FORMAT
309       !Config Def   = 1
310       !Config Help  = First year for land use vegetation (2D map by pft).
311       !Config         If VEGET_YEAR is set to 0, this means there is no time axis.
312       !Config Units = [FLAG]
313       CALL getin_p('VEGET_YEAR', veget_year_orig)
314    ENDIF
315
316
317    !Config Key   = NINPUT_REINIT
318    !Config Desc  = booleen to indicate that a new N INPUT file will be used.
319    !Config If    = -
320    !Config Def   = y
321    !Config Help  = The parameter is used to bypass ninput_year count
322    !Config         and reinitialize it with NINPUT_YEAR parameter.
323    !Config         Then it is possible to change N INPUT file.
324    !Config Units = [FLAG]
325    CALL getin_p('NINPUT_REINIT', ninput_reinit)
326   
327    !Config Key   = NINPUT_YEAR
328    !Config Desc  = Year of the N input map to be read
329    !Config If    = -
330    !Config Def   = 1
331    !Config Help  = First year for N inputs vegetation
332    !Config         If NINPUT_YEAR is set to 0, this means there is no time axis.
333    !Config Units = [FLAG]
334    CALL getin_p('NINPUT_YEAR', ninput_year_orig)
335   
336    !Config Key   = NINPUT_SUFFIX_YEAR
337    !Config Desc  = Do the input dataset have a 'year' suffix
338    !Config If    = -
339    !Config Def   = false
340    !Config Help  = First year for N inputs vegetation
341    !Config         If NINPUT_YEAR is set to true, one adds a suffix for the 'year' in the Ninput datasets
342    !Config Units = [FLAG]
343    CALL getin_p('NINPUT_SUFFIX_YEAR', ninput_suffix_year)
344       
345
346!!$        ! DS : Add warning in case of a wrong configuration (need to be discussed)
347!!$        ! 4.
348!!$        IF ( .NOT.(impveg) .AND. impsoilt) THEN
349!!$           CALL ipslerr_p(2,'veget_config', &
350!!$               &     'Problem : try to activate impose_soilt without activating impose_veg.',&
351!!$               &     'Are you sure ?', &
352!!$               &     '(check your parameters).')
353!!$        ENDIF
354!!$
355
356  END SUBROUTINE veget_config
357
358
359!! ================================================================================================================================
360!! SUBROUTINE   : veget_config
361!!
362!>\BRIEF         This subroutine reads in the configuration file the imposed values of the parameters for all SECHIBA modules. 
363!!
364!! DESCRIPTION  : None
365!!
366!! RECENT CHANGE(S): None
367!!
368!! MAIN OUTPUT VARIABLE(S):
369!!
370!! REFERENCE(S) :
371!!
372!! FLOWCHART    :
373!! \n
374!_ ================================================================================================================================
375
376  SUBROUTINE config_sechiba_parameters
377
378    IMPLICIT NONE
379
380    !! 0. Variables and parameters declaration
381
382    !! 0.4 Local variables
383
384    !_ ================================================================================================================================
385
386    ! Global : parameters used by many modules
387    CALL getin_p('TESTPFT',testpft)
388
389    !
390    !Config Key   = MAXMASS_SNOW
391    !Config Desc  = The maximum mass of a snow
392    !Config If    = OK_SECHIBA or HYDROL_CWRR
393    !Config Def   = 3000.
394    !Config Help  =
395    !Config Units = [kg/m^2] 
396    CALL getin_p('MAXMASS_SNOW',maxmass_snow)
397    !
398    !Config Key   = SNOWCRI
399    !Config Desc  = Sets the amount above which only sublimation occures
400    !Config If    = OK_SECHIBA or HYDROL_CWRR
401    !Config Def   = 1.5
402    !Config Help  =
403    !Config Units = [kg/m^2] 
404    CALL getin_p('SNOWCRI',snowcri)
405    !
406    !! Initialization of sneige
407    sneige = snowcri/mille
408    !
409    !Config Key   = MIN_WIND
410    !Config Desc  = Minimum wind speed
411    !Config If    = OK_SECHIBA
412    !Config Def   = 0.1
413    !Config Help  =
414    !Config Units = [m/s]
415    CALL getin_p('MIN_WIND',min_wind)
416    !
417    !Config Key   = MAX_SNOW_AGE
418    !Config Desc  = Maximum period of snow aging
419    !Config If    = OK_SECHIBA
420    !Config Def   = 50.
421    !Config Help  =
422    !Config Units = [days?]
423    CALL getin_p('MAX_SNOW_AGE',max_snow_age)
424    !
425    !Config Key   = SNOW_TRANS
426    !Config Desc  = Transformation time constant for snow
427    !Config If    = OK_SECHIBA
428    !Config Def   = 0.2
429    !Config Help  = optimized on 04/07/2016
430    !Config Units = [m]   
431    CALL getin_p('SNOW_TRANS',snow_trans)
432
433    !-
434    ! condveg
435    !-
436    !
437    !Config Key   = HEIGHT_DISPLACEMENT
438    !Config Desc  = Magic number which relates the height to the displacement height.
439    !Config If    = OK_SECHIBA
440    !Config Def   = 0.75
441    !Config Help  =
442    !Config Units = [m] 
443    CALL getin_p('HEIGHT_DISPLACEMENT',height_displacement)
444    !
445    !Config Key   = Z0_BARE
446    !Config Desc  = bare soil roughness length
447    !Config If    = OK_SECHIBA
448    !Config Def   = 0.01
449    !Config Help  =
450    !Config Units = [m]   
451    CALL getin_p('Z0_BARE',z0_bare)
452    !
453    !Config Key   = Z0_ICE
454    !Config Desc  = ice roughness length
455    !Config If    = OK_SECHIBA
456    !Config Def   = 0.001
457    !Config Help  =
458    !Config Units = [m]   
459    CALL getin_p('Z0_ICE',z0_ice)
460    !
461    !Config Key   = TCST_SNOWA
462    !Config Desc  = Time constant of the albedo decay of snow
463    !Config If    = OK_SECHIBA
464    !Config Def   = 10.0
465    !Config Help  = optimized on 04/07/2016
466    !Config Units = [days]
467    CALL getin_p('TCST_SNOWA',tcst_snowa)
468    !
469    !Config Key   = SNOWCRI_ALB
470    !Config Desc  = Critical value for computation of snow albedo
471    !Config If    = OK_SECHIBA
472    !Config Def   = 10.
473    !Config Help  =
474    !Config Units = [cm] 
475    CALL getin_p('SNOWCRI_ALB',snowcri_alb)
476    !
477    !
478    !Config Key   = VIS_DRY
479    !Config Desc  = The correspondance table for the soil color numbers and their albedo
480    !Config If    = OK_SECHIBA
481    !Config Def   = 0.24, 0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.27
482    !Config Help  =
483    !Config Units = [-] 
484    CALL getin_p('VIS_DRY',vis_dry)
485    !
486    !Config Key   = NIR_DRY
487    !Config Desc  = The correspondance table for the soil color numbers and their albedo
488    !Config If    = OK_SECHIBA
489    !Config Def   = 0.48, 0.44, 0.40, 0.36, 0.32, 0.28, 0.24, 0.20, 0.55
490    !Config Help  =
491    !Config Units = [-]   
492    CALL getin_p('NIR_DRY',nir_dry)
493    !
494    !Config Key   = VIS_WET
495    !Config Desc  = The correspondance table for the soil color numbers and their albedo
496    !Config If    = OK_SECHIBA 
497    !Config Def   = 0.12, 0.11, 0.10, 0.09, 0.08, 0.07, 0.06, 0.05, 0.15
498    !Config Help  =
499    !Config Units = [-]   
500    CALL getin_p('VIS_WET',vis_wet)
501    !
502    !Config Key   = NIR_WET
503    !Config Desc  = The correspondance table for the soil color numbers and their albedo
504    !Config If    = OK_SECHIBA
505    !Config Def   = 0.24, 0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.31
506    !Config Help  =
507    !Config Units = [-]   
508    CALL getin_p('NIR_WET',nir_wet)
509    !
510    !Config Key   = ALBSOIL_VIS
511    !Config Desc  =
512    !Config If    = OK_SECHIBA
513    !Config Def   = 0.18, 0.16, 0.16, 0.15, 0.12, 0.105, 0.09, 0.075, 0.25
514    !Config Help  =
515    !Config Units = [-] 
516    CALL getin_p('ALBSOIL_VIS',albsoil_vis)
517    !
518    !Config Key   = ALBSOIL_NIR
519    !Config Desc  =
520    !Config If    = OK_SECHIBA
521    !Config Def   = 0.36, 0.34, 0.34, 0.33, 0.30, 0.25, 0.20, 0.15, 0.45
522    !Config Help  =
523    !Config Units = [-] 
524    CALL getin_p('ALBSOIL_NIR',albsoil_nir)
525    !-
526    !
527    !Config Key   = ALB_DEADLEAF
528    !Config Desc  = albedo of dead leaves, VIS+NIR
529    !Config If    = OK_SECHIBA
530    !Config Def   = 0.12, 0.35
531    !Config Help  =
532    !Config Units = [-]     
533    CALL getin_p('ALB_DEADLEAF',alb_deadleaf)
534    !
535    !Config Key   = ALB_ICE
536    !Config Desc  = albedo of ice, VIS+NIR
537    !Config If    = OK_SECHIBA
538    !Config Def   = 0.60, 0.20
539    !Config Help  =
540    !Config Units = [-] 
541    CALL getin_p('ALB_ICE',alb_ice)
542    !
543    ! Get the fixed snow albedo if needed
544    !
545    !Config Key   = CONDVEG_SNOWA
546    !Config Desc  = The snow albedo used by SECHIBA
547    !Config Def   = 1.E+20
548    !Config if    = OK_SECHIBA
549    !Config Help  = This option allows the user to impose a snow albedo.
550    !Config         Default behaviour is to use the model of snow albedo
551    !Config         developed by Chalita (1993).
552    !Config Units = [-]
553    CALL getin_p('CONDVEG_SNOWA',fixed_snow_albedo)
554    !
555    !Config Key   = ALB_BARE_MODEL
556    !Config Desc  = Switch bare soil albedo dependent (if TRUE) on soil wetness
557    !Config Def   = n
558    !Config if    = OK_SECHIBA
559    !Config Help  = If TRUE, the model for bare soil albedo is the old formulation.
560    !Config         Then it depend on the soil dry or wetness. If FALSE, it is the
561    !Config         new computation that is taken, it is the mean of soil albedo.
562    !Config Units = [FLAG]
563    CALL getin_p('ALB_BARE_MODEL',alb_bare_model)
564    !
565    !Config Key   = ALB_BG_MODIS
566    !Config Desc  = Read bare soil albedo from file with background MODIS data
567    !Config Def   = n
568    !Config if    = OK_SECHIBA
569    !Config Help  = If TRUE, the bare soil albedo is read from file
570    !Config         based on background MODIS data. 
571    !Config         If FALSE, computaion depends on ALB_BARE_MODEL
572    !Config Units = [FLAG]
573    CALL getin_p('ALB_BG_MODIS',alb_bg_modis)
574    !
575    !Config Key   = IMPOSE_AZE
576    !Config Desc  = Should the surface parameters be prescribed
577    !Config Def   = n
578    !Config if    = OK_SECHIBA
579    !Config Help  = This flag allows the user to impose the surface parameters
580    !Config         (Albedo Roughness and Emissivity). It is espacially interesting for 0D
581    !Config         simulations. On the globe it does not make too much sense as
582    !Config         it imposes the same vegetation everywhere
583    !Config Units = [FLAG]
584    CALL getin_p('IMPOSE_AZE',impaze)
585    !
586    IF(impaze) THEN
587       !
588       !Config Key   = CONDVEG_Z0
589       !Config Desc  = Surface roughness
590       !Config Def   = 0.15
591       !Config If    = IMPOSE_AZE
592       !Config Help  = Surface rougness to be used on the point if a 0-dim version
593       !Config         of SECHIBA is used. Look at the description of the forcing 
594       !Config         data for the correct value.
595       !Config Units = [m]
596       CALL getin_p('CONDVEG_Z0', z0_scal) 
597       !
598       !Config Key   = ROUGHHEIGHT
599       !Config Desc  = Height to be added to the height of the first level
600       !Config Def   = 0.0
601       !Config If    = IMPOSE_AZE
602       !Config Help  = ORCHIDEE assumes that the atmospheric level height is counted
603       !Config         from the zero wind level. Thus to take into account the roughness
604       !Config         of tall vegetation we need to correct this by a certain fraction
605       !Config         of the vegetation height. This is called the roughness height in
606       !Config         ORCHIDEE talk.
607       !Config Units = [m]
608       CALL getin_p('ROUGHHEIGHT', roughheight_scal)
609       !
610       !Config Key   = CONDVEG_ALBVIS
611       !Config Desc  = SW visible albedo for the surface
612       !Config Def   = 0.25
613       !Config If    = IMPOSE_AZE
614       !Config Help  = Surface albedo in visible wavelengths to be used
615       !Config         on the point if a 0-dim version of SECHIBA is used.
616       !Config         Look at the description of the forcing data for
617       !Config         the correct value.
618       !Config Units = [-]
619       CALL getin_p('CONDVEG_ALBVIS', albedo_scal(ivis))
620       !
621       !Config Key   = CONDVEG_ALBNIR
622       !Config Desc  = SW near infrared albedo for the surface
623       !Config Def   = 0.25
624       !Config If    = IMPOSE_AZE
625       !Config Help  = Surface albedo in near infrared wavelengths to be used
626       !Config         on the point if a 0-dim version of SECHIBA is used.
627       !Config         Look at the description of the forcing data for
628       !Config         the correct value.
629       !Config Units = [-] 
630       CALL getin_p('CONDVEG_ALBNIR', albedo_scal(inir))
631       !
632       !Config Key   = CONDVEG_EMIS
633       !Config Desc  = Emissivity of the surface for LW radiation
634       !Config Def   = 1.0
635       !Config If    = IMPOSE_AZE
636       !Config Help  = The surface emissivity used for compution the LE emission
637       !Config         of the surface in a 0-dim version. Values range between
638       !Config         0.97 and 1.. The GCM uses 0.98.
639       !Config Units = [-]
640       CALL getin_p('CONDVEG_EMIS', emis_scal)
641    ENDIF
642
643    CALL getin_p('NEW_WATSTRESS',new_watstress)
644    IF(new_watstress) THEN
645       CALL getin_p('ALPHA_WATSTRESS',alpha_watstress)
646    ENDIF
647
648    !
649    !Config Key   = ROUGH_DYN
650    !Config Desc  = Account for a dynamic roughness height
651    !Config Def   = y
652    !Config if    = OK_SECHIBA
653    !Config Help  = If this flag is set to true (y) then the roughness
654    !Config         height is computed dynamically, varying with LAI
655    !Config Units = [FLAG]
656    CALL getin_p('ROUGH_DYN',rough_dyn)
657
658    IF ( rough_dyn ) THEN
659       !
660       !Config Key   = C1
661       !Config Desc  = Constant used in the formulation of the ratio of
662       !Config         the ratio of friction velocity to the wind speed
663       !Config         at the canopy top
664       !Config         See Ershadi et al. (2015) for more info
665       !Config Def   = 0.32
666       !Config If    = ROUGH_DYN
667       !Config Help  =
668       !Config Units = [-]
669       CALL getin_p('C1', c1)
670       !
671       !Config Key   = C2
672       !Config Desc  = Constant used in the formulation of the ratio of
673       !Config         the ratio of friction velocity to the wind speed
674       !Config         at the canopy top
675       !Config         See Ershadi et al. (2015) for more info
676       !Config Def   = 0.264
677       !Config If    = ROUGH_DYN
678       !Config Help  =
679       !Config Units = [-]
680       CALL getin_p('C2', c2)
681       !
682       !Config Key   = C3
683       !Config Desc  = Constant used in the formulation of the ratio of
684       !Config         the ratio of friction velocity to the wind speed
685       !Config         at the canopy top
686       !Config         See Ershadi et al. (2015) for more info
687       !Config Def   = 15.1
688       !Config If    = ROUGH_DYN
689       !Config Help  =
690       !Config Units = [-]
691       CALL getin_p('C3', c3)
692       !
693       !Config Key   = Cdrag_foliage
694       !Config Desc  = Drag coefficient of the foliage
695       !Config         See Ershadi et al. (2015) and Su et al. (2001)
696       !Config         for more info
697       !Config Def   = 0.2
698       !Config If    = ROUGH_DYN
699       !Config Help  =
700       !Config Units = [-]
701       CALL getin_p('CDRAG_FOLIAGE', Cdrag_foliage)
702       !
703       !Config Key   = Ct
704       !Config Desc  = Heat transfer coefficient of the leaf
705       !Config         See Ershadi et al. (2015) and Su et al. (2001)
706       !Config         for more info
707       !Config Def   = 0.01
708       !Config If    = ROUGH_DYN
709       !Config Help  =
710       !Config Units = [-]
711       CALL getin_p('CT', Ct)
712       !
713       !Config Key   = Prandtl
714       !Config Desc  = Prandtl number used in the calculation of Ct*
715       !Config         See Su et al. (2001) for more info
716       !Config Def   = 0.71
717       !Config If    = ROUGH_DYN
718       !Config Help  =
719       !Config Units = [-]
720       CALL getin_p('PRANDTL', Prandtl)
721    ENDIF
722    !-
723    ! Variables related to the explicitsnow module
724    !-
725    !Config Key = xansmax
726    !Config Desc = maximum snow albedo
727    !Config If = OK_SECHIBA
728    !Config Def = 0.85
729    !Config Help =
730    !Config Units = [-]
731    CALL getin_p('XANSMAX',xansmax)
732    !
733    !Config Key = xansmin
734    !Config Desc = minimum snow albedo
735    !Config If = OK_SECHIBA
736    !Config Def = 0.50
737    !Config Help =
738    !Config Units = [-]
739    CALL getin_p('XANSMIN',xansmin)
740    !
741    !Config Key = xans_todry
742    !Config Desc = albedo decay rate for the dry snow
743    !Config If = OK_SECHIBA
744    !Config Def = 0.008
745    !Config Help =
746    !Config Units = [S-1]
747    CALL getin_p('XANSDRY',xans_todry)
748    !
749    !Config Key = xans_t
750    !Config Desc = albedo decay rate for the wet snow
751    !Config If = OK_SECHIBA
752    !Config Def = 0.24
753    !Config Help =
754    !Config Units = [S-1]
755    CALL getin_p('XANS_T',xans_t)
756
757    !Config Key = xrhosmax
758    !Config Desc = maximum snow density
759    !Config If = OK_SECHIBA
760    !Config Def = 750
761    !Config Help =
762    !Config Units = [-]
763    CALL getin_p('XRHOSMAX',xrhosmax)
764    !
765    !Config Key = xwsnowholdmax1
766    !Config Desc = snow holding capacity 1
767    !Config If = OK_SECHIBA
768    !Config Def = 0.03
769    !Config Help =
770    !Config Units = [-]
771    CALL getin_p('XWSNOWHOLDMAX1',xwsnowholdmax1)
772    !
773    !Config Key = xwsnowholdmax2
774    !Config Desc = snow holding capacity 2
775    !Config If = OK_SECHIBA
776    !Config Def = 0.10
777    !Config Help =
778    !Config Units = [-]
779    CALL getin_p('XWSNOWHOLDMAX2',xwsnowholdmax2)
780    !
781    !Config Key = xsnowrhohold
782    !Config Desc = snow density
783    !Config If = OK_SECHIBA
784    !Config Def = 200.0
785    !Config Help =
786    !Config Units = [kg/m3]
787    CALL getin_p('XSNOWRHOHOLD',xsnowrhohold)
788    !
789    !Config Key = ZSNOWTHRMCOND1
790    !Config Desc = Thermal conductivity Coef 1
791    !Config If = OK_SECHIBA
792    !Config Def = 0.02
793    !Config Help =
794    !Config Units = [W/m/K]
795    CALL getin_p('ZSNOWTHRMCOND1',ZSNOWTHRMCOND1)
796    !
797    !Config Key = ZSNOWTHRMCOND2
798    !Config Desc = Thermal conductivity Coef 2
799    !Config If = OK_SECHIBA
800    !Config Def = 2.5E-6
801    !Config Help =
802    !Config Units = [W m5/(kg2 K)]
803    CALL getin_p('ZSNOWTHRMCOND2',ZSNOWTHRMCOND2)
804    !
805    !Config Key = ZSNOWTHRMCOND_AVAP
806    !Config Desc = Thermal conductivity Coef 1 water vapor
807    !Config If = OK_SECHIBA
808    !Config Def = -0.06023
809    !Config Help =
810    !Config Units = [W/m/K]
811    CALL getin_p('ZSNOWTHRMCOND_AVAP',ZSNOWTHRMCOND_AVAP)
812    !
813    !Config Key = ZSNOWTHRMCOND_BVAP
814    !Config Desc = Thermal conductivity Coef 2 water vapor
815    !Config If = OK_SECHIBA
816    !Config Def = -2.5425
817    !Config Help =
818    !Config Units = [W/m]
819    CALL getin_p('ZSNOWTHRMCOND_BVAP',ZSNOWTHRMCOND_BVAP)
820    !
821    !Config Key = ZSNOWTHRMCOND_CVAP
822    !Config Desc = Thermal conductivity Coef 3 water vapor
823    !Config If = OK_SECHIBA
824    !Config Def = -289.99
825    !Config Help =
826    !Config Units = [K]
827    CALL getin_p('ZSNOWTHRMCOND_CVAP',ZSNOWTHRMCOND_CVAP)
828
829    !Snow compaction factors
830    !Config Key = ZSNOWCMPCT_RHOD
831    !Config Desc = Snow compaction coefficent
832    !Config If = OK_SECHIBA
833    !Config Def = 150.0
834    !Config Help =
835    !Config Units = [kg/m3]
836    CALL getin_p('ZSNOWCMPCT_RHOD',ZSNOWCMPCT_RHOD)
837
838    !Config Key = ZSNOWCMPCT_ACM
839    !Config Desc = Coefficent for the thermal conductivity
840    !Config If = OK_SECHIBA
841    !Config Def = 2.8e-6
842    !Config Help =
843    !Config Units = [1/s]
844    CALL getin_p('ZSNOWCMPCT_ACM',ZSNOWCMPCT_ACM)
845
846    !Config Key = ZSNOWCMPCT_BCM
847    !Config Desc = Coefficent for the thermal conductivity
848    !Config If = OK_SECHIBA
849    !Config Def = 0.04
850    !Config Help =
851    !Config Units = [1/K]
852    CALL getin_p('ZSNOWCMPCT_BCM',ZSNOWCMPCT_BCM)
853
854    !Config Key = ZSNOWCMPCT_CCM
855    !Config Desc = Coefficent for the thermal conductivity
856    !Config If = OK_SECHIBA
857    !Config Def = 460.
858    !Config Help =
859    !Config Units = [m3/kg]
860    CALL getin_p('ZSNOWCMPCT_CCM',ZSNOWCMPCT_CCM)
861
862    !Config Key = ZSNOWCMPCT_V0
863    !Config Desc = Vapor coefficent for the thermal conductivity
864    !Config If = OK_SECHIBA
865    !Config Def = 3.7e7
866    !Config Help =
867    !Config Units = [Pa/s]
868    CALL getin_p('ZSNOWCMPCT_V0',ZSNOWCMPCT_V0)
869
870    !Config Key = ZSNOWCMPCT_VT
871    !Config Desc = Vapor coefficent for the thermal conductivity
872    !Config If = OK_SECHIBA
873    !Config Def = 0.081
874    !Config Help =
875    !Config Units = [1/K]
876    CALL getin_p('ZSNOWCMPCT_VT',ZSNOWCMPCT_VT)
877
878    !Config Key = ZSNOWCMPCT_VR
879    !Config Desc = Vapor coefficent for the thermal conductivity
880    !Config If = OK_SECHIBA
881    !Config Def = 0.018
882    !Config Help =
883    !Config Units = [m3/kg]
884    CALL getin_p('ZSNOWCMPCT_VR',ZSNOWCMPCT_VR)
885
886
887    !Surface resistance
888    !
889    !Config Key = CB
890    !Config Desc = Constant of the Louis scheme
891    !Config If = OK_SECHIBA
892    !Config Def = 5.0
893    !Config Help =
894    !Config Units = [-]
895    CALL getin_p('CB',cb)
896    !
897    !Config Key = CC
898    !Config Desc = Constant of the Louis scheme
899    !Config If = OK_SECHIBA
900    !Config Def = 5.0
901    !Config Help =
902    !Config Units = [-]
903    CALL getin_p('CC',cc)
904    !
905    !Config Key = CD
906    !Config Desc = Constant of the Louis scheme
907    !Config If = OK_SECHIBA
908    !Config Def = 5.0
909    !Config Help =
910    !Config Units = [-]
911    CALL getin_p('CD',cd)
912    !
913    !Config Key = RAYT_CSTE
914    !Config Desc = Constant in the computation of surface resistance 
915    !Config If = OK_SECHIBA
916    !Config Def = 125
917    !Config Help =
918    !Config Units = [W.m^{-2}]
919    CALL getin_p('RAYT_CSTE',rayt_cste)
920    !
921    !Config Key = DEFC_PLUS
922    !Config Desc = Constant in the computation of surface resistance 
923    !Config If = OK_SECHIBA
924    !Config Def = 23.E-3
925    !Config Help =
926    !Config Units = [K.W^{-1}]
927    CALL getin_p('DEFC_PLUS',defc_plus)
928    !
929    !Config Key = DEFC_MULT
930    !Config Desc = Constant in the computation of surface resistance 
931    !Config If = OK_SECHIBA
932    !Config Def = 1.5
933    !Config Help =
934    !Config Units = [K.W^{-1}]
935    CALL getin_p('DEFC_MULT',defc_mult)
936    !
937
938    !
939    !-
940    ! diffuco
941    !-
942    !
943    !Config Key   = NLAI
944    !Config Desc  = Number of LAI levels
945    !Config If    = OK_SECHIBA
946    !Config Def   = 20
947    !Config Help  =
948    !Config Units = [-] 
949    CALL getin_p('NLAI',nlai)
950    !
951    !Config Key   = LAIMAX
952    !Config Desc  = Maximum LAI
953    !Config If    = OK_SECHIBA
954    !Config Def   =
955    !Config Help  =
956    !Config Units = [m^2/m^2]   
957    CALL getin_p('LAIMAX',laimax)
958    !
959    !Config Key   = DEW_VEG_POLY_COEFF
960    !Config Desc  = coefficients of the polynome of degree 5 for the dew
961    !Config If    = OK_SECHIBA
962    !Config Def   = 0.887773, 0.205673, 0.110112, 0.014843, 0.000824, 0.000017
963    !Config Help  =
964    !Config Units = [-]   
965    CALL getin_p('DEW_VEG_POLY_COEFF',dew_veg_poly_coeff)
966    !
967    !Config Key   = DOWNREGULATION_CO2
968    !Config Desc  = Activation of CO2 downregulation
969    !Config If    = OK_SECHIBA
970    !Config Def   = n
971    !Config Help  =
972    !Config Units = [FLAG]   
973    CALL getin_p('DOWNREGULATION_CO2',downregulation_co2)
974    !
975    !Config Key   = DOWNREGULATION_CO2_BASELEVEL
976    !Config Desc  = CO2 base level
977    !Config If    = OK_SECHIBA
978    !Config Def   = 280.
979    !Config Help  =
980    !Config Units = [ppm]   
981    CALL getin_p('DOWNREGULATION_CO2_BASELEVEL',downregulation_co2_baselevel)
982
983   
984    !Config Key   = GB_REF
985    !Config Desc  = Leaf bulk boundary layer resistance
986    !Config If    = OK_CO2
987    !Config Def   = 1./25.
988    !Config Help  =
989    !Config Units = [s m-1]   
990    CALL getin_p('GB_REF',gb_ref)
991
992
993    !-
994    ! slowproc
995    !-
996    !
997    !Config Key   = CLAYFRACTION_DEFAULT
998    !Config Desc  = default fraction of clay
999    !Config If    = OK_SECHIBA
1000    !Config Def   = 0.2
1001    !Config Help  =
1002    !Config Units = [-]   
1003    CALL getin_p('CLAYFRACTION_DEFAULT',clayfraction_default)
1004
1005    !Config Key   = SILTFRACTION_DEFAULT
1006    !Config Desc  = default fraction of silt
1007    !Config If    = OK_SECHIBA
1008    !Config Def   = 0.5
1009    !Config Help  =
1010    !Config Units = [-]   
1011    CALL getin_p('SILTFRACTION_DEFAULT',siltfraction_default)
1012   
1013    !Config Key   = BULK_DEFAULT
1014    !Config Desc  = default bulk density
1015    !Config If    = OK_SECHIBA
1016    !Config Def   = 1000
1017    !Config Help  =
1018    !Config Units = [kg/m3]   
1019    CALL getin_p('BULK_DEFAULT',bulk_default)
1020   
1021    !Config Key   = PH_DEFAULT
1022    !Config Desc  = default soil pH
1023    !Config If    = OK_SECHIBA
1024    !Config Def   = 5.5
1025    !Config Help  =
1026    !Config Units = [-]   
1027    CALL getin_p('PH_DEFAULT',ph_default)
1028   
1029    !Config Key   = MIN_VEGFRAC
1030    !Config Desc  = Minimal fraction of mesh a vegetation type can occupy
1031    !Config If    = OK_SECHIBA
1032    !Config Def   = 0.001
1033    !Config Help  =
1034    !Config Units = [-] 
1035    CALL getin_p('MIN_VEGFRAC',min_vegfrac)
1036    !
1037    !Config Key   = STEMPDIAG_BID
1038    !Config Desc  = only needed for an initial LAI if there is no restart file
1039    !Config If    = OK_SECHIBA
1040    !Config Def   = 280.
1041    !Config Help  =
1042    !Config Units = [K]
1043    CALL getin_p('STEMPDIAG_BID',stempdiag_bid)
1044    !
1045
1046  END SUBROUTINE config_sechiba_parameters
1047
1048
1049!! ================================================================================================================================
1050!! SUBROUTINE   : config_co2_parameters
1051!!
1052!>\BRIEF        This subroutine reads in the configuration file all the parameters
1053!! needed when OK_CO2 is set to true. (ie : when the photosynthesis is activated)
1054!!
1055!! DESCRIPTION  : None
1056!!
1057!! RECENT CHANGE(S): None
1058!!
1059!! MAIN OUTPUT VARIABLE(S): None
1060!!
1061!! REFERENCE(S) :
1062!!
1063!! FLOWCHART    :
1064!! \n
1065!_ ================================================================================================================================
1066
1067  SUBROUTINE config_co2_parameters
1068
1069    IMPLICIT NONE
1070
1071    !! 0. Variables and parameters declaration
1072
1073    !! 0.4 Local variables
1074
1075    !_ ================================================================================================================================
1076
1077    !
1078    !Config Key   = LAI_LEVEL_DEPTH
1079    !Config Desc  =
1080    !Config If    = OK_CO2
1081    !Config Def   = 0.15
1082    !Config Help  =
1083    !Config Units = [-] 
1084    CALL getin_p('LAI_LEVEL_DEPTH',lai_level_depth)
1085    !
1086    !Config Key   = Oi
1087    !Config Desc  = Intercellular oxygen partial pressure
1088    !Config If    = OK_CO2
1089    !Config Def   = 210000.
1090    !Config Help  = See Legend of Figure 6 of Yin et al. (2009)
1091    !Config Units = [ubar] 
1092    CALL getin_p('Oi',Oi)
1093
1094
1095  END SUBROUTINE config_co2_parameters
1096
1097
1098!! ================================================================================================================================
1099!! SUBROUTINE   : config_stomate_parameters
1100!!
1101!>\BRIEF        This subroutine reads in the configuration file all the parameters
1102!! needed when stomate is activated (ie : when OK_STOMATE is set to true).
1103!!
1104!! DESCRIPTION  : None
1105!!
1106!! RECENT CHANGE(S): None
1107!!
1108!! MAIN OUTPUT VARIABLE(S):
1109!!
1110!! REFERENCE(S) :
1111!!
1112!! FLOWCHART    :
1113!! \n
1114!_ ================================================================================================================================
1115
1116  SUBROUTINE config_stomate_parameters
1117
1118    IMPLICIT NONE
1119
1120    !! 0. Variables and parameters declaration
1121
1122    !! 0.4 Local variables   
1123
1124
1125    !_ ================================================================================================================================
1126
1127    !-
1128    ! constraints_parameters
1129    !-
1130    !
1131    !Config Key   = TOO_LONG
1132    !Config Desc  = longest sustainable time without regeneration (vernalization)
1133    !Config If    = OK_STOMATE
1134    !Config Def   = 5.
1135    !Config Help  =
1136    !Config Units = [days]   
1137    CALL getin_p('TOO_LONG',too_long)
1138
1139    !-
1140    ! fire parameters
1141    !-
1142    !
1143    !Config Key   = TAU_FIRE
1144    !Config Desc  = Time scale for memory of the fire index (days). Validated for one year in the DGVM.
1145    !Config If    = OK_STOMATE
1146    !Config Def   = 30.
1147    !Config Help  =
1148    !Config Units = [days]   
1149    CALL getin_p('TAU_FIRE',tau_fire)
1150    !
1151    !Config Key   = LITTER_CRIT
1152    !Config Desc  = Critical litter quantity for fire
1153    !Config If    = OK_STOMATE
1154    !Config Def   = 200.
1155    !Config Help  =
1156    !Config Units = [gC/m^2] 
1157    CALL getin_p('LITTER_CRIT',litter_crit)
1158
1159    !Config Key   = FIRE_RESIST_LIGNIN
1160    !Config Desc  =
1161    !Config If    = OK_STOMATE
1162    !Config Def   = 0.5
1163    !Config Help  =
1164    !Config Units = [-] 
1165    CALL getin_p('FIRE_RESIST_LIGNIN',fire_resist_lignin)
1166
1167    !Config Key   = CO2FRAC
1168    !Config Desc  = What fraction of a burned plant compartment goes into the atmosphere
1169    !Config If    = OK_STOMATE
1170    !Config Def   = 0.95, 0.95, 0., 0.3, 0., 0., 0.95, 0.95
1171    !Config Help  =
1172    !Config Units = [-] 
1173    CALL getin_p('CO2FRAC',co2frac)
1174    !
1175    !Config Key   = BCFRAC_COEFF
1176    !Config Desc  =
1177    !Config If    = OK_STOMATE
1178    !Config Def   = 0.3, 1.3, 88.2
1179    !Config Help  =
1180    !Config Units = [-] 
1181    CALL getin_p('BCFRAC_COEFF',bcfrac_coeff)
1182    !
1183    !Config Key   = FIREFRAC_COEFF
1184    !Config Desc  =
1185    !Config If    = OK_STOMATE
1186    !Config Def   = 0.45, 0.8, 0.6, 0.13
1187    !Config Help  =
1188    !Config Units = [-]   
1189    CALL getin_p('FIREFRAC_COEFF',firefrac_coeff)
1190
1191    !Config Key   = REF_GREFF
1192    !Config Desc  = Asymptotic maximum mortality rate
1193    !Config If    = OK_STOMATE
1194    !Config Def   = 0.035
1195    !Config Help  = Set asymptotic maximum mortality rate from Sitch 2003
1196    !Config         (they use 0.01) (year^{-1})
1197    !Config Units = [1/year] 
1198    CALL getin_p('REF_GREFF',ref_greff)
1199    !-
1200    ! allocation parameters
1201    !-
1202    !Config Key   = RESERVE_TIME_TREE
1203    !Config Desc  = maximum time during which reserve is used (trees)
1204    !Config If    = OK_STOMATE
1205    !Config Def   = 30.
1206    !Config Help  =
1207    !Config Units = [days]   
1208    CALL getin_p('RESERVE_TIME_TREE',reserve_time_tree)
1209    !
1210    !Config Key   = RESERVE_TIME_GRASS
1211    !Config Desc  = maximum time during which reserve is used (grasses)
1212    !Config If    = OK_STOMATE
1213    !Config Def   = 20.
1214    !Config Help  =
1215    !Config Units = [days]   
1216    CALL getin_p('RESERVE_TIME_GRASS',reserve_time_grass)
1217
1218    !-
1219    ! data parameters
1220    !
1221    !Config Key   = PRECIP_CRIT
1222    !Config Desc  = minimum precip
1223    !Config If    = OK_STOMATE
1224    !Config Def   = 100.
1225    !Config Help  =
1226    !Config Units = [mm/year] 
1227    CALL getin_p('PRECIP_CRIT',precip_crit)
1228    !
1229    !Config Key   = GDD_CRIT_ESTAB
1230    !Config Desc  = minimum gdd for establishment of saplings
1231    !Config If    = OK_STOMATE
1232    !Config Def   = 150.
1233    !Config Help  =
1234    !Config Units = [-] 
1235    CALL getin_p('GDD_CRIT_ESTAB',gdd_crit_estab)
1236    !
1237    !Config Key   = FPC_CRIT
1238    !Config Desc  = critical fpc, needed for light competition and establishment
1239    !Config If    = OK_STOMATE
1240    !Config Def   = 0.95
1241    !Config Help  =
1242    !Config Units = [-] 
1243    CALL getin_p('FPC_CRIT',fpc_crit)
1244    !
1245    !Config Key   = ALPHA_GRASS
1246    !Config Desc  = sapling characteristics : alpha's
1247    !Config If    = OK_STOMATE
1248    !Config Def   = 0.5
1249    !Config Help  =
1250    !Config Units = [-]   
1251    CALL getin_p('ALPHA_GRASS',alpha_grass)
1252    !
1253    !Config Key   = ALPHA_TREE
1254    !Config Desc  = sapling characteristics : alpha's
1255    !Config If    = OK_STOMATE
1256    !Config Def   = 1.
1257    !Config Help  =
1258    !Config Units = [-]   
1259    CALL getin_p('ALPHA_TREE',alpha_tree)
1260
1261    !Config Key   = STRUCT_TO_LEAVES
1262    !Config Desc  = Fraction of structural carbon in grass and crops as a share of the leaf
1263    ! carbon pool. Only used for grasses and crops (thus NOT for trees)
1264    !Config If    = OK_STOMATE
1265    !Config Def   = 0.5
1266    !Config Help  =
1267    !Config Units = [-]   
1268    CALL getin_p(' STRUCT_TO_LEAVES',struct_to_leaves)
1269
1270    !Config Key   = LABILE_TO_TOTAL
1271    !Config Desc  = Fraction of the labile pool in trees, grasses and crops as a share of the
1272    ! total carbon pool (accounting for the N-content of the different tissues).
1273    !Config If    = OK_STOMATE
1274    !Config Def   = 0.01
1275    !Config Help  =
1276    !Config Units = [-]   
1277    CALL getin_p('LABILE_TO_TOTAL',labile_to_total)
1278
1279    !Config Key   = TAU_HUM_MONTH
1280    !Config Desc  = time scales for phenology and other processes
1281    !Config If    = OK_STOMATE
1282    !Config Def   = 20.
1283    !Config Help  =
1284    !Config Units = [days] 
1285    CALL getin_p('TAU_HUM_MONTH',tau_hum_month)
1286    !
1287    !Config Key   = TAU_HUM_WEEK
1288    !Config Desc  = time scales for phenology and other processes
1289    !Config If    = OK_STOMATE
1290    !Config Def   = 7.
1291    !Config Help  =
1292    !Config Units = [days]   
1293    CALL getin_p('TAU_HUM_WEEK',tau_hum_week)
1294    !
1295    !Config Key   = TAU_T2M_MONTH
1296    !Config Desc  = time scales for phenology and other processes
1297    !Config If    = OK_STOMATE
1298    !Config Def   = 20.
1299    !Config Help  =
1300    !Config Units = [days]     
1301    CALL getin_p('TAU_T2M_MONTH',tau_t2m_month)
1302    !
1303    !Config Key   = TAU_T2M_WEEK
1304    !Config Desc  = time scales for phenology and other processes
1305    !Config If    = OK_STOMATE
1306    !Config Def   = 7.
1307    !Config Help  =
1308    !Config Units = [days]   
1309    CALL getin_p('TAU_T2M_WEEK',tau_t2m_week)
1310    !
1311    !Config Key   = TAU_TSOIL_MONTH
1312    !Config Desc  = time scales for phenology and other processes
1313    !Config If    = OK_STOMATE
1314    !Config Def   = 20.
1315    !Config Help  =
1316    !Config Units = [days]     
1317    CALL getin_p('TAU_TSOIL_MONTH',tau_tsoil_month)
1318    !
1319    !Config Key   = TAU_SOILHUM_MONTH
1320    !Config Desc  = time scales for phenology and other processes
1321    !Config If    = OK_STOMATE
1322    !Config Def   = 20.
1323    !Config Help  =
1324    !Config Units = [days]   
1325    CALL getin_p('TAU_SOILHUM_MONTH',tau_soilhum_month)
1326    !
1327    !Config Key   = TAU_GPP_WEEK
1328    !Config Desc  = time scales for phenology and other processes
1329    !Config If    = OK_STOMATE
1330    !Config Def   = 7.
1331    !Config Help  =
1332    !Config Units = [days]   
1333    CALL getin_p('TAU_GPP_WEEK',tau_gpp_week)
1334    !
1335    !Config Key   = TAU_GDD
1336    !Config Desc  = time scales for phenology and other processes
1337    !Config If    = OK_STOMATE
1338    !Config Def   = 40.
1339    !Config Help  =
1340    !Config Units = [days]   
1341    CALL getin_p('TAU_GDD',tau_gdd)
1342    !
1343    !Config Key   = TAU_NGD
1344    !Config Desc  = time scales for phenology and other processes
1345    !Config If    = OK_STOMATE
1346    !Config Def   = 50.
1347    !Config Help  =
1348    !Config Units = [days]   
1349    CALL getin_p('TAU_NGD',tau_ngd)
1350    !
1351    !Config Key   = COEFF_TAU_LONGTERM
1352    !Config Desc  = time scales for phenology and other processes
1353    !Config If    = OK_STOMATE
1354    !Config Def   = 3.
1355    !Config Help  =
1356    !Config Units = [days]   
1357    CALL getin_p('COEFF_TAU_LONGTERM',coeff_tau_longterm)
1358    !-
1359    !
1360    !Config Key   = BM_SAPL_CARBRES
1361    !Config Desc  =
1362    !Config If    = OK_STOMATE
1363    !Config Def   = 5.
1364    !Config Help  =
1365    !Config Units = [-]   
1366    CALL getin_p('BM_SAPL_CARBRES',bm_sapl_carbres)
1367    !
1368    !Config Key   = BM_SAPL_SAPABOVE
1369    !Config Desc  =
1370    !Config If    = OK_STOMATE
1371    !Config Def   = 0.5
1372    !Config Help  =
1373    !Config Units = [-]   
1374    CALL getin_p('BM_SAPL_SAPABOVE',bm_sapl_sapabove)
1375    !
1376    !Config Key   = BM_SAPL_HEARTABOVE
1377    !Config Desc  =
1378    !Config If    = OK_STOMATE
1379    !Config Def   = 2.
1380    !Config Help  =
1381    !Config Units = [-]   
1382    CALL getin_p('BM_SAPL_HEARTABOVE',bm_sapl_heartabove)
1383    !
1384    !Config Key   = BM_SAPL_HEARTBELOW
1385    !Config Desc  =
1386    !Config If    = OK_STOMATE
1387    !Config Def   = 2.
1388    !Config Help  =
1389    !Config Units = [-]   
1390    CALL getin_p('BM_SAPL_HEARTBELOW',bm_sapl_heartbelow)
1391
1392    !Config Key   = BM_SAPL_LABILE
1393    !Config Desc  =
1394    !Config If    = OK_STOMATE
1395    !Config Def   = 5.
1396    !Config Help  =
1397    !Config Units = [-]   
1398    CALL getin_p('BM_SAPL_LABILE',bm_sapl_labile)
1399
1400    !Config Key   = INIT_SAPL_MASS_LABILE
1401    !Config Desc  =
1402    !Config If    = OK_STOMATE
1403    !Config Def   = 5.
1404    !Config Help  =
1405    !Config Units = [-]   
1406    CALL getin_p('INIT_SAPL_MASS_LABILE',init_sapl_mass_labile)
1407
1408    !Config Key   = INIT_SAPL_MASS_LEAF_NAT
1409    !Config Desc  =
1410    !Config If    = OK_STOMATE
1411    !Config Def   = 0.1
1412    !Config Help  =
1413    !Config Units = [-]   
1414    CALL getin_p('INIT_SAPL_MASS_LEAF_NAT',init_sapl_mass_leaf_nat)
1415    !
1416    !Config Key   = INIT_SAPL_MASS_LEAF_AGRI
1417    !Config Desc  =
1418    !Config If    = OK_STOMATE
1419    !Config Def   = 1.
1420    !Config Help  =
1421    !Config Units = [-]   
1422    CALL getin_p('INIT_SAPL_MASS_LEAF_AGRI',init_sapl_mass_leaf_agri)
1423    !
1424    !Config Key   = INIT_SAPL_MASS_CARBRES
1425    !Config Desc  =
1426    !Config If    = OK_STOMATE
1427    !Config Def   = 5.
1428    !Config Help  =
1429    !Config Units = [-]   
1430    CALL getin_p('INIT_SAPL_MASS_CARBRES',init_sapl_mass_carbres)
1431    !
1432    !Config Key   = INIT_SAPL_MASS_ROOT
1433    !Config Desc  =
1434    !Config If    = OK_STOMATE
1435    !Config Def   = 0.1
1436    !Config Help  =
1437    !Config Units = [-]   
1438    CALL getin_p('INIT_SAPL_MASS_ROOT',init_sapl_mass_root)
1439    !
1440    !Config Key   = INIT_SAPL_MASS_FRUIT
1441    !Config Desc  =
1442    !Config If    = OK_STOMATE
1443    !Config Def   = 0.3
1444    !Config Help  =
1445    !Config Units = [-]   
1446    CALL getin_p('INIT_SAPL_MASS_FRUIT',init_sapl_mass_fruit)
1447    !
1448    !Config Key   = CN_SAPL_INIT
1449    !Config Desc  =
1450    !Config If    = OK_STOMATE
1451    !Config Def   = 0.5
1452    !Config Help  =
1453    !Config Units = [-]   
1454    CALL getin_p('CN_SAPL_INIT',cn_sapl_init)
1455    !
1456    !Config Key   = MIGRATE_TREE
1457    !Config Desc  =
1458    !Config If    = OK_STOMATE
1459    !Config Def   = 10000.
1460    !Config Help  =
1461    !Config Units = [m/year]   
1462    CALL getin_p('MIGRATE_TREE',migrate_tree)
1463    !
1464    !Config Key   = MIGRATE_GRASS
1465    !Config Desc  =
1466    !Config If    = OK_STOMATE
1467    !Config Def   = 10000.
1468    !Config Help  =
1469    !Config Units = [m/year]   
1470    CALL getin_p('MIGRATE_GRASS',migrate_grass)
1471    !
1472    !Config Key   = LAI_INITMIN_TREE
1473    !Config Desc  =
1474    !Config If    = OK_STOMATE
1475    !Config Def   = 0.3
1476    !Config Help  =
1477    !Config Units = [m^2/m^2] 
1478    CALL getin_p('LAI_INITMIN_TREE',lai_initmin_tree)
1479    !
1480    !Config Key   = LAI_INITMIN_GRASS
1481    !Config Desc  =
1482    !Config If    = OK_STOMATE
1483    !Config Def   = 0.1
1484    !Config Help  =
1485    !Config Units = [m^2/m^2]   
1486    CALL getin_p('LAI_INITMIN_GRASS',lai_initmin_grass)
1487    !
1488    !Config Key   = DIA_COEFF
1489    !Config Desc  =
1490    !Config If    = OK_STOMATE
1491    !Config Def   = 4., 0.5
1492    !Config Help  =
1493    !Config Units = [-]   
1494    CALL getin_p('DIA_COEFF',dia_coeff)
1495    !
1496    !Config Key   = MAXDIA_COEFF
1497    !Config Desc  =
1498    !Config If    = OK_STOMATE
1499    !Config Def   = 100., 0.01
1500    !Config Help  =
1501    !Config Units = [-]   
1502    CALL getin_p('MAXDIA_COEFF',maxdia_coeff)
1503    !
1504    !Config Key   = BM_SAPL_LEAF
1505    !Config Desc  =
1506    !Config If    = OK_STOMATE
1507    !Config Def   = 4., 4., 0.8, 5.
1508    !Config Help  =
1509    !Config Units = [-] 
1510    CALL getin_p('BM_SAPL_LEAF',bm_sapl_leaf)
1511
1512    !-
1513    ! litter parameters
1514    !-
1515
1516    !Config Key   = CN
1517    !Config Desc  = C/N ratio
1518    !Config If    = OK_STOMATE
1519    !Config Def   = 40., 40., 40., 40., 40., 40., 40., 40.
1520    !Config Help  =
1521    !Config Units = [-] 
1522    CALL getin_p('CN',CN_fix)
1523
1524    !Config Key   = FRAC_SOIL_STRUCT_SUA
1525    !Config Desc  = frac_soil(istructural,isurface,iabove)
1526    !Config If    = OK_STOMATE
1527    !Config Def   = 0.55
1528    !Config Help  =
1529    !Config Units = [-]
1530    CALL getin_p('FRAC_SOIL_STRUCT_SUA',frac_soil_struct_sua)
1531
1532    !Config Key   = FRAC_SOIL_METAB_SUA
1533    !Config Desc  = frac_soil(imetabolic,isurface,iabove)
1534    !Config If    = OK_STOMATE
1535    !Config Def   = 0.4
1536    !Config Help  =
1537    !Config Units = [-]   
1538    CALL getin_p('FRAC_SOIL_METAB_SUA',frac_soil_metab_sua)
1539
1540    !Config Key   = TURN_METABOLIC
1541    !Config Desc  =
1542    !Config If    = OK_STOMATE
1543    !Config Def   = 0.066
1544    !Config Help  =
1545    !Config Units = [days]
1546    CALL getin_p('TURN_METABOLIC',turn_metabolic)
1547
1548    !Config Key   = TURN_STRUCT
1549    !Config Desc  =
1550    !Config If    = OK_STOMATE
1551    !Config Def   = 0.245
1552    !Config Help  =
1553    !Config Units = [days]
1554    CALL getin_p('TURN_STRUCT',turn_struct)
1555
1556    !Config Key   = TURN_WOODY
1557    !Config Desc  =
1558    !Config If    = OK_STOMATE
1559    !Config Def   = 0.75
1560    !Config Help  =
1561    !Config Units = [days]
1562    CALL getin_p('TURN_WOODY',turn_woody)
1563
1564    !Config Key   = METABOLIC_REF_FRAC
1565    !Config Desc  =
1566    !Config If    = OK_STOMATE
1567    !Config Def   = 0.85 
1568    !Config Help  =
1569    !Config Units = [-]
1570    CALL getin_p('METABOLIC_REF_FRAC',metabolic_ref_frac)
1571
1572    !Config Key   = Z_DECOMP
1573    !Config Desc  = scaling depth for soil activity
1574    !Config If    = OK_STOMATE
1575    !Config Def   = 0.2
1576    !Config Help  =
1577    !Config Units = [m]   
1578    CALL getin_p('Z_DECOMP',z_decomp)
1579
1580    !Config Key   = FRAC_SOIL_STRUCT_A
1581    !Config Desc  = frac_soil(istructural,iactive,ibelow)
1582    !Config If    = OK_STOMATE
1583    !Config Def   = 0.45
1584    !Config Help  =
1585    !Config Units = [-]
1586    CALL getin_p('FRAC_SOIL_STRUCT_AB',frac_soil_struct_ab)
1587    !
1588    !Config Key   = FRAC_SOIL_STRUCT_SA
1589    !Config Desc  = frac_soil(istructural,islow,iabove)
1590    !Config If    = OK_STOMATE
1591    !Config Def   = 0.7 
1592    !Config Help  =
1593    !Config Units = [-]   
1594    CALL getin_p('FRAC_SOIL_STRUCT_SA',frac_soil_struct_sa)
1595    !
1596    !Config Key   = FRAC_SOIL_STRUCT_SB
1597    !Config Desc  = frac_soil(istructural,islow,ibelow)
1598    !Config If    = OK_STOMATE
1599    !Config Def   = 0.7 
1600    !Config Help  =
1601    !Config Units = [-]   
1602    CALL getin_p('FRAC_SOIL_STRUCT_SB',frac_soil_struct_sb)
1603    !
1604    !Config Key   = FRAC_SOIL_METAB_AB
1605    !Config Desc  = frac_soil(imetabolic,iactive,ibelow)
1606    !Config If    = OK_STOMATE
1607    !Config Def   = 0.45 
1608    !Config Help  =
1609    !Config Units = [-]   
1610    CALL getin_p('FRAC_SOIL_METAB_AB',frac_soil_metab_ab)
1611    !
1612    !
1613    !Config Key   = METABOLIC_LN_RATIO
1614    !Config Desc  =
1615    !Config If    = OK_STOMATE
1616    !Config Def   = 0.018 
1617    !Config Help  =
1618    !Config Units = [-]   
1619    CALL getin_p('METABOLIC_LN_RATIO',metabolic_LN_ratio) 
1620    !
1621    !Config Key   = SOIL_Q10
1622    !Config Desc  =
1623    !Config If    = OK_STOMATE
1624    !Config Def   = 0.69 (=ln2)
1625    !Config Help  =
1626    !Config Units = [-]
1627    CALL getin_p('SOIL_Q10',soil_Q10)
1628    !
1629    !Config Key   = SOIL_Q10_UPTAKE
1630    !Config Desc  =
1631    !Config If    = OK_STOMATE
1632    !Config Def   = 0.69 (=ln2)
1633    !Config Help  =
1634    !Config Units = [-]
1635    CALL getin_p('SOIL_Q10_UPTAKE',soil_Q10_uptake)
1636    !
1637    !Config Key   = TSOIL_REF
1638    !Config Desc  =
1639    !Config If    = OK_STOMATE
1640    !Config Def   = 30.
1641    !Config Help  =
1642    !Config Units = [C]   
1643    CALL getin_p('TSOIL_REF',tsoil_ref)
1644    !
1645    !Config Key   = LITTER_STRUCT_COEF
1646    !Config Desc  =
1647    !Config If    = OK_STOMATE
1648    !Config Def   = 3.
1649    !Config Help  =
1650    !Config Units = [-]   
1651    CALL getin_p('LITTER_STRUCT_COEF',litter_struct_coef)
1652    !
1653    !Config Key   = MOIST_COEFF
1654    !Config Desc  =
1655    !Config If    = OK_STOMATE
1656    !Config Def   = 1.1, 2.4, 0.29
1657    !Config Help  =
1658    !Config Units = [-]   
1659    CALL getin_p('MOIST_COEFF',moist_coeff)
1660    !
1661    !Config Key   = MOISTCONT_MIN
1662    !Config Desc  = minimum soil wetness to limit the heterotrophic respiration
1663    !Config If    = OK_STOMATE
1664    !Config Def   = 0.25
1665    !Config Help  =
1666    !Config Units = [-]
1667    CALL getin_p('MOISTCONT_MIN',moistcont_min)
1668
1669    !-
1670    ! lpj parameters
1671    !-
1672    !
1673    !Config Key   = FRAC_TURNOVER_DAILY
1674    !Config Desc  =
1675    !Config If    = OK_STOMATE
1676    !Config Def   = 0.55
1677    !Config Help  =
1678    !Config Units = [-]
1679    CALL getin_p('FRAC_TURNOVER_DAILY',frac_turnover_daily)   
1680
1681    !-
1682    ! npp parameters
1683    !-
1684    !
1685    !Config Key   = TAX_MAX
1686    !Config Desc  = maximum fraction of allocatable biomass used for maintenance respiration
1687    !Config If    = OK_STOMATE
1688    !Config Def   = 0.8
1689    !Config Help  =
1690    !Config Units = [-]   
1691    CALL getin_p('TAX_MAX',tax_max) 
1692
1693    !-
1694    ! phenology parameters
1695    !-
1696    !
1697    !Config Key   = ALWAYS_INIT
1698    !Config Desc  = take carbon from atmosphere if carbohydrate reserve too small?
1699    !Config If    = OK_STOMATE
1700    !Config Def   = n
1701    !Config Help  =
1702    !Config Units = [-]   
1703    CALL getin_p('ALWAYS_INIT',always_init)
1704    !
1705    !Config Key   = MIN_GROWTHINIT_TIME
1706    !Config Desc  = minimum time since last beginning of a growing season
1707    !Config If    = OK_STOMATE
1708    !Config Def   = 300.
1709    !Config Help  =
1710    !Config Units = [days] 
1711    CALL getin_p('MIN_GROWTHINIT_TIME',min_growthinit_time)
1712    !
1713    !Config Key   = MOIAVAIL_ALWAYS_TREE
1714    !Config Desc  = moisture availability above which moisture tendency doesn't matter
1715    !Config If    = OK_STOMATE
1716    !Config Def   = 1.0
1717    !Config Help  =
1718    !Config Units = [-]   
1719    CALL getin_p('MOIAVAIL_ALWAYS_TREE',moiavail_always_tree)
1720    !
1721    !Config Key   = MOIAVAIL_ALWAYS_GRASS
1722    !Config Desc  = moisture availability above which moisture tendency doesn't matter
1723    !Config If    = OK_STOMATE
1724    !Config Def   = 0.6
1725    !Config Help  =
1726    !Config Units = [-]   
1727    CALL getin_p('MOIAVAIL_ALWAYS_GRASS',moiavail_always_grass)
1728    !
1729    !Config Key   = T_ALWAYS_ADD
1730    !Config Desc  = monthly temp. above which temp. tendency doesn't matter
1731    !Config If    = OK_STOMATE
1732    !Config Def   = 10.
1733    !Config Help  =
1734    !Config Units = [C]   
1735    CALL getin_p('T_ALWAYS_ADD',t_always_add)
1736    !
1737    !
1738    !Config Key   = GDDNCD_REF
1739    !Config Desc  =
1740    !Config If    = OK_STOMATE
1741    !Config Def   = 603.
1742    !Config Help  =
1743    !Config Units = [-]   
1744    CALL getin_p('GDDNCD_REF',gddncd_ref)
1745    !
1746    !Config Key   = GDDNCD_CURVE
1747    !Config Desc  =
1748    !Config If    = OK_STOMATE
1749    !Config Def   = 0.0091
1750    !Config Help  =
1751    !Config Units = [-] 
1752    CALL getin_p('GDDNCD_CURVE',gddncd_curve)
1753    !
1754    !Config Key   = GDDNCD_OFFSET
1755    !Config Desc  =
1756    !Config If    = OK_STOMATE
1757    !Config Def   = 64.
1758    !Config Help  =
1759    !Config Units = [-] 
1760    CALL getin_p('GDDNCD_OFFSET',gddncd_offset)
1761    !-
1762    ! prescribe parameters
1763    !-
1764    !
1765    !Config Key   = BM_SAPL_RESCALE
1766    !Config Desc  =
1767    !Config If    = OK_STOMATE
1768    !Config Def   = 40.
1769    !Config Help  =
1770    !Config Units = [-] 
1771    CALL getin_p('BM_SAPL_RESCALE',bm_sapl_rescale)
1772
1773    !-
1774    ! respiration parameters
1775    !-
1776    !
1777    !Config Key   = MAINT_RESP_MIN_VMAX
1778    !Config Desc  =
1779    !Config If    = OK_STOMATE
1780    !Config Def   = 0.3
1781    !Config Help  =
1782    !Config Units = [-] 
1783    CALL getin_p('MAINT_RESP_MIN_VMAX',maint_resp_min_vmax) 
1784    !
1785    !Config Key   = MAINT_RESP_COEFF
1786    !Config Desc  =
1787    !Config If    = OK_STOMATE
1788    !Config Def   = 1.4
1789    !Config Help  =
1790    !Config Units = [-]
1791    CALL getin_p('MAINT_RESP_COEFF',maint_resp_coeff)
1792
1793    !-
1794    ! soilcarbon parameters
1795    !-
1796    !Config Key   = ACTIVE_TO_PASS_CLAY_FRAC
1797    !Config Desc  =
1798    !Config if    = OK_STOMATE
1799    !Config Def   = 0.68 
1800    !Config Help  =
1801    !Config Units = [-]
1802    CALL getin_p('ACTIVE_TO_PASS_CLAY_FRAC',active_to_pass_clay_frac)
1803
1804
1805    !Config Key   = ACTIVE_TO_PASS_REF_FRAC
1806    !Config Desc  = Fixed fraction from Active to Passive pool
1807    !Config if    = OK_STOMATE
1808    !Config Def   = 0.003
1809    !Config Help  =
1810    !Config Units = [-]
1811    CALL getin_p('ACTIVE_TO_PASS_REF_FRAC',active_to_pass_ref_frac) 
1812    !
1813    !Config Key   = SURF_TO_SLOW_REF_FRAC
1814    !Config Desc  = Fixed fraction from Surface to Slow pool
1815    !Config if    = OK_STOMATE
1816    !Config Def   = 0.4
1817    !Config Help  =
1818    !Config Units = [-]
1819    CALL getin_p('SURF_TO_SLOW_REF_FRAC',surf_to_slow_ref_frac) 
1820    !
1821    !Config Key   = ACTIVE_TO_CO2_REF_FRAC
1822    !Config Desc  = Fixed fraction from Active pool to CO2 emission
1823    !Config if    = OK_STOMATE
1824    !Config Def   = 0.85
1825    !Config Help  =
1826    !Config Units = [-]
1827    CALL getin_p('ACTIVE_TO_CO2_REF_FRAC',active_to_co2_ref_frac) 
1828    !
1829    !Config Key   = SLOW_TO_PASS_REF_FRAC
1830    !Config Desc  = Fixed fraction from Slow to Passive pool
1831    !Config if    = OK_STOMATE
1832    !Config Def   = 0.003
1833    !Config Help  =
1834    !Config Units = [-]
1835    CALL getin_p('SLOW_TO_PASS_REF_FRAC',slow_to_pass_ref_frac) 
1836    !
1837    !Config Key   = SLOW_TO_CO2_REF_FRAC
1838    !Config Desc  = Fixed fraction from Slow pool to CO2 emission
1839    !Config if    = OK_STOMATE
1840    !Config Def   = 0.55
1841    !Config Help  =
1842    !Config Units = [-]
1843    CALL getin_p('SLOW_TO_CO2_REF_FRAC',slow_to_co2_ref_frac) 
1844    !
1845    !Config Key   = PASS_TO_ACTIVE_REF_FRAC
1846    !Config Desc  = Fixed fraction from Passive to Active pool
1847    !Config if    = OK_STOMATE
1848    !Config Def   = 0.45
1849    !Config Help  =
1850    !Config Units = [-]
1851    CALL getin_p('PASS_TO_ACTIVE_REF_FRAC',pass_to_active_ref_frac) 
1852    !
1853    !Config Key   = PASS_TO_SLOW_REF_FRAC
1854    !Config Desc  = Fixed fraction from Passive to Slow pool
1855    !Config if    = OK_STOMATE
1856    !Config Def   = 0.
1857    !Config Help  =
1858    !Config Units = [-]
1859    CALL getin_p('PASS_TO_SLOW_REF_FRAC',pass_to_slow_ref_frac) 
1860    !
1861    !Config Key   = ACTIVE_TO_CO2_CLAY_SILT_FRAC
1862    !Config Desc  = Clay-Silt-dependant fraction from Active pool to CO2 emission
1863    !Config if    = OK_STOMATE
1864    !Config Def   = 0.68
1865    !Config Help  =
1866    !Config Units = [-]
1867    CALL getin_p('ACTIVE_TO_CO2_CLAY_SILT_FRAC',active_to_co2_clay_silt_frac) 
1868    !
1869    !Config Key   = SLOW_TO_PASS_CLAY_FRAC
1870    !Config Desc  = Clay-dependant fraction from Slow to Passive pool
1871    !Config if    = OK_STOMATE
1872    !Config Def   = -0.009
1873    !Config Help  =
1874    !Config Units = [-]
1875    CALL getin_p('SLOW_TO_PASS_CLAY_FRAC',slow_to_pass_clay_frac) 
1876    !
1877    !Config Key   = SOM_TURN_IACTIVE
1878    !Config Desc  = turnover in active pool
1879    !Config if    = OK_STOMATE
1880    !Config Def   = 7.3
1881    !Config Help  =
1882    !Config Units =  [year-1]
1883    CALL getin_p('SOM_TURN_IACTIVE',som_turn_iactive)
1884    !
1885    !Config Key   = SOM_TURN_ISLOW
1886    !Config Desc  = turnover in slow pool
1887    !Config if    = OK_STOMATE
1888    !Config Def   = 0.2
1889    !Config Help  =
1890    !Config Units = [year-1]
1891    CALL getin_p('SOM_TURN_ISLOW',som_turn_islow)
1892    !
1893    !Config Key   = SOM_TURN_IPASSIVE
1894    !Config Desc  = turnover in passive pool
1895    !Config if    = OK_STOMATE
1896    !Config Def   = 0.0045
1897    !Config Help  =
1898    !Config Units = [year-1]
1899    CALL getin_p('SOM_TURN_IPASSIVE',som_turn_ipassive)
1900    !
1901    !Config Key   = SOM_TURN_IACTIVE_CLAY_FRAC
1902    !Config Desc  = clay-dependant parameter impacting on turnover rate of active pool - Tm parameter of Parton et al. 1993 (-)
1903    !Config if    = OK_STOMATE
1904    !Config Def   = 0.75
1905    !Config Help  =
1906    !Config Units = [-]
1907    CALL getin_p('SOM_TURN_IACTIVE_CLAY_FRAC',som_turn_iactive_clay_frac)
1908    !
1909    !Config Key   = CN_TARGET_IACTIVE_REF
1910    !Config Desc  = CN target ratio of active pool for soil min N = 0
1911    !Config if    = OK_STOMATE
1912    !Config Def   = 15.
1913    !Config Help  =
1914    !Config Units = [-]
1915    CALL getin_p('CN_TARGET_IACTIVE_REF',CN_target_iactive_ref)
1916    !
1917    !Config Key   = CN_TARGET_ISLOW_REF
1918    !Config Desc  = CN target ratio of slow pool for soil min N = 0
1919    !Config if    = OK_STOMATE
1920    !Config Def   = 20.
1921    !Config Help  =
1922    !Config Units = [-]
1923    CALL getin_p('CN_TARGET_ISLOW_REF',CN_target_islow_ref)
1924    !
1925    !Config Key   = CN_TARGET_IPASSIVE_REF
1926    !Config Desc  = CN target ratio of passive pool for soil min N = 0
1927    !Config if    = OK_STOMATE
1928    !Config Def   = 10.
1929    !Config Help  =
1930    !Config Units = [-]
1931    CALL getin_p('CN_TARGET_IPASSIVE_REF',CN_target_ipassive_ref)
1932    !
1933    !Config Key   = CN_TARGET_IACTIVE_NMIN
1934    !Config Desc  = CN target ratio change per mineral N unit (g m-2) for active pool
1935    !Config if    = OK_STOMATE
1936    !Config Def   = -6.
1937    !Config Help  =
1938    !Config Units = [(g m-2)-1]
1939    CALL getin_p('CN_TARGET_IACTIVE_NMIN',CN_target_iactive_Nmin)
1940    !
1941    !Config Key   = CN_TARGET_ISLOW_NMIN
1942    !Config Desc  = CN target ratio change per mineral N unit (g m-2) for slow pool
1943    !Config if    = OK_STOMATE
1944    !Config Def   = -4.
1945    !Config Help  =
1946    !Config Units = [(g m-2)-1]
1947    CALL getin_p('CN_TARGET_ISLOW_NMIN',CN_target_islow_Nmin)
1948    !
1949    !Config Key   = CN_TARGET_IPASSIVE_NMIN
1950    !Config Desc  = CN target ratio change per mineral N unit (g m-2) for passive pool
1951    !Config if    = OK_STOMATE
1952    !Config Def   = -1.5
1953    !Config Help  =
1954    !Config Units = [(g m-2)-1]
1955    CALL getin_p('CN_TARGET_IPASSIVE_NMIN',CN_target_ipassive_Nmin)
1956
1957    ! soil nitrogen dynamic parameters
1958    !-
1959    !Config Key   = H_SAXTON
1960    !Config Desc  = Coefficient h for defining maximum porosity
1961    !Config If    = OK_STOMATE
1962    !Config Def   = 0.332
1963    !Config Help  =
1964    !Config Units = [-] 
1965    CALL getin_p('H_SAXTON',h_saxton)
1966    !-
1967    !Config Key   = H_SAXTON
1968    !Config Desc  = Coefficient j for defining maximum porosity
1969    !Config If    = OK_STOMATE
1970    !Config Def   = -7.251*1e-4
1971    !Config Help  =
1972    !Config Units = [-] 
1973    CALL getin_p('J_SAXTON',j_saxton)
1974    !-
1975    !Config Key   = K_SAXTON
1976    !Config Desc  = Coefficient k for defining maximum porosity
1977    !Config If    = OK_STOMATE
1978    !Config Def   = O.1276
1979    !Config Help  =
1980    !Config Units = [-] 
1981    CALL getin_p('K_SAXTON',K_saxton)
1982    !-
1983    !Config Key   = DIFFUSIONO2_POWER_1
1984    !Config Desc  = Power used in the equation defining the diffusion of oxygen in soil
1985    !Config If    = OK_STOMATE
1986    !Config Def   = 3.33
1987    !Config Help  =
1988    !Config Units = [-] 
1989    CALL getin_p('DIFFUSIONO2_POWER_1',diffusionO2_power_1)
1990    !-
1991    !Config Key   = DIFFUSIONO2_POWER_2
1992    !Config Desc  = Power used in the equation defining the diffusion of oxygen in soil
1993    !Config If    = OK_STOMATE
1994    !Config Def   = 2.0
1995    !Config Help  =
1996    !Config Units = [-] 
1997    CALL getin_p('DIFFUSIONO2_POWER_2',diffusionO2_power_2)
1998    !-
1999    !Config Key   = F_NOFROST
2000    !Config Desc  = Temperature-related Factor impacting on Oxygen diffusion rate
2001    !Config If    = OK_STOMATE
2002    !Config Def   = 1.2
2003    !Config Help  =
2004    !Config Units = [-] 
2005    CALL getin_p('F_NOFROST',F_nofrost)
2006    !-
2007    !Config Key   = F_FROST
2008    !Config Desc  = Temperature-related Factor impacting on Oxygen diffusion rate
2009    !Config If    = OK_STOMATE
2010    !Config Def   = 0.8
2011    !Config Help  =
2012    !Config Units = [-] 
2013    CALL getin_p('F_FROST',F_frost)
2014    !-
2015    !Config Key   = A_ANVF
2016    !Config Desc  = Coefficient used in the calculation of Volumetric fraction of anaerobic microsites
2017    !Config If    = OK_STOMATE
2018    !Config Def   = 0.85
2019    !Config Help  =
2020    !Config Units = [-] 
2021    CALL getin_p('A_ANVF',a_anvf)
2022    !-
2023    !Config Key   = B_ANVF
2024    !Config Desc  = Coefficient used in the calculation of Volumetric fraction of anaerobic microsites
2025    !Config If    = OK_STOMATE
2026    !Config Def   = 1.
2027    !Config Help  =
2028    !Config Units = [-] 
2029    CALL getin_p('B_ANVF',b_anvf)
2030    !-
2031    !Config Key   = A_FIXNH4
2032    !Config Desc  = Coefficient used in the calculation of the Fraction of adsorbed NH4+
2033    !Config If    = OK_STOMATE
2034    !Config Def   = 0.41
2035    !Config Help  =
2036    !Config Units = [-] 
2037    CALL getin_p('A_FIXNH4',a_FixNH4)
2038    !-
2039    !Config Key   = B_FIXNH4
2040    !Config Desc  = Coefficient used in the calculation of the Fraction of adsorbed NH4+
2041    !Config If    = OK_STOMATE
2042    !Config Def   = -0.47
2043    !Config Help  =
2044    !Config Units = [-] 
2045    CALL getin_p('B_FIXNH4',b_FixNH4)
2046    !-
2047    !Config Key   = CLAY_MAX
2048    !Config Desc  = Coefficient used in the calculation of the Fraction of adsorbed NH4+
2049    !Config If    = OK_STOMATE
2050    !Config Def   = 0.63
2051    !Config Help  =
2052    !Config Units = [-] 
2053    CALL getin_p('CLAY_MAX',clay_max)
2054    !-
2055    !Config Key   = FWNIT_0
2056    !Config Desc  = Coefficient used in the calculation of the Response of Nitrification to soil moisture
2057    !Config If    = OK_STOMATE
2058    !Config Def   = -0.0243
2059    !Config Help  =
2060    !Config Units = [-] 
2061    CALL getin_p('FWNIT_0',fwnit_0)
2062    !-
2063    !Config Key   = FWNIT_1
2064    !Config Desc  = Coefficient used in the calculation of the Response of Nitrification to soil moisture
2065    !Config If    = OK_STOMATE
2066    !Config Def   = 0.9975
2067    !Config Help  =
2068    !Config Units = [-] 
2069    CALL getin_p('FWNIT_1',fwnit_1)
2070    !-
2071    !Config Key   = FWNIT_2
2072    !Config Desc  = Coefficient used in the calculation of the Response of Nitrification to soil moisture
2073    !Config If    = OK_STOMATE
2074    !Config Def   = -5.5368
2075    !Config Help  =
2076    !Config Units = [-] 
2077    CALL getin_p('FWNIT_2',fwnit_2)
2078    !-
2079    !Config Key   = FWNIT_3
2080    !Config Desc  = Coefficient used in the calculation of the Response of Nitrification to soil moisture
2081    !Config If    = OK_STOMATE
2082    !Config Def   = 17.651
2083    !Config Help  =
2084    !Config Units = [-] 
2085    CALL getin_p('FWNIT_3',fwnit_3)
2086    !-
2087    !Config Key   = FWNIT_4
2088    !Config Desc  = Coefficient used in the calculation of the Response of Nitrification to soil moisture
2089    !Config If    = OK_STOMATE
2090    !Config Def   = -12.904
2091    !Config Help  =
2092    !Config Units = [-] 
2093    CALL getin_p('FWNIT_4',fwnit_4)
2094    !-
2095    !Config Key   = FT_NIT_0
2096    !Config Desc  = Coefficient used in the calculation of the Response of Nitrification to Temperature
2097    !Config If    = OK_STOMATE
2098    !Config Def   = -0.0233
2099    !Config Help  =
2100    !Config Units = [-] 
2101    CALL getin_p('FT_NIT_0',ft_nit_0)
2102    !-
2103    !Config Key   = FT_NIT_1
2104    !Config Desc  = Coefficient used in the calculation of the Response of Nitrification to Temperature
2105    !Config If    = OK_STOMATE
2106    !Config Def   = 0.3094
2107    !Config Help  =
2108    !Config Units = [-] 
2109    CALL getin_p('FT_NIT_1',ft_nit_1)
2110    !-
2111    !Config Key   = FT_NIT_2
2112    !Config Desc  = Coefficient used in the calculation of the Response of Nitrification to Temperature
2113    !Config If    = OK_STOMATE
2114    !Config Def   = -0.2234
2115    !Config Help  =
2116    !Config Units = [-] 
2117    CALL getin_p('FT_NIT_2',ft_nit_2)
2118    !-
2119    !Config Key   = FT_NIT_3
2120    !Config Desc  = Coefficient used in the calculation of the Response of Nitrification to Temperature
2121    !Config If    = OK_STOMATE
2122    !Config Def   = 0.1566
2123    !Config Help  =
2124    !Config Units = [-] 
2125    CALL getin_p('FT_NIT_3',ft_nit_3)
2126    !-
2127    !Config Key   = FT_NIT_4
2128    !Config Desc  = Coefficient used in the calculation of the Response of Nitrification to Temperature
2129    !Config If    = OK_STOMATE
2130    !Config Def   = -0.0272
2131    !Config Help  =
2132    !Config Units = [-] 
2133    CALL getin_p('FT_NIT_4',ft_nit_4)
2134    !-
2135    !Config Key   = FPH_0
2136    !Config Desc  = Coefficient used in the calculation of the Response of Nitrification to pH
2137    !Config If    = OK_STOMATE
2138    !Config Def   = -1.2314
2139    !Config Help  =
2140    !Config Units = [-] 
2141    CALL getin_p('FPH_0',fph_0)
2142    !-
2143    !Config Key   = FPH_1
2144    !Config Desc  = Coefficient used in the calculation of the Response of Nitrification to pH
2145    !Config If    = OK_STOMATE
2146    !Config Def   = 0.7347
2147    !Config Help  =
2148    !Config Units = [-] 
2149    CALL getin_p('FPH_1',fph_1)
2150    !-
2151    !Config Key   = FPH_2
2152    !Config Desc  = Coefficient used in the calculation of the Response of Nitrification to pH
2153    !Config If    = OK_STOMATE
2154    !Config Def   = -0.0604
2155    !Config Help  =
2156    !Config Units = [-] 
2157    CALL getin_p('FPH_2',fph_2)
2158    !-
2159    !Config Key   = FTV_0
2160    !Config Desc  = Coefficient used in the calculation of the response of NO2 or NO production during nitrificationof to Temperature
2161    !Config If    = OK_STOMATE
2162    !Config Def   = 2.72
2163    !Config Help  =
2164    !Config Units = [-] 
2165    CALL getin_p('FTV_0',ftv_0)
2166    !-
2167    !Config Key   = FTV_1
2168    !Config Desc  = Coefficient used in the calculation of the response of NO2 or NO production during nitrificationof to Temperature
2169    !Config If    = OK_STOMATE
2170    !Config Def   = 34.6
2171    !Config Help  =
2172    !Config Units = [-] 
2173    CALL getin_p('FTV_1',ftv_1)
2174    !-
2175    !Config Key   = FTV_2
2176    !Config Desc  = Coefficient used in the calculation of the response of NO2 or NO production during nitrificationof to Temperature
2177    !Config If    = OK_STOMATE
2178    !Config Def   = 9615.
2179    !Config Help  =
2180    !Config Units = [-] 
2181    CALL getin_p('FTV_2',ftv_2)
2182    !-
2183    !Config Key   = K_NITRIF
2184    !Config Desc  = Nitrification rate at 20 ◩C and field capacity
2185    !Config If    = OK_STOMATE
2186    !Config Def   = 0.2
2187    !Config Help  =
2188    !Config Units = [day**-1] 
2189    CALL getin_p('K_NITRIF',k_nitrif)
2190    !-
2191    !Config Key   = N2O_NITRIF_P
2192    !Config Desc  = Reference n2o production per N-NO3 produced g N-N2O
2193    !Config If    = OK_STOMATE
2194    !Config Def   = 0.0006
2195    !Config Help  =
2196    !Config Units = [gN-N2O (gN-NO3)-1] 
2197    CALL getin_p('N2O_NITRIF_P',n2o_nitrif_p)
2198    !-
2199    !Config Key   = NO_NITRIF_P
2200    !Config Desc  = Reference NO production per N-NO3 produced g N-N2O
2201    !Config If    = OK_STOMATE
2202    !Config Def   = 0.0025
2203    !Config Help  =
2204    !Config Units = [gN-NO (gN-NO3)-1] 
2205    CALL getin_p('NO_NITRIF_P',no_nitrif_p)
2206    !-
2207    !Config Key   = CHEMO_T0
2208    !Config Desc  = Coefficient used in the calculation of the Response of NO production from chemodenitrification to Temperature
2209    !Config If    = OK_STOMATE
2210    !Config Def   = -31494
2211    !Config Help  =
2212    !Config Units = [-] 
2213    CALL getin_p('CHEMO_T0',chemo_t0)
2214    !-
2215    !Config Key   = CHEMO_PH0
2216    !Config Desc  = Coefficient used in the calculation of the Response of NO production from chemodenitrification to pH
2217    !Config If    = OK_STOMATE
2218    !Config Def   = -1.62
2219    !Config Help  =
2220    !Config Units = [-] 
2221    CALL getin_p('CHEMO_PH0',chemo_ph0)
2222    !-
2223    !Config Key   = CHEMO_0
2224    !Config Desc  = Coefficient used in the calculation of NO production from chemodenitrification
2225    !Config If    = OK_STOMATE
2226    !Config Def   = 30.
2227    !Config Help  =
2228    !Config Units = [-] 
2229    CALL getin_p('CHEMO_0',chemo_0)
2230    !-
2231    !Config Key   = CHEMO_1
2232    !Config Desc  = Coefficient used in the calculation of NO production from chemodenitrification
2233    !Config If    = OK_STOMATE
2234    !Config Def   = 16565
2235    !Config Help  =
2236    !Config Units = [-] 
2237    CALL getin_p('CHEMO_1',chemo_1)
2238    !-
2239    !Config Key   = FT_DENIT_0
2240    !Config Desc  = Coefficient used in the response of relative growth rate of total denitrifiers to Temperature
2241    !Config If    = OK_STOMATE
2242    !Config Def   = 2.
2243    !Config Help  =
2244    !Config Units = [-] 
2245    CALL getin_p('FT_DENIT_0',ft_denit_0)
2246    !-
2247    !Config Key   = FT_DENIT_1
2248    !Config Desc  = Coefficient used in the response of relative growth rate of total denitrifiers to Temperature
2249    !Config If    = OK_STOMATE
2250    !Config Def   = 22.5
2251    !Config Help  =
2252    !Config Units = [-] 
2253    CALL getin_p('FT_DENIT_1',ft_denit_1)
2254    !-
2255    !Config Key   = FT_DENIT_2
2256    !Config Desc  = Coefficient used in the response of relative growth rate of total denitrifiers to Temperature
2257    !Config If    = OK_STOMATE
2258    !Config Def   = 10
2259    !Config Help  =
2260    !Config Units = [-] 
2261    CALL getin_p('FT_DENIT_2',ft_denit_2)
2262    !-
2263    !Config Key   = FPH_NO3_0
2264    !Config Desc  = Coefficient used in the response of relative growth rate of NO3 denitrifiers to pH
2265    !Config If    = OK_STOMATE
2266    !Config Def   = 4.25
2267    !Config Help  =
2268    !Config Units = [-] 
2269    CALL getin_p('FPH_NO3_0',fph_no3_0)
2270    !-
2271    !Config Key   = FPH_NO3_1
2272    !Config Desc  = Coefficient used in the response of relative growth rate of NO3 denitrifiers to pH
2273    !Config If    = OK_STOMATE
2274    !Config Def   = 0.5
2275    !Config Help  =
2276    !Config Units = [-] 
2277    CALL getin_p('FPH_NO3_1',fph_no3_1)
2278    !-
2279    !Config Key   = FPH_NO_0
2280    !Config Desc  = Coefficient used in the response of relative growth rate of NO denitrifiers to pH
2281    !Config If    = OK_STOMATE
2282    !Config Def   = 5.25
2283    !Config Help  =
2284    !Config Units = [-] 
2285    CALL getin_p('FPH_NO_0',fph_no_0)
2286    !-
2287    !Config Key   = FPH_NO_1
2288    !Config Desc  = Coefficient used in the response of relative growth rate of NO denitrifiers to pH
2289    !Config If    = OK_STOMATE
2290    !Config Def   = 1.
2291    !Config Help  =
2292    !Config Units = [-] 
2293    CALL getin_p('FPH_NO_1',fph_no_1)
2294    !-
2295    !Config Key   = FPH_N2O_0
2296    !Config Desc  = Coefficient used in the response of relative growth rate of N2O denitrifiers to pH
2297    !Config If    = OK_STOMATE
2298    !Config Def   = 6.25
2299    !Config Help  =
2300    !Config Units = [-] 
2301    CALL getin_p('FPH_N2O_0',fph_n2o_0)
2302    !-
2303    !Config Key   = FPH_N2O_1
2304    !Config Desc  = Coefficient used in the response of relative growth rate of N2O denitrifiers to pH
2305    !Config If    = OK_STOMATE
2306    !Config Def   = 1.5
2307    !Config Help  =
2308    !Config Units = [-] 
2309    CALL getin_p('FPH_N2O_1',fph_n2o_1)
2310    !-
2311    !Config Key   = KN
2312    !Config Desc  = Half Saturation of N oxydes
2313    !Config If    = OK_STOMATE
2314    !Config Def   = 0.083
2315    !Config Help  =
2316    !Config Units = [kgN/m**3] 
2317    CALL getin_p('KN',Kn)
2318    !-
2319    !Config Key   = MU_NO3_MAX
2320    !Config Desc  = Maximum Relative growth rate of NO3 denitrifiers
2321    !Config If    = OK_STOMATE
2322    !Config Def   = 0.67
2323    !Config Help  =
2324    !Config Units = [hour**-1] 
2325    CALL getin_p('MU_NO3_MAX',mu_no3_max)
2326    !-
2327    !Config Key   = MU_NO_MAX
2328    !Config Desc  = Maximum Relative growth rate of NO denitrifiers
2329    !Config If    = OK_STOMATE
2330    !Config Def   = 0.34
2331    !Config Help  =
2332    !Config Units = [hour**-1] 
2333    CALL getin_p('MU_NO_MAX',mu_no_max)
2334    !-
2335    !Config Key   = MU_N2O_MAX
2336    !Config Desc  = Maximum Relative growth rate of N2O denitrifiers
2337    !Config If    = OK_STOMATE
2338    !Config Def   = 0.34
2339    !Config Help  =
2340    !Config Units = [hour**-1] 
2341    CALL getin_p('MU_N2O_MAX',mu_n2o_max)
2342    !-
2343    !Config Key   = Y_NO3
2344    !Config Desc  = Maximum growth yield of NO3 denitrifiers on N oxydes
2345    !Config If    = OK_STOMATE
2346    !Config Def   = 0.401
2347    !Config Help  =
2348    !Config Units = [kgC / kgN] 
2349    CALL getin_p('Y_NO3',Y_no3)
2350    !-
2351    !Config Key   = Y_NO
2352    !Config Desc  = Maximum growth yield of NO denitrifiers on N oxydes
2353    !Config If    = OK_STOMATE
2354    !Config Def   = 0.428
2355    !Config Help  =
2356    !Config Units = [kgC / kgN] 
2357    CALL getin_p('Y_NO',Y_no)
2358    !-
2359    !Config Key   = Y_N2O
2360    !Config Desc  = Maximum growth yield of N2O denitrifiers on N oxydes
2361    !Config If    = OK_STOMATE
2362    !Config Def   = 0.151
2363    !Config Help  =
2364    !Config Units = [kgC / kgN] 
2365    CALL getin_p('Y_N2O',Y_n2O)
2366    !-
2367    !Config Key   = M_NO3
2368    !Config Desc  = Maintenance coefficient on NO3
2369    !Config If    = OK_STOMATE
2370    !Config Def   = 0.09
2371    !Config Help  =
2372    !Config Units = [kgN / kgC / hour] 
2373    CALL getin_p('M_NO3',M_no3)
2374    !-
2375    !Config Key   = M_NO
2376    !Config Desc  = Maintenance coefficient on NO
2377    !Config If    = OK_STOMATE
2378    !Config Def   = 0.035
2379    !Config Help  =
2380    !Config Units = [kgN / kgC / hour] 
2381    CALL getin_p('M_NO',M_no)
2382    !-
2383    !Config Key   = M_N2O
2384    !Config Desc  = Maintenance coefficient on N2O
2385    !Config If    = OK_STOMATE
2386    !Config Def   = 0.079
2387    !Config Help  =
2388    !Config Units = [kgN / kgC / hour] 
2389    CALL getin_p('M_N2O',M_n2o)
2390    !-
2391    !Config Key   = MAINT_C
2392    !Config Desc  = Maintenance coefficient of carbon
2393    !Config If    = OK_STOMATE
2394    !Config Def   = 0.0076
2395    !Config Help  =
2396    !Config Units = [kgC / kgC / hour] 
2397    CALL getin_p('MAINT_C',Maint_c)
2398    !-
2399    !Config Key   = YC
2400    !Config Desc  = Maximum growth yield on soluble carbon
2401    !Config If    = OK_STOMATE
2402    !Config Def   = 0.503
2403    !Config Help  =
2404    !Config Units = [kgC / kgC ] 
2405    CALL getin_p('YC',Yc)
2406    !-
2407    !Config Key   = F_CLAY_0
2408    !Config Desc  = Coefficient used in the eq. defining the response of N-emission to clay fraction
2409    !Config If    = OK_STOMATE
2410    !Config Def   = 0.13
2411    !Config Help  =
2412    !Config Units = [-] 
2413    CALL getin_p('F_CLAY_0',F_clay_0)
2414    !-
2415    !Config Key   = F_CLAY_1
2416    !Config Desc  = Coefficient used in the eq. defining the response of N-emission to clay fraction
2417    !Config If    = OK_STOMATE
2418    !Config Def   = -0.079
2419    !Config Help  =
2420    !Config Units = [-] 
2421    CALL getin_p('F_CLAY_1',F_clay_1)
2422    !-
2423    !Config Key   = RATIO_NH4_FERT
2424    !Config Desc  = Proportion of ammonium in the fertilizers (ammo-nitrate)
2425    !Config If    = OK_STOMATE
2426    !Config Def   = 0.875
2427    !Config Help  =
2428    !Config Units = [-] 
2429    CALL getin_p('RATIO_NH4_FERT',ratio_nh4_fert)
2430    !-
2431    ! Arrays
2432    !-
2433    !-
2434    !Config Key   = VMAX_UPTAKE
2435    !Config Desc  = Vmax of nitrogen uptake by plants for Ammonium (ind.1) and Nitrate (ind.2)
2436    !Config If    = OK_STOMATE
2437    !Config Def   = 3. 3.
2438    !Config Help  =
2439    !Config Units = [umol (g DryWeight_root)-1 h-1)] 
2440    CALL getin_p('VMAX_UPTAKE',vmax_uptake)
2441    !-
2442    !Config Key   = K_N_MIN
2443    !Config Desc  = [NH4+] and [NO3-] for which the Nuptake equals vmax/2.
2444    !Config If    = OK_STOMATE
2445    !Config Def   = 30. 30.
2446    !Config Help  =
2447    !Config Units = [umol per litter] 
2448    CALL getin_p('K_N_min',K_N_min)
2449    !-
2450    !Config Key   = LOW_K_N_MIN
2451    !Config Desc  = Rate of N uptake not associated with Michaelis- Menten Kinetics for Ammonium
2452    !Config If    = OK_STOMATE
2453    !Config Def   = 0.0002 0.0002
2454    !Config Help  =
2455    !Config Units = [umol**-1] 
2456    CALL getin_p('LOW_K_N_min',low_K_N_min)
2457
2458    !-
2459    !Config Key   = DMAX
2460    !Config Desc  = ?????????????
2461    !Config If    = OK_STOMATE
2462    !Config Def   = 0.25
2463    !Config Help  =
2464    !Config Units = ???
2465    CALL getin_p('LEAF_N_DMAX',DMAX)
2466
2467    !-
2468    ! growth_fun_all
2469    !-
2470    !Config Key   = NCIRC
2471    !Config Desc  = Number of basal area classes in allocation scheme
2472    !               circ classes could be considered as cohorts within a stand
2473    !Config If    = OK_STOMATE, functional allocation
2474    !Config Def   = 2
2475    !Config Help  =
2476    !Config Units = [-]
2477    CALL getin_p('NCIRC',ncirc) 
2478
2479
2480    !-
2481    !Config Key   = BLYPASS_CC_BUG
2482    !Config Desc  = There is a bug somewhere which allows the circumference classes to
2483    !               deviate from monotonically increasing order, which can cause a problem.
2484    !               Setting this to TRUE disables the check for this condition and impliments
2485    !               a small patch for the one problem which has manifested.  This needs to
2486    !               be found.
2487    !Config If    = OK_STOMATE, functional allocation
2488    !Config Def   = FALSE
2489    !Config Help  =
2490    !Config Units = [-]
2491    CALL getin_p('BYPASS_CC_BUG',lbypass_cc) 
2492
2493
2494    !
2495    !Config Key   = SYNC_THRESHOLD
2496    !Config Desc  = The threshold value for a warning when we sync biomass
2497    !Config If    = OK_STOMATE, functional allocation
2498    !Config Def   = 0.1
2499    !Config Help  =
2500    !Config Units = [-] 
2501    CALL getin_p('SYNC_THRESHOLD',sync_threshold)
2502
2503
2504    !
2505    !Config Key   = TEST_GRID
2506    !Config Desc  = grid cell for which extra output is written to the out_execution file
2507    !Config If    = OK_STOMATE
2508    !Config Def   = 1
2509    !Config Help  =
2510    !Config Units = [-]
2511    CALL getin_p('TEST_GRID',test_grid)   
2512
2513
2514    !
2515    !Config Key   = TEST_PFT
2516    !Config Desc  = pft for which extra output is written to the out_execution file
2517    !Config If    = OK_STOMATE
2518    !Config Def   = 6
2519    !Config Help  =
2520    !Config Units = [-]   
2521    CALL getin_p('TEST_PFT',test_pft)   
2522
2523    CALL getin_p('LD_FAKE_HEIGHT', ld_fake_height)
2524
2525    CALL getin_p('LD_ALLOC', ld_alloc)
2526    !
2527    !Config Key   = MAX_DELTA_KF
2528    !Config Desc  = Maximum change in KF from one time step to another
2529    !Config If    = OK_STOMATE, functional allocation
2530    !Config Def   = 0.1
2531    !Config Help  =
2532    !Config Units = [m] 
2533    CALL getin_p('MAX_DELTA_KF',max_delta_KF)
2534    !
2535
2536    !
2537    !Config Key   = MAINT_FROM_GPP
2538    !Config Desc  = Some carbon needs to remain to support the growth, hence,
2539    !               respiration will be limited. In this case resp_maint
2540    !               (gC m-2 dt-1) should not be more than 80% (::maint_from_gpp)
2541    !               of the GPP (gC m-2 s-1)
2542    !Config If    = OK_STOMATE, functional allocation
2543    !Config Def   = 0.8
2544    !Config Help  =
2545    !Config Units = [-] 
2546    CALL getin_p('MAINT_FROM_GPP',maint_from_gpp)
2547
2548
2549    !-
2550    ! turnover parameters
2551    !-
2552    !
2553    !Config Key   = NEW_TURNOVER_TIME_REF
2554    !Config Desc  =
2555    !Config If    = OK_STOMATE
2556    !Config Def   = 20.
2557    !Config Help  =
2558    !Config Units = [days] 
2559    CALL getin_p('NEW_TURNOVER_TIME_REF',new_turnover_time_ref)
2560
2561    !Config Key   = LEAF_AGE_CRIT_TREF
2562    !Config Desc  =
2563    !Config If    = OK_STOMATE
2564    !Config Def   = 20.
2565    !Config Help  =
2566    !Config Units = [days] 
2567    CALL getin_p('LEAF_AGE_CRIT_TREF',leaf_age_crit_tref)
2568    !
2569    !Config Key   = LEAF_AGE_CRIT_COEFF
2570    !Config Desc  =
2571    !Config If    = OK_STOMATE
2572    !Config Def   = 1.5, 0.75, 10.
2573    !Config Help  =
2574    !Config Units = [-]
2575    CALL getin_p('LEAF_AGE_CRIT_COEFF',leaf_age_crit_coeff)
2576
2577    !-
2578    ! vmax parameters
2579    !-
2580    !
2581    !Config Key   = VMAX_OFFSET
2582    !Config Desc  = offset (minimum relative vcmax)
2583    !Config If    = OK_STOMATE
2584    !Config Def   = 0.3
2585    !Config Help  = offset (minimum vcmax/vmax_opt)
2586    !Config Units = [-] 
2587    CALL getin_p('VMAX_OFFSET',vmax_offset)
2588    !
2589    !Config Key   = LEAFAGE_FIRSTMAX
2590    !Config Desc  = leaf age at which vmax attains vcmax_opt (in fraction of critical leaf age)
2591    !Config If    = OK_STOMATE
2592    !Config Def   = 0.03
2593    !Config Help  = relative leaf age at which vmax attains vcmax_opt
2594    !Config Units = [-]
2595    CALL getin_p('LEAFAGE_FIRSTMAX',leafage_firstmax)
2596    !
2597    !Config Key   = LEAFAGE_LASTMAX
2598    !Config Desc  = leaf age at which vmax falls below vcmax_opt (in fraction of critical leaf age)
2599    !Config If    = OK_STOMATE
2600    !Config Def   = 0.5
2601    !Config Help  = relative leaf age at which vmax falls below vcmax_opt
2602    !Config Units = [-] 
2603    CALL getin_p('LEAFAGE_LASTMAX',leafage_lastmax)
2604    !
2605    !Config Key   = LEAFAGE_OLD
2606    !Config Desc  = leaf age at which vmax attains its minimum (in fraction of critical leaf age)
2607    !Config If    = OK_STOMATE
2608    !Config Def   = 1.
2609    !Config Help  = relative leaf age at which vmax attains its minimum
2610    !Config Units = [-] 
2611    CALL getin_p('LEAFAGE_OLD',leafage_old)
2612
2613    !-
2614    ! season parameters
2615    !-
2616    !
2617    !Config Key   = GPPFRAC_DORMANCE
2618    !Config Desc  = rapport maximal GPP/GGP_max pour dormance
2619    !Config If    = OK_STOMATE
2620    !Config Def   = 0.2
2621    !Config Help  =
2622    !Config Units = [-]
2623    CALL getin_p('GPPFRAC_DORMANCE',gppfrac_dormance)
2624    !
2625    !Config Key   = TAU_CLIMATOLOGY
2626    !Config Desc  = tau for "climatologic variables
2627    !Config If    = OK_STOMATE
2628    !Config Def   = 20
2629    !Config Help  =
2630    !Config Units = [days]
2631    CALL getin_p('TAU_CLIMATOLOGY',tau_climatology)
2632    !
2633    !Config Key   = HVC1
2634    !Config Desc  = parameters for herbivore activity
2635    !Config If    = OK_STOMATE
2636    !Config Def   = 0.019
2637    !Config Help  =
2638    !Config Units = [-] 
2639    CALL getin_p('HVC1',hvc1)
2640    !
2641    !Config Key   = HVC2
2642    !Config Desc  = parameters for herbivore activity
2643    !Config If    = OK_STOMATE
2644    !Config Def   = 1.38
2645    !Config Help  =
2646    !Config Units = [-] 
2647    CALL getin_p('HVC2',hvc2)
2648    !
2649    !Config Key   = LEAF_FRAC_HVC
2650    !Config Desc  = parameters for herbivore activity
2651    !Config If    = OK_STOMATE
2652    !Config Def   = 0.33
2653    !Config Help  =
2654    !Config Units = [-]
2655    CALL getin_p('LEAF_FRAC_HVC',leaf_frac_hvc)
2656    !
2657    !Config Key   = TLONG_REF_MAX
2658    !Config Desc  = maximum reference long term temperature
2659    !Config If    = OK_STOMATE
2660    !Config Def   = 303.1
2661    !Config Help  =
2662    !Config Units = [K] 
2663    CALL getin_p('TLONG_REF_MAX',tlong_ref_max)
2664    !
2665    !Config Key   = TLONG_REF_MIN
2666    !Config Desc  = minimum reference long term temperature
2667    !Config If    = OK_STOMATE
2668    !Config Def   = 253.1
2669    !Config Help  =
2670    !Config Units = [K] 
2671    CALL getin_p('TLONG_REF_MIN',tlong_ref_min)
2672    !
2673    !Config Key   = NCD_MAX_YEAR
2674    !Config Desc  =
2675    !Config If    = OK_STOMATE
2676    !Config Def   = 3.
2677    !Config Help  = NCD : Number of Chilling Days
2678    !Config Units = [days]
2679    CALL getin_p('NCD_MAX_YEAR',ncd_max_year)
2680    !
2681    !Config Key   = GDD_THRESHOLD
2682    !Config Desc  =
2683    !Config If    = OK_STOMATE
2684    !Config Def   = 5.
2685    !Config Help  = GDD : Growing-Degree-Day
2686    !Config Units = [days]
2687    CALL getin_p('GDD_THRESHOLD',gdd_threshold)
2688    !
2689    !Config Key   = GREEN_AGE_EVER
2690    !Config Desc  =
2691    !Config If    = OK_STOMATE
2692    !Config Def   = 2.
2693    !Config Help  =
2694    !Config Units = [-] 
2695    CALL getin_p('GREEN_AGE_EVER',green_age_ever)
2696    !
2697    !Config Key   = GREEN_AGE_DEC
2698    !Config Desc  =
2699    !Config If    = OK_STOMATE
2700    !Config Def   = 0.5
2701    !Config Help  =
2702    !Config Units = [-]
2703    CALL getin_p('GREEN_AGE_DEC',green_age_dec)
2704
2705  END SUBROUTINE config_stomate_parameters
2706
2707!! ================================================================================================================================
2708!! SUBROUTINE   : config_dgvm_parameters
2709!!
2710!>\BRIEF        This subroutine reads in the configuration file all the parameters
2711!! needed when the DGVM model is activated (ie : when ok_dgvm is set to true).
2712!!
2713!! DESCRIPTION  : None
2714!!
2715!! RECENT CHANGE(S): None
2716!!
2717!! MAIN OUTPUT VARIABLE(S):
2718!!
2719!! REFERENCE(S) :
2720!!
2721!! FLOWCHART    :
2722!! \n
2723!_ ================================================================================================================================
2724
2725  SUBROUTINE config_dgvm_parameters   
2726
2727    IMPLICIT NONE
2728
2729    !! 0. Variables and parameters declaration
2730
2731    !! 0.4 Local variables
2732
2733    !_ ================================================================================================================================   
2734
2735    !-
2736    ! establish parameters
2737    !-
2738    !
2739    !Config Key   = ESTAB_MAX_TREE
2740    !Config Desc  = Maximum tree establishment rate
2741    !Config If    = OK_DGVM
2742    !Config Def   = 0.12
2743    !Config Help  =
2744    !Config Units = [-]   
2745    CALL getin_p('ESTAB_MAX_TREE',estab_max_tree)
2746    !
2747    !Config Key   = ESTAB_MAX_GRASS
2748    !Config Desc  = Maximum grass establishment rate
2749    !Config If    = OK_DGVM
2750    !Config Def   = 0.12
2751    !Config Help  =
2752    !Config Units = [-] 
2753    CALL getin_p('ESTAB_MAX_GRASS',estab_max_grass)
2754    !
2755    !Config Key   = ESTABLISH_SCAL_FACT
2756    !Config Desc  =
2757    !Config If    = OK_DGVM
2758    !Config Def   = 5.
2759    !Config Help  =
2760    !Config Units = [-]
2761    CALL getin_p('ESTABLISH_SCAL_FACT',establish_scal_fact)
2762    !
2763    !Config Key   = MAX_TREE_COVERAGE
2764    !Config Desc  =
2765    !Config If    = OK_DGVM
2766    !Config Def   = 0.98
2767    !Config Help  =
2768    !Config Units = [-]
2769    CALL getin_p('MAX_TREE_COVERAGE',max_tree_coverage)
2770    !
2771    !Config Key   = IND_0_ESTAB
2772    !Config Desc  =
2773    !Config If    = OK_DGVM
2774    !Config Def   = 0.2
2775    !Config Help  =
2776    !Config Units = [-] 
2777    CALL getin_p('IND_0_ESTAB',ind_0_estab)
2778
2779    !-
2780    ! light parameters
2781    !-
2782    !
2783    !Config Key   = ANNUAL_INCREASE
2784    !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)?
2785    !Config If    = OK_DGVM
2786    !Config Def   = y
2787    !Config Help  =
2788    !Config Units = [FLAG]
2789    CALL getin_p('ANNUAL_INCREASE',annual_increase)
2790    !
2791    !Config Key   = MIN_COVER
2792    !Config Desc  = For trees, minimum fraction of crown area occupied
2793    !Config If    = OK_DGVM
2794    !Config Def   = 0.05
2795    !Config Help  =
2796    !Config Units = [-] 
2797    CALL getin_p('MIN_COVER',min_cover)
2798
2799    !-
2800    ! pftinout parameters
2801    !
2802    !Config Key   = IND_0
2803    !Config Desc  = initial density of individuals
2804    !Config If    = OK_DGVM
2805    !Config Def   = 0.02
2806    !Config Help  =
2807    !Config Units = [-] 
2808    CALL getin_p('IND_0',ind_0)
2809    !
2810    !Config Key   = MIN_AVAIL
2811    !Config Desc  = minimum availability
2812    !Config If    = OK_DGVM
2813    !Config Def   = 0.01
2814    !Config Help  =
2815    !Config Units = [-] 
2816    CALL getin_p('MIN_AVAIL',min_avail)
2817    !
2818    !Config Key   = RIP_TIME_MIN
2819    !Config Desc  =
2820    !Config If    = OK_DGVM
2821    !Config Def   = 1.25
2822    !Config Help  =
2823    !Config Units = [year] 
2824    CALL getin_p('RIP_TIME_MIN',RIP_time_min)
2825    !
2826    !Config Key   = NPP_LONGTERM_INIT
2827    !Config Desc  =
2828    !Config If    = OK_DGVM
2829    !Config Def   = 10.
2830    !Config Help  =
2831    !Config Units = [gC/m^2/year]
2832    CALL getin_p('NPP_LONGTERM_INIT',npp_longterm_init)
2833    !
2834    !Config Key   = EVERYWHERE_INIT
2835    !Config Desc  =
2836    !Config If    = OK_DGVM
2837    !Config Def   = 0.05
2838    !Config Help  =
2839    !Config Units = [-]
2840    CALL getin_p('EVERYWHERE_INIT',everywhere_init)
2841
2842
2843  END SUBROUTINE config_dgvm_parameters
2844
2845
2846!! ================================================================================================================================
2847!! FUNCTION   : get_printlev
2848!!
2849!>\BRIEF        Read global PRINTLEV parmeter and local PRINTLEV_modname
2850!!
2851!! DESCRIPTION  : The first time this function is called the parameter PRINTLEV is read from run.def file.
2852!!                It is stored in the variable named printlev which is declared in constantes_var.f90. printlev
2853!!                can be accesed each module in ORCHIDEE which makes use of constantes_var module.
2854!!
2855!!                This function also reads the parameter PRINTLEV_modname for run.def file. modname is the
2856!!                intent(in) character string to this function. If the variable is set in run.def file, the corresponding
2857!!                value is returned. Otherwise the value of printlev is returnd as default.
2858!!
2859!! RECENT CHANGE(S): None
2860!!
2861!! MAIN OUTPUT VARIABLE(S): The local output level for the module set as intent(in) argument.
2862!!
2863!! REFERENCE(S) :
2864!!
2865!! FLOWCHART    :
2866!! \n
2867!_ ================================================================================================================================
2868
2869  FUNCTION get_printlev ( modname )
2870
2871    !! 0.1 Input arguments
2872    CHARACTER(LEN=*), INTENT(IN) :: modname
2873
2874    !! 0.2 Returned variable
2875    INTEGER       :: get_printlev
2876
2877    !! 0.3 Local variables
2878    LOGICAL, SAVE :: first=.TRUE.
2879
2880    !_ ================================================================================================================================
2881
2882    !! 1.0  Read the global PRINTLEV from run.def. This is only done at first call to this function.
2883    IF (first) THEN
2884       ! Set default value for printlev
2885       ! printlev is a public variable declared in constantes_var
2886       printlev=1
2887       !Config Key   = PRINTLEV
2888       !Config Desc  = Print level for text output
2889       !Config If    =
2890       !Config Help  = Possible values are:
2891       !Config         0    No output,
2892       !Config         1    Minimum writing for long simulations,
2893       !Config         2    More basic information for long simulations,
2894       !Config         3    First debug level,
2895       !Config         4    Higher debug level
2896       !Config Def   = 1
2897       !Config Units = [0, 1, 2, 3, 4]
2898       CALL getin_p('PRINTLEV',printlev)
2899       first=.FALSE.
2900
2901       !Config Key   = PRINTLEV_modname
2902       !Config Desc  = Specific print level of text output for the module "modname". Default as PRINTLEV.
2903       !Config Def   = 1
2904       !Config If    =
2905       !Config Help  = Use this option to activate a different level of text output
2906       !Config         for a specific module. This can be activated for several modules
2907       !Config         at the same time. Use for example PRINTLEV_sechiba.
2908       !Config Units = [0, 1, 2, 3, 4]
2909    END IF
2910
2911    ! Set default value as the standard printlev
2912    get_printlev=printlev
2913    ! Read optional value from run.def file
2914    CALL getin_p('PRINTLEV_'//modname, get_printlev)
2915
2916  END FUNCTION get_printlev
2917
2918
2919END MODULE constantes
Note: See TracBrowser for help on using the repository browser.