source: branches/ORCHIDEE_3_CMIP6/ORCHIDEE/src_parameters/constantes.f90 @ 7599

Last change on this file since 7599 was 6781, checked in by nicolas.vuichard, 4 years ago

add a parameter defining the sensitivity of denitrification to SOM

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