source: branches/publications/ORCHIDEE-PEAT_r5488/src_parameters/constantes.f90 @ 5491

Last change on this file since 5491 was 5323, checked in by chunjing.qiu, 6 years ago

Add oldpeat

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