source: branches/publications/ORCHIDEE_GLUC_r6545/src_parameters/constantes.f90 @ 8398

Last change on this file since 8398 was 5252, checked in by chao.yue, 6 years ago

commit a flag for transition involvign bioenergy

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