source: branches/publications/ORCHIDEE-ICE_SurfaceMassBalance/src_parameters/constantes.f90 @ 8398

Last change on this file since 8398 was 7396, checked in by christophe.dumas, 2 years ago

New 3 layer ice scheme on ice-sheet area that can be activated via the OK_ICE_SHEET flag

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