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

Last change on this file since 7820 was 7820, checked in by josefine.ghattas, 20 months ago

Update orchidee.default in ORCHIDEE_2_2 not done for a while. Change some comments to be capitalized to be corresponding to the keywords.

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