source: branches/publications/ORCHIDEE-LEAK-r5919/src_parameters/constantes.f90 @ 8066

Last change on this file since 8066 was 5315, checked in by ronny.lauerwald, 7 years ago

Bug fix DOC inputs in floodplains and swamps

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