source: branches/publications/ORCHIDEE_SOM_13C_r4859/src_parameters/constantes.f90 @ 7911

Last change on this file since 7911 was 4859, checked in by marta.camino, 7 years ago

13C fractionation and root enrichment included and depth dependent diffusion coef

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