source: branches/ORCHIDEE_2_2/ORCHIDEE/src_parameters/constantes.f90 @ 6396

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

Added link to ticket for information

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