source: tags/ORCHIDEE_4_1/ORCHIDEE/src_parameters/constantes.f90 @ 7852

Last change on this file since 7852 was 7672, checked in by sebastiaan.luyssaert, 2 years ago

Decouple NBP consistency checking from mass balance checks. ERR_ACT = 3 will now check for mass balance closure. Until it works for all configurations, NBP consistency checking is only activated when setting ERR_ACT = 4

  • Property svn:keywords set to Date Revision
File size: 132.8 KB
Line 
1! =================================================================================================================================
2! MODULE       : constantes
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE      : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF        "constantes" module contains subroutines to initialize most of the exernalized parameters. This module
10!!              also make a use to the module constantes_var where the parameters are declared.
11!!
12!!\n DESCRIPTION: This module contains subroutines to initialize most of the exernalized parameters. This module
13!!                also make a use to the module constantes_var where the parameters are declared.\n
14!!                This module can be used to acces the subroutines and the constantes. The constantes declarations
15!!                can also be used seperatly with "USE constantes_var".
16!!
17!! RECENT CHANGE(S): Didier Solyga : This module contains now all the externalized parameters of ORCHIDEE
18!!                   listed by modules which are not pft-dependent 
19!!                   Josefine Ghattas 2013 : The declaration part has been extracted and moved to module constates_var
20!!
21!! REFERENCE(S) :
22!! - Louis, Jean-Francois (1979), A parametric model of vertical eddy fluxes in the atmosphere.
23!! Boundary Layer Meteorology, 187-202.
24!!
25!! SVN          :
26!! $HeadURL: $
27!! $Date$
28!! $Revision$
29!! \n
30!_ ================================================================================================================================
31
32MODULE constantes
33
34  USE constantes_var
35  USE defprec
36  USE ioipsl_para, ONLY : getin_p, ipslerr_p
37  USE mod_orchidee_para_var, ONLY : numout
38  USE time, ONLY : one_day, dt_sechiba
39
40  IMPLICIT NONE
41 
42CONTAINS
43
44
45!! ================================================================================================================================
46!! SUBROUTINE   : activate_sub_models
47!!
48!>\BRIEF         This subroutine reads the flags in the configuration file to
49!! activate some sub-models like routing, irrigation, fire, herbivory, ... 
50!!
51!! DESCRIPTION  : None
52!!
53!! RECENT CHANGE(S): None
54!!
55!! MAIN OUTPUT VARIABLE(S): None
56!!
57!! REFERENCE(S) : None
58!!
59!! FLOWCHART    : None
60!! \n
61!_ ================================================================================================================================
62
63  SUBROUTINE activate_sub_models()
64
65    IMPLICIT NONE
66
67    !! 0. Variables and parameters declaration
68
69    !! 0.4 Local variables
70
71    !_ ================================================================================================================================
72
73    IF (ok_stomate) THEN
74
75       !Config Key   = HERBIVORES
76       !Config Desc  = herbivores allowed?
77       !Config If    = OK_STOMATE
78       !Config Def   = n
79       !Config Help  = With this variable, you can determine
80       !Config         if herbivores are activated
81       !Config Units = [FLAG]
82       CALL getin_p('HERBIVORES', ok_herbivores)
83       !
84       !Config Key   = TREAT_EXPANSION
85       !Config Desc  = treat expansion of PFTs across a grid cell?
86       !Config If    = OK_STOMATE
87       !Config Def   = n
88       !Config Help  = With this variable, you can determine
89       !Config         whether we treat expansion of PFTs across a
90       !Config         grid cell.
91       !Config Units = [FLAG]
92       CALL getin_p('TREAT_EXPANSION', treat_expansion)
93
94       !Config Key   = 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     !
158     ! HACKS
159     !
160     !Config Key   = HACK_ENERBIL_HYDROL
161     !Config Desc  = Flag to skip a particular block of code in mleb.f90
162     !Config If    = -
163     !Config Def   = n
164     !Config Help  = Flag to skip a particular block of code in mleb.f90
165     !               which results in incorrect results for large scale simulations.
166     !Config Units = [FLAG]
167     CALL getin_p('HACK_ENERBIL_HYDROL',hack_enerbil_hydrol)
168     !
169     !Config Key   = HACK_E_FRAC
170     !Config Desc  = Bypass root length in the calculation of psi_soilroot
171     !Config If    = OK_HYDROL_ARCH
172     !Config Def   = n
173     !Config Help  = Bypass root length in the calculation of psi_soilroot
174     !Config Units = [FLAG]
175     CALL getin_p('HACK_E_FRAC',hack_e_frac)
176     
177     !Config Key   = HACK_PGAP
178     !Config Desc  = Flag to use Lambert Beer instead of Pgap
179     !Config If    = -
180     !Config Def   = n
181     !Config Help  = Flag to use Lambert Beer instead of Pgap to calculate veget.
182     !               Only for debugging as it may introduce inconsistencies.
183     !Config Units = [FLAG]
184     CALL getin_p('HACK_PGAP',hack_pgap)     
185
186     !Config Key   = HACK_VESSEL_LOSS
187     !Config Desc  = constant vessel_loss in hydraulic_rachitecture
188     !Config If    = OK_VESSEL_MORTALITY
189     !Config Def   = -9999
190     !Config Help  = When set outside the range from 0 to 1 it will not be used.
191     !Config Units = unitless
192     CALL getin_p('HACK_VESSEL_LOSS',hack_vessel_loss)
193
194     !Config Key   = HACK_VEGET_MAX_NEW
195     !Config Desc  = Prescribe VEGET_MAX_NEW rather than reading from a map
196     !Config If    = -
197     !Config Def   = n
198     !Config Help  = Read veget_max_new from run.def. This is intended to
199     !               be used in combination with a restart file. It only
200     !               works once per simulation. It can be used to debug
201     !               simplified LCC test cases. See slowproc.f90 for more
202     !               details. Only for debugging as it will introduce
203     !               inconsistencies.
204     !Config Units = [FLAG]
205     CALL getin_p('HACK_VEGET_MAX_NEW',hack_veget_max_new) 
206
207    !
208    ! Check consistency (see later)
209    !
210!!$        IF(.NOT.(ok_routing) .AND. (doirrigation .OR. dofloodplains)) THEN
211!!$           CALL ipslerr_p(2,'activate_sub_models', &
212!!$               &     'Problem :you tried to activate the irrigation and floodplains without activating the routing',&
213!!$               &     'Are you sure ?', &
214!!$               &     '(check your parameters).')
215!!$        ENDIF
216
217!!$        IF(.NOT.(ok_stomate) .AND. (ok_herbivores .OR. treat_expansion .OR. lpj_gap_const_mort &
218!!$            & .OR. harvest_agri .OR. disable_fire)) THEN
219!!$          CALL ipslerr_p(2,'activate_sub_models', &
220!!$               &     'Problem : try to activate the following options : herbivory, treat_expansion, fire,',&
221!!$               &     'harvest_agri and constant mortality without stomate activated.',&
222!!$               &     '(check your parameters).')
223!!$        ENDIF
224
225
226  END SUBROUTINE activate_sub_models
227
228!! ================================================================================================================================
229!! SUBROUTINE   : veget_config
230!!
231!>\BRIEF         This subroutine reads the flags controlling the configuration for
232!! the vegetation : impose_veg, veget_mpa, lai_map, etc...       
233!!
234!! DESCRIPTION  : None
235!!
236!! RECENT CHANGE(S): None
237!!
238!! MAIN OUTPUT VARIABLE(S):
239!!
240!! REFERENCE(S) :
241!!
242!! FLOWCHART    :
243!! \n
244!_ ================================================================================================================================
245
246  SUBROUTINE veget_config
247
248    IMPLICIT NONE
249
250    !! 0. Variables and parameters declaration
251
252    !! 0.4 Local variables 
253    CHARACTER(LEN=30)          :: veget_str         !! update frequency for landuse   
254    INTEGER                    :: l
255
256    !_ ================================================================================================================================
257
258
259    !Config Key   = AGRICULTURE
260    !Config Desc  = agriculture allowed?
261    !Config If    = OK_SECHIBA or OK_STOMATE
262    !Config Def   = y
263    !Config Help  = With this variable, you can determine
264    !Config         whether agriculture is allowed
265    !Config Units = [FLAG]
266    CALL getin_p('AGRICULTURE', agriculture)
267    !
268    !Config Key   = IMPOSE_VEG
269    !Config Desc  = Should the vegetation be prescribed ?
270    !Config If    = OK_SECHIBA or OK_STOMATE
271    !Config Def   = n
272    !Config Help  = This flag allows the user to impose a vegetation distribution
273    !Config         and its characteristics. It is espacially interesting for 0D
274    !Config         simulations. On the globe it does not make too much sense as
275    !Config         it imposes the same vegetation everywhere
276    !Config Units = [FLAG]
277    CALL getin_p('IMPOSE_VEG', impveg)
278
279    !Config Key   = IMPOSE_SOILT
280    !Config Desc  = Should the soil type be prescribed ?
281    !Config Def   = n
282    !Config If    =
283    !Config Help  = This flag allows the user to impose a soil type distribution.
284    !Config         It is espacially interesting for 0D
285    !Config         simulations. On the globe it does not make too much sense as
286    !Config         it imposes the same soil everywhere
287    !Config Units = [FLAG]
288    CALL getin_p('IMPOSE_SOILT', impsoilt)     
289
290    !Config Key   = IMPOSE_SLOPE
291    !Config Desc  = Should reinf_slope be prescribed ?
292    !Config Def   = n
293    !Config If    =
294    !Config Help  = This flag allows the user to impose a uniform fraction of 
295    !Config         reinfiltrated surface runoff, with value REINF_SLOPE
296    !Config Units = [FLAG]
297    CALL getin_p('IMPOSE_SLOPE', impslope)
298
299    !Config Key   = IMPOSE_NINPUT_DEP
300    !Config Desc  = Should the N inputs from atmospheric deposition be prescribed ?
301    !Config Def   = n
302    !Config If    = NOT IMPOSE_CN
303    !Config Help  = This flag allows the user to impose N inputs from atmospheric deposition
304    !Config         It is espacially interesting for 0D
305    !Config         simulations. On the globe it does not make too much sense as
306    !Config         it imposes the same N inputs everywhere
307    !Config Units = [FLAG]
308    CALL getin_p('IMPOSE_NINPUT_DEP', impose_ninput_dep)     
309
310    !Config Key   = IMPOSE_NINPUT_FERT
311    !Config Desc  = Should the N inputs from fertilizer be prescribed ?
312    !Config Def   = n
313    !Config If    = -
314    !Config Help  = This flag allows the user to impose N inputs from fertilizer application
315    !Config         It is espacially interesting for 0D
316    !Config         simulations. On the globe it does not make too much sense as
317    !Config         it imposes the same N inputs everywhere
318    !Config Units = [FLAG]
319    CALL getin_p('IMPOSE_NINPUT_FERT', impose_ninput_fert)
320
321    !Config Key   = IMPOSE_NINPUT_MANURE
322    !Config Desc  = Should the N inputs from manure be prescribed ?
323    !Config Def   = n
324    !Config If    = -
325    !Config Help  = This flag allows the user to impose N inputs from manure application
326    !Config         It is espacially interesting for 0D
327    !Config         simulations. On the globe it does not make too much sense as
328    !Config         it imposes the same N inputs everywhere
329    !Config Units = [FLAG]
330    CALL getin_p('IMPOSE_NINPUT_MANURE', impose_ninput_manure)
331
332    !Config Key   = IMPOSE_NINPUT_BNF
333    !Config Desc  = Should the N inputs from biological nitrogen fixation (BNF) be prescribed ?
334    !Config Def   = n
335    !Config If    = -
336    !Config Help  = This flag allows the user to impose N inputs from biological nitrogen fixation (BNF)
337    !Config         It is espacially interesting for 0D
338    !Config         simulations. On the globe it does not make too much sense as
339    !Config         it imposes the same N inputs everywhere
340    !Config Units = [FLAG]
341    CALL getin_p('IMPOSE_NINPUT_BNF', impose_ninput_bnf)
342       
343   
344    !Config Key   = LAI_MAP
345    !Config Desc  = Read the LAI map
346    !Config If    = OK_SECHIBA or OK_STOMATE
347    !Config Def   = n
348    !Config Help  = It is possible to read a 12 month LAI map which will
349    !Config         then be interpolated to daily values as needed.
350    !Config Units = [FLAG]
351    CALL getin_p('LAI_MAP',read_lai)
352
353
354    !Config Key   = VEGET_UPDATE
355    !Config Desc  = Update vegetation frequency: 0Y or 1Y
356    !Config If    =
357    !Config Def   = 0Y
358    !Config Help  = The veget datas will be update each this time step. Must be 0Y if IMPOSE_VEG=y.
359    !Config Units = [years]
360    veget_update=0
361    WRITE(veget_str,'(a)') '0Y'
362    CALL getin_p('VEGET_UPDATE', veget_str)
363    l=INDEX(TRIM(veget_str),'Y')
364    READ(veget_str(1:(l-1)),"(I2.2)") veget_update
365
366    ! Coherence test : veget_update can only be 0 or 1
367    IF (veget_update /= 0 .AND. veget_update /= 1) then
368       WRITE(numout,*) "Error in veget_update=", veget_update
369       CALL ipslerr_p(3,'veget_config','VEGET_UPDATE can only be 0Y or 1Y.',&
370            'Please correcte run.def file for VEGET_UPDATE','')
371    END IF
372
373   
374    ! Coherence test for impveg and veget_update. Land use change can not be activated with impveg.
375    IF (impveg .AND. veget_update > 0) THEN
376       WRITE(numout,*) 'veget_update=',veget_update,' is not coeherent with impveg=',impveg
377       CALL ipslerr_p(3,'slowproc_init','Incoherent values between impveg and veget_update', &
378            'VEGET_UPDATE must be equal to 0Y if IMPOSE_VEG=y (impveg=true)','')
379    END IF 
380 
381
382    !Config Key   = VEGETMAP_RESET
383    !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.
384    !Config If    =
385    !Config Def   = n
386    !Config Help  = Use this option to change vegetation map while keeping VEGET_UPDATE=0Y
387    !Config Units = [FLAG]
388    CALL getin_p('VEGETMAP_RESET', vegetmap_reset)
389
390
391    !Config Key   = NINPUT_REINIT
392    !Config Desc  = booleen to indicate that a new N INPUT file will be used.
393    !Config If    = -
394    !Config Def   = y
395    !Config Help  = When set to y, the counter for the year of data grabbed in
396    !Config         the Nitrogen input files will be reset to be equal to that of
397    !Config         the first year present in the input file. 
398    !Config         Then it is possible to change N INPUT file.
399    !Config         Only seems to be
400    !Config         useful set to n when the Nitrogen input file contains multiple years?
401    !Config Units = [FLAG]
402    CALL getin_p('NINPUT_REINIT', ninput_reinit)
403   
404    !Config Key   = NINPUT_YEAR
405    !Config Desc  = Year of the N input map to be read
406    !Config If    = -
407    !Config Def   = 1
408    !Config Help  = First year for N inputs vegetation
409    !Config         If NINPUT_YEAR is set to 0, this means there is no time axis in the Nitrogen
410    !Config         input map.  If there is a time axis, NINPUT_YEAR can be set to any four digit year.
411    !Config         The code will look for an input file name corresponding to this year and
412    !Config         take the data from this file.
413    !Config Units = [FLAG]
414    CALL getin_p('NINPUT_YEAR', ninput_year_orig)
415   
416    !Config Key   = NINPUT_SUFFIX_YEAR
417    !Config Desc  = Do the Ninput dataset have a 'year' suffix
418    !Config If    = -
419    !Config Def   = false
420    !Config Help  = A flag to indicate if nitrogen input files have a year suffix (before .nc)
421    !Config         If NINPUT_SUFFIX_YEAR is set to true, the code searches for a Nitrogen input file of the
422    !Config         format "filename_YEAR.nc" where YEAR is the NINPUT_YEAR
423    !Config Units = [FLAG]
424    CALL getin_p('NINPUT_SUFFIX_YEAR', ninput_suffix_year)
425       
426
427  END SUBROUTINE veget_config
428
429
430!! ================================================================================================================================
431!! SUBROUTINE   : veget_config
432!!
433!>\BRIEF         This subroutine reads in the configuration file the imposed values of the parameters for all SECHIBA modules. 
434!!
435!! DESCRIPTION  : None
436!!
437!! RECENT CHANGE(S): None
438!!
439!! MAIN OUTPUT VARIABLE(S):
440!!
441!! REFERENCE(S) :
442!!
443!! FLOWCHART    :
444!! \n
445!_ ================================================================================================================================
446
447  SUBROUTINE config_sechiba_parameters
448
449    IMPLICIT NONE
450
451    !! 0. Variables and parameters declaration
452
453    !! 0.4 Local variables
454    REAL(r_std) :: nudge_tau_mc     !! Temporary variable read from run.def
455    REAL(r_std) :: nudge_tau_snow   !! Temporary variable read from run.def
456    INTEGER     :: ilevel           !! index
457
458    !_ ================================================================================================================================
459
460    ! Global : parameters used by many modules
461    CALL getin_p('TESTPFT',testpft)
462
463    !
464    !Config Key   = MAXMASS_SNOW
465    !Config Desc  = The maximum mass of a snow
466    !Config If    = OK_SECHIBA
467    !Config Def   = 3000.
468    !Config Help  =
469    !Config Units = [kg/m^2] 
470    CALL getin_p('MAXMASS_SNOW',maxmass_snow)
471    !
472    !Config Key   = SNOWCRI
473    !Config Desc  = Sets the amount above which only sublimation occures
474    !Config If    = OK_SECHIBA
475    !Config Def   = 1.5
476    !Config Help  =
477    !Config Units = [kg/m^2] 
478    CALL getin_p('SNOWCRI',snowcri)
479    !
480    !! Initialization of sneige
481    sneige = snowcri/mille
482    !
483    !Config Key   = MIN_WIND
484    !Config Desc  = Minimum wind speed
485    !Config If    = OK_SECHIBA
486    !Config Def   = 0.1
487    !Config Help  =
488    !Config Units = [m/s]
489    CALL getin_p('MIN_WIND',min_wind)
490    !
491    !Config Key   = MAX_SNOW_AGE
492    !Config Desc  = Maximum period of snow aging
493    !Config If    = OK_SECHIBA
494    !Config Def   = 50.
495    !Config Help  =
496    !Config Units = [days?]
497    CALL getin_p('MAX_SNOW_AGE',max_snow_age)
498    !
499    !Config Key   = SNOW_TRANS
500    !Config Desc  = Transformation time constant for snow
501    !Config If    = OK_SECHIBA
502    !Config Def   = 0.2
503    !Config Help  = optimized on 04/07/2016
504    !Config Units = [m]   
505    CALL getin_p('SNOW_TRANS',snow_trans)
506
507   
508    !Config Key   = OK_NUDGE_MC
509    !Config Desc  = Activate nudging of soil moisture
510    !Config Def   = n
511    !Config If    =
512    !Config Help  =
513    !Config Units = [FLAG]
514    ok_nudge_mc = .FALSE.
515    CALL getin_p('OK_NUDGE_MC', ok_nudge_mc)
516
517    !Config Key   = NUDGE_TAU_MC
518    !Config Desc  = Relaxation time for nudging of soil moisture expressed in fraction of the day
519    !Config Def   = 1
520    !Config If    = OK_NUDGE_MC
521    !Config Help  =
522    !Config Units = [-]
523    nudge_tau_mc = 1.0
524    CALL getin_p('NUDGE_TAU_MC', nudge_tau_mc)
525    IF (nudge_tau_mc < dt_sechiba/one_day) CALL ipslerr_p(3, 'hydrol_initialize', &
526         'NUDGE_TAU_MC is smaller than the time step in sechiba which is not allowed.', &
527         'Set NUDGE_TAU_MC higher or equal to dt_sechiba/one_day','')
528    ! Calculate alpha to be used in hydrol
529    alpha_nudge_mc = dt_sechiba/(one_day*nudge_tau_mc)
530    IF (printlev>=2) WRITE(numout, *) 'ok_nudge_mc, nudge_tau_mc, alpha_nudge_mc =', &
531         ok_nudge_mc, nudge_tau_mc, alpha_nudge_mc
532
533    !Config Key   = OK_NUDGE_SNOW
534    !Config Desc  = Activate nudging of snow variables
535    !Config Def   = n
536    !Config If    =
537    !Config Help  =
538    !Config Units = [FLAG]
539    ok_nudge_snow = .FALSE.
540    CALL getin_p('OK_NUDGE_SNOW', ok_nudge_snow)
541
542    !Config Key   = NUDGE_TAU_SNOW
543    !Config Desc  = Relaxation time for nudging of snow variables
544    !Config Def   = 1
545    !Config If    = OK_NUDGE_SNOW
546    !Config Help  =
547    !Config Units = [-]
548    nudge_tau_snow = 1.0
549    CALL getin_p('NUDGE_TAU_SNOW', nudge_tau_snow)
550    IF (nudge_tau_snow < dt_sechiba/one_day) CALL ipslerr_p(3, 'hydrol_initialize', &
551         'NUDGE_TAU_SNOW is smaller than the time step in sechiba which is not allowed.', &
552         'Set NUDGE_TAU_SNOW higher or equal to dt_sechiba/one_day','')
553    ! Calculate alpha to be used in hydrol
554    alpha_nudge_snow = dt_sechiba/(one_day*nudge_tau_snow)
555    IF (printlev>=2) WRITE(numout, *) 'ok_nudge_snow, nudge_tau_snow, alpha_nudge_snow =', &
556         ok_nudge_snow, nudge_tau_snow, alpha_nudge_snow
557
558
559    !Config Key   = NUDGE_INTERPOL_WITH_XIOS
560    !Config Desc  = Activate reading and interpolation with XIOS for nudging fields
561    !Config Def   = n
562    !Config If    = OK_NUDGE_MC or OK_NUDGE_SNOW
563    !Config Help  =
564    !Config Units = [FLAG]
565    nudge_interpol_with_xios = .FALSE.
566    CALL getin_p('NUDGE_INTERPOL_WITH_XIOS', nudge_interpol_with_xios)
567
568    !-
569    ! condveg
570    !-
571    !
572    !Config Key   = HEIGHT_DISPLACEMENT
573    !Config Desc  = Magic number which relates the height to the displacement height.
574    !Config If    = OK_SECHIBA
575    !Config Def   = 0.75
576    !Config Help  =
577    !Config Units = [m] 
578    CALL getin_p('HEIGHT_DISPLACEMENT',height_displacement)
579    !
580    !Config Key   = Z0_BARE
581    !Config Desc  = bare soil roughness length
582    !Config If    = OK_SECHIBA
583    !Config Def   = 0.01
584    !Config Help  =
585    !Config Units = [m]   
586    CALL getin_p('Z0_BARE',z0_bare)
587    !
588    !Config Key   = Z0_ICE
589    !Config Desc  = ice roughness length
590    !Config If    = OK_SECHIBA
591    !Config Def   = 0.001
592    !Config Help  =
593    !Config Units = [m]   
594    CALL getin_p('Z0_ICE',z0_ice)
595    !
596    !Config Key   = OK_SNOW_ALBEDO_CLM3
597    !Config Desc  = Calculate the snow albedo according to CLM3
598    !Config If    = OK_SECHIBA
599    !Config Def   = TRUE
600    !Config Help  =
601    !Config Units = [FLAG]
602    CALL getin_p('OK_SNOW_ALBEDO_CLM3',ok_snow_albedo_clm3)
603
604    IF (ok_snow_albedo_clm3) THEN
605       !
606       !Config Key   = ALB_SNOW_0_VIS
607       !Config Desc  = Albedo for VIS of fresh snow
608       !Config If    = OK_SECHIBA
609       !Config Def   = 0.95
610       !Config Help  =
611       !Config Units = [-]
612       CALL getin_p('ALB_SNOW_0_VIS',alb_snow_0(ivis))
613       !
614       !Config Key   = ALB_SNOW_0_NIR
615       !Config Desc  = Albedo for NIR of fresh snow
616       !Config If    = OK_SECHIBA
617       !Config Def   = 0.65
618       !Config Help  =
619       !Config Units = [-]
620       CALL getin_p('ALB_SNOW_0_NIR',alb_snow_0(inir))
621       !
622       !Config Key   = C_ALBEDO_VIS
623       !Config Desc  = constant in albedo calculation
624       !Config If    = OK_SECHIBA
625       !Config Def   = 0.2
626       !Config Help  =
627       !Config Units = [-]
628       CALL getin_p('C_ALBEDO_VIS',c_albedo(ivis))
629       !
630       !Config Key   = C_ALBEDO_NIR
631       !Config Desc  = constant in albedo calculation
632       !Config If    = OK_SECHIBA
633       !Config Def   = 0.65
634       !Config Help  =
635       !Config Units = [-]
636       CALL getin_p('C_ALBEDO_NIR',c_albedo(inir))
637
638    ENDIF
639    !
640    !Config Key   = TCST_SNOWA
641    !Config Desc  = Time constant of the albedo decay of snow
642    !Config If    = OK_SECHIBA
643    !Config Def   = 10.0
644    !Config Help  = optimized on 04/07/2016
645    !Config Units = [days]
646    CALL getin_p('TCST_SNOWA',tcst_snowa)
647    !
648    !Config Key   = SNOWCRI_ALB
649    !Config Desc  = Critical value for computation of snow albedo
650    !Config If    = OK_SECHIBA
651    !Config Def   = 10.
652    !Config Help  =
653    !Config Units = [cm] 
654    CALL getin_p('SNOWCRI_ALB',snowcri_alb)
655    !
656    !
657    !Config Key   = VIS_DRY
658    !Config Desc  = The correspondance table for the soil color numbers and their albedo
659    !Config If    = OK_SECHIBA
660    !Config Def   = 0.24, 0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.27
661    !Config Help  =
662    !Config Units = [-] 
663    CALL getin_p('VIS_DRY',vis_dry)
664    !
665    !Config Key   = NIR_DRY
666    !Config Desc  = The correspondance table for the soil color numbers and their albedo
667    !Config If    = OK_SECHIBA
668    !Config Def   = 0.48, 0.44, 0.40, 0.36, 0.32, 0.28, 0.24, 0.20, 0.55
669    !Config Help  =
670    !Config Units = [-]   
671    CALL getin_p('NIR_DRY',nir_dry)
672    !
673    !Config Key   = VIS_WET
674    !Config Desc  = The correspondance table for the soil color numbers and their albedo
675    !Config If    = OK_SECHIBA 
676    !Config Def   = 0.12, 0.11, 0.10, 0.09, 0.08, 0.07, 0.06, 0.05, 0.15
677    !Config Help  =
678    !Config Units = [-]   
679    CALL getin_p('VIS_WET',vis_wet)
680    !
681    !Config Key   = NIR_WET
682    !Config Desc  = The correspondance table for the soil color numbers and their albedo
683    !Config If    = OK_SECHIBA
684    !Config Def   = 0.24, 0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.31
685    !Config Help  =
686    !Config Units = [-]   
687    CALL getin_p('NIR_WET',nir_wet)
688    !
689    !Config Key   = ALBSOIL_VIS
690    !Config Desc  =
691    !Config If    = OK_SECHIBA
692    !Config Def   = 0.18, 0.16, 0.16, 0.15, 0.12, 0.105, 0.09, 0.075, 0.25
693    !Config Help  =
694    !Config Units = [-] 
695    CALL getin_p('ALBSOIL_VIS',albsoil_vis)
696    !
697    !Config Key   = ALBSOIL_NIR
698    !Config Desc  =
699    !Config If    = OK_SECHIBA
700    !Config Def   = 0.36, 0.34, 0.34, 0.33, 0.30, 0.25, 0.20, 0.15, 0.45
701    !Config Help  =
702    !Config Units = [-] 
703    CALL getin_p('ALBSOIL_NIR',albsoil_nir)
704    !-
705    !
706    !Config Key   = ALB_DEADLEAF
707    !Config Desc  = albedo of dead leaves, VIS+NIR
708    !Config If    = OK_SECHIBA
709    !Config Def   = 0.12, 0.35
710    !Config Help  =
711    !Config Units = [-]     
712    CALL getin_p('ALB_DEADLEAF',alb_deadleaf)
713    !
714    !Config Key   = ALB_ICE
715    !Config Desc  = albedo of ice, VIS+NIR
716    !Config If    = OK_SECHIBA
717    !Config Def   = 0.60, 0.20
718    !Config Help  =
719    !Config Units = [-] 
720    CALL getin_p('ALB_ICE',alb_ice)
721    !
722    ! Get the fixed snow albedo if needed
723    !
724    !Config Key   = CONDVEG_SNOWA
725    !Config Desc  = The snow albedo used by SECHIBA
726    !Config Def   = 1.E+20
727    !Config if    = OK_SECHIBA
728    !Config Help  = This option allows the user to impose a snow albedo.
729    !Config         Default behaviour is to use the model of snow albedo
730    !Config         developed by Chalita (1993).
731    !Config Units = [-]
732    CALL getin_p('CONDVEG_SNOWA',fixed_snow_albedo)
733    !
734    !Config Key   = ALB_BARE_MODEL
735    !Config Desc  = Switch bare soil albedo dependent (if TRUE) on soil wetness
736    !Config Def   = n
737    !Config if    = OK_SECHIBA
738    !Config Help  = If TRUE, the model for bare soil albedo is the old formulation.
739    !Config         Then it depend on the soil dry or wetness. If FALSE, it is the
740    !Config         new computation that is taken, it is the mean of soil albedo.
741    !Config Units = [FLAG]
742    CALL getin_p('ALB_BARE_MODEL',alb_bare_model)
743    !
744    !Config Key   = ALB_BG_MODIS
745    !Config Desc  = Read bare soil albedo from file with background MODIS data
746    !Config Def   = n
747    !Config if    = OK_SECHIBA
748    !Config Help  = If TRUE, the bare soil albedo is read from file
749    !Config         based on background MODIS data. 
750    !Config         If FALSE, computaion depends on ALB_BARE_MODEL
751    !Config Units = [FLAG]
752    CALL getin_p('ALB_BG_MODIS',alb_bg_modis)
753    !
754    !Config Key   = IMPOSE_AZE
755    !Config Desc  = Should the surface parameters be prescribed
756    !Config Def   = n
757    !Config if    = OK_SECHIBA
758    !Config Help  = This flag allows the user to impose the surface parameters
759    !Config         (Albedo Roughness and Emissivity). It is espacially interesting for 0D
760    !Config         simulations. On the globe it does not make too much sense as
761    !Config         it imposes the same vegetation everywhere
762    !Config Units = [FLAG]
763    CALL getin_p('IMPOSE_AZE',impaze)
764    !
765    IF(impaze) THEN
766       !
767       !Config Key   = CONDVEG_Z0
768       !Config Desc  = Surface roughness
769       !Config Def   = 0.15
770       !Config If    = IMPOSE_AZE
771       !Config Help  = Surface rougness to be used on the point if a 0-dim version
772       !Config         of SECHIBA is used. Look at the description of the forcing 
773       !Config         data for the correct value.
774       !Config Units = [m]
775       CALL getin_p('CONDVEG_Z0', z0_scal) 
776       !
777       !Config Key   = ROUGHHEIGHT
778       !Config Desc  = Height to be added to the height of the first level
779       !Config Def   = 0.0
780       !Config If    = IMPOSE_AZE
781       !Config Help  = ORCHIDEE assumes that the atmospheric level height is counted
782       !Config         from the zero wind level. Thus to take into account the roughness
783       !Config         of tall vegetation we need to correct this by a certain fraction
784       !Config         of the vegetation height. This is called the roughness height in
785       !Config         ORCHIDEE talk.
786       !Config Units = [m]
787       CALL getin_p('ROUGHHEIGHT', roughheight_scal)
788       !
789       !Config Key   = CONDVEG_ALBVIS
790       !Config Desc  = SW visible albedo for the surface
791       !Config Def   = 0.25
792       !Config If    = IMPOSE_AZE
793       !Config Help  = Surface albedo in visible wavelengths to be used
794       !Config         on the point if a 0-dim version of SECHIBA is used.
795       !Config         Look at the description of the forcing data for
796       !Config         the correct value.
797       !Config Units = [-]
798       CALL getin_p('CONDVEG_ALBVIS', albedo_scal(ivis))
799       !
800       !Config Key   = CONDVEG_ALBNIR
801       !Config Desc  = SW near infrared albedo for the surface
802       !Config Def   = 0.25
803       !Config If    = IMPOSE_AZE
804       !Config Help  = Surface albedo in near infrared wavelengths to be used
805       !Config         on the point if a 0-dim version of SECHIBA is used.
806       !Config         Look at the description of the forcing data for
807       !Config         the correct value.
808       !Config Units = [-] 
809       CALL getin_p('CONDVEG_ALBNIR', albedo_scal(inir))
810       !
811       !Config Key   = CONDVEG_EMIS
812       !Config Desc  = Emissivity of the surface for LW radiation
813       !Config Def   = 1.0
814       !Config If    = IMPOSE_AZE
815       !Config Help  = The surface emissivity used for compution the LE emission
816       !Config         of the surface in a 0-dim version. Values range between
817       !Config         0.97 and 1.. The GCM uses 0.98.
818       !Config Units = [-]
819       CALL getin_p('CONDVEG_EMIS', emis_scal)
820    ENDIF
821
822    CALL getin_p('NEW_WATSTRESS',new_watstress)
823    IF(new_watstress) THEN
824       CALL getin_p('ALPHA_WATSTRESS',alpha_watstress)
825    ENDIF
826
827    !
828    !Config Key   = ROUGH_DYN
829    !Config Desc  = Account for a dynamic roughness height
830    !Config Def   = y
831    !Config if    = OK_SECHIBA
832    !Config Help  = If this flag is set to true (y) then the roughness
833    !Config         height is computed dynamically, varying with LAI
834    !Config Units = [FLAG]
835    CALL getin_p('ROUGH_DYN',rough_dyn)
836
837    IF ( rough_dyn ) THEN
838       !
839       !Config Key   = C1
840       !Config Desc  = Constant used in the formulation of the ratio of
841       !Config         the ratio of friction velocity to the wind speed
842       !Config         at the canopy top
843       !Config         See Ershadi et al. (2015) for more info
844       !Config Def   = 0.32
845       !Config If    = ROUGH_DYN
846       !Config Help  =
847       !Config Units = [-]
848       CALL getin_p('C1', c1)
849       !
850       !Config Key   = C2
851       !Config Desc  = Constant used in the formulation of the ratio of
852       !Config         the ratio of friction velocity to the wind speed
853       !Config         at the canopy top
854       !Config         See Ershadi et al. (2015) for more info
855       !Config Def   = 0.264
856       !Config If    = ROUGH_DYN
857       !Config Help  =
858       !Config Units = [-]
859       CALL getin_p('C2', c2)
860       !
861       !Config Key   = C3
862       !Config Desc  = Constant used in the formulation of the ratio of
863       !Config         the ratio of friction velocity to the wind speed
864       !Config         at the canopy top
865       !Config         See Ershadi et al. (2015) for more info
866       !Config Def   = 15.1
867       !Config If    = ROUGH_DYN
868       !Config Help  =
869       !Config Units = [-]
870       CALL getin_p('C3', c3)
871       !
872       !Config Key   = Cdrag_foliage
873       !Config Desc  = Drag coefficient of the foliage
874       !Config         See Ershadi et al. (2015) and Su et al. (2001)
875       !Config         for more info
876       !Config Def   = 0.2
877       !Config If    = ROUGH_DYN
878       !Config Help  =
879       !Config Units = [-]
880       CALL getin_p('CDRAG_FOLIAGE', Cdrag_foliage)
881       !
882       !Config Key   = Ct
883       !Config Desc  = Heat transfer coefficient of the leaf
884       !Config         See Ershadi et al. (2015) and Su et al. (2001)
885       !Config         for more info
886       !Config Def   = 0.01
887       !Config If    = ROUGH_DYN
888       !Config Help  =
889       !Config Units = [-]
890       CALL getin_p('CT', Ct)
891       !
892       !Config Key   = Prandtl
893       !Config Desc  = Prandtl number used in the calculation of Ct*
894       !Config         See Su et al. (2001) for more info
895       !Config Def   = 0.71
896       !Config If    = ROUGH_DYN
897       !Config Help  =
898       !Config Units = [-]
899       CALL getin_p('PRANDTL', Prandtl)
900    ENDIF
901    !-
902    ! Variables related to the explicitsnow module
903    !-
904    !Config Key = xansmax
905    !Config Desc = maximum snow albedo
906    !Config If = OK_SECHIBA
907    !Config Def = 0.85
908    !Config Help =
909    !Config Units = [-]
910    CALL getin_p('XANSMAX',xansmax)
911    !
912    !Config Key = xansmin
913    !Config Desc = minimum snow albedo
914    !Config If = OK_SECHIBA
915    !Config Def = 0.50
916    !Config Help =
917    !Config Units = [-]
918    CALL getin_p('XANSMIN',xansmin)
919    !
920    !Config Key = xans_todry
921    !Config Desc = albedo decay rate for the dry snow
922    !Config If = OK_SECHIBA
923    !Config Def = 0.008
924    !Config Help =
925    !Config Units = [S-1]
926    CALL getin_p('XANSDRY',xans_todry)
927    !
928    !Config Key = xans_t
929    !Config Desc = albedo decay rate for the wet snow
930    !Config If = OK_SECHIBA
931    !Config Def = 0.24
932    !Config Help =
933    !Config Units = [S-1]
934    CALL getin_p('XANS_T',xans_t)
935
936    !Config Key = xrhosmax
937    !Config Desc = maximum snow density
938    !Config If = OK_SECHIBA
939    !Config Def = 750
940    !Config Help =
941    !Config Units = [-]
942    CALL getin_p('XRHOSMAX',xrhosmax)
943    !
944    !Config Key = xwsnowholdmax1
945    !Config Desc = snow holding capacity 1
946    !Config If = OK_SECHIBA
947    !Config Def = 0.03
948    !Config Help =
949    !Config Units = [-]
950    CALL getin_p('XWSNOWHOLDMAX1',xwsnowholdmax1)
951    !
952    !Config Key = xwsnowholdmax2
953    !Config Desc = snow holding capacity 2
954    !Config If = OK_SECHIBA
955    !Config Def = 0.10
956    !Config Help =
957    !Config Units = [-]
958    CALL getin_p('XWSNOWHOLDMAX2',xwsnowholdmax2)
959    !
960    !Config Key = xsnowrhohold
961    !Config Desc = snow density
962    !Config If = OK_SECHIBA
963    !Config Def = 200.0
964    !Config Help =
965    !Config Units = [kg/m3]
966    CALL getin_p('XSNOWRHOHOLD',xsnowrhohold)
967    !
968    !Config Key = ZSNOWTHRMCOND1
969    !Config Desc = Thermal conductivity Coef 1
970    !Config If = OK_SECHIBA
971    !Config Def = 0.02
972    !Config Help =
973    !Config Units = [W/m/K]
974    CALL getin_p('ZSNOWTHRMCOND1',ZSNOWTHRMCOND1)
975    !
976    !Config Key = ZSNOWTHRMCOND2
977    !Config Desc = Thermal conductivity Coef 2
978    !Config If = OK_SECHIBA
979    !Config Def = 2.5E-6
980    !Config Help =
981    !Config Units = [W m5/(kg2 K)]
982    CALL getin_p('ZSNOWTHRMCOND2',ZSNOWTHRMCOND2)
983    !
984    !Config Key = ZSNOWTHRMCOND_AVAP
985    !Config Desc = Thermal conductivity Coef 1 water vapor
986    !Config If = OK_SECHIBA
987    !Config Def = -0.06023
988    !Config Help =
989    !Config Units = [W/m/K]
990    CALL getin_p('ZSNOWTHRMCOND_AVAP',ZSNOWTHRMCOND_AVAP)
991    !
992    !Config Key = ZSNOWTHRMCOND_BVAP
993    !Config Desc = Thermal conductivity Coef 2 water vapor
994    !Config If = OK_SECHIBA
995    !Config Def = -2.5425
996    !Config Help =
997    !Config Units = [W/m]
998    CALL getin_p('ZSNOWTHRMCOND_BVAP',ZSNOWTHRMCOND_BVAP)
999    !
1000    !Config Key = ZSNOWTHRMCOND_CVAP
1001    !Config Desc = Thermal conductivity Coef 3 water vapor
1002    !Config If = OK_SECHIBA
1003    !Config Def = -289.99
1004    !Config Help =
1005    !Config Units = [K]
1006    CALL getin_p('ZSNOWTHRMCOND_CVAP',ZSNOWTHRMCOND_CVAP)
1007
1008    !Snow compaction factors
1009    !Config Key = ZSNOWCMPCT_RHOD
1010    !Config Desc = Snow compaction coefficent
1011    !Config If = OK_SECHIBA
1012    !Config Def = 150.0
1013    !Config Help =
1014    !Config Units = [kg/m3]
1015    CALL getin_p('ZSNOWCMPCT_RHOD',ZSNOWCMPCT_RHOD)
1016
1017    !Config Key = ZSNOWCMPCT_ACM
1018    !Config Desc = Coefficent for the thermal conductivity
1019    !Config If = OK_SECHIBA
1020    !Config Def = 2.8e-6
1021    !Config Help =
1022    !Config Units = [1/s]
1023    CALL getin_p('ZSNOWCMPCT_ACM',ZSNOWCMPCT_ACM)
1024
1025    !Config Key = ZSNOWCMPCT_BCM
1026    !Config Desc = Coefficent for the thermal conductivity
1027    !Config If = OK_SECHIBA
1028    !Config Def = 0.04
1029    !Config Help =
1030    !Config Units = [1/K]
1031    CALL getin_p('ZSNOWCMPCT_BCM',ZSNOWCMPCT_BCM)
1032
1033    !Config Key = ZSNOWCMPCT_CCM
1034    !Config Desc = Coefficent for the thermal conductivity
1035    !Config If = OK_SECHIBA
1036    !Config Def = 460.
1037    !Config Help =
1038    !Config Units = [m3/kg]
1039    CALL getin_p('ZSNOWCMPCT_CCM',ZSNOWCMPCT_CCM)
1040
1041    !Config Key = ZSNOWCMPCT_V0
1042    !Config Desc = Vapor coefficent for the thermal conductivity
1043    !Config If = OK_SECHIBA
1044    !Config Def = 3.7e7
1045    !Config Help =
1046    !Config Units = [Pa/s]
1047    CALL getin_p('ZSNOWCMPCT_V0',ZSNOWCMPCT_V0)
1048
1049    !Config Key = ZSNOWCMPCT_VT
1050    !Config Desc = Vapor coefficent for the thermal conductivity
1051    !Config If = OK_SECHIBA
1052    !Config Def = 0.081
1053    !Config Help =
1054    !Config Units = [1/K]
1055    CALL getin_p('ZSNOWCMPCT_VT',ZSNOWCMPCT_VT)
1056
1057    !Config Key = ZSNOWCMPCT_VR
1058    !Config Desc = Vapor coefficent for the thermal conductivity
1059    !Config If = OK_SECHIBA
1060    !Config Def = 0.018
1061    !Config Help =
1062    !Config Units = [m3/kg]
1063    CALL getin_p('ZSNOWCMPCT_VR',ZSNOWCMPCT_VR)
1064
1065
1066    !Surface resistance
1067    !
1068    !Config Key = CB
1069    !Config Desc = Constant of the Louis scheme
1070    !Config If = OK_SECHIBA
1071    !Config Def = 5.0
1072    !Config Help =
1073    !Config Units = [-]
1074    CALL getin_p('CB',cb)
1075    !
1076    !Config Key = CC
1077    !Config Desc = Constant of the Louis scheme
1078    !Config If = OK_SECHIBA
1079    !Config Def = 5.0
1080    !Config Help =
1081    !Config Units = [-]
1082    CALL getin_p('CC',cc)
1083    !
1084    !Config Key = CD
1085    !Config Desc = Constant of the Louis scheme
1086    !Config If = OK_SECHIBA
1087    !Config Def = 5.0
1088    !Config Help =
1089    !Config Units = [-]
1090    CALL getin_p('CD',cd)
1091    !
1092    !Config Key = RAYT_CSTE
1093    !Config Desc = Constant in the computation of surface resistance 
1094    !Config If = OK_SECHIBA
1095    !Config Def = 125
1096    !Config Help =
1097    !Config Units = [W.m^{-2}]
1098    CALL getin_p('RAYT_CSTE',rayt_cste)
1099    !
1100    !Config Key = DEFC_PLUS
1101    !Config Desc = Constant in the computation of surface resistance 
1102    !Config If = OK_SECHIBA
1103    !Config Def = 23.E-3
1104    !Config Help =
1105    !Config Units = [K.W^{-1}]
1106    CALL getin_p('DEFC_PLUS',defc_plus)
1107    !
1108    !Config Key = DEFC_MULT
1109    !Config Desc = Constant in the computation of surface resistance 
1110    !Config If = OK_SECHIBA
1111    !Config Def = 1.5
1112    !Config Help =
1113    !Config Units = [K.W^{-1}]
1114    CALL getin_p('DEFC_MULT',defc_mult)
1115
1116    !+++CHECK+++
1117    ! We can add some consistency checks and possibly
1118    ! simplify the definition of the canopy layering
1119    ! (reduce the number of variables)
1120    !
1121    ! Configuration : The number of canopy levels to use in
1122    !                 the albedo and energy budget
1123    !
1124    !Config Key   = NLAI
1125    !Config Desc  = Number of photosyntheis canopy levels
1126    !Config If    = OK_SECHIBA
1127    !Config Def   = 10
1128    !Config Help  = The number of canopy levels to be used in
1129    !               per enegy budget canopy level photosynthesis
1130    !Config Units = [-]
1131    CALL getin_p("NLAI",nlai)
1132    WRITE(numout,'(I4,A)') nlai,' levels are used for each canopy ' &
1133         // 'level to calculate photosynthesis.'
1134   
1135    ! This is a variable that we'll pass around for convenience, in particular
1136    ! when going into a subroutine.
1137    nlevels_tot = nlevels * nlai
1138    DO ilevel=1,nlevels
1139       WRITE(numout,*) 'Albedo canopy level ',ilevel,&
1140            ' has a lower boundary at ',z_level(ilevel),' meters.'
1141    ENDDO
1142   
1143    ! Sets the levels for the energy calculations based on the
1144    ! ENERGY_CONTROL flag.
1145    IF( ENERGY_CONTROL .LE. 3 ) THEN        ! single layer
1146       
1147       jnlvls = 1
1148       jnlvls_under = 0
1149       jnlvls_canopy = 1
1150       jnlvls_over = 0   
1151       
1152    ELSEIF( ENERGY_CONTROL .EQ. 4 ) THEN   ! multi-layer
1153       
1154       jnlvls = 29
1155       jnlvls_under = 10
1156       jnlvls_canopy = 10
1157        jnlvls_over = 9
1158       
1159     ELSEIF( ENERGY_CONTROL .EQ. 5 ) THEN  ! run.def specified
1160        !Config Key   = JNLVLS
1161        !Config Desc  = number of photosyntheis canopy levels
1162        !Config If    = OK_SECHIBA
1163        !Config Def   = 29
1164        !Config Help  = The total number of layers in the
1165        !Config       = multi-layer energy budget calculations
1166        !Config Units = [-]
1167        jnlvls = 29
1168        CALL getin_p("JNLVLS",jnlvls)
1169       
1170        !Config Key   = JNLVLS_UNDER
1171        !Config Desc  = number of energy layers under the canopy
1172        !Config If    = OK_SECHIBA
1173        !Config Def   = 10
1174        !Config Help  = Number of energy layers under the canopy
1175        !Config       = used for multi-layer energy budget calculations
1176        !Config Units = [-]
1177        jnlvls_under = 10
1178        CALL getin_p("JNLVLS_UNDER",jnlvls_under)
1179
1180        !Config Key   = JNLVLS_CANOPY
1181        !Config Desc  = number of energy layers in the canopy
1182        !Config If    = OK_SECHIBA
1183        !Config Def   = 10
1184        !Config Help  = Number of energy, albedo and photosynthesis
1185        !Config       = layers in the canopy used for multi-layer
1186        !Confog       = energy budget calculations
1187        !Config Units = [-]
1188        jnlvls_canopy = 10
1189        CALL getin_p("JNLVLS_CANOPY",jnlvls_canopy)
1190
1191        !Config Key   = JNLVLS_OVER
1192        !Config Desc  = number of energy layers over the canopy
1193        !Config If    = OK_SECHIBA
1194        !Config Def   = 10
1195        !Config Help  = Number of energy layers over the canopy
1196        !Config       = used for multi-layer energy budget calculations
1197        !Config Units = [-]
1198        jnlvls_over = 9
1199        CALL getin_p("JNLVLS_OVER",jnlvls_over)
1200     ENDIF ! (ENERGY_CONTROL)
1201
1202     WRITE(numout,*)'The set JNLVLS levels', jnlvls, jnlvls_under,jnlvls_canopy,jnlvls_over 
1203
1204     !Config Key   = NLEV_TOP
1205     !Config Desc  = Maximum number of canopy levels that are
1206     !               used to construct the "top" layer of the
1207     !               canopy. The top layer is used in the
1208     !               calculation transpiration.
1209     !               Should not exceed nlai
1210     !Config If    = OK_SECHIBA
1211     !Config Def   = 10
1212     !Config Help  =
1213     !Config Units = [-]
1214     nlev_top = 10
1215     CALL getin_p('NLEV_TOP',nlev_top)       
1216     IF(nlev_top .GT. nlai) THEN
1217        nlev_top = nlai
1218        WRITE(numout,*) 'The numbers of levels in the "top" was '
1219        WRITE(numout,*) '  larger than the total number of levels'
1220        WRITE(numout,*) '  AUTO CORRECT: nlev_top now = ',nlev_top
1221     ENDIF
1222
1223     !+++++++++++
1224
1225     !
1226     !-
1227     ! diffuco
1228     !-
1229     !
1230     !Config Key   = LAIMAX
1231     !Config Desc  = Maximum LAI
1232     !Config If    = OK_SECHIBA
1233     !Config Def   =
1234     !Config Help  =
1235     !Config Units = [m^2/m^2]   
1236     CALL getin_p('LAIMAX',laimax)
1237     !
1238     !Config Key   = DEW_VEG_POLY_COEFF
1239     !Config Desc  = coefficients of the polynome of degree 5 for the dew
1240     !Config If    = OK_SECHIBA
1241     !Config Def   = 0.887773, 0.205673, 0.110112, 0.014843, 0.000824, 0.000017
1242     !Config Help  =
1243     !Config Units = [-]   
1244     CALL getin_p('DEW_VEG_POLY_COEFF',dew_veg_poly_coeff)
1245     !
1246     !Config Key   = DOWNREGULATION_CO2
1247     !Config Desc  = Activation of CO2 downregulation
1248     !Config If    = OK_SECHIBA
1249     !Config Def   = y
1250     !Config Help  =
1251     !Config Units = [FLAG]   
1252     CALL getin_p('DOWNREGULATION_CO2',downregulation_co2)
1253     !
1254     !Config Key   = DOWNREGULATION_CO2_BASELEVEL
1255     !Config Desc  = CO2 base level
1256     !Config If    = OK_SECHIBA
1257     !Config Def   = 380.
1258     !Config Help  =
1259     !Config Units = [ppm]   
1260     CALL getin_p('DOWNREGULATION_CO2_BASELEVEL',downregulation_co2_baselevel)
1261   
1262     !Config Key   = GB_REF
1263     !Config Desc  = Leaf bulk boundary layer resistance
1264     !Config If    =
1265     !Config Def   = 1./25.
1266     !Config Help  =
1267     !Config Units = [s m-1]   
1268     CALL getin_p('GB_REF',gb_ref)
1269
1270    !Config Key   = BULK_DEFAULT
1271    !Config Desc  = default bulk density
1272    !Config If    = OK_SECHIBA
1273    !Config Def   = 1000.0
1274    !Config Help  = The bulk density is the weight of soil in a
1275    !Config         given volume.  This default is used if no other value
1276    !Config         is found in the restart file.
1277    !Config Units = [kg/m3]   
1278    CALL getin_p('BULK_DEFAULT',bulk_default)
1279   
1280    !Config Key   = PH_DEFAULT
1281    !Config Desc  = default soil pH
1282    !Config If    = OK_SECHIBA
1283    !Config Def   = 5.5
1284    !Config Help  = Gives the value of the soil pH if a value is not
1285    !Config         found in the restart file.
1286    !Config Units = [-]   
1287    CALL getin_p('PH_DEFAULT',ph_default)
1288
1289    !
1290    !Config Key   = MIN_VEGFRAC
1291    !Config Desc  = Minimal fraction of mesh a vegetation type can occupy
1292    !Config If    = OK_SECHIBA
1293    !Config Def   = 0.001
1294    !Config Help  =
1295    !Config Units = [-] 
1296    CALL getin_p('MIN_VEGFRAC',min_vegfrac)
1297
1298    IF (min_vegfrac.LT.min_stomate) THEN
1299       
1300       ! In slowproc_adjust_delta_veget_max several series of IF-statements implicitly
1301       ! assume that min_vegfarc > min_stomate. If this is not the case strange things
1302       ! may happen. These strange things woul probably surface as a mass balance problem
1303       ! or a problem with conserving the surface areas of a pixel. It is a very easy
1304       ! inconsistency to catch at this point. It may be much harder to understand
1305       ! what is going wrong if the model is used with an inconstent min_vegfrac value.
1306       WRITE(numout,*) 'min_vegfrac and min_stomate ', min_vegfrac, min_stomate
1307       CALL ipslerr_p(3,'Check your run.def','min_vegfrac should be larger than min_stomate',&
1308            'If not several of the IF-statements in slowproc_adjust_delta_veget_max',&
1309            'may not work as intended')
1310
1311    END IF
1312    !
1313    !Config Key   = STEMPDIAG_BID
1314    !Config Desc  = only needed for an initial LAI if there is no restart file
1315    !Config If    = OK_SECHIBA
1316    !Config Def   = 280.
1317    !Config Help  =
1318    !Config Units = [K]
1319    CALL getin_p('STEMPDIAG_BID',stempdiag_bid)
1320 
1321    !
1322    !Config Key   = MIN_N
1323    !Config Desc  = Minimum allowable n_mineralisation in som_dynamics
1324    !Config If    = OK_STOMATE
1325    !Config Def   = 0.0001
1326    !Config Help  =
1327    !Config Units = gNH4-N/m^2/day
1328    CALL getin_p('MIN_N',min_n)   
1329    !
1330    !Config Key   = MAX_CN
1331    !Config Desc  = Maximum allowable ratio of som_input_total(:,icarbon)
1332    !               to som_input_total(:,initrogen).
1333    !Config If    = OK_STOMATE
1334    !Config Def   = 250
1335    !Config Help  =
1336    !Config Units = [-]
1337    CALL getin_p('MAX_CN',max_cn)
1338    !
1339    !Config Key   = SNC
1340    !Config Desc  = Structural nitrogen concentration
1341    !Config If    = OK_STOMATE
1342    !Config Def   = 0.004
1343    !Config Help  = Structural nitrogen [gN gC-1] based on C:N of dead wood
1344    !               (White et al., 2000) assuming carbon dry matter ratio of 0.5
1345    !Config Units = [gN gC-1]
1346    CALL getin_p('SNC',snc)
1347    !
1348    !Config Key   = SUGAR_LOAD_MIN
1349    !Config Desc  = Lower bound for sugar loading when used to regulate NUE
1350    !Config If    = OK_STOMATE
1351    !Config Def   = 0.0
1352    !Config Help  = Sugar loading is a ratio that will be contained between
1353    !               sugar_load_min and sugar_load_max. If it is 1 all is perfect
1354    !Config Units = [-]
1355    CALL getin_p('SUGAR_LOAD_MIN',sugar_load_min)
1356    !
1357    !Config Key   = SUGAR_LOAD_MAX
1358    !Config Desc  = Upper bound for sugar loading when used to regulate NUE
1359    !Config If    = OK_STOMATE
1360    !Config Def   = 1.0
1361    !Config Help  = Sugar loading is a ratio that will be contained between
1362    !               sugar_load_min and sugar_load_max. If it is 1 all is perfect
1363    !Config Units = [-]
1364    CALL getin_p('SUGAR_LOAD_MAX',sugar_load_max)
1365    !-
1366    !Config Key   = NCIRC
1367    !Config Desc  = Number of basal area classes in allocation scheme
1368    !               circ classes could be considered as cohorts within a stand
1369    !Config If    = OK_STOMATE, OK_SECHIBA
1370    !Config Def   = 2
1371    !Config Help  =
1372    !Config Units = [-]
1373    CALL getin_p('NCIRC',ncirc)
1374    !
1375    !Config Key   = SLOPE_RA
1376    !Config Desc  = Reduction factor to make resp_maint less temperature sensitive
1377    !Config If    = OK_STOMATE
1378    !Config Def   = 1.
1379    !Config Help  =
1380    !Config Units = [-]
1381    CALL getin_p('SLOPE_RA',slope_ra)
1382    !
1383    !Config Key   = LAIEFF_SOLAR_ANGLE
1384    !Config Desc  = The solar zenith angle for effective LAI
1385    !Config If    = OK_SECHIBA
1386    !Config Def   = 60
1387    !Config Help  = The solar zenith angle used in the calculation of the
1388    !               effective LAI. Pinty recommends a value of 60 degrees.
1389    !Config Units = [degrees]
1390    laieff_solar_angle=60.0_r_std
1391    CALL getin_p('LAIEFF_SOLAR_ANGLE',laieff_solar_angle) 
1392    WRITE(numout,*) 'Maximum number of optimization steps'//&
1393         'tried for albedo n-layer optimization [degrees]: ',laieff_solar_angle
1394    ! convert to radians
1395    laieff_solar_angle=laieff_solar_angle/180.0_r_std*pi 
1396    !
1397    !Config Key   = LAIEFF_ZERO_CUTOFF
1398    !Config Desc  = Cutoff for effective lai values
1399    !Config If    = OK_SECHIBA
1400    !Config Def   = 0.0000001
1401    !Config Help  = This is an arbitrary cutoff to make sure we don't pass
1402    !               zero values of crown diameter and trunk diameter
1403    !               to a subroutine that will choke on them
1404    !Config Units = [-]
1405    laieff_zero_cutoff=0.0000001_r_std
1406    CALL getin_p('LAIEFF_ZERO_CUTOFF',laieff_zero_cutoff) 
1407    WRITE(numout,*) 'A minimum threshold for trunk and crown '//&
1408         'diameters for numerical stability: ',laieff_zero_cutoff
1409    !
1410    !Config Key   = DIRECT_LIGHT_WEIGHT
1411    !Config Desc  = The weighting factor to weight different sources of light
1412    !Config If    = OK_SECHIBA
1413    !Config Def   = 0.5
1414    !Config Help  = The weighting factor used in the calculation of the
1415    !               albedo and canopy absorbed light from different sources.
1416    !               Currently LDMZ and forcing files don't have information
1417    !               on the amount of solar radiation hitting the canopy
1418    !               directly from the sun (collimated) or first reflected off
1419    !               clouds and aerosols.  But these values are calculated in
1420    !               the albedo routines.  We combine them into a single
1421    !               value with a simple weighting controlled by this variable.
1422    !               We select a value of 0.5 because we don't know what will
1423    !               be generally applicable.
1424    !Config Units = [degrees]
1425    direct_light_weight=0.5_r_std
1426    CALL getin_p('direct_light_weight',direct_light_weight) 
1427    WRITE(numout,*) 'Weighting fraction for calculating the total'//&
1428         'albedo and absorbed light from direct and diffuse sources [-]: ',direct_light_weight
1429
1430    !Config Key   = MAINT_RESP_CONTROL
1431    !Config Desc  = Sets the approach to calculate Rm
1432    !Config If    = OK_SECHIBA
1433    !Config Def   = 'cn'
1434    !Config Help  =  Choose between two options to calculate the maint respiration. If
1435    !                set to 'nitrogen' the plant nitrogen pools and temperature will
1436    !                drive maint_resp. If set to 'c/n', maint_resp will be adjusted for
1437    !                the expected c/n ratio of the plant biomass. Also the temperature
1438    !                control itself is calculated according to Krinner et al 2005 instead
1439    !                of Sitch et al 2003.
1440    !Config Units = [-]
1441    maint_resp_control='cn'
1442    CALL getin_p('MAINT_RESP_CONTROL',maint_resp_control) 
1443    WRITE(numout,*) 'Maintenance respiration is based on ',maint_resp_control
1444    !
1445    !Config Key   = CROWN_PACKING
1446    !Config Desc  = Packing efficiency of the crowns within the canopy space
1447    !Config If    = OK_SECHIBA
1448    !Config Def   = 1.
1449    !Config Help  = The crowns are assumed to be ellipsoids. The sum of all the
1450    !               individual crown volumes may exceed the entire canopys space
1451    !               given by the surface*height. If this happens the crown dimensions
1452    !               (the axes of the ellipsoids) will be recalculated. This
1453    !               calculation assume a packing efficiency. Note that close-packing
1454    !               of spheres has a maximum efficiency of 0.74 (listed as some mental
1455    !               guidance). Lower packing efficiencies will result in more gaps and
1456    !               has consequences for all variables that rely on veget.
1457    !Config Units = [-]
1458    CALL getin_p('CROWN_PACKING',crown_packing)
1459   
1460
1461  END SUBROUTINE config_sechiba_parameters
1462
1463
1464!! ================================================================================================================================
1465!! SUBROUTINE   : config_co2_parameters
1466!!
1467!>\BRIEF        This subroutine reads in the configuration file all the parameters when impose_param=TRUE
1468!!
1469!! DESCRIPTION  : None
1470!!
1471!! RECENT CHANGE(S): None
1472!!
1473!! MAIN OUTPUT VARIABLE(S): None
1474!!
1475!! REFERENCE(S) :
1476!!
1477!! FLOWCHART    :
1478!! \n
1479!_ ================================================================================================================================
1480
1481  SUBROUTINE config_co2_parameters
1482
1483    IMPLICIT NONE
1484
1485    !! 0. Variables and parameters declaration
1486
1487    !! 0.4 Local variables
1488
1489    !_ ================================================================================================================================
1490
1491    !
1492    !Config Key   = LAI_LEVEL_DEPTH
1493    !Config Desc  =
1494    !Config If    =
1495    !Config Def   = 0.15
1496    !Config Help  =
1497    !Config Units = [-] 
1498    CALL getin_p('LAI_LEVEL_DEPTH',lai_level_depth)
1499    !
1500    !Config Key   = Oi
1501    !Config Desc  = Intercellular oxygen partial pressure
1502    !Config If    =
1503    !Config Def   = 210000.
1504    !Config Help  = See Legend of Figure 6 of Yin et al. (2009)
1505    !Config Units = [ubar] 
1506    CALL getin_p('Oi',Oi)
1507
1508    !Config Key   = THRESHOLD_C13_ASSIM
1509    !Config Desc  = If assimilation falls below this threshold the delta_c13 is set to zero
1510    !Config If    = OK_C13
1511    !Config Def   = 0.01
1512    !Config Help  =
1513    !Config Units = [-] 
1514    CALL getin_p('THRESHOLD_C13_ASSIM',threshold_c13_assim)
1515    !
1516    !Config Key   = C13_A
1517    !Config Desc  = Coefficient for fractionation occurring due to diffusion in air
1518    !Config If    = OK_C13
1519    !Config Def   = 0.01
1520    !Config Help  =
1521    !Config Units = [-] 
1522    CALL getin_p('C13_A',c13_a)
1523    !
1524    !Config Key   = C13_B
1525    !Config Desc  = Coefficient for fractionation caused by carboxylation
1526    !Config If    = OK_C13
1527    !Config Def   = 0.01
1528    !Config Help  =
1529    !Config Units = [-] 
1530    CALL getin_p('C13_B',c13_b)
1531
1532  END SUBROUTINE config_co2_parameters
1533
1534
1535!! ================================================================================================================================
1536!! SUBROUTINE   : config_stomate_parameters
1537!!
1538!>\BRIEF        This subroutine reads in the configuration file all the parameters
1539!! needed when stomate is activated (ie : when OK_STOMATE is set to true).
1540!!
1541!! DESCRIPTION  : None
1542!!
1543!! RECENT CHANGE(S): None
1544!!
1545!! MAIN OUTPUT VARIABLE(S):
1546!!
1547!! REFERENCE(S) :
1548!!
1549!! FLOWCHART    :
1550!! \n
1551!_ ================================================================================================================================
1552
1553  SUBROUTINE config_stomate_parameters
1554
1555    IMPLICIT NONE
1556
1557    !! 0. Variables and parameters declaration
1558
1559    !! 0.4 Local variables
1560    LOGICAL                          :: l_error     !! Check errors in allocation
1561    INTEGER(i_std)                   :: ier         !! Check errors in allocation
1562
1563    !_ ================================================================================================================================
1564
1565     l_error = .FALSE.
1566
1567    !Config Key   = EXP_KF
1568    !Config Desc  = Exponential of the sensitivity of k_latosa to tree height
1569    !Config If    = OK_STOMATE
1570    !Config Def   = 1.0
1571    !Config Help  = Exponential used to tune the sensitivity of k_latosa to tree
1572    !               height.
1573    !Config Units = [-]   
1574    CALL getin_p('EXP_KF',exp_kf)
1575
1576    !-
1577    ! constraints_parameters
1578    !-
1579    !
1580    !Config Key   = TOO_LONG
1581    !Config Desc  = longest sustainable time without regeneration (vernalization)
1582    !Config If    = OK_STOMATE
1583    !Config Def   = 5.
1584    !Config Help  =
1585    !Config Units = [days]   
1586    CALL getin_p('TOO_LONG',too_long)
1587
1588    !-
1589    ! fire parameters
1590    !-
1591    !
1592    !Config Key   = TAU_FIRE
1593    !Config Desc  = Time scale for memory of the fire index (days). Validated for one year in the DGVM.
1594    !Config If    = OK_STOMATE
1595    !Config Def   = 30.
1596    !Config Help  =
1597    !Config Units = [days]   
1598    CALL getin_p('TAU_FIRE',tau_fire)
1599    !
1600    !Config Key   = LITTER_CRIT
1601    !Config Desc  = Critical litter quantity for fire
1602    !Config If    = OK_STOMATE
1603    !Config Def   = 200.
1604    !Config Help  =
1605    !Config Units = [gC/m^2] 
1606    CALL getin_p('LITTER_CRIT',litter_crit)
1607
1608    !Config Key   = FIRE_RESIST_LIGNIN
1609    !Config Desc  =
1610    !Config If    = OK_STOMATE
1611    !Config Def   = 0.5
1612    !Config Help  =
1613    !Config Units = [-] 
1614    CALL getin_p('FIRE_RESIST_LIGNIN',fire_resist_lignin)
1615
1616    !Config Key   = CO2FRAC
1617    !Config Desc  = What fraction of a burned plant compartment goes into the atmosphere
1618    !Config If    = OK_STOMATE
1619    !Config Def   = 0.95, 0.95, 0., 0.3, 0., 0., 0.95, 0.95
1620    !Config Help  =
1621    !Config Units = [-] 
1622    CALL getin_p('CO2FRAC',co2frac)
1623    !
1624    !Config Key   = BCFRAC_COEFF
1625    !Config Desc  =
1626    !Config If    = OK_STOMATE
1627    !Config Def   = 0.3, 1.3, 88.2
1628    !Config Help  =
1629    !Config Units = [-] 
1630    CALL getin_p('BCFRAC_COEFF',bcfrac_coeff)
1631    !
1632    !Config Key   = FIREFRAC_COEFF
1633    !Config Desc  =
1634    !Config If    = OK_STOMATE
1635    !Config Def   = 0.45, 0.8, 0.6, 0.13
1636    !Config Help  =
1637    !Config Units = [-]   
1638    CALL getin_p('FIREFRAC_COEFF',firefrac_coeff)
1639
1640    !Config Key   = REF_GREFF
1641    !Config Desc  = Asymptotic maximum mortality rate
1642    !Config If    = OK_STOMATE
1643    !Config Def   = 0.035
1644    !Config Help  = Set asymptotic maximum mortality rate from Sitch 2003
1645    !Config         (they use 0.01) (year^{-1})
1646    !Config Units = [1/year] 
1647    CALL getin_p('REF_GREFF',ref_greff)
1648    !-
1649    ! allocation parameters
1650    !-
1651    !Config Key   = RESERVE_TIME_TREE
1652    !Config Desc  = maximum time during which reserve is used (trees)
1653    !Config If    = OK_STOMATE
1654    !Config Def   = 30.
1655    !Config Help  =
1656    !Config Units = [days]   
1657    CALL getin_p('RESERVE_TIME_TREE',reserve_time_tree)
1658    !
1659    !Config Key   = RESERVE_TIME_GRASS
1660    !Config Desc  = maximum time during which reserve is used (grasses)
1661    !Config If    = OK_STOMATE
1662    !Config Def   = 20.
1663    !Config Help  =
1664    !Config Units = [days]   
1665    CALL getin_p('RESERVE_TIME_GRASS',reserve_time_grass)
1666
1667    !-
1668    ! data parameters
1669    !
1670    !Config Key   = PRECIP_CRIT
1671    !Config Desc  = minimum precip
1672    !Config If    = OK_STOMATE
1673    !Config Def   = 100.
1674    !Config Help  =
1675    !Config Units = [mm/year] 
1676    CALL getin_p('PRECIP_CRIT',precip_crit)
1677    !
1678    !Config Key   = GDD_CRIT_ESTAB
1679    !Config Desc  = minimum gdd for establishment of saplings
1680    !Config If    = OK_STOMATE
1681    !Config Def   = 150.
1682    !Config Help  =
1683    !Config Units = [-] 
1684    CALL getin_p('GDD_CRIT_ESTAB',gdd_crit_estab)
1685    !
1686    !Config Key   = FPC_CRIT
1687    !Config Desc  = critical fpc, needed for light competition and establishment
1688    !Config If    = OK_STOMATE
1689    !Config Def   = 0.95
1690    !Config Help  =
1691    !Config Units = [-] 
1692    CALL getin_p('FPC_CRIT',fpc_crit)
1693    !
1694    !Config Key   = ALPHA_GRASS
1695    !Config Desc  = sapling characteristics : alpha's
1696    !Config If    = OK_STOMATE
1697    !Config Def   = 0.5
1698    !Config Help  =
1699    !Config Units = [-]   
1700    CALL getin_p('ALPHA_GRASS',alpha_grass)
1701    !
1702    !Config Key   = ALPHA_TREE
1703    !Config Desc  = sapling characteristics : alpha's
1704    !Config If    = OK_STOMATE
1705    !Config Def   = 1.
1706    !Config Help  =
1707    !Config Units = [-]   
1708    CALL getin_p('ALPHA_TREE',alpha_tree)
1709
1710    !Config Key   = STRUCT_TO_LEAVES
1711    !Config Desc  = Fraction of structural carbon in grass and crops as a share of the leaf
1712    ! carbon pool. Only used for grasses and crops (thus NOT for trees)
1713    !Config If    = OK_STOMATE
1714    !Config Def   = 0.05
1715    !Config Help  = NOTE: the line using this variable is
1716    !Config         commented out in r5976, and thus this variable is
1717    !Config         not used.
1718    !Config Units = [-]   
1719    CALL getin_p(' STRUCT_TO_LEAVES',struct_to_leaves)
1720
1721    !Config Key   = LABILE_TO_TOTAL
1722    !Config Desc  = Fraction of the labile pool in trees, grasses and crops as a share of the
1723    ! total carbon pool (accounting for the N-content of the different tissues).
1724    !Config If    = OK_STOMATE
1725    !Config Def   = 0.01
1726    !Config Help  =
1727    !Config Units = [-]   
1728    CALL getin_p('LABILE_TO_TOTAL',labile_to_total)
1729
1730    !Config Key   = TAU_HUM_MONTH
1731    !Config Desc  = time scales for phenology and other processes
1732    !Config If    = OK_STOMATE
1733    !Config Def   = 20.
1734    !Config Help  =
1735    !Config Units = [days] 
1736    CALL getin_p('TAU_HUM_MONTH',tau_hum_month)
1737    !
1738    !Config Key   = TAU_HUM_WEEK
1739    !Config Desc  = time scales for phenology and other processes
1740    !Config If    = OK_STOMATE
1741    !Config Def   = 7.
1742    !Config Help  =
1743    !Config Units = [days]   
1744    CALL getin_p('TAU_HUM_WEEK',tau_hum_week)
1745    !
1746    !Config Key   = TAU_T2M_MONTH
1747    !Config Desc  = time scales for phenology and other processes
1748    !Config If    = OK_STOMATE
1749    !Config Def   = 20.
1750    !Config Help  =
1751    !Config Units = [days]     
1752    CALL getin_p('TAU_T2M_MONTH',tau_t2m_month)
1753    !
1754    !Config Key   = TAU_T2M_WEEK
1755    !Config Desc  = time scales for phenology and other processes
1756    !Config If    = OK_STOMATE
1757    !Config Def   = 7.
1758    !Config Help  =
1759    !Config Units = [days]   
1760    CALL getin_p('TAU_T2M_WEEK',tau_t2m_week)
1761    !
1762    !Config Key   = TAU_TSOIL_MONTH
1763    !Config Desc  = time scales for phenology and other processes
1764    !Config If    = OK_STOMATE
1765    !Config Def   = 20.
1766    !Config Help  =
1767    !Config Units = [days]     
1768    CALL getin_p('TAU_TSOIL_MONTH',tau_tsoil_month)
1769    !
1770    !Config Key   = TAU_GPP_WEEK
1771    !Config Desc  = time scales for phenology and other processes
1772    !Config If    = OK_STOMATE
1773    !Config Def   = 7.
1774    !Config Help  =
1775    !Config Units = [days]   
1776    CALL getin_p('TAU_GPP_WEEK',tau_gpp_week)
1777    !
1778    !Config Key   = TAU_GDD
1779    !Config Desc  = time scales for phenology and other processes
1780    !Config If    = OK_STOMATE
1781    !Config Def   = 40.
1782    !Config Help  =
1783    !Config Units = [days]   
1784    CALL getin_p('TAU_GDD',tau_gdd)
1785    !
1786    !Config Key   = TAU_NGD
1787    !Config Desc  = time scales for phenology and other processes
1788    !Config If    = OK_STOMATE
1789    !Config Def   = 50.
1790    !Config Help  =
1791    !Config Units = [days]   
1792    CALL getin_p('TAU_NGD',tau_ngd)
1793    !
1794    !Config Key   = COEFF_TAU_LONGTERM
1795    !Config Desc  = time scales for phenology and other processes
1796    !Config If    = OK_STOMATE
1797    !Config Def   = 3.
1798    !Config Help  =
1799    !Config Units = [days]   
1800    CALL getin_p('COEFF_TAU_LONGTERM',coeff_tau_longterm)
1801    !-
1802    !
1803    !Config Key   = BM_SAPL_CARBRES
1804    !Config Desc  =
1805    !Config If    = OK_STOMATE
1806    !Config Def   = 5.
1807    !Config Help  =
1808    !Config Units = [-]   
1809    CALL getin_p('BM_SAPL_CARBRES',bm_sapl_carbres)
1810    !
1811    !Config Key   = BM_SAPL_SAPABOVE
1812    !Config Desc  =
1813    !Config If    = OK_STOMATE
1814    !Config Def   = 0.5
1815    !Config Help  =
1816    !Config Units = [-]   
1817    CALL getin_p('BM_SAPL_SAPABOVE',bm_sapl_sapabove)
1818    !
1819    !Config Key   = BM_SAPL_HEARTABOVE
1820    !Config Desc  =
1821    !Config If    = OK_STOMATE
1822    !Config Def   = 2.
1823    !Config Help  =
1824    !Config Units = [-]   
1825    CALL getin_p('BM_SAPL_HEARTABOVE',bm_sapl_heartabove)
1826    !
1827    !Config Key   = BM_SAPL_HEARTBELOW
1828    !Config Desc  =
1829    !Config If    = OK_STOMATE
1830    !Config Def   = 2.
1831    !Config Help  =
1832    !Config Units = [-]   
1833    CALL getin_p('BM_SAPL_HEARTBELOW',bm_sapl_heartbelow)
1834
1835    !Config Key   = BM_SAPL_LABILE
1836    !Config Desc  =
1837    !Config If    = OK_STOMATE
1838    !Config Def   = 5.
1839    !Config Help  =
1840    !Config Units = [-]   
1841    CALL getin_p('BM_SAPL_LABILE',bm_sapl_labile)
1842
1843    !Config Key   = INIT_SAPL_MASS_LABILE
1844    !Config Desc  =
1845    !Config If    = OK_STOMATE
1846    !Config Def   = 5.
1847    !Config Help  =
1848    !Config Units = [-]   
1849    CALL getin_p('INIT_SAPL_MASS_LABILE',init_sapl_mass_labile)
1850
1851    !Config Key   = INIT_SAPL_MASS_LEAF_NAT
1852    !Config Desc  =
1853    !Config If    = OK_STOMATE
1854    !Config Def   = 0.1
1855    !Config Help  =
1856    !Config Units = [-]   
1857    CALL getin_p('INIT_SAPL_MASS_LEAF_NAT',init_sapl_mass_leaf_nat)
1858    !
1859    !Config Key   = INIT_SAPL_MASS_LEAF_AGRI
1860    !Config Desc  =
1861    !Config If    = OK_STOMATE
1862    !Config Def   = 1.
1863    !Config Help  =
1864    !Config Units = [-]   
1865    CALL getin_p('INIT_SAPL_MASS_LEAF_AGRI',init_sapl_mass_leaf_agri)
1866    !
1867    !Config Key   = INIT_SAPL_MASS_CARBRES
1868    !Config Desc  =
1869    !Config If    = OK_STOMATE
1870    !Config Def   = 5.
1871    !Config Help  =
1872    !Config Units = [-]   
1873    CALL getin_p('INIT_SAPL_MASS_CARBRES',init_sapl_mass_carbres)
1874    !
1875    !Config Key   = INIT_SAPL_MASS_ROOT
1876    !Config Desc  =
1877    !Config If    = OK_STOMATE
1878    !Config Def   = 0.1
1879    !Config Help  =
1880    !Config Units = [-]   
1881    CALL getin_p('INIT_SAPL_MASS_ROOT',init_sapl_mass_root)
1882    !
1883    !Config Key   = INIT_SAPL_MASS_FRUIT
1884    !Config Desc  =
1885    !Config If    = OK_STOMATE
1886    !Config Def   = 0.3
1887    !Config Help  =
1888    !Config Units = [-]   
1889    CALL getin_p('INIT_SAPL_MASS_FRUIT',init_sapl_mass_fruit)
1890    !
1891    !Config Key   = CN_SAPL_INIT
1892    !Config Desc  =
1893    !Config If    = OK_STOMATE
1894    !Config Def   = 0.5
1895    !Config Help  =
1896    !Config Units = [-]   
1897    CALL getin_p('CN_SAPL_INIT',cn_sapl_init)
1898    !
1899    !Config Key   = MIGRATE_TREE
1900    !Config Desc  =
1901    !Config If    = OK_STOMATE
1902    !Config Def   = 10000.
1903    !Config Help  =
1904    !Config Units = [m/year]   
1905    CALL getin_p('MIGRATE_TREE',migrate_tree)
1906    !
1907    !Config Key   = MIGRATE_GRASS
1908    !Config Desc  =
1909    !Config If    = OK_STOMATE
1910    !Config Def   = 10000.
1911    !Config Help  =
1912    !Config Units = [m/year]   
1913    CALL getin_p('MIGRATE_GRASS',migrate_grass)
1914    !
1915    !Config Key   = LAI_INITMIN_TREE
1916    !Config Desc  =
1917    !Config If    = OK_STOMATE
1918    !Config Def   = 0.3
1919    !Config Help  =
1920    !Config Units = [m^2/m^2] 
1921    CALL getin_p('LAI_INITMIN_TREE',lai_initmin_tree)
1922    !
1923    !Config Key   = LAI_INITMIN_GRASS
1924    !Config Desc  =
1925    !Config If    = OK_STOMATE
1926    !Config Def   = 0.1
1927    !Config Help  =
1928    !Config Units = [m^2/m^2]   
1929    CALL getin_p('LAI_INITMIN_GRASS',lai_initmin_grass)
1930    !
1931    !Config Key   = DIA_COEFF
1932    !Config Desc  =
1933    !Config If    = OK_STOMATE
1934    !Config Def   = 4., 0.5
1935    !Config Help  =
1936    !Config Units = [-]   
1937    CALL getin_p('DIA_COEFF',dia_coeff)
1938    !
1939    !Config Key   = MAXDIA_COEFF
1940    !Config Desc  =
1941    !Config If    = OK_STOMATE
1942    !Config Def   = 100., 0.01
1943    !Config Help  =
1944    !Config Units = [-]   
1945    CALL getin_p('MAXDIA_COEFF',maxdia_coeff)
1946    !
1947    !Config Key   = BM_SAPL_LEAF
1948    !Config Desc  =
1949    !Config If    = OK_STOMATE
1950    !Config Def   = 4., 4., 0.8, 5.
1951    !Config Help  =
1952    !Config Units = [-] 
1953    CALL getin_p('BM_SAPL_LEAF',bm_sapl_leaf)
1954
1955    !-
1956    ! litter parameters
1957    !-
1958
1959    !Config Key   = CN
1960    !Config Desc  = C/N ratio
1961    !Config If    = OK_STOMATE
1962    !Config Def   = 40., 40., 40., 40., 40., 40., 40., 40.
1963    !Config Help  =
1964    !Config Units = [-] 
1965    CALL getin_p('CN',CN_fix)
1966
1967    !Config Key   = FRAC_SOIL_STRUCT_SUA
1968    !Config Desc  = frac_soil(istructural,isurface,iabove)
1969    !Config If    = OK_STOMATE
1970    !Config Def   = 0.55
1971    !Config Help  =
1972    !Config Units = [-]
1973    CALL getin_p('FRAC_SOIL_STRUCT_SUA',frac_soil_struct_sua)
1974
1975    !Config Key   = FRAC_SOIL_METAB_SUA
1976    !Config Desc  = frac_soil(imetabolic,isurface,iabove)
1977    !Config If    = OK_STOMATE
1978    !Config Def   = 0.4
1979    !Config Help  =
1980    !Config Units = [-]   
1981    CALL getin_p('FRAC_SOIL_METAB_SUA',frac_soil_metab_sua)
1982
1983    !Config Key   = TURN_METABOLIC
1984    !Config Desc  =
1985    !Config If    = OK_STOMATE
1986    !Config Def   = 0.066
1987    !Config Help  =
1988    !Config Units = [days]
1989    CALL getin_p('TURN_METABOLIC',turn_metabolic)
1990
1991    !Config Key   = TURN_STRUCT
1992    !Config Desc  =
1993    !Config If    = OK_STOMATE
1994    !Config Def   = 0.245
1995    !Config Help  =
1996    !Config Units = [days]
1997    CALL getin_p('TURN_STRUCT',turn_struct)
1998
1999    !Config Key   = TURN_WOODY
2000    !Config Desc  =
2001    !Config If    = OK_STOMATE
2002    !Config Def   = 0.75
2003    !Config Help  =
2004    !Config Units = [days]
2005    CALL getin_p('TURN_WOODY',turn_woody)
2006
2007    !Config Key   = METABOLIC_REF_FRAC
2008    !Config Desc  =
2009    !Config If    = OK_STOMATE
2010    !Config Def   = 0.85 
2011    !Config Help  =
2012    !Config Units = [-]
2013    CALL getin_p('METABOLIC_REF_FRAC',metabolic_ref_frac)
2014
2015    !Config Key   = Z_DECOMP
2016    !Config Desc  = scaling depth for soil activity
2017    !Config If    = OK_STOMATE
2018    !Config Def   = 0.2
2019    !Config Help  =
2020    !Config Units = [m]   
2021    CALL getin_p('Z_DECOMP',z_decomp)
2022
2023    !Config Key   = FRAC_SOIL_STRUCT_A
2024    !Config Desc  = frac_soil(istructural,iactive,ibelow)
2025    !Config If    = OK_STOMATE
2026    !Config Def   = 0.45
2027    !Config Help  =
2028    !Config Units = [-]
2029    CALL getin_p('FRAC_SOIL_STRUCT_AB',frac_soil_struct_ab)
2030    !
2031    !Config Key   = FRAC_SOIL_STRUCT_SA
2032    !Config Desc  = frac_soil(istructural,islow,iabove)
2033    !Config If    = OK_STOMATE
2034    !Config Def   = 0.7 
2035    !Config Help  =
2036    !Config Units = [-]   
2037    CALL getin_p('FRAC_SOIL_STRUCT_SA',frac_soil_struct_sa)
2038    !
2039    !Config Key   = FRAC_SOIL_STRUCT_SB
2040    !Config Desc  = frac_soil(istructural,islow,ibelow)
2041    !Config If    = OK_STOMATE
2042    !Config Def   = 0.7 
2043    !Config Help  =
2044    !Config Units = [-]   
2045    CALL getin_p('FRAC_SOIL_STRUCT_SB',frac_soil_struct_sb)
2046    !
2047    !Config Key   = FRAC_SOIL_METAB_AB
2048    !Config Desc  = frac_soil(imetabolic,iactive,ibelow)
2049    !Config If    = OK_STOMATE
2050    !Config Def   = 0.45 
2051    !Config Help  =
2052    !Config Units = [-]   
2053    CALL getin_p('FRAC_SOIL_METAB_AB',frac_soil_metab_ab)
2054    !
2055    !
2056    !Config Key   = METABOLIC_LN_RATIO
2057    !Config Desc  =
2058    !Config If    = OK_STOMATE
2059    !Config Def   = 0.018 
2060    !Config Help  =
2061    !Config Units = [-]   
2062    CALL getin_p('METABOLIC_LN_RATIO',metabolic_LN_ratio) 
2063    !
2064    !Config Key   = SOIL_Q10
2065    !Config Desc  =
2066    !Config If    = OK_STOMATE
2067    !Config Def   = 0.69 (=ln2)
2068    !Config Help  =
2069    !Config Units = [-]
2070    CALL getin_p('SOIL_Q10',soil_Q10)
2071    !
2072    !Config Key   = SOIL_Q10_UPTAKE
2073    !Config Desc  =
2074    !Config If    = OK_STOMATE
2075    !Config Def   = 0.69 (=ln2)
2076    !Config Help  =
2077    !Config Units = [-]
2078    CALL getin_p('SOIL_Q10_UPTAKE',soil_Q10_uptake)
2079    !
2080    !Config Key   = TSOIL_REF
2081    !Config Desc  =
2082    !Config If    = OK_STOMATE
2083    !Config Def   = 30.
2084    !Config Help  =
2085    !Config Units = [C]   
2086    CALL getin_p('TSOIL_REF',tsoil_ref)
2087    !
2088    !Config Key   = LITTER_STRUCT_COEF
2089    !Config Desc  =
2090    !Config If    = OK_STOMATE
2091    !Config Def   = 3.
2092    !Config Help  =
2093    !Config Units = [-]   
2094    CALL getin_p('LITTER_STRUCT_COEF',litter_struct_coef)
2095    !
2096    !Config Key   = MOIST_COEFF
2097    !Config Desc  =
2098    !Config If    = OK_STOMATE
2099    !Config Def   = 1.1, 2.4, 0.29
2100    !Config Help  =
2101    !Config Units = [-]   
2102    CALL getin_p('MOIST_COEFF',moist_coeff)
2103    !
2104    !Config Key   = MOISTCONT_MIN
2105    !Config Desc  = minimum soil wetness to limit the heterotrophic respiration
2106    !Config If    = OK_STOMATE
2107    !Config Def   = 0.25
2108    !Config Help  =
2109    !Config Units = [-]
2110    CALL getin_p('MOISTCONT_MIN',moistcont_min)
2111
2112    !Config Key   = FUNGIVORES
2113    !Config Desc  = N released for plant uptake due to fungivore consumption
2114    !Config If    = OK_STOMATE
2115    !Config Def   = 0.3
2116    !Config Help  =
2117    !Config Units = [-]
2118    CALL getin_p('FUNGIVORES',fungivores)
2119    !
2120    !Config Key   = FRAC_WOODY
2121    !Config Desc  = Coefficient for determining the lignin fraction of woody litter
2122    !Config If    = OK_STOMATE
2123    !Config Def   = 0.65
2124    !Config Help  =
2125    !Config Units = [-]
2126    CALL getin_p('FRAC_WOODY',frac_woody)
2127     
2128
2129    !-
2130    ! lpj parameters
2131    !-
2132    !
2133    !Config Key   = FRAC_TURNOVER_DAILY
2134    !Config Desc  =
2135    !Config If    = OK_STOMATE
2136    !Config Def   = 0.55
2137    !Config Help  =
2138    !Config Units = [-]
2139    CALL getin_p('FRAC_TURNOVER_DAILY',frac_turnover_daily)   
2140
2141    !-
2142    ! npp parameters
2143    !-
2144    !
2145    !Config Key   = TAX_MAX
2146    !Config Desc  = maximum fraction of allocatable biomass used for maintenance respiration
2147    !Config If    = OK_STOMATE
2148    !Config Def   = 0.8
2149    !Config Help  =
2150    !Config Units = [-]   
2151    CALL getin_p('TAX_MAX',tax_max) 
2152
2153    !-
2154    ! phenology parameters
2155    !-
2156    !Config Key   = MIN_GROWTHINIT_TIME
2157    !Config Desc  = minimum time since last beginning of a growing season
2158    !Config If    = OK_STOMATE
2159    !Config Def   = 300.
2160    !Config Help  =
2161    !Config Units = [days] 
2162    CALL getin_p('MIN_GROWTHINIT_TIME',min_growthinit_time)
2163    !
2164    !Config Key   = RELSOILMOIST_ALWAYS_TREE
2165    !Config Desc  = relative soil moisture availability above which moisture tendency doesn't matter
2166    !Config If    = OK_STOMATE
2167    !Config Def   = 1.0
2168    !Config Help  =
2169    !Config Units = [-]   
2170    CALL getin_p('RELSOILMOIST_ALWAYS_TREE',relsoilmoist_always_tree)
2171    !
2172    !Config Key   = RELSOILMOIST_ALWAYS_GRASS
2173    !Config Desc  = moisture availability above which moisture tendency doesn't matter
2174    !Config If    = OK_STOMATE
2175    !Config Def   = 0.6
2176    !Config Help  =
2177    !Config Units = [-]   
2178    CALL getin_p('RELSOILMOIST_ALWAYS_GRASS',relsoilmoist_always_grass)
2179    !
2180    !Config Key   = T_ALWAYS_ADD
2181    !Config Desc  = monthly temp. above which temp. tendency doesn't matter
2182    !Config If    = OK_STOMATE
2183    !Config Def   = 10.
2184    !Config Help  =
2185    !Config Units = [C]   
2186    CALL getin_p('T_ALWAYS_ADD',t_always_add)
2187    !
2188    !
2189    !Config Key   = GDDNCD_REF
2190    !Config Desc  =
2191    !Config If    = OK_STOMATE
2192    !Config Def   = 603.
2193    !Config Help  =
2194    !Config Units = [-]   
2195    CALL getin_p('GDDNCD_REF',gddncd_ref)
2196    !
2197    !Config Key   = GDDNCD_CURVE
2198    !Config Desc  =
2199    !Config If    = OK_STOMATE
2200    !Config Def   = 0.0091
2201    !Config Help  =
2202    !Config Units = [-] 
2203    CALL getin_p('GDDNCD_CURVE',gddncd_curve)
2204    !
2205    !Config Key   = GDDNCD_OFFSET
2206    !Config Desc  =
2207    !Config If    = OK_STOMATE
2208    !Config Def   = 64.
2209    !Config Help  =
2210    !Config Units = [-] 
2211    CALL getin_p('GDDNCD_OFFSET',gddncd_offset)
2212    !-
2213    ! respiration parameters
2214    !-
2215    !
2216    !Config Key   = MAINT_RESP_MIN_VMAX
2217    !Config Desc  =
2218    !Config If    = OK_STOMATE
2219    !Config Def   = 0.3
2220    !Config Help  =
2221    !Config Units = [-] 
2222    CALL getin_p('MAINT_RESP_MIN_VMAX',maint_resp_min_vmax) 
2223    !
2224    !Config Key   = MAINT_RESP_COEFF
2225    !Config Desc  =
2226    !Config If    = OK_STOMATE
2227    !Config Def   = 1.4
2228    !Config Help  =
2229    !Config Units = [-]
2230    CALL getin_p('MAINT_RESP_COEFF',maint_resp_coeff)
2231
2232    !-
2233    ! soilcarbon parameters
2234    !-
2235    !Config Key   = ACTIVE_TO_PASS_CLAY_FRAC
2236    !Config Desc  =
2237    !Config if    = OK_STOMATE
2238    !Config Def   = 0.68 
2239    !Config Help  =
2240    !Config Units = [-]
2241    CALL getin_p('ACTIVE_TO_PASS_CLAY_FRAC',active_to_pass_clay_frac)
2242
2243
2244    !Config Key   = ACTIVE_TO_PASS_REF_FRAC
2245    !Config Desc  = Fixed fraction from Active to Passive pool
2246    !Config if    = OK_STOMATE
2247    !Config Def   = 0.003
2248    !Config Help  =
2249    !Config Units = [-]
2250    CALL getin_p('ACTIVE_TO_PASS_REF_FRAC',active_to_pass_ref_frac) 
2251    !
2252    !Config Key   = SURF_TO_SLOW_REF_FRAC
2253    !Config Desc  = Fixed fraction from Surface to Slow pool
2254    !Config if    = OK_STOMATE
2255    !Config Def   = 0.4
2256    !Config Help  =
2257    !Config Units = [-]
2258    CALL getin_p('SURF_TO_SLOW_REF_FRAC',surf_to_slow_ref_frac) 
2259    !
2260    !Config Key   = ACTIVE_TO_CO2_REF_FRAC
2261    !Config Desc  = Fixed fraction from Active pool to CO2 emission
2262    !Config if    = OK_STOMATE
2263    !Config Def   = 0.85
2264    !Config Help  =
2265    !Config Units = [-]
2266    CALL getin_p('ACTIVE_TO_CO2_REF_FRAC',active_to_co2_ref_frac) 
2267    !
2268    !Config Key   = SLOW_TO_PASS_REF_FRAC
2269    !Config Desc  = Fixed fraction from Slow to Passive pool
2270    !Config if    = OK_STOMATE
2271    !Config Def   = 0.003
2272    !Config Help  =
2273    !Config Units = [-]
2274    CALL getin_p('SLOW_TO_PASS_REF_FRAC',slow_to_pass_ref_frac) 
2275    !
2276    !Config Key   = SLOW_TO_CO2_REF_FRAC
2277    !Config Desc  = Fixed fraction from Slow pool to CO2 emission
2278    !Config if    = OK_STOMATE
2279    !Config Def   = 0.55
2280    !Config Help  =
2281    !Config Units = [-]
2282    CALL getin_p('SLOW_TO_CO2_REF_FRAC',slow_to_co2_ref_frac) 
2283    !
2284    !Config Key   = PASS_TO_ACTIVE_REF_FRAC
2285    !Config Desc  = Fixed fraction from Passive to Active pool
2286    !Config if    = OK_STOMATE
2287    !Config Def   = 0.45
2288    !Config Help  =
2289    !Config Units = [-]
2290    CALL getin_p('PASS_TO_ACTIVE_REF_FRAC',pass_to_active_ref_frac) 
2291    !
2292    !Config Key   = PASS_TO_SLOW_REF_FRAC
2293    !Config Desc  = Fixed fraction from Passive to Slow pool
2294    !Config if    = OK_STOMATE
2295    !Config Def   = 0.
2296    !Config Help  =
2297    !Config Units = [-]
2298    CALL getin_p('PASS_TO_SLOW_REF_FRAC',pass_to_slow_ref_frac) 
2299    !
2300    !Config Key   = ACTIVE_TO_CO2_CLAY_SILT_FRAC
2301    !Config Desc  = Clay-Silt-dependant fraction from Active pool to CO2 emission
2302    !Config if    = OK_STOMATE
2303    !Config Def   = 0.68
2304    !Config Help  =
2305    !Config Units = [-]
2306    CALL getin_p('ACTIVE_TO_CO2_CLAY_SILT_FRAC',active_to_co2_clay_silt_frac) 
2307    !
2308    !Config Key   = SLOW_TO_PASS_CLAY_FRAC
2309    !Config Desc  = Clay-dependant fraction from Slow to Passive pool
2310    !Config if    = OK_STOMATE
2311    !Config Def   = -0.009
2312    !Config Help  =
2313    !Config Units = [-]
2314    CALL getin_p('SLOW_TO_PASS_CLAY_FRAC',slow_to_pass_clay_frac) 
2315    !
2316    !Config Key   = SOM_TURN_IACTIVE
2317    !Config Desc  = turnover in active pool
2318    !Config if    = OK_STOMATE
2319    !Config Def   = 7.3
2320    !Config Help  =
2321    !Config Units =  [year-1]
2322    CALL getin_p('SOM_TURN_IACTIVE',som_turn_iactive)
2323    !
2324    !Config Key   = SOM_TURN_ISLOW
2325    !Config Desc  = turnover in slow pool
2326    !Config if    = OK_STOMATE
2327    !Config Def   = 0.2
2328    !Config Help  =
2329    !Config Units = [year-1]
2330    CALL getin_p('SOM_TURN_ISLOW',som_turn_islow)
2331    !
2332    !Config Key   = SOM_TURN_IPASSIVE
2333    !Config Desc  = turnover in passive pool
2334    !Config if    = OK_STOMATE
2335    !Config Def   = 0.0045
2336    !Config Help  =
2337    !Config Units = [year-1]
2338    CALL getin_p('SOM_TURN_IPASSIVE',som_turn_ipassive)
2339    !
2340    !Config Key   = FSLOW
2341    !Config Desc  = converting factor from active to slow pool turnover
2342    !Config if    = OK_STOMATE and OK_SOIL_CARBON_DISCRETIZATION
2343    !Config Def   = 37
2344    !Config Help  =
2345    !Config Units = [-]
2346    CALL getin_p('FSLOW',fslow)
2347    !
2348    !Config Key   = FPASSIVE
2349    !Config Desc  = converting factor from active to slow pool turnover
2350    !Config if    = OK_STOMATE and OK_SOIL_CARBON_DISCRETIZATION
2351    !Config Def   = 1617.45
2352    !Config Help  =
2353    !Config Units = [-]
2354    CALL getin_p('FPASSIVE',fpassive)
2355    !
2356    !Config Key   = STOMATE_TAU
2357    !Config Desc  = turnover of the active pool
2358    !Config if    = OK_STOMATE and OK_SOIL_CARBON_DISCRETIZATION
2359    !Config Def   = 4.699E6
2360    !Config Help  =
2361    !Config Units = [seconds]
2362    CALL getin_p('STOMATE_TAU',stomate_tau)
2363    !
2364    !Config Key   = DEPTH_MODIFIER
2365    !Config Desc  = turnover rate modifier depending on depth
2366    !Config if    = OK_STOMATE and OK_SOIL_CARBON_DISCRETIZATION
2367    !Config Def   = 1.E6
2368    !Config Help  =
2369    !Config Units = [-]
2370    CALL getin_p('DEPTH_MODIFIER',depth_modifier)
2371    !
2372    !Config Key   = SOM_TURN_IACTIVE_CLAY_FRAC
2373    !Config Desc  = clay-dependant parameter impacting on turnover rate of active pool - Tm parameter of Parton et al. 1993 (-)
2374    !Config if    = OK_STOMATE
2375    !Config Def   = 0.75
2376    !Config Help  =
2377    !Config Units = [-]
2378    CALL getin_p('SOM_TURN_IACTIVE_CLAY_FRAC',som_turn_iactive_clay_frac)
2379    !
2380    !Config Key   = SOM_INIT_ACTIVE
2381    !Config Desc  = Initial active SOM carbon
2382    !Config if    = OK_STOMATE
2383    !Config Def   = 1000
2384    !Config Help  = Putting some carbon in the soil speeds-up the spinup. As
2385    !               this carbon comes with some soil nitrogen it also helps
2386    !               to grow vegetation when starting from scratch
2387    !Config Units = [g m-2]
2388    CALL getin_p('SOM_INIT_ACTIVE',som_init_active)
2389    !
2390    !Config Key   = SOM_INIT_SLOW
2391    !Config Desc  = Initial slow SOM carbon
2392    !Config if    = OK_STOMATE
2393    !Config Def   = 3000
2394    !Config Help  = Putting some carbon in the soil speeds-up the spinup. As
2395    !               this carbon comes with some soil nitrogen it also helps
2396    !               to grow vegetation when starting from scratch
2397    !Config Units = [g m-2]
2398    CALL getin_p('SOM_INIT_SLOW',som_init_slow)
2399    !
2400    !Config Key   = SOM_INIT_PASSIVE
2401    !Config Desc  = Initial passive SOM carbon
2402    !Config if    = OK_STOMATE
2403    !Config Def   = 3000
2404    !Config Help  = Putting some carbon in the soil speeds-up the spinup. As
2405    !               this carbon comes with some soil nitrogen it also helps
2406    !               to grow vegetation when starting from scratch
2407    !Config Units = [g m-2]
2408    CALL getin_p('SOM_INIT_PASSIVE',som_init_passive)
2409    !
2410    !Config Key   = SOM_INIT_SURFACE
2411    !Config Desc  = Initial surface SOM carbon
2412    !Config if    = OK_STOMATE
2413    !Config Def   = 1000
2414    !Config Help  =
2415    !Config Units = [g m-2]
2416    CALL getin_p('SOM_INIT_SURFACE',som_init_surface)
2417    !
2418    !Config Key   = CN_TARGET_IACTIVE_REF
2419    !Config Desc  = CN target ratio of active pool for soil min N = 0
2420    !Config if    = OK_STOMATE
2421    !Config Def   = 15.
2422    !Config Help  = Putting some carbon in the soil speeds-up the spinup. As
2423    !               this carbon comes with some soil nitrogen it also helps
2424    !               to grow vegetation when starting from scratch
2425    !Config Units = [-]
2426    CALL getin_p('CN_TARGET_IACTIVE_REF',CN_target_iactive_ref)
2427    !
2428    !Config Key   = CN_TARGET_ISLOW_REF
2429    !Config Desc  = CN target ratio of slow pool for soil min N = 0
2430    !Config if    = OK_STOMATE
2431    !Config Def   = 20.
2432    !Config Help  =
2433    !Config Units = [-]
2434    CALL getin_p('CN_TARGET_ISLOW_REF',CN_target_islow_ref)
2435    !
2436    !Config Key   = CN_TARGET_IPASSIVE_REF
2437    !Config Desc  = CN target ratio of passive pool for soil min N = 0
2438    !Config if    = OK_STOMATE
2439    !Config Def   = 10.
2440    !Config Help  =
2441    !Config Units = [-]
2442    CALL getin_p('CN_TARGET_IPASSIVE_REF',CN_target_ipassive_ref)
2443    !
2444    !Config Key   = CN_TARGET_IACTIVE_NMIN
2445    !Config Desc  = CN target ratio change per mineral N unit (g m-2) for active pool
2446    !Config if    = OK_STOMATE
2447    !Config Def   = -6.
2448    !Config Help  =
2449    !Config Units = [(g m-2)-1]
2450    CALL getin_p('CN_TARGET_IACTIVE_NMIN',CN_target_iactive_Nmin)
2451    !
2452    !Config Key   = CN_TARGET_ISLOW_NMIN
2453    !Config Desc  = CN target ratio change per mineral N unit (g m-2) for slow pool
2454    !Config if    = OK_STOMATE
2455    !Config Def   = -4.
2456    !Config Help  =
2457    !Config Units = [(g m-2)-1]
2458    CALL getin_p('CN_TARGET_ISLOW_NMIN',CN_target_islow_Nmin)
2459    !
2460    !Config Key   = CN_TARGET_IPASSIVE_NMIN
2461    !Config Desc  = CN target ratio change per mineral N unit (g m-2) for passive pool
2462    !Config if    = OK_STOMATE
2463    !Config Def   = -1.5
2464    !Config Help  =
2465    !Config Units = [(g m-2)-1]
2466    CALL getin_p('CN_TARGET_IPASSIVE_NMIN',CN_target_ipassive_Nmin)
2467
2468    ! soil nitrogen dynamic parameters
2469    !-
2470    !Config Key   = H_SAXTON
2471    !Config Desc  = Coefficient h for computing soil moisture content at saturation
2472    !Config If    = OK_STOMATE
2473    !Config Def   = 0.332
2474    !Config Help  = Used for soil porosity when calculating the maximum
2475    !Config         pore volume of the soil in to calculate the
2476    !Config         volumetric fraction of aneorobic microsites (ANVF) in
2477    !Config         the soil, which gives an idea of how much aneorobic
2478    !Config         bacteria can be transforming soil nitrogen.
2479    !Config Units = [m^3/m^3] 
2480    CALL getin_p('H_SAXTON',h_saxton)
2481    !-
2482    !Config Key   = J_SAXTON
2483    !Config Desc  = Coefficient j for computing soil moisture content at saturation
2484    !Config If    = OK_STOMATE
2485    !Config Def   = -7.251*1e-4
2486    !Config Help  = Used for soil porosity when calculating the maximum
2487    !Config         pore volume of the soil in to calculate the
2488    !Config         volumetric fraction of aneorobic microsites (ANVF) in
2489    !Config         the soil, which gives an idea of how much aneorobic
2490    !Config         bacteria can be transforming soil nitrogen
2491    !Config Units = [m^3/m^3] 
2492    CALL getin_p('J_SAXTON',j_saxton)
2493    !-
2494    !Config Key   = K_SAXTON
2495    !Config Desc  = Coefficient k for computing soil moisture content at saturation
2496    !Config If    = OK_STOMATE
2497    !Config Def   = O.1276
2498    !Config Help  = Used for soil porosity when calculating the maximum
2499    !Config         pore volume of the soil in to calculate the
2500    !Config         volumetric fraction of aneorobic microsites (ANVF) in
2501    !Config         the soil, which gives an idea of how much aneorobic
2502    !Config         bacteria can be transforming soil nitrogen
2503    !Config Units = [m^3/m^3] 
2504    CALL getin_p('K_SAXTON',k_saxton)
2505    !-
2506    !Config Key   = DIFFUSIONO2_POWER_1
2507    !Config Desc  = Power used in the equation defining the diffusion of oxygen in soil
2508    !Config If    = OK_STOMATE
2509    !Config Def   = 3.33
2510    !Config Help  = Diffusion of oxygen determines how well anerobic bacteria
2511    !Config         bacteria can live in the soil, which impacts the nitrogen
2512    !Config         dynamics.  This is taken from the literature.
2513    !Config Units = [-] 
2514    CALL getin_p('DIFFUSIONO2_POWER_1',diffusionO2_power_1)
2515    !-
2516    !Config Key   = DIFFUSIONO2_POWER_2
2517    !Config Desc  = Power used in the equation defining the diffusion of oxygen in soil
2518    !Config If    = OK_STOMATE
2519    !Config Def   = 2.0
2520    !Config Help  = Diffusion of oxygen determines how well anerobic bacteria
2521    !Config         bacteria can live in the soil, which impacts the nitrogen
2522    !Config         dynamics.  This is taken from the literature.
2523    !Config Units = [-] 
2524    CALL getin_p('DIFFUSIONO2_POWER_2',diffusionO2_power_2)
2525    !-
2526    !Config Key   = F_NOFROST
2527    !Config Desc  = Temperature-related Factor impacting on Oxygen diffusion rate
2528    !Config If    = OK_STOMATE
2529    !Config Def   = 1.2
2530    !Config Help  = Diffusion of oxygen determines how well anerobic bacteria
2531    !Config         bacteria can live in the soil, which impacts the nitrogen
2532    !Config         dynamics.  This is taken from the literature.
2533    !Config Units = [-] 
2534    CALL getin_p('F_NOFROST',F_nofrost)
2535    !-
2536    !Config Key   = F_FROST
2537    !Config Desc  = Temperature-related Factor impacting on Oxygen diffusion rate
2538    !Config If    = OK_STOMATE
2539    !Config Def   = 0.8
2540    !Config Help  = Diffusion of oxygen determines how well anerobic bacteria
2541    !Config         bacteria can live in the soil, which impacts the nitrogen
2542    !Config         dynamics.  This is taken from the literature.
2543    !Config Units = [-] 
2544    CALL getin_p('F_FROST',F_frost)
2545    !-
2546    !Config Key   = A_ANVF
2547    !Config Desc  = Coefficient used in the calculation of Volumetric fraction of anaerobic microsites
2548    !Config If    = OK_STOMATE
2549    !Config Def   = 0.85
2550    !Config Help  = Anerobic bacteria grow in soil microsites, which impact
2551    !Config         nitrogen dynamics.  The equation using these parameters
2552    !Config         is from the literature, but no values are given in the
2553    !Config         paper.  This value is taken from a previous version of
2554    !Config         the code.
2555    !Config Units = [-] 
2556    CALL getin_p('A_ANVF',a_anvf)
2557    !-
2558    !Config Key   = B_ANVF
2559    !Config Desc  = Coefficient used in the calculation of Volumetric fraction of anaerobic microsites
2560    !Config If    = OK_STOMATE
2561    !Config Def   = 1.
2562    !Config Help  = Anerobic bacteria grow in soil microsites, which impact
2563    !Config         nitrogen dynamics.  The equation using these parameters
2564    !Config         is from the literature, but no values are given in the
2565    !Config         paper.  This value is taken from a previous version of
2566    !Config         the code.
2567    !Config Units = [-] 
2568    CALL getin_p('B_ANVF',b_anvf)
2569    !-
2570    !Config Key   = A_FIXNH4
2571    !Config Desc  = Coefficient used in the calculation of the Fraction of adsorbed NH4+
2572    !Config If    = OK_STOMATE
2573    !Config Def   = 0.41
2574    !Config Help  = In particular, this seems to be for the calculation of
2575    !Config         adsorption onto soil clays.  Taken from the literature.
2576    !Config Units = [-] 
2577    CALL getin_p('A_FIXNH4',a_FixNH4)
2578    !-
2579    !Config Key   = B_FIXNH4
2580    !Config Desc  = Coefficient used in the calculation of the Fraction of adsorbed NH4+
2581    !Config If    = OK_STOMATE
2582    !Config Def   = -0.47
2583    !Config Help  = In particular, this seems to be for the calculation of
2584    !Config         adsorption onto soil clays.  Taken from the literature.
2585    !Config Units = [-] 
2586    CALL getin_p('B_FIXNH4',b_FixNH4)
2587    !-
2588    !Config Key   = CLAY_MAX
2589    !Config Desc  = Coefficient used in the calculation of the Fraction of adsorbed NH4+
2590    !Config If    = OK_STOMATE
2591    !Config Def   = 0.63
2592    !Config Help  = In particular, this seems to be for the calculation of
2593    !Config         adsorption onto soil clays.  Taken from the literature.
2594    !Config Units = [-] 
2595    CALL getin_p('CLAY_MAX',clay_max)
2596    !-
2597    !Config Key   = FW_NIT_0
2598    !Config Desc  = Coefficient used in the calculation of the Response of Nitrification to soil moisture
2599    !Config If    = OK_STOMATE
2600    !Config Def   = -0.0243
2601    !Config Help  = Taken from the literature.
2602    !Config Units = [-] 
2603    CALL getin_p('FW_NIT_0',fw_nit_0)
2604    !-
2605    !Config Key   = FW_NIT_1
2606    !Config Desc  = Coefficient used in the calculation of the Response of Nitrification to soil moisture
2607    !Config If    = OK_STOMATE
2608    !Config Def   = 0.9975
2609    !Config Help  = Taken from the literature.
2610    !Config Units = [-] 
2611    CALL getin_p('FW_NIT_1',fw_nit_1)
2612    !-
2613    !Config Key   = FW__NIT_2
2614    !Config Desc  = Coefficient used in the calculation of the Response of Nitrification to soil moisture
2615    !Config If    = OK_STOMATE
2616    !Config Def   = -5.5368
2617    !Config Help  = Taken from the literature.
2618    !Config Units = [-] 
2619    CALL getin_p('FW_NIT_2',fw_nit_2)
2620    !-
2621    !Config Key   = FW_NIT_3
2622    !Config Desc  = Coefficient used in the calculation of the Response of Nitrification to soil moisture
2623    !Config If    = OK_STOMATE
2624    !Config Def   = 17.651
2625    !Config Help  = Taken from the literature.
2626    !Config Units = [-] 
2627    CALL getin_p('FW_NIT_3',fw_nit_3)
2628    !-
2629    !Config Key   = FW_NIT_4
2630    !Config Desc  = Coefficient used in the calculation of the Response of Nitrification to soil moisture
2631    !Config If    = OK_STOMATE
2632    !Config Def   = -12.904
2633    !Config Help  = Taken from the literature.
2634    !Config Units = [-] 
2635    CALL getin_p('FW_NIT_4',fw_nit_4)
2636    !-
2637    !Config Key   = FT_NIT_0
2638    !Config Desc  = Coefficient used in the calculation of the Response of Nitrification to Temperature
2639    !Config If    = OK_STOMATE
2640    !Config Def   = -0.0233
2641    !Config Help  =
2642    !Config Units = [-] 
2643    CALL getin_p('FT_NIT_0',ft_nit_0)
2644    !-
2645    !Config Key   = FT_NIT_1
2646    !Config Desc  = Coefficient used in the calculation of the Response of Nitrification to Temperature
2647    !Config If    = OK_STOMATE
2648    !Config Def   = 0.3094
2649    !Config Help  = Taken from the literature.  NOTE: Zhang et al 2002 fold
2650    !Config         in the factor 0.1 with the parameter for the term linear
2651    !Config         in temperature (ft_nit_1), while we group it with the soil
2652    !Config         temperature as per the rest of the terms.  Checking
2653    !Config         the parameter values, this leads to a first impression
2654    !Config         that they differ by a factor of 10, when in reality the
2655    !Config         same overall result is calculated.
2656    !Config Units = [-] 
2657    CALL getin_p('FT_NIT_1',ft_nit_1)
2658    !-
2659    !Config Key   = FT_NIT_2
2660    !Config Desc  = Coefficient used in the calculation of the Response of Nitrification to Temperature
2661    !Config If    = OK_STOMATE
2662    !Config Def   = -0.2234
2663    !Config Help  =
2664    !Config Units = [-] 
2665    CALL getin_p('FT_NIT_2',ft_nit_2)
2666    !-
2667    !Config Key   = FT_NIT_3
2668    !Config Desc  = Coefficient used in the calculation of the Response of Nitrification to Temperature
2669    !Config If    = OK_STOMATE
2670    !Config Def   = 0.1566
2671    !Config Help  =
2672    !Config Units = [-] 
2673    CALL getin_p('FT_NIT_3',ft_nit_3)
2674    !-
2675    !Config Key   = FT_NIT_4
2676    !Config Desc  = Coefficient used in the calculation of the Response of Nitrification to Temperature
2677    !Config If    = OK_STOMATE
2678    !Config Def   = -0.0272
2679    !Config Help  =
2680    !Config Units = [-] 
2681    CALL getin_p('FT_NIT_4',ft_nit_4)
2682    !-
2683    !Config Key   = FPH_0
2684    !Config Desc  = Coefficient used in the calculation of the Response of Nitrification to pH
2685    !Config If    = OK_STOMATE
2686    !Config Def   = -1.2314
2687    !Config Help  = Taken from the literature.
2688    !Config Units = [-] 
2689    CALL getin_p('FPH_0',fph_0)
2690    !-
2691    !Config Key   = FPH_1
2692    !Config Desc  = Coefficient used in the calculation of the Response of Nitrification to pH
2693    !Config If    = OK_STOMATE
2694    !Config Def   = 0.7347
2695    !Config Help  = Taken from the literature.
2696    !Config Units = [-] 
2697    CALL getin_p('FPH_1',fph_1)
2698    !-
2699    !Config Key   = FPH_2
2700    !Config Desc  = Coefficient used in the calculation of the Response of Nitrification to pH
2701    !Config If    = OK_STOMATE
2702    !Config Def   = -0.0604
2703    !Config Help  = Taken from the literature.
2704    !Config Units = [-] 
2705    CALL getin_p('FPH_2',fph_2)
2706    !-
2707    !Config Key   = FTV_0
2708    !Config Desc  = Coefficient used in the calculation of the response of NO2 or NO production during nitrificationof to Temperature
2709    !Config If    = OK_STOMATE
2710    !Config Def   = 2.72
2711    !Config Help  =
2712    !Config Units = [-] 
2713    CALL getin_p('FTV_0',ftv_0)
2714    !-
2715    !Config Key   = FTV_1
2716    !Config Desc  = Coefficient used in the calculation of the response of NO2 or NO production during nitrificationof to Temperature
2717    !Config If    = OK_STOMATE
2718    !Config Def   = 34.6
2719    !Config Help  =
2720    !Config Units = [-] 
2721    CALL getin_p('FTV_1',ftv_1)
2722    !-
2723    !Config Key   = FTV_2
2724    !Config Desc  = Coefficient used in the calculation of the response of NO2 or NO production during nitrificationof to Temperature
2725    !Config If    = OK_STOMATE
2726    !Config Def   = 9615.
2727    !Config Help  =
2728    !Config Units = [-] 
2729    CALL getin_p('FTV_2',ftv_2)
2730    !-
2731    !Config Key   = K_NITRIF
2732    !Config Desc  = Nitrification rate at 20 ◩C and field capacity
2733    !Config If    = OK_STOMATE
2734    !Config Def   = 2.0
2735    !Config Help  = The literature value is 0.2, Schmid et al., 2001
2736    !Config         (https://doi.org/10.1023/A:1012694218748)
2737    !Config         However, the value in OCN appears to be 2.0.  We keep
2738    !Config         the OCN value (see stomate_soilcarbon.f90 for more info).
2739    !Config Units = [day**-1] 
2740    CALL getin_p('K_NITRIF',k_nitrif)
2741    !-
2742    !Config Key   = N2O_NITRIF_P
2743    !Config Desc  = Reference n2o production per N-NO3 produced g N-N2O
2744    !Config If    = OK_STOMATE
2745    !Config Def   = 0.0006
2746    !Config Help  = Taken from Zhang et al., 2002 - Appendix A p. 102
2747    !Config Units = [gN-N2O (gN-NO3)-1] 
2748    CALL getin_p('N2O_NITRIF_P',n2o_nitrif_p)
2749    !-
2750    !Config Key   = NO_NITRIF_P
2751    !Config Desc  = Reference NO production per N-NO3 produced g N-N2O
2752    !Config If    = OK_STOMATE
2753    !Config Def   = 0.0025
2754    !Config Help  = Taken from Zhang et al., 2002 - Appendix A p. 102
2755    !Config Units = [gN-NO (gN-NO3)-1] 
2756    CALL getin_p('NO_NITRIF_P',no_nitrif_p)
2757    !-
2758    !Config Key   = CHEMO_T0
2759    !Config Desc  = Coefficient used in the calculation of the Response of NO production from chemodenitrification to Temperature
2760    !Config If    = OK_STOMATE
2761    !Config Def   = -31494
2762    !Config Help  =
2763    !Config Units = [-] 
2764    CALL getin_p('CHEMO_T0',chemo_t0)
2765    !-
2766    !Config Key   = CHEMO_PH0
2767    !Config Desc  = Coefficient used in the calculation of the Response of NO production from chemodenitrification to pH
2768    !Config If    = OK_STOMATE
2769    !Config Def   = -1.62
2770    !Config Help  =
2771    !Config Units = [-] 
2772    CALL getin_p('CHEMO_PH0',chemo_ph0)
2773    !-
2774    !Config Key   = CHEMO_0
2775    !Config Desc  = Coefficient used in the calculation of NO production from chemodenitrification
2776    !Config If    = OK_STOMATE
2777    !Config Def   = 30.
2778    !Config Help  =
2779    !Config Units = [-] 
2780    CALL getin_p('CHEMO_0',chemo_0)
2781    !-
2782    !Config Key   = CHEMO_1
2783    !Config Desc  = Coefficient used in the calculation of NO production from chemodenitrification
2784    !Config If    = OK_STOMATE
2785    !Config Def   = 16565
2786    !Config Help  =
2787    !Config Units = [-] 
2788    CALL getin_p('CHEMO_1',chemo_1)
2789    !-
2790    !Config Key   = FT_DENIT_0
2791    !Config Desc  = Coefficient used in the response of relative growth rate of total denitrifiers to Temperature
2792    !Config If    = OK_STOMATE
2793    !Config Def   = 2.
2794    !Config Help  =
2795    !Config Units = [-] 
2796    CALL getin_p('FT_DENIT_0',ft_denit_0)
2797    !-
2798    !Config Key   = FT_DENIT_1
2799    !Config Desc  = Coefficient used in the response of relative growth rate of total denitrifiers to Temperature
2800    !Config If    = OK_STOMATE
2801    !Config Def   = 22.5
2802    !Config Help  =
2803    !Config Units = [-] 
2804    CALL getin_p('FT_DENIT_1',ft_denit_1)
2805    !-
2806    !Config Key   = FT_DENIT_2
2807    !Config Desc  = Coefficient used in the response of relative growth rate of total denitrifiers to Temperature
2808    !Config If    = OK_STOMATE
2809    !Config Def   = 10
2810    !Config Help  =
2811    !Config Units = [-] 
2812    CALL getin_p('FT_DENIT_2',ft_denit_2)
2813    !-
2814    !Config Key   = FPH_NO3_0
2815    !Config Desc  = Coefficient used in the response of relative growth rate of NO3 denitrifiers to pH
2816    !Config If    = OK_STOMATE
2817    !Config Def   = 4.25
2818    !Config Help  =
2819    !Config Units = [-] 
2820    CALL getin_p('FPH_NO3_0',fph_no3_0)
2821    !-
2822    !Config Key   = FPH_NO3_1
2823    !Config Desc  = Coefficient used in the response of relative growth rate of NO3 denitrifiers to pH
2824    !Config If    = OK_STOMATE
2825    !Config Def   = 0.5
2826    !Config Help  =
2827    !Config Units = [-] 
2828    CALL getin_p('FPH_NO3_1',fph_no3_1)
2829    !-
2830    !Config Key   = FPH_NO_0
2831    !Config Desc  = Coefficient used in the response of relative growth rate of NO denitrifiers to pH
2832    !Config If    = OK_STOMATE
2833    !Config Def   = 5.25
2834    !Config Help  =
2835    !Config Units = [-] 
2836    CALL getin_p('FPH_NO_0',fph_no_0)
2837    !-
2838    !Config Key   = FPH_NO_1
2839    !Config Desc  = Coefficient used in the response of relative growth rate of NO denitrifiers to pH
2840    !Config If    = OK_STOMATE
2841    !Config Def   = 1.
2842    !Config Help  =
2843    !Config Units = [-] 
2844    CALL getin_p('FPH_NO_1',fph_no_1)
2845    !-
2846    !Config Key   = FPH_N2O_0
2847    !Config Desc  = Coefficient used in the response of relative growth rate of N2O denitrifiers to pH
2848    !Config If    = OK_STOMATE
2849    !Config Def   = 6.25
2850    !Config Help  =
2851    !Config Units = [-] 
2852    CALL getin_p('FPH_N2O_0',fph_n2o_0)
2853    !-
2854    !Config Key   = FPH_N2O_1
2855    !Config Desc  = Coefficient used in the response of relative growth rate of N2O denitrifiers to pH
2856    !Config If    = OK_STOMATE
2857    !Config Def   = 1.5
2858    !Config Help  =
2859    !Config Units = [-] 
2860    CALL getin_p('FPH_N2O_1',fph_n2o_1)
2861    !-
2862    !Config Key   = KN
2863    !Config Desc  = Half Saturation of N oxydes
2864    !Config If    = OK_STOMATE
2865    !Config Def   = 0.083
2866    !Config Help  =
2867    !Config Units = [kgN/m**3] 
2868    CALL getin_p('KN',Kn)
2869    !-
2870    !Config Key   = CTE_BACT
2871    !Config Desc  = Denitrification activiy of bacteria     
2872    !Config If    = OK_STOMATE
2873    !Config Def   = 0.00005
2874    !Config Help  =
2875    !Config Units = [-]
2876    CALL getin_p('CTE_BACT',cte_bact)
2877    !-
2878    !Config Key   = MU_NO3_MAX
2879    !Config Desc  = Maximum Relative growth rate of NO3 denitrifiers
2880    !Config If    = OK_STOMATE
2881    !Config Def   = 0.67
2882    !Config Help  =
2883    !Config Units = [hour**-1] 
2884    CALL getin_p('MU_NO3_MAX',mu_no3_max)
2885    !-
2886    !Config Key   = MU_NO_MAX
2887    !Config Desc  = Maximum Relative growth rate of NO denitrifiers
2888    !Config If    = OK_STOMATE
2889    !Config Def   = 0.34
2890    !Config Help  =
2891    !Config Units = [hour**-1] 
2892    CALL getin_p('MU_NO_MAX',mu_no_max)
2893    !-
2894    !Config Key   = MU_N2O_MAX
2895    !Config Desc  = Maximum Relative growth rate of N2O denitrifiers
2896    !Config If    = OK_STOMATE
2897    !Config Def   = 0.34
2898    !Config Help  =
2899    !Config Units = [hour**-1] 
2900    CALL getin_p('MU_N2O_MAX',mu_n2o_max)
2901    !-
2902    !Config Key   = Y_NO3
2903    !Config Desc  = Maximum growth yield of NO3 denitrifiers on N oxydes
2904    !Config If    = OK_STOMATE
2905    !Config Def   = 0.401
2906    !Config Help  =
2907    !Config Units = [kgC / kgN] 
2908    CALL getin_p('Y_NO3',Y_no3)
2909    !-
2910    !Config Key   = Y_NO
2911    !Config Desc  = Maximum growth yield of NO denitrifiers on N oxydes
2912    !Config If    = OK_STOMATE
2913    !Config Def   = 0.428
2914    !Config Help  =
2915    !Config Units = [kgC / kgN] 
2916    CALL getin_p('Y_NO',Y_no)
2917    !-
2918    !Config Key   = Y_N2O
2919    !Config Desc  = Maximum growth yield of N2O denitrifiers on N oxydes
2920    !Config If    = OK_STOMATE
2921    !Config Def   = 0.151
2922    !Config Help  =
2923    !Config Units = [kgC / kgN] 
2924    CALL getin_p('Y_N2O',Y_n2O)
2925    !-
2926    !Config Key   = M_NO3
2927    !Config Desc  = Maintenance coefficient on NO3
2928    !Config If    = OK_STOMATE
2929    !Config Def   = 0.09
2930    !Config Help  =
2931    !Config Units = [kgN / kgC / hour] 
2932    CALL getin_p('M_NO3',M_no3)
2933    !-
2934    !Config Key   = M_NO
2935    !Config Desc  = Maintenance coefficient on NO
2936    !Config If    = OK_STOMATE
2937    !Config Def   = 0.035
2938    !Config Help  =
2939    !Config Units = [kgN / kgC / hour] 
2940    CALL getin_p('M_NO',M_no)
2941    !-
2942    !Config Key   = M_N2O
2943    !Config Desc  = Maintenance coefficient on N2O
2944    !Config If    = OK_STOMATE
2945    !Config Def   = 0.079
2946    !Config Help  =
2947    !Config Units = [kgN / kgC / hour] 
2948    CALL getin_p('M_N2O',M_n2o)
2949    !-
2950    !Config Key   = MAINT_C
2951    !Config Desc  = Maintenance coefficient of carbon
2952    !Config If    = OK_STOMATE
2953    !Config Def   = 0.0076
2954    !Config Help  =
2955    !Config Units = [kgC / kgC / hour] 
2956    CALL getin_p('MAINT_C',Maint_c)
2957    !-
2958    !Config Key   = YC
2959    !Config Desc  = Maximum growth yield on soluble carbon
2960    !Config If    = OK_STOMATE
2961    !Config Def   = 0.503
2962    !Config Help  =
2963    !Config Units = [kgC / kgC ] 
2964    CALL getin_p('YC',Yc)
2965    !-
2966    !Config Key   = F_CLAY_0
2967    !Config Desc  = Coefficient used in the eq. defining the response of N-emission to clay fraction
2968    !Config If    = OK_STOMATE
2969    !Config Def   = 0.13
2970    !Config Help  =
2971    !Config Units = [-] 
2972    CALL getin_p('F_CLAY_0',F_clay_0)
2973    !-
2974    !Config Key   = F_CLAY_1
2975    !Config Desc  = Coefficient used in the eq. defining the response of N-emission to clay fraction
2976    !Config If    = OK_STOMATE
2977    !Config Def   = -0.079
2978    !Config Help  =
2979    !Config Units = [-] 
2980    CALL getin_p('F_CLAY_1',F_clay_1)
2981    !-
2982    !Config Key   = RATIO_NH4_FERT
2983    !Config Desc  = Proportion of ammonium in the fertilizers (ammo-nitrate)
2984    !Config If    = OK_STOMATE
2985    !Config Def   = 0.875
2986    !Config Help  =
2987    !Config Units = [-] 
2988    CALL getin_p('RATIO_NH4_FERT',ratio_nh4_fert)
2989    !-
2990    !Config Key   = CN_RATIO_MANURE
2991    !Config Desc  = C:N ratio of organic fertilizers coming from Fuchs,et al,
2992    !Effets agronomiques attendus de l’épandage des Mafor sur les écosystÚmes
2993    !agricoles et forestiers, Valoris. des matiÚres Fertil. d’origine résiduaire
2994    !sur les sols à usage Agric. ou For., 364–567 [online] mean over table 3-1-1
2995    !Config If    = OK_STOMATE
2996    !Config Def   = 13.7
2997    !Config Help  =
2998    !Config Units = [-] 
2999    CALL getin_p('CN_RATIO_MANURE',cn_ratio_manure)
3000    !-
3001    !-
3002    ! Arrays
3003    !-
3004    !Config Key   = K_N_MIN
3005    !Config Desc  = [NH4+] and [NO3-] for which the Nuptake equals vmax/2.
3006    !Config If    = OK_STOMATE
3007    !Config Def   = 30. 30.
3008    !Config Help  =
3009    !Config Units = [umol per litter] 
3010    CALL getin_p('K_N_min',K_N_min)
3011    !-
3012    !Config Key   = LOW_K_N_MIN
3013    !Config Desc  = Rate of N uptake not associated with Michaelis- Menten Kinetics for Ammonium
3014    !Config If    = OK_STOMATE
3015    !Config Def   = 0.0002 0.0002
3016    !Config Help  =
3017    !Config Units = [umol**-1] 
3018    CALL getin_p('LOW_K_N_min',low_K_N_min)
3019
3020    !Config Key   = EMM_FAC
3021    !Config Desc  = Factor for reducing NH3 emission 
3022    !Config If    = OK_NCYCLE
3023    !Config Def   = 0.2
3024    !Config Help  =
3025    !Config Units = [-] 
3026    CALL getin_p('EMM_FAC',emm_fac)
3027
3028    !Config Key   = FACT_KN_NO
3029    !Config Desc  = Factor for adusting kn constant for NOx production
3030    !Config If    = OK_NCYCLE
3031    !Config Def   = 0.012
3032    !Config Help  =
3033    !Config Units = [-] 
3034    CALL getin_p('FACT_KN_NO',fact_kn_no)
3035
3036    !Config Key   = FACT_KN_N2O
3037    !Config Desc  = Factor for adusting kn constant for N2O production
3038    !Config If    = OK_NCYCLE
3039    !Config Def   = 0.04
3040    !Config Help  =
3041    !Config Units = [-] 
3042    CALL getin_p('FACT_KN_N2O',fact_kn_n2o)
3043
3044    !Config Key   = KFWDENIT
3045    !Config Desc  = Factor for adjusting sensitivity of denitrification to water content
3046    !Config If    = OK_NCYCLE
3047    !Config Def   = -5.
3048    !Config Help  =
3049    !Config Units = [-]
3050    CALL getin_p('KFWDENIT',kfwdenit)
3051
3052    !Config Key   = FWDENITFC
3053    !Config Desc  = Value at field capacity of the sensitivity function of denitrification to water content
3054    !Config If    = OK_NCYCLE
3055    !Config Def   = 0.05
3056    !Config Help  =
3057    !Config Units = [-]
3058    CALL getin_p('FWDENITFC',fwdenitfc)
3059
3060    !Config Key   = FRACN_DRAINAGE
3061    !Config Desc  = Fraction of NH3/NO3 loss by drainage
3062    !Config If    = OK_NCYCLE
3063    !Config Def   = 1.0
3064    !Config Help  =
3065    !Config Units = [-] 
3066    CALL getin_p('FRACN_DRAINAGE',fracn_drainage)
3067
3068    !Config Key   = FRACN_RUNOFF
3069    !Config Desc  = Fraction of NH3/NO3 loss by runoff
3070    !Config If    = OK_NCYCLE
3071    !Config Def   = 0.3
3072    !Config Help  =
3073    !Config Units = [-] 
3074    CALL getin_p('FRACN_RUNOFF',fracn_runoff)
3075
3076    !-
3077    !Config Key   = LEAF_N_DMAX
3078    !Config Desc  = ?????????????
3079    !Config If    = OK_STOMATE
3080    !Config Def   = 0.25
3081    !Config Help  =
3082    !Config Units = ???
3083    CALL getin_p('LEAF_N_DMAX',DMAX)
3084
3085    !-
3086    !Config Key   = P_N_UPTAKE
3087    !Config Desc  = Minimum value of the correction factor for plant N uptake
3088    !               case of enough N in the reserve
3089    !Config If    = OK_STOMATE
3090    !Config Def   = 0.6
3091    !Config Help  =
3092    !Config Units = [-]
3093    CALL getin_p('P_N_UPTAKE',p_n_uptake)
3094
3095    !-
3096    ! growth_fun_all
3097    !
3098    !Config Key   = SYNC_THRESHOLD
3099    !Config Desc  = The threshold value for a warning when we sync biomass
3100    !Config If    = OK_STOMATE
3101    !Config Def   = 0.1
3102    !Config Help  =
3103    !Config Units = [-] 
3104    CALL getin_p('SYNC_THRESHOLD',sync_threshold)
3105
3106
3107    !
3108    !Config Key   = TEST_GRID
3109    !Config Desc  = grid cell for which extra output is written to the out_execution file
3110    !Config If    = OK_STOMATE
3111    !Config Def   = 1
3112    !Config Help  =
3113    !Config Units = [-]
3114    CALL getin_p('TEST_GRID',test_grid)   
3115
3116
3117    !
3118    !Config Key   = TEST_PFT
3119    !Config Desc  = pft for which extra output is written to the out_execution file
3120    !Config If    = OK_STOMATE
3121    !Config Def   = 6
3122    !Config Help  =
3123    !Config Units = [-]   
3124    CALL getin_p('TEST_PFT',test_pft)   
3125
3126    !+++++++++++  DEBUG +++++++++++++++
3127    !Config Key   = LNVGRASSPATCH
3128    !Config Desc  = Activates a patch for grasslands that Nicolas came up with
3129    !Config If    = OK_STOMATE
3130    !Config Def   = FALSE
3131    !Config Help  = Related to senesence and leaf age classes
3132    !Config Units = [-]   
3133    CALL getin_p('LNVGRASSPATCH',LNVGRASSPATCH) 
3134    !++++++++++++++++++++++++++++++++++
3135
3136    !
3137    !Config Key   = MAX_DELTA_KF
3138    !Config Desc  = Maximum change in KF from one time step to another
3139    !Config If    = OK_STOMATE
3140    !Config Def   = 0.1
3141    !Config Help  =
3142    !Config Units = [m] 
3143    CALL getin_p('MAX_DELTA_KF',max_delta_KF)
3144    !
3145
3146    !
3147    !Config Key   = MAINT_FROM_GPP
3148    !Config Desc  = Some carbon needs to remain to support the growth, hence,
3149    !               respiration will be limited. In this case resp_maint
3150    !               (gC m-2 dt-1) should not be more than 80% (::maint_from_gpp)
3151    !               of the GPP (gC m-2 s-1)
3152    !Config If    = OK_STOMATE
3153    !Config Def   = 0.8
3154    !Config Help  =
3155    !Config Units = [-] 
3156    CALL getin_p('MAINT_FROM_GPP',maint_from_gpp)
3157
3158
3159    !-
3160    ! turnover parameters
3161    !-
3162    !
3163    !Config Key   = NEW_TURNOVER_TIME_REF
3164    !Config Desc  =
3165    !Config If    = OK_STOMATE
3166    !Config Def   = 20.
3167    !Config Help  =
3168    !Config Units = [days] 
3169    CALL getin_p('NEW_TURNOVER_TIME_REF',new_turnover_time_ref)
3170
3171    !-
3172    ! vmax parameters
3173    !-
3174    !
3175    !Config Key   = VMAX_OFFSET
3176    !Config Desc  = offset (minimum relative vcmax)
3177    !Config If    = OK_STOMATE
3178    !Config Def   = 0.3
3179    !Config Help  = offset (minimum vcmax/vmax_opt)
3180    !Config Units = [-] 
3181    CALL getin_p('VMAX_OFFSET',vmax_offset)
3182    !
3183    !Config Key   = LEAFAGE_FIRSTMAX
3184    !Config Desc  = leaf age at which vmax attains vcmax_opt (in fraction of critical leaf age)
3185    !Config If    = OK_STOMATE
3186    !Config Def   = 0.03
3187    !Config Help  = relative leaf age at which vmax attains vcmax_opt
3188    !Config Units = [-]
3189    CALL getin_p('LEAFAGE_FIRSTMAX',leafage_firstmax)
3190    !
3191    !Config Key   = LEAFAGE_LASTMAX
3192    !Config Desc  = leaf age at which vmax falls below vcmax_opt (in fraction of critical leaf age)
3193    !Config If    = OK_STOMATE
3194    !Config Def   = 0.5
3195    !Config Help  = relative leaf age at which vmax falls below vcmax_opt
3196    !Config Units = [-] 
3197    CALL getin_p('LEAFAGE_LASTMAX',leafage_lastmax)
3198    !
3199    !Config Key   = LEAFAGE_OLD
3200    !Config Desc  = leaf age at which vmax attains its minimum (in fraction of critical leaf age)
3201    !Config If    = OK_STOMATE
3202    !Config Def   = 1.
3203    !Config Help  = relative leaf age at which vmax attains its minimum
3204    !Config Units = [-] 
3205    CALL getin_p('LEAFAGE_OLD',leafage_old)
3206    !
3207    !-
3208    ! season parameters
3209    !-
3210    !
3211    !Config Key   = GPPFRAC_DORMANCE
3212    !Config Desc  = rapport maximal GPP/GGP_max pour dormance
3213    !Config If    = OK_STOMATE
3214    !Config Def   = 0.2
3215    !Config Help  =
3216    !Config Units = [-]
3217    CALL getin_p('GPPFRAC_DORMANCE',gppfrac_dormance)
3218    !
3219    !Config Key   = TAU_CLIMATOLOGY
3220    !Config Desc  = tau for "climatologic variables
3221    !Config If    = OK_STOMATE
3222    !Config Def   = 20
3223    !Config Help  =
3224    !Config Units = [days]
3225    CALL getin_p('TAU_CLIMATOLOGY',tau_climatology)
3226    !
3227    !Config Key   = HVC1
3228    !Config Desc  = parameters for herbivore activity
3229    !Config If    = OK_STOMATE
3230    !Config Def   = 0.019
3231    !Config Help  =
3232    !Config Units = [-] 
3233    CALL getin_p('HVC1',hvc1)
3234    !
3235    !Config Key   = HVC2
3236    !Config Desc  = parameters for herbivore activity
3237    !Config If    = OK_STOMATE
3238    !Config Def   = 1.38
3239    !Config Help  =
3240    !Config Units = [-] 
3241    CALL getin_p('HVC2',hvc2)
3242    !
3243    !Config Key   = LEAF_FRAC_HVC
3244    !Config Desc  = parameters for herbivore activity
3245    !Config If    = OK_STOMATE
3246    !Config Def   = 0.33
3247    !Config Help  =
3248    !Config Units = [-]
3249    CALL getin_p('LEAF_FRAC_HVC',leaf_frac_hvc)
3250    !
3251    !Config Key   = TLONG_REF_MAX
3252    !Config Desc  = maximum reference long term temperature
3253    !Config If    = OK_STOMATE
3254    !Config Def   = 303.1
3255    !Config Help  =
3256    !Config Units = [K] 
3257    CALL getin_p('TLONG_REF_MAX',tlong_ref_max)
3258    !
3259    !Config Key   = TLONG_REF_MIN
3260    !Config Desc  = minimum reference long term temperature
3261    !Config If    = OK_STOMATE
3262    !Config Def   = 253.1
3263    !Config Help  =
3264    !Config Units = [K] 
3265    CALL getin_p('TLONG_REF_MIN',tlong_ref_min)
3266    !
3267    !Config Key   = NCD_MAX_YEAR
3268    !Config Desc  =
3269    !Config If    = OK_STOMATE
3270    !Config Def   = 3.
3271    !Config Help  = NCD : Number of Chilling Days
3272    !Config Units = [days]
3273    CALL getin_p('NCD_MAX_YEAR',ncd_max_year)
3274    !
3275    !Config Key   = GDD_THRESHOLD
3276    !Config Desc  =
3277    !Config If    = OK_STOMATE
3278    !Config Def   = 5.
3279    !Config Help  = GDD : Growing-Degree-Day
3280    !Config Units = [days]
3281    CALL getin_p('GDD_THRESHOLD',gdd_threshold)
3282    !
3283    !Config Key   = GREEN_AGE_EVER
3284    !Config Desc  =
3285    !Config If    = OK_STOMATE
3286    !Config Def   = 2.
3287    !Config Help  =
3288    !Config Units = [-] 
3289    CALL getin_p('GREEN_AGE_EVER',green_age_ever)
3290    !
3291    !Config Key   = GREEN_AGE_DEC
3292    !Config Desc  =
3293    !Config If    = OK_STOMATE
3294    !Config Def   = 0.5
3295    !Config Help  =
3296    !Config Units = [-]
3297    CALL getin_p('GREEN_AGE_DEC',green_age_dec)
3298
3299
3300    !Config Key   = NGD_MIN_DORMANCE
3301    !Config Desc  = Minimum length (days) of the dormance period for species with the ngd phenology type
3302    !Config If    = OK_STOMATE
3303    !Config Def   = 90.
3304    !Config Help  =
3305    !Config Units = [days]
3306    CALL getin_p('NGD_MIN_DORMANCE',ngd_min_dormance)
3307 
3308   
3309    !Config Key   = NAGEC
3310    !Config Desc  = Number of age classes
3311    !Config If    = OK_STOMATE
3312    !Config Def   = 1
3313    !Config Help  = Number of age classes in forestry and lcchange
3314    !               age classes could be considered age classes across stands
3315    !               in the same pixel. They help to describe landscape heterogeneity
3316    !               they are most useful when land cover change is used.
3317    !Config Units = [-]
3318    nagec = 1
3319    CALL getin_p('NAGEC',nagec)
3320    !
3321   
3322    ALLOCATE(age_class_bound(nagec),stat=ier)
3323    l_error = l_error .OR. (ier /= 0)
3324    IF (l_error) THEN
3325       WRITE(numout,*) 'Memory allocation error for age_class_bound. We stop. We need nagec words',nagec
3326       STOP 'constantes.f90'
3327    ENDIF
3328    !
3329    !Config Key   = AGE_CLASS_BOUND
3330    !Config Desc  = Boundaries of the age classes
3331    !Config If    = OK_STOMATE
3332    !Config Def   = 5.0
3333    !Config Help  = The number of age class bounds should be identical
3334    !               to NAGEC. Two sets of default values are provided.
3335    !Config Units = [m]
3336    IF(nagec == 4)THEN
3337       age_class_bound(1) = 0.07
3338       age_class_bound(2) = 0.20
3339       age_class_bound(3) = 0.40
3340       age_class_bound(4) = 5.00
3341    ELSEIF(nagec == 1)THEN
3342       age_class_bound(1) = 5.00
3343    ELSE
3344       age_class_bound(:) = -9999.
3345    ENDIF
3346    CALL getin_p('AGE_CLASS_BOUND',age_class_bound)
3347
3348    IF (age_class_bound(1) == -9999.) THEN
3349       WRITE(numout,*) 'The code does not contain default values for age_class_bound'
3350       WRITE(numout,*) 'for this number of age classes (nagec) ',nagec
3351       CALL ipslerr_p (3,'age_class_distr', 'Define age class bounds',&
3352            'add default values in constantes.f90',& 
3353            'or add values in the orchidee_pft.def')
3354    END IF
3355
3356    ! Check for inconsistent configuration
3357    IF (spinup_analytic .AND. veget_update .GT.0 .AND. nagec .GT.1) THEN
3358       WRITE(numout,*) 'Use the analytical spinup, ',spinup_analytic
3359       WRITE(numout,*) 'Use land cover changes, ',veget_update
3360       WRITE(numout,*) 'Number of age classes, ',nagec
3361       CALL ipslerr_p(3,'The spinup cannot handle land cover changes',&
3362            'and age classes at the same time',&
3363            'If you really need a spinup with lcc you will have to',&
3364            'further develop the code in age_class_distr (sapiens_lcchange.f90)')
3365    END IF
3366    !
3367    !Config Key   = MIN_WATER_STRESS
3368    !Config Desc  = Minimal value for wstress_fac
3369    !Config If    = OK_STOMATE
3370    !Config Def   = 0.1
3371    !Config Help  =
3372    !Config Units = [-] 
3373    CALL getin_p('MIN_WATER_STRESS',min_water_stress)
3374    !
3375    !Config Key   = NDIA_HARVEST
3376    !Config Desc  = Number of basal area classes in which the harvest is stored
3377    !Config If    = OK_STOMATE
3378    !Config Def   = 5
3379    !Config Help  = Number of basal area classes in which the harvest
3380    !               is stored. This is useful when harvest is further
3381    !               used in a wood-use module
3382    !Config Units = [-]
3383    ndia_harvest = 5
3384    CALL getin_p('NDIA_HARVEST',ndia_harvest)
3385    !
3386    !Config Key   = MAX_HARVEST_DIA
3387    !Config Desc  = The maximum diamter of tree which can be harvested
3388    !Config If    = OK_STOMATE
3389    !Config Def   = 1.0
3390    !Config Help  = The maximum diamter of tree which can be
3391    !               harvested.  Notice that we will create a class
3392    !               that is one size larger than this to make sure
3393    !               we keep track of all the wood.
3394    !Config Units = [m]
3395    CALL getin_p('MAX_HARVEST_DIA',max_harvest_dia) 
3396
3397    !Config Key   = N_PAI
3398    !Config Desc  = Number of years used for the calculation of the periodic annual increment
3399    !Config If    = OK_STOMATE
3400    !Config Def   = 5
3401    !Config Help  =
3402    !Config Units = [-]
3403    CALL getin_p('N_PAI',n_pai)
3404    !
3405    !Config Key   = NTREES_PROFIT
3406    !Config Desc  = Number of trees below which the forest will be cut and replanted
3407    !Config If    = FOREST_MANAGEMENT 
3408    !Config Def   = 100
3409    !Config Help  = Fewer trees than ntrees_profit is considered no
3410    !               longer profitable. Hence the stand will be cut
3411    !               and replaced. It mimics disturbance in unmanaged forests
3412    !               and it prevents forest from becoming unrealistically old.
3413    !Config Units = [number of trees]
3414    ntrees_profit=1
3415    CALL getin_p('NTREES_PROFIT',ntrees_profit)
3416    !
3417    ! If we don't read the new species from a map, we will use veget_max
3418    ! instead. So we will replant with the current species. This will
3419    ! only happen if species_change_force equals -9999. If
3420    ! species_change_force has a different value in the run.def that
3421    ! value will be used. Note that species_change_force is intended for
3422    ! testing and debugging.
3423    !Config Key   = SPECIES_CHANGE_FORCE
3424    !Config Desc  = New species after a final cut for testing and debugging only
3425    !Config If    = OK_STOMATE
3426    !Config Def   = -9999
3427    !Config Help  = If we don't read the new species from a map, we will use veget_max
3428    !               instead. So we will replant with the current species. This will
3429    !               only happen if species_change_force equals -9999. If
3430    !               species_change_force has a different value in the run.def that
3431    !               value will be used. Note that species_change_force is intended for
3432    !               testing and debugging.
3433    !Config Units = [PFT number]
3434    species_change_force=-9999
3435    CALL getin_p('SPECIES_CHANGE_FORCE',species_change_force)
3436
3437    !Config Key   = FM_CHANGE_FORCE
3438    !Config Desc  = New management after a final cut for testing and debugging only
3439    !Config If    = OK_STOMATE, LCHANGE_SPECIES
3440    !Config Def   = ifm_none
3441    !Config Help  = If we don't read the new speciesFM strategies from a map, we
3442    !               will force it with this variable. Following a harvest all
3443    !               management will be set to unmanaged.
3444    !Config Units = [1, 2, 3 or 4; unitless]
3445    fm_change_force = ifm_none
3446    CALL getin_p('FM_CHANGE_FORCE',fm_change_force)     
3447
3448    ! Bark beetle attack module
3449    !Config Key   = nb_years_bgi
3450    !Config Desc  = numbers of years over which bark beetle generation index is calculated
3451    !Config If    = OK_PEST, OK_STOMATE
3452    !Config Def   = 3
3453    !Config Help  = numbers we have to average to calculate the bark beetle
3454    !generation index. use in beetle damage module
3455    !Config Units = [years]
3456    nb_years_bgi = 3
3457    CALL getin_p('NB_YEARS_BGI',nb_years_bgi)
3458
3459    !-
3460    ! windthrow
3461    !-
3462    !Config Key   = DAILY_MAX_TUNE
3463    !Config Desc  = Non linear tuning factor for daily maximum wind speed used in windthrow module
3464    !Config If    = OK_WINDTHROW, stomate main program
3465    !Config Def   = 1.000
3466    !Config Help  =
3467    !Config Units = [-]
3468    daily_max_tune = 1.000
3469    CALL getin_p('DAILY_MAX_TUNE',daily_max_tune)
3470
3471    !Config Key   = WIND_SPEED_STORM_THR
3472    !Config Desc  = the wind speed threshold above which is_storm flag is set to TRUE
3473    !Config If    = OK_WINDTHROW, stomate main program
3474    !Config Def   = 20.000
3475    !Config Help  =
3476    !Config Units = meter per second
3477    wind_speed_storm_thr = 20.000
3478    CALL getin_p('WIND_SPEED_STORM_THR',wind_speed_storm_thr)
3479
3480    !Config Key   = NB_DAYS_STORM
3481    !Config Desc  = the number of days at which the max wind speed is less than wind_speed_storm_thr
3482    !Config If    = OK_WINDTHROW, stomate main program
3483    !Config Def   = 5
3484    !Config Help  =
3485    !Config Units = days
3486    nb_days_storm = 5
3487    CALL getin_p('NB_DAYS_STORM',nb_days_storm)
3488
3489    !Config Key   = FORCED_CLEAR_CUT
3490    !Config Desc  = Use to force a clear cut at a specific year during a simulation.
3491    !Config If    = OK_STOMATE
3492    !Config Def   = .FALSE.
3493    !Config Help  =
3494    !Config Units = year
3495    forced_clear_cut= .FALSE.
3496    CALL getin_p('FORCED_CLEAR_CUT',forced_clear_cut)
3497
3498    !Config Key   = USE_HEIGHT_DOM
3499    !Config Desc  = Use the dominant vegetation height instead of the average height when calculating roughness length
3500    !Config If    = OK_STOMATE
3501    !Config Def   = .FALSE.
3502    !Config Help  = This is a somewhat odd switch, since it impacts sechiba
3503    !               but can only be used when stomate is activated.
3504    !Config Units = [-]
3505    use_height_dom= .FALSE.
3506    CALL getin_p('USE_HEIGHT_DOM',use_height_dom)
3507
3508    !Config Key   = ERR_ACT
3509    !Config Desc  = Action following an error
3510    !Config If    = OK_STOMATE
3511    !Config Def   = 1
3512    !Config Help  = The code distinguishes between two options to check for mass balance
3513    !               problems:
3514    !               ERR_ACT = 1 is recommended when running global
3515    !               long-term simulations. Under this option, mass balance closure is
3516    !               checked for all biogeochemical processes but only at the highest level
3517    !               thus stomate.f90 and stomate_lpj.f90. Although the mass balance checks
3518    !               are not very expensive in terms of computer time, skipping the numerous
3519    !               lower level checks is expected to save some time. Under this option the
3520    !               mass balance error is only written to the history file. No information
3521    !               is provided in which subroutine the problem occurred.
3522    !               ERR_ACT = 2
3523    !               is recommended when developing and testing the model. Now the mass
3524    !               balance is explicitly checked in stomate.f90, stomate_lpj.f90 and all
3525    !               its subroutines. Under this option the mass balance error is written to
3526    !               the history file and if the mass balance is not closed, the warning
3527    !               message will indicate in which subroutine the problem likely
3528    !               originated.
3529    !               ERR_ACT = 3 is recommended when having a problem with
3530    !               mass balance closure. The mass balance is explicitly checked in
3531    !               stomate.f90, stomate_lpj.f90 and all its subroutines. If a mass balance
3532    !               occurs, the model is stopped.
3533    !               ERR_ACT = 4 is for mass balance enthousiasts.
3534    !               If the model crashed on a mass balance issue in stomate_growth_fun_all
3535    !               this setting will activate intermediate checks. Intermediate checks may
3536    !               help to narrow down in which part of the code the problem occurs. It also
3537    !               activates nbp consistency checks for those interested in better defining
3538    !               nep, nbp and tracing all the C and N in stomate_lpj.f90
3539    !Config Units = [1: write to history file, 2: warn and write to history file, and 3&4: stop the model]
3540    err_act = 1
3541    CALL getin_p('ERR_ACT',err_act)
3542
3543    SELECT CASE (err_act)
3544    CASE(1)
3545        WRITE(numout,*) 'Many ipserr messages will be skipped'
3546        plev = 0
3547    CASE(2)
3548        WRITE(numout,*) 'In case of an error the user will be warned'
3549        plev = 2
3550    CASE(3, 4)
3551        WRITE(numout,*) 'In case of an error the model will be stopped'
3552        plev = 3
3553    CASE DEFAULT
3554        CALL ipslerr_p(3,'Error in constantes.f90',&
3555            'Unknown value for ERR_ACT',&
3556            'Not clear how to treat errors','')   
3557    ENDSELECT
3558
3559  END SUBROUTINE config_stomate_parameters
3560
3561!! ================================================================================================================================
3562!! SUBROUTINE   : config_dgvm_parameters
3563!!
3564!>\BRIEF        This subroutine reads in the configuration file all the parameters
3565!! needed when the DGVM model is activated (ie : when ok_dgvm is set to true).
3566!!
3567!! DESCRIPTION  : None
3568!!
3569!! RECENT CHANGE(S): None
3570!!
3571!! MAIN OUTPUT VARIABLE(S):
3572!!
3573!! REFERENCE(S) :
3574!!
3575!! FLOWCHART    :
3576!! \n
3577!_ ================================================================================================================================
3578
3579  SUBROUTINE config_dgvm_parameters   
3580
3581    IMPLICIT NONE
3582
3583    !! 0. Variables and parameters declaration
3584
3585    !! 0.4 Local variables
3586
3587    !_ ================================================================================================================================   
3588
3589    !-
3590    ! establish parameters
3591    !-
3592    !
3593    !Config Key   = ESTAB_MAX_TREE
3594    !Config Desc  = Maximum tree establishment rate
3595    !Config If    = OK_DGVM
3596    !Config Def   = 0.12
3597    !Config Help  =
3598    !Config Units = [-]   
3599    CALL getin_p('ESTAB_MAX_TREE',estab_max_tree)
3600    !
3601    !Config Key   = ESTAB_MAX_GRASS
3602    !Config Desc  = Maximum grass establishment rate
3603    !Config If    = OK_DGVM
3604    !Config Def   = 0.12
3605    !Config Help  =
3606    !Config Units = [-] 
3607    CALL getin_p('ESTAB_MAX_GRASS',estab_max_grass)
3608    !
3609    !Config Key   = ESTABLISH_SCAL_FACT
3610    !Config Desc  =
3611    !Config If    = OK_DGVM
3612    !Config Def   = 5.
3613    !Config Help  =
3614    !Config Units = [-]
3615    CALL getin_p('ESTABLISH_SCAL_FACT',establish_scal_fact)
3616    !
3617    !Config Key   = MAX_TREE_COVERAGE
3618    !Config Desc  =
3619    !Config If    = OK_DGVM
3620    !Config Def   = 0.98
3621    !Config Help  =
3622    !Config Units = [-]
3623    CALL getin_p('MAX_TREE_COVERAGE',max_tree_coverage)
3624    !
3625    !Config Key   = IND_0_ESTAB
3626    !Config Desc  =
3627    !Config If    = OK_DGVM
3628    !Config Def   = 0.2
3629    !Config Help  =
3630    !Config Units = [-] 
3631    CALL getin_p('IND_0_ESTAB',ind_0_estab)
3632
3633    !-
3634    ! light parameters
3635    !-
3636    !
3637    !Config Key   = ANNUAL_INCREASE
3638    !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)?
3639    !Config If    = OK_DGVM
3640    !Config Def   = y
3641    !Config Help  =
3642    !Config Units = [FLAG]
3643    CALL getin_p('ANNUAL_INCREASE',annual_increase)
3644    !
3645    !Config Key   = MIN_COVER
3646    !Config Desc  = For trees, minimum fraction of crown area occupied
3647    !Config If    = OK_DGVM
3648    !Config Def   = 0.05
3649    !Config Help  =
3650    !Config Units = [-] 
3651    CALL getin_p('MIN_COVER',min_cover)
3652
3653    !-
3654    ! pftinout parameters
3655    !
3656    !Config Key   = IND_0
3657    !Config Desc  = initial density of individuals
3658    !Config If    = OK_DGVM
3659    !Config Def   = 0.02
3660    !Config Help  =
3661    !Config Units = [-] 
3662    CALL getin_p('IND_0',ind_0)
3663    !
3664    !Config Key   = MIN_AVAIL
3665    !Config Desc  = minimum availability
3666    !Config If    = OK_DGVM
3667    !Config Def   = 0.01
3668    !Config Help  =
3669    !Config Units = [-] 
3670    CALL getin_p('MIN_AVAIL',min_avail)
3671    !
3672    !Config Key   = RIP_TIME_MIN
3673    !Config Desc  =
3674    !Config If    = OK_DGVM
3675    !Config Def   = 1.25
3676    !Config Help  =
3677    !Config Units = [year] 
3678    CALL getin_p('RIP_TIME_MIN',RIP_time_min)
3679    !
3680    !Config Key   = NPP_LONGTERM_INIT
3681    !Config Desc  =
3682    !Config If    = OK_DGVM
3683    !Config Def   = 10.
3684    !Config Help  =
3685    !Config Units = [gC/m^2/year]
3686    CALL getin_p('NPP_LONGTERM_INIT',npp_longterm_init)
3687    !
3688    !Config Key   = EVERYWHERE_INIT
3689    !Config Desc  =
3690    !Config If    = OK_DGVM
3691    !Config Def   = 0.05
3692    !Config Help  =
3693    !Config Units = [-]
3694    CALL getin_p('EVERYWHERE_INIT',everywhere_init)
3695
3696    !Config Key   = OK_FORCE_PHENO
3697    !Config Desc  = Use to force phenology when the conditions are not suitable
3698    !Config If    = OK_STOMATE
3699    !Config Def   = .TRUE.
3700    !Config Help  = Temperature phenology is very predictable and happens every year but
3701    !               moisture-driven phenology is less stable because the conditions
3702    !               may not be satisfied during 12 months resulting in a year without
3703    !               a canopy. If the model has passed the average budbreak day by a
3704    !               prescribed PFT-specific offset (::force_pheno), budbreak will be forced
3705    !               (given the condition that buds are avaialble)
3706    !Config Units = [-]
3707    CALL getin_p('OK_FORCE_PHENO',ok_force_pheno)
3708
3709  END SUBROUTINE config_dgvm_parameters
3710
3711
3712!! ================================================================================================================================
3713!! FUNCTION   : get_printlev
3714!!
3715!>\BRIEF        Read global PRINTLEV parmeter and local PRINTLEV_modname
3716!!
3717!! DESCRIPTION  : The first time this function is called the parameter PRINTLEV is read from run.def file.
3718!!                It is stored in the variable named printlev which is declared in constantes_var.f90. printlev
3719!!                can be accesed each module in ORCHIDEE which makes use of constantes_var module.
3720!!
3721!!                This function also reads the parameter PRINTLEV_modname for run.def file. modname is the
3722!!                intent(in) character string to this function. If the variable is set in run.def file, the corresponding
3723!!                value is returned. Otherwise the value of printlev is returnd as default.
3724!!
3725!! RECENT CHANGE(S): None
3726!!
3727!! MAIN OUTPUT VARIABLE(S): The local output level for the module set as intent(in) argument.
3728!!
3729!! REFERENCE(S) :
3730!!
3731!! FLOWCHART    :
3732!! \n
3733!_ ================================================================================================================================
3734
3735  FUNCTION get_printlev ( modname )
3736
3737    !! 0.1 Input arguments
3738    CHARACTER(LEN=*), INTENT(IN) :: modname
3739
3740    !! 0.2 Returned variable
3741    INTEGER(i_std)               :: get_printlev
3742
3743    !! 0.3 Local variables
3744    LOGICAL, SAVE :: first=.TRUE.
3745!$OMP THREADPRIVATE(first)
3746
3747    !_ ================================================================================================================================
3748
3749    !! 1.0  Read the global PRINTLEV from run.def. This is only done at first call to this function.
3750    IF (first) THEN
3751       !Config Key   = PRINTLEV
3752       !Config Desc  = Print level for text output
3753       !Config If    =
3754       !Config Help  = Possible values are:
3755       !Config         0    No output,
3756       !Config         1    Minimum writing for long simulations,
3757       !Config         2    More basic information for long simulations,
3758       !Config         3    First debug level,
3759       !Config         4    Higher debug level
3760       !Config Def   = 2
3761       !Config Units = [0, 1, 2, 3, 4]
3762       ! Default value is set in constantes_var
3763       CALL getin_p('PRINTLEV',printlev)
3764       first=.FALSE.
3765
3766       !Config Key   = PRINTLEV_modname
3767       !Config Desc  = Specific print level of text output for the module "modname". Default as PRINTLEV.
3768       !Config Def   = PRINTLEV
3769       !Config If    =
3770       !Config Help  = Use this option to activate a different level of text output
3771       !Config         for a specific module. This can be activated for several modules
3772       !Config         at the same time. Use for example PRINTLEV_sechiba.
3773       !Config Units = [0, 1, 2, 3, 4]
3774    END IF
3775
3776    ! Set default value as the standard printlev
3777    get_printlev=printlev
3778    ! Read optional value from run.def file
3779    CALL getin_p('PRINTLEV_'//modname, get_printlev)
3780
3781  END FUNCTION get_printlev
3782
3783
3784END MODULE constantes
Note: See TracBrowser for help on using the repository browser.