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

Last change on this file since 8418 was 8418, checked in by bertrand.guenet, 5 months ago

The Moyano function describing the soil moisture effect on OM decomposition is added

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