source: branches/publications/ORCHIDEE_CN-P_v1.2_r5986/ORCHIDEE/src_parameters/constantes.f90

Last change on this file was 5980, checked in by daniel.goll, 6 years ago

dsg

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