source: branches/publications/ORCHIDEE_CAN_r3069/src_parameters/constantes.f90 @ 7346

Last change on this file since 7346 was 3069, checked in by sebastiaan.luyssaert, 9 years ago

PROD: tested gloabally for the zoomed European grid for 20 years. Do not use the previous commit as there were problems with svn it does not contain the described changes. This commit contains the bug fixes to species change and added functionality to change forest management following mortality or a harvest.

  • Property svn:keywords set to Date Revision
File size: 105.5 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!! ================================================================================================================================
46!! SUBROUTINE   : activate_sub_models
47!!
48!>\BRIEF         This subroutine reads the flags in the configuration file to
49!! activate some sub-models like routing, irrigation, fire, herbivory, ... 
50!!
51!! DESCRIPTION  : None
52!!
53!! RECENT CHANGE(S): None
54!!
55!! MAIN OUTPUT VARIABLE(S): None
56!!
57!! REFERENCE(S) : None
58!!
59!! FLOWCHART    : None
60!! \n
61!_ ================================================================================================================================
62
63   SUBROUTINE activate_sub_models(active_flags)
64
65     IMPLICIT NONE
66
67     !! 0. Variables and parameters declaration
68
69     !! 0.1 Input variables
70
71     TYPE(control_type), INTENT(in) :: active_flags     !! What parts of the code are activated ?
72
73     !! 0.4 Local variables
74
75     LOGICAL, SAVE ::  first_call = .TRUE.             !! To keep first call trace (true/false)
76!$OMP THREADPRIVATE(first_call)
77
78!_ ================================================================================================================================
79
80     IF (first_call) THEN
81           
82        IF (active_flags%ok_stomate) THEN
83
84           !
85           !Config Key   = TREAT_EXPANSION
86           !Config Desc  = treat expansion of PFTs across a grid cell?
87           !Config If    = OK_STOMATE
88           !Config Def   = n
89           !Config Help  = With this variable, you can determine
90           !Config         whether we treat expansion of PFTs across a
91           !Config         grid cell.
92           !Config Units = [FLAG]
93           CALL getin_p('TREAT_EXPANSION', treat_expansion)
94           !
95           !Config Key   = FIRE_DISABLE
96           !Config Desc  = no fire allowed
97           !Config If    = OK_STOMATE
98           !Config Def   = n
99           !Config Help  = With this variable, you can allow or not
100           !Config         the estimation of CO2 lost by fire
101           !Config Units = [FLAG]
102           CALL getin_p('FIRE_DISABLE', disable_fire)
103           !
104           !Config Key   = SPINUP_ANALYTIC
105           !Config Desc  = Activation of the analytic resolution of the spinup.
106           !Config If    = OK_STOMATE
107           !Config Def   = n
108           !Config Help  = Activate this option if you want to solve the spinup by the Gauss-Jordan method.
109           !Config Units = BOOLEAN   
110           CALL getin_p('SPINUP_ANALYTIC',spinup_analytic)
111
112        ENDIF
113
114        !
115        ! Check consistency (see later)
116        !
117!!$        IF(.NOT.(ok_routing) .AND. (doirrigation .OR. dofloodplains)) THEN
118!!$           CALL ipslerr_p(2,'activate_sub_models', &
119!!$               &     'Problem :you tried to activate the irrigation and floodplains without activating the routing',&
120!!$               &     'Are you sure ?', &
121!!$               &     '(check your parameters).')
122!!$        ENDIF
123       
124!!$        IF(.NOT.(ok_stomate) .AND. (ok_herbivores .OR. treat_expansion .OR. ok_constant_mortality &
125!!$            & .OR. harvest_agri .OR. disable_fire)) THEN
126!!$          CALL ipslerr_p(2,'activate_sub_models', &
127!!$               &     'Problem : try to activate the following options : herbivory, treat_expansion, fire,',&
128!!$               &     'harvest_agri and constant mortality without stomate activated.',&
129!!$               &     '(check your parameters).')
130!!$        ENDIF
131           
132        first_call =.FALSE.
133
134     ENDIF
135
136   END SUBROUTINE activate_sub_models
137!
138!=
139!
140
141!! ================================================================================================================================
142!! SUBROUTINE   : veget_config
143!!
144!>\BRIEF         This subroutine reads the flags controlling the configuration for
145!! the vegetation : impose_veg, veget_mpa, lai_map, etc...       
146!!
147!! DESCRIPTION  : None
148!!
149!! RECENT CHANGE(S): None
150!!
151!! MAIN OUTPUT VARIABLE(S):
152!!
153!! REFERENCE(S) :
154!!
155!! FLOWCHART    :
156!! \n
157!_ ================================================================================================================================
158
159   SUBROUTINE veget_config
160
161     IMPLICIT NONE
162
163     !! 0. Variables and parameters declaration
164
165     !! 0.4 Local variables 
166
167     LOGICAL, SAVE ::  first_call = .TRUE.        !! To keep first call trace (true/false) 
168!$OMP THREADPRIVATE(first_call)
169
170!_ ================================================================================================================================
171     
172     IF (first_call) THEN 
173
174        !Config Key   = AGRICULTURE
175        !Config Desc  = agriculture allowed?
176        !Config If    = OK_SECHIBA or OK_STOMATE
177        !Config Def   = y
178        !Config Help  = With this variable, you can determine
179        !Config         whether agriculture is allowed
180        !Config Units = [FLAG]
181        CALL getin_p('AGRICULTURE', agriculture)
182        !
183        !Config Key   = IMPOSE_VEG
184        !Config Desc  = Should the vegetation be prescribed ?
185        !Config If    = OK_SECHIBA or OK_STOMATE
186        !Config Def   = n
187        !Config Help  = This flag allows the user to impose a vegetation distribution
188        !Config         and its characteristics. It is espacially interesting for 0D
189        !Config         simulations. On the globe it does not make too much sense as
190        !Config         it imposes the same vegetation everywhere
191        !Config Units = [FLAG]
192        CALL getin_p('IMPOSE_VEG', impveg)
193
194        IF (impveg) THEN
195           !Config Key   = IMPOSE_SOILT
196           !Config Desc  = Should the soil type be prescribed ?
197           !Config Def   = n
198           !Config If    = IMPOSE_VEG
199           !Config Help  = This flag allows the user to impose a soil type distribution.
200           !Config         It is espacially interesting for 0D
201           !Config         simulations. On the globe it does not make too much sense as
202           !Config         it imposes the same soil everywhere
203           !Config Units = [FLAG]
204           CALL getin_p('IMPOSE_SOILT', impsoilt)     
205        ENDIF
206
207        !Config Key   = LAI_MAP
208        !Config Desc  = Read the LAI map
209        !Config If    = OK_SECHIBA or OK_STOMATE
210        !Config Def   = n
211        !Config Help  = It is possible to read a 12 month LAI map which will
212        !Config         then be interpolated to daily values as needed.
213        !Config Units = [FLAG]
214        CALL getin_p('LAI_MAP',read_lai)
215
216        IF(read_lai) THEN
217           !Config Key   = SLOWPROC_LAI_OLD_INTERPOL
218           !Config Desc  = Flag to use old "interpolation" of LAI
219           !Config If    = LAI_MAP
220           !Config Def   = n
221           !Config Help  = If you want to recover the old (ie orchidee_1_2 branch)
222           !Config         "interpolation" of LAI map.
223           !Config Units = [FLAG]
224           CALL getin_p('SLOWPROC_LAI_OLD_INTERPOL',old_lai)
225        ENDIF
226 
227        !Config Key   = LAND_USE
228        !Config Desc  = Read a land_use vegetation map
229        !Config If    = OK_SECHIBA or OK_STOMATE
230        !Config Def   = y
231        !Config Help  = pft values are needed, max time axis is 293
232        !Config Units = [FLAG]
233        CALL getin_p('LAND_USE',land_use)
234
235        IF(land_use) THEN
236           !Config Key   = VEGET_REINIT
237           !Config Desc  = booleen to indicate that a new LAND USE file will be used.
238           !Config If    = LAND_USE
239           !Config Def   = y
240           !Config Help  = The parameter is used to bypass veget_year count
241           !Config         and reinitialize it with VEGET_YEAR parameter.
242           !Config         Then it is possible to change LAND USE file.
243           !Config Units = [FLAG]
244           CALL getin_p('VEGET_REINIT', veget_reinit)
245           !
246!!$           ! MOVED to control-structure
247!!$           !Config Key   = LAND_COVER_CHANGE
248!!$           !Config Desc  = treat land use modifications
249!!$           !Config If    = LAND_USE
250!!$           !Config Def   = n
251!!$           !Config Help  = With this variable, you can use a Land Use map
252!!$           !Config         to simulate anthropic modifications such as
253!!$           !Config         deforestation.
254!!$           !Config Units = [FLAG]
255!!$           CALL getin_p('LAND_COVER_CHANGE', lcchange)
256           !
257           !Config Key   = VEGET_YEAR
258           !Config Desc  = Year of the land_use vegetation map to be read
259           !Config If    = LAND_USE
260           !Config Def   = 1
261           !Config Help  = First year for landuse vegetation (2D map by pft).
262           !Config         If VEGET_YEAR is set to 0, this means there is no time axis.
263           !Config Units = [FLAG]
264           CALL getin_p('VEGET_YEAR', veget_year_orig)
265        ENDIF
266
267        IF(.NOT. impveg .AND. .NOT. land_use) THEN
268           !Config Key   = SLOWPROC_VEGET_OLD_INTERPOL
269           !Config Desc  = Flag to use old "interpolation" of vegetation map.
270           !Config If    = NOT(IMPOSE_VEG) and NOT(LAND_USE)
271           !Config Def   = n
272           !Config Help  = If you want to recover the old (ie orchidee_1_2 branch)
273           !Config         "interpolation" of vegetation map.
274           !Config Units = [FLAG]
275           CALL getin_p('SLOWPROC_VEGET_OLD_INTERPOL',old_veget)
276         ENDIF 
277
278         !
279         ! Check consistency
280         !
281         ! 1. You have to activate agriculture and land_use
282         IF ( .NOT. agriculture .AND. land_use ) THEN
283            CALL ipslerr_p(2,'veget_config', &
284                 &     'Problem with agriculture desactivated and Land Use activated.',&
285                 &     'Are you sure ?', &
286                 &     '(check your parameters).')
287         ENDIF
288
289
290        first_call = .FALSE.
291
292     ENDIF
293
294!!$        ! DS : Add warning in case of a wrong configuration (need to be discussed)
295!!$        ! 2.
296!!$        IF (.NOT.(read_lai) .AND. old_lai) THEN
297!!$           CALL ipslerr_p(2,'veget_config', &
298!!$               &     'Problem with lai_map desactivated and old_lai activated.',&
299!!$               &     'Are you sure ?', &
300!!$               &     '(check your parameters).')
301!!$        ENDIF
302!!$   
303!!$        ! 3.
304!!$        IF ((impveg .OR. land_use) .AND. old_veget) THEN
305!!$           CALL ipslerr_p(2,'veget_config', &
306!!$                &     'Problem : try to use the old interpolation with a land use map or in impose_veg.',&
307!!$                &     'Are you sure ?', &
308!!$                &     '(check your parameters).')
309!!$        ENDIF
310!!$
311!!$        ! 4.
312!!$        IF ( .NOT.(impveg) .AND. impsoilt) THEN
313!!$           CALL ipslerr_p(2,'veget_config', &
314!!$               &     'Problem : try to activate impose_soilt without activating impose_veg.',&
315!!$               &     'Are you sure ?', &
316!!$               &     '(check your parameters).')
317!!$        ENDIF
318!!$
319!!$        ! 5.
320!!$        IF (.NOT.(land_use) .AND. (veget_reinit)) THEN
321!!$           CALL ipslerr_p(2,'veget_config', &
322!!$                &     'Problem : try to use a land_use map without activating land_use.',&
323!!$                &     'Are you sure ?', &
324!!$                &     '(check your parameters).')       
325!!$        ENDIF
326!!$
327!!$        ! 6.
328!!$        IF (.NOT.(land_use) .AND. lcchange) THEN
329!!$           CALL ipslerr_p(2,'veget_config', &
330!!$                &     'Problem : lcchange is activated without activating land_use.',&
331!!$                &     'Are you sure ?', &
332!!$                &     '(check your parameters).')       
333!!$        ENDIF
334           
335   END SUBROUTINE veget_config
336!
337!=
338!
339
340!! ================================================================================================================================
341!! SUBROUTINE   : veget_config
342!!
343!>\BRIEF         This subroutine reads in the configuration file the imposed values of the parameters for all SECHIBA modules. 
344!!
345!! DESCRIPTION  : None
346!!
347!! RECENT CHANGE(S): None
348!!
349!! MAIN OUTPUT VARIABLE(S):
350!!
351!! REFERENCE(S) :
352!!
353!! FLOWCHART    :
354!! \n
355!_ ================================================================================================================================
356
357   SUBROUTINE config_sechiba_parameters(active_flags)
358
359     IMPLICIT NONE
360
361     !! 0. Variables and parameters declaration
362
363     !! 0.1 Input variables
364
365     TYPE(control_type), INTENT(in) :: active_flags     !! What parts of the code are activated ?
366
367     !! 0.4 Local variables
368     
369     LOGICAL, SAVE ::  first_call = .TRUE.    !! To keep first call trace (true/false)
370!$OMP THREADPRIVATE(first_call)
371     INTEGER :: ier, ilevel
372
373!_ ================================================================================================================================
374     
375     IF(first_call) THEN 
376       
377        ! Global : parameters used by many modules
378        !
379        !Config Key   = MAXMASS_SNOW
380        !Config Desc  = The maximum mass of a snow pack
381        !Config If    = OK_SECHIBA or HYDROL_CWRR
382        !Config Def   = 3000.
383        !Config Help  =
384        !Config Units = [kg/m^2] 
385        CALL getin_p('MAXMASS_SNOW',maxmass_snow)
386        !
387        !Config Key   = SNOWCRI
388        !Config Desc  = Sets the amount above which only sublimation occures
389        !Config If    = OK_SECHIBA or HYDROL_CWRR
390        !Config Def   = 1.5
391        !Config Help  =
392        !Config Units = [kg/m^2] 
393        CALL getin_p('SNOWCRI',snowcri)
394        !
395        !! Initialization of sneige
396        sneige = snowcri/mille
397        !
398        !Config Key   = MIN_WIND
399        !Config Desc  = Minimum wind speed
400        !Config If    = OK_SECHIBA
401        !Config Def   = 0.1
402        !Config Help  =
403        !Config Units = [m/s]
404        CALL getin_p('MIN_WIND',min_wind)
405        !
406        !Config Key   = MAX_SNOW_AGE
407        !Config Desc  = Maximum period of snow aging
408        !Config If    = OK_SECHIBA
409        !Config Def   = 50.
410        !Config Help  =
411        !Config Units = [days?]
412        CALL getin_p('MAX_SNOW_AGE',max_snow_age)
413        !
414        !Config Key   = SNOW_TRANS
415        !Config Desc  = Transformation time constant for snow
416        !Config If    = OK_SECHIBA
417        !Config Def   = 0.3
418        !Config Help  =
419        !Config Units = [m]   
420        CALL getin_p('SNOW_TRANS',snow_trans)
421 
422        !-
423        ! condveg
424        !-
425        !
426        !Config Key   = Z0_OVER_HEIGHT
427        !Config Desc  = to get z0 from height
428        !Config If    = OK_SECHIBA
429        !Config Def   = 1/16.
430        !Config Help  =
431        !Config Units = [-]   
432        CALL getin_p('Z0_OVER_HEIGHT',z0_over_height)
433        !
434        !Config Key   = HEIGHT_DISPLACEMENT
435        !Config Desc  = Magic number which relates the height to the displacement height.
436        !Config If    = OK_SECHIBA
437        !Config Def   = 0.75
438        !Config Help  =
439        !Config Units = [m] 
440        CALL getin_p('HEIGHT_DISPLACEMENT',height_displacement)
441        !
442        !Config Key   = Z0_BARE
443        !Config Desc  = bare soil roughness length
444        !Config If    = OK_SECHIBA
445        !Config Def   = 0.01
446        !Config Help  =
447        !Config Units = [m]   
448        CALL getin_p('Z0_BARE',z0_bare)
449        !
450        !Config Key   = Z0_ICE
451        !Config Desc  = ice roughness length
452        !Config If    = OK_SECHIBA
453        !Config Def   = 0.001
454        !Config Help  =
455        !Config Units = [m]   
456        CALL getin_p('Z0_ICE',z0_ice)
457        !
458        !Config Key   = TCST_SNOWA
459        !Config Desc  = Time constant of the albedo decay of snow
460        !Config If    = OK_SECHIBA
461        !Config Def   = 5.0
462        !Config Help  =
463        !Config Units = [days]
464        CALL getin_p('TCST_SNOWA',tcst_snowa)
465        !
466        !Config Key   = SNOWCRI_ALB
467        !Config Desc  = Critical value for computation of snow albedo
468        !Config If    = OK_SECHIBA
469        !Config Def   = 10.
470        !Config Help  =
471        !Config Units = [cm] 
472        CALL getin_p('SNOWCRI_ALB',snowcri_alb)
473        !
474        !
475        !Config Key   = VIS_DRY
476        !Config Desc  = The correspondance table for the soil color numbers and their albedo
477        !Config If    = OK_SECHIBA
478        !Config Def   = 0.24, 0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.27
479        !Config Help  =
480        !Config Units = [-] 
481        CALL getin_p('VIS_DRY',vis_dry)
482        !
483        !Config Key   = NIR_DRY
484        !Config Desc  = The correspondance table for the soil color numbers and their albedo
485        !Config If    = OK_SECHIBA
486        !Config Def   = 0.48, 0.44, 0.40, 0.36, 0.32, 0.28, 0.24, 0.20, 0.55
487        !Config Help  =
488        !Config Units = [-]   
489        CALL getin_p('NIR_DRY',nir_dry)
490        !
491        !Config Key   = VIS_WET
492        !Config Desc  = The correspondance table for the soil color numbers and their albedo
493        !Config If    = OK_SECHIBA 
494        !Config Def   = 0.12, 0.11, 0.10, 0.09, 0.08, 0.07, 0.06, 0.05, 0.15
495        !Config Help  =
496        !Config Units = [-]   
497        CALL getin_p('VIS_WET',vis_wet)
498        !
499        !Config Key   = NIR_WET
500        !Config Desc  = The correspondance table for the soil color numbers and their albedo
501        !Config If    = OK_SECHIBA
502        !Config Def   = 0.24, 0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.31
503        !Config Help  =
504        !Config Units = [-]   
505        CALL getin_p('NIR_WET',nir_wet)
506        !
507        !Config Key   = ALBSOIL_VIS
508        !Config Desc  =
509        !Config If    = OK_SECHIBA
510        !Config Def   = 0.18, 0.16, 0.16, 0.15, 0.12, 0.105, 0.09, 0.075, 0.25
511        !Config Help  =
512        !Config Units = [-] 
513        CALL getin_p('ALBSOIL_VIS',albsoil_vis)
514        !
515        !Config Key   = ALBSOIL_NIR
516        !Config Desc  =
517        !Config If    = OK_SECHIBA
518        !Config Def   = 0.36, 0.34, 0.34, 0.33, 0.30, 0.25, 0.20, 0.15, 0.45
519        !Config Help  =
520        !Config Units = [-] 
521        CALL getin_p('ALBSOIL_NIR',albsoil_nir)
522        !-
523        !
524        !Config Key   = ALB_DEADLEAF
525        !Config Desc  = albedo of dead leaves, VIS+NIR
526        !Config If    = OK_SECHIBA
527        !Config Def   = 0.12, 0.35
528        !Config Help  =
529        !Config Units = [-]     
530        CALL getin_p('ALB_DEADLEAF',alb_deadleaf)
531        !
532        !Config Key   = ALB_ICE
533        !Config Desc  = albedo of ice, VIS+NIR
534        !Config If    = OK_SECHIBA
535        !Config Def   = 0.60, 0.20
536        !Config Help  =
537        !Config Units = [-] 
538        CALL getin_p('ALB_ICE',alb_ice)
539        !
540        !Config Key   = mstemp
541        !Config Desc  = global annual mean surface temperature
542        !Config If    = OK_STOMATE
543        !Config Def   = 13.9
544        !Config Help  =
545        !Config Units = [-] 
546        CALL getin_p('MSTEMP',mstemp)
547        !
548        !
549        ! Get the fixed snow albedo if needed
550        !
551        !Config Key   = CONDVEG_SNOWA
552        !Config Desc  = The snow albedo used by SECHIBA
553        !Config Def   = 1.E+20
554        !Config if    = OK_SECHIBA
555        !Config Help  = This option allows the user to impose a snow albedo.
556        !Config         Default behaviour is to use the model of snow albedo
557        !Config         developed by Chalita (1993).
558        !Config Units = [-]
559        CALL getin_p('CONDVEG_SNOWA',fixed_snow_albedo)
560        !
561        !Config Key   = ALB_BARE_MODEL
562        !Config Desc  = Switch bare soil albedo dependent (if TRUE) on soil wetness
563        !Config Def   = n
564        !Config if    = OK_SECHIBA
565        !Config Help  = If TRUE, the model for bare soil albedo is the old formulation.
566        !Config         Then it depend on the soil dry or wetness. If FALSE, it is the
567        !Config         new computation that is taken, it is the mean of soil albedo.
568        !Config Units = [FLAG]
569        CALL getin_p('ALB_BARE_MODEL',alb_bare_model)
570        !
571        !Config Key   = Z0CDRAG_AVE
572        !Config Desc  = Average method for z0
573        !Config Def   = y
574        !Config if    = OK_SECHIBA
575        !Config Help  = If this flag is set to true (y) then the neutral Cdrag
576        !Config         is averaged instead of the log(z0). This should be
577        !Config         the prefered option. We still wish to keep the other
578        !Config         option so we can come back if needed. If this is
579        !Config         desired then one should set Z0CDRAG_AVE=n
580        !Config Units = [FLAG]
581        CALL getin_p('Z0CDRAG_AVE',z0cdrag_ave)
582        !
583        !Config Key   = IMPOSE_AZE
584        !Config Desc  = Should the surface parameters be prescribed
585        !Config Def   = n
586        !Config if    = OK_SECHIBA
587        !Config Help  = This flag allows the user to impose the surface parameters
588        !Config         (Albedo Roughness and Emissivity). It is espacially interesting for 0D
589        !Config         simulations. On the globe it does not make too much sense as
590        !Config         it imposes the same vegetation everywhere
591        !Config Units = [FLAG]
592        CALL getin_p('IMPOSE_AZE',impaze)
593        !
594        IF(impaze) THEN
595           !
596           !Config Key   = CONDVEG_Z0
597           !Config Desc  = Surface roughness
598           !Config Def   = 0.15
599           !Config If    = IMPOSE_AZE
600           !Config Help  = Surface rougness to be used on the point if a 0-dim version
601           !Config         of SECHIBA is used. Look at the description of the forcing 
602           !Config         data for the correct value.
603           !Config Units = [m]
604           CALL getin_p('CONDVEG_Z0', z0_scal) 
605           !
606           !Config Key   = ROUGHHEIGHT
607           !Config Desc  = Height to be added to the height of the first level
608           !Config Def   = 0.0
609           !Config If    = IMPOSE_AZE
610           !Config Help  = ORCHIDEE assumes that the atmospheric level height is counted
611           !Config         from the zero wind level. Thus to take into account the roughness
612           !Config         of tall vegetation we need to correct this by a certain fraction
613           !Config         of the vegetation height. This is called the roughness height in
614           !Config         ORCHIDEE talk.
615           !Config Units = [m]
616           CALL getin_p('ROUGHHEIGHT', roughheight_scal)
617           !
618           !Config Key   = CONDVEG_ALBVIS
619           !Config Desc  = SW visible albedo for the surface
620           !Config Def   = 0.25
621           !Config If    = IMPOSE_AZE
622           !Config Help  = Surface albedo in visible wavelengths to be used
623           !Config         on the point if a 0-dim version of SECHIBA is used.
624           !Config         Look at the description of the forcing data for
625           !Config         the correct value.
626           !Config Units = [-]
627           CALL getin_p('CONDVEG_ALBVIS', albedo_scal(ivis))
628           !
629           !Config Key   = CONDVEG_ALBNIR
630           !Config Desc  = SW near infrared albedo for the surface
631           !Config Def   = 0.25
632           !Config If    = IMPOSE_AZE
633           !Config Help  = Surface albedo in near infrared wavelengths to be used
634           !Config         on the point if a 0-dim version of SECHIBA is used.
635           !Config         Look at the description of the forcing data for
636           !Config         the correct value.
637           !Config Units = [-] 
638           CALL getin_p('CONDVEG_ALBNIR', albedo_scal(inir))
639           !
640           !Config Key   = CONDVEG_EMIS
641           !Config Desc  = Emissivity of the surface for LW radiation
642           !Config Def   = 1.0
643           !Config If    = IMPOSE_AZE
644           !Config Help  = The surface emissivity used for compution the LE emission
645           !Config         of the surface in a 0-dim version. Values range between
646           !Config         0.97 and 1.. The GCM uses 0.98.
647           !Config Units = [-]
648           CALL getin_p('CONDVEG_EMIS', emis_scal)
649
650        ENDIF
651
652        !-
653        ! Variables related to the explicitsnow module
654        !-
655        !Config Key = xansmax
656        !Config Desc = maximum snow albedo
657        !Config If = OK_SECHIBA
658        !Config Def = 0.85
659        !Config Help =
660        !Config Units = [-]
661        CALL getin_p('XANSMAX',xansmax)
662        !
663        !Config Key = xansmin
664        !Config Desc = minimum snow albedo
665        !Config If = OK_SECHIBA
666        !Config Def = 0.50
667        !Config Help =
668        !Config Units = [-]
669        CALL getin_p('XANSMIN',xansmin)
670        !
671        !Config Key = xans_todry
672        !Config Desc = albedo decay rate for the dry snow
673        !Config If = OK_SECHIBA
674        !Config Def = 0.008
675        !Config Help =
676        !Config Units = [S-1]
677        CALL getin_p('XANSDRY',xans_todry)
678        !
679        !Config Key = xans_t
680        !Config Desc = albedo decay rate for the wet snow
681        !Config If = OK_SECHIBA
682        !Config Def = 0.24
683        !Config Help =
684        !Config Units = [S-1]
685        CALL getin_p('XANS_T',xans_t)
686
687        !Config Key = xrhosmax
688        !Config Desc = maximum snow density
689        !Config If = OK_SECHIBA
690        !Config Def = 750
691        !Config Help =
692        !Config Units = [-]
693        CALL getin_p('XRHOSMAX',xrhosmax)
694        !
695        !Config Key = xwsnowholdmax1
696        !Config Desc = snow holding capacity 1
697        !Config If = OK_SECHIBA
698        !Config Def = 0.03
699        !Config Help =
700        !Config Units = [-]
701        CALL getin_p('XWSNOWHOLDMAX1',xwsnowholdmax1)
702        !
703        !Config Key = xwsnowholdmax2
704        !Config Desc = snow holding capacity 2
705        !Config If = OK_SECHIBA
706        !Config Def = 0.10
707        !Config Help =
708        !Config Units = [-]
709        CALL getin_p('XWSNOWHOLDMAX2',xwsnowholdmax2)
710        !
711        !Config Key = xsnowrhohold
712        !Config Desc = snow density
713        !Config If = OK_SECHIBA
714        !Config Def = 200.0
715        !Config Help =
716        !Config Units = [kg/m3]
717        CALL getin_p('XSNOWRHOHOLD',xsnowrhohold)
718        !
719        !Config Key = ZSNOWTHRMCOND1
720        !Config Desc = Thermal conductivity Coef 1
721        !Config If = OK_SECHIBA
722        !Config Def = 0.02
723        !Config Help =
724        !Config Units = [W/m/K]
725        CALL getin_p('ZSNOWTHRMCOND1',ZSNOWTHRMCOND1)
726        !
727        !Config Key = ZSNOWTHRMCOND2
728        !Config Desc = Thermal conductivity Coef 2
729        !Config If = OK_SECHIBA
730        !Config Def = 2.5E-6
731        !Config Help =
732        !Config Units = [W m5/(kg2 K)]
733        CALL getin_p('ZSNOWTHRMCOND2',ZSNOWTHRMCOND2)
734        !
735        !Config Key = ZSNOWTHRMCOND_AVAP
736        !Config Desc = Thermal conductivity Coef 1 water vapor
737        !Config If = OK_SECHIBA
738        !Config Def = -0.06023
739        !Config Help =
740        !Config Units = [W/m/K]
741        CALL getin_p('ZSNOWTHRMCOND_AVAP',ZSNOWTHRMCOND_AVAP)
742        !
743        !Config Key = ZSNOWTHRMCOND_BVAP
744        !Config Desc = Thermal conductivity Coef 2 water vapor
745        !Config If = OK_SECHIBA
746        !Config Def = -2.5425
747        !Config Help =
748        !Config Units = [W/m]
749        CALL getin_p('ZSNOWTHRMCOND_BVAP',ZSNOWTHRMCOND_BVAP)
750        !
751        !Config Key = ZSNOWTHRMCOND_CVAP
752        !Config Desc = Thermal conductivity Coef 3 water vapor
753        !Config If = OK_SECHIBA
754        !Config Def = -289.99
755        !Config Help =
756        !Config Units = [K]
757        CALL getin_p('ZSNOWTHRMCOND_CVAP',ZSNOWTHRMCOND_CVAP)
758
759        !Snow compaction factors
760        !Config Key = ZSNOWCMPCT_RHOD
761        !Config Desc = Snow compaction coefficent
762        !Config If = OK_SECHIBA
763        !Config Def = 150.0
764        !Config Help =
765        !Config Units = [kg/m3]
766        CALL getin_p('ZSNOWCMPCT_RHOD',ZSNOWCMPCT_RHOD)
767
768        !Config Key = ZSNOWCMPCT_ACM
769        !Config Desc = Coefficent for the thermal conductivity
770        !Config If = OK_SECHIBA
771        !Config Def = 2.8e-6
772        !Config Help =
773        !Config Units = [1/s]
774        CALL getin_p('ZSNOWCMPCT_ACM',ZSNOWCMPCT_ACM)
775
776        !Config Key = ZSNOWCMPCT_BCM
777        !Config Desc = Coefficent for the thermal conductivity
778        !Config If = OK_SECHIBA
779        !Config Def = 0.04
780        !Config Help =
781        !Config Units = [1/K]
782        CALL getin_p('ZSNOWCMPCT_BCM',ZSNOWCMPCT_BCM)
783
784        !Config Key = ZSNOWCMPCT_CCM
785        !Config Desc = Coefficent for the thermal conductivity
786        !Config If = OK_SECHIBA
787        !Config Def = 460.
788        !Config Help =
789        !Config Units = [m3/kg]
790        CALL getin_p('ZSNOWCMPCT_CCM',ZSNOWCMPCT_CCM)
791
792        !Config Key = ZSNOWCMPCT_V0
793        !Config Desc = Vapor coefficent for the thermal conductivity
794        !Config If = OK_SECHIBA
795        !Config Def = 3.7e7
796        !Config Help =
797        !Config Units = [Pa/s]
798        CALL getin_p('ZSNOWCMPCT_V0',ZSNOWCMPCT_V0)
799
800        !Config Key = ZSNOWCMPCT_VT
801        !Config Desc = Vapor coefficent for the thermal conductivity
802        !Config If = OK_SECHIBA
803        !Config Def = 0.081
804        !Config Help =
805        !Config Units = [1/K]
806        CALL getin_p('ZSNOWCMPCT_VT',ZSNOWCMPCT_VT)
807
808        !Config Key = ZSNOWCMPCT_VR
809        !Config Desc = Vapor coefficent for the thermal conductivity
810        !Config If = OK_SECHIBA
811        !Config Def = 0.018
812        !Config Help =
813        !Config Units = [m3/kg]
814        CALL getin_p('ZSNOWCMPCT_VR',ZSNOWCMPCT_VR)
815
816
817        !Surface resistance
818        !
819        !Config Key = CB
820        !Config Desc = Constant of the Louis scheme
821        !Config If = OK_SECHIBA
822        !Config Def = 5.0
823        !Config Help =
824        !Config Units = [-]
825        CALL getin_p('CB',cb)
826        !
827        !Config Key = CC
828        !Config Desc = Constant of the Louis scheme
829        !Config If = OK_SECHIBA
830        !Config Def = 5.0
831        !Config Help =
832        !Config Units = [-]
833        CALL getin_p('CC',cc)
834        !
835        !Config Key = CD
836        !Config Desc = Constant of the Louis scheme
837        !Config If = OK_SECHIBA
838        !Config Def = 5.0
839        !Config Help =
840        !Config Units = [-]
841        CALL getin_p('CD',cd)
842        !
843        !Config Key = RAYT_CSTE
844        !Config Desc = Constant in the computation of surface resistance 
845        !Config If = OK_SECHIBA
846        !Config Def = 125
847        !Config Help =
848        !Config Units = [W.m^{-2}]
849        CALL getin_p('RAYT_CSTE',rayt_cste)
850        !
851        !Config Key = DEFC_PLUS
852        !Config Desc = Constant in the computation of surface resistance 
853        !Config If = OK_SECHIBA
854        !Config Def = 23.E-3
855        !Config Help =
856        !Config Units = [K.W^{-1}]
857        CALL getin_p('DEFC_PLUS',defc_plus)
858        !
859        !Config Key = DEFC_MULT
860        !Config Desc = Constant in the computation of surface resistance 
861        !Config If = OK_SECHIBA
862        !Config Def = 1.5
863        !Config Help =
864        !Config Units = [K.W^{-1}]
865        CALL getin_p('DEFC_MULT',defc_mult)
866
867
868
869           !
870           ! Configuration : The number of canopy levels to use in the albedo and energy budget
871           !
872
873!!$           !Config Key   = NLEVELS
874!!$           !Config Desc  = number of canopy levels
875!!$           !Config If    = OK_SECHIBA
876!!$           !Config Def   = 1
877!!$           !Config Help  = The number of canopy levels to be used in the energy budget/albedo
878!!$           !Config Units = [-]
879!!$           !
880!!$           nlevels=1
881!!$           CALL getin_p("NLEVELS",nlevels)
882!!$           WRITE(numout,*)'The number of canopy levels used by the albedo is : ', nlevels
883           !Config Key   = NLEVELS_PHOTO
884           !Config Desc  = number of photosyntheis canopy levels per enegy budget canopy level
885           !Config If    = OK_SECHIBA
886           !Config Def   = 4
887           !Config Help  = The number of canopy levels to be used in photosynthesis
888           !Config Units = [-]
889           !
890           nlevels_photo=20
891           CALL getin_p("NLEVELS_PHOTO",nlevels_photo)
892           WRITE(numout,'(I4,A)') nlevels_photo,' levels are used for each canopy ' &
893                // 'level to calculate photosynthesis.'
894
895           ! This is a variable that we'll pass around for convenience, in particular
896           ! when going into a subroutine.
897           nlevels_tot = nlevels * nlevels_photo
898
899!!$           ALLOCATE(z_level(1:nlevels),stat=ier)
900!!$           IF (ier .NE. 0) THEN
901!!$              WRITE (numout,*) ' error in z_level allocation. We stop. We need nlevels words = ',nlevels
902!!$              CALL ipslerr_p(3,'constantes.f90','config_sechiba_parameters','','')
903!!$           ENDIF
904!!$           IF(nlevels .GT. 1)THEN
905!!$              ! if you are using more than one level, you need to define the bottom of the level heights,
906!!$              ! in meters
907!!$
908!!$              !Config Key   = Z_LEVEL
909!!$              !Config Desc  = Height of the bottom of each level
910!!$              !Config If    = OK_SECHIBA
911!!$              !Config Def   = 0.0
912!!$              !Config Help  = The number of canopy levels to be used in the energy budget/albedo
913!!$              !Config Units = [-]
914!!$              CALL getin_p('Z_LEVEL',z_level(:))
915!!$
916!!$              WRITE(numout,*) 'WARNING: Using more than one canopy level.'
917!!$              WRITE(numout,*) '         Double check the input file to be sure that you give the lower level boundaries'
918!!$              WRITE(numout,*) '         for EACH level, as I cannot verify that myself.'
919!!$
920!!$           ELSE
921!!$              z_level(1)=zero
922!!$           ENDIF
923
924           DO ilevel=1,nlevels
925              WRITE(numout,*) 'Albedo canopy level ',ilevel,' has a lower boundary at ',z_level(ilevel),' meters.'
926           ENDDO
927
928
929
930
931        !Config Key   = JNLVLS
932        !Config Desc  = number of total levels in the energy budget scheme
933        !Config If    = OK_SECHIBA
934        !Config Def   = 1
935        !Config Help  = The number of total levels in the energy budget scheme
936        !Config Units = [-]
937        !
938        jnlvls = 1                     !! Number of levels in the multilayer energy budget scheme
939        CALL getin_p("JNLVLS",jnlvls)
940        WRITE(numout,'(I4,A)') jnlvls,' total levels are used in the multilayer'  &
941                // 'energy budget scheme.'
942
943        jnlvls_under = 10               !! Number of levels in the understorey of the multilayer energy budget scheme
944
945
946        !Config Key   = JNLVLS_UNDER
947        !Config Desc  = number of canopy levels in the understorey of the energy budget scheme
948        !Config If    = OK_SECHIBA
949        !Config Def   = 1
950        !Config Help  = The number of canopy levels in the understorey of the energy budget scheme
951        !Config Units = [-]
952        !
953
954        CALL getin_p("JNLVLS_UNDER",jnlvls_under)
955           WRITE(numout,'(I4,A)') jnlvls_under,' levels are used for the understorey ' &
956                // 'in the multilayer energy budget scheme.'
957
958        jnlvls_canopy = 8               !! Number of levels in the canopy of the multilayer energy budget scheme
959
960
961        !Config Key   = JNLVLS_CANOPY
962        !Config Desc  = number of levels in the canopy of the energy budget scheme
963        !Config If    = OK_SECHIBA
964        !Config Def   = 1
965        !Config Help  = The number of levels in the canopy of the energy budget scheme
966        !Config Units = [-]
967        !
968
969        CALL getin_p("JNLVLS_CANOPY",jnlvls_canopy)
970        WRITE(numout,'(I4,A)') jnlvls_canopy,' levels are used for the canopy ' &
971                // 'in the multilayer energy budget scheme.'
972
973        jnlvls_over = 11                !! Number of levels in the overstorey of the multilayer energy budget scheme
974
975
976        !Config Key   = JNLVLS_OVER
977        !Config Desc  = number of canopy levels in the overstorey of the energy budget scheme
978        !Config If    = OK_SECHIBA
979        !Config Def   = 1
980        !Config Help  = The number of canopy levels in the overstorey of the energy budget scheme
981        !Config Units = [-]
982        !
983
984        CALL getin_p("JNLVLS_OVER",jnlvls_over)
985        WRITE(numout,'(I4,A)') jnlvls_over,' levels are used for the overstorey ' &
986                // 'in the multilayer energy budget scheme.'
987
988
989        !
990        !-
991        ! diffuco
992        !-
993        !
994        !Config Key   = NLEV_TOP
995        !Config Desc  = Maximum number of canopy levels that are
996        !               used to construct the "top" layer of the
997        !               canopy. The top layer is used in the
998        !               calculation transpiration.
999        !               Should not exceed nlevels_photo
1000        !Config If    = OK_SECHIBA
1001        !Config Def   = 20
1002        !Config Help  =
1003        !Config Units = [-]
1004        nlev_top = 20
1005        CALL getin_p('NLEV_TOP',nlev_top)       
1006        IF(nlev_top .GT. nlevels_photo) THEN
1007           nlev_top = nlevels_photo
1008           WRITE(numout,*) 'The numbers of levels in the "top" was '
1009           WRITE(numout,*) '  larger than the total number of levels'
1010           WRITE(numout,*) '  AUTO CORRECT: nlev_top now = ',nlev_top
1011        ENDIF
1012
1013        !Config Key   = NLAI
1014        !Config Desc  = Number of LAI levels
1015        !Config If    = OK_SECHIBA
1016        !Config Def   = 20
1017        !Config Help  =
1018        !Config Units = [-] 
1019        CALL getin_p('NLAI',nlai)
1020        !
1021        !Config Key   = LAIMAX
1022        !Config Desc  = Maximum LAI
1023        !Config If    = OK_SECHIBA
1024        !Config Def   =
1025        !Config Help  =
1026        !Config Units = [m^2/m^2]   
1027        CALL getin_p('LAIMAX',laimax)
1028        !
1029        !Config Key   = DEW_VEG_POLY_COEFF
1030        !Config Desc  = coefficients of the polynome of degree 5 for the dew
1031        !Config If    = OK_SECHIBA
1032        !Config Def   = 0.887773, 0.205673, 0.110112, 0.014843, 0.000824, 0.000017
1033        !Config Help  =
1034        !Config Units = [-]   
1035        CALL getin_p('DEW_VEG_POLY_COEFF',dew_veg_poly_coeff)
1036        !
1037        !Config Key   = DOWNREGULATION_CO2
1038        !Config Desc  = Activation of CO2 downregulation
1039        !Config If    = OK_SECHIBA
1040        !Config Def   = n
1041        !Config Help  =
1042        !Config Units = [FLAG]   
1043        CALL getin_p('DOWNREGULATION_CO2',downregulation_co2)
1044        !
1045        !Config Key   = DOWNREGULATION_CO2_BASELEVEL
1046        !Config Desc  = CO2 base level
1047        !Config If    = OK_SECHIBA
1048        !Config Def   = 280.
1049        !Config Help  =
1050        !Config Units = [ppm]   
1051        CALL getin_p('DOWNREGULATION_CO2_BASELEVEL',downregulation_co2_baselevel)
1052        !-
1053        ! slowproc
1054        !-
1055        !
1056        !Config Key   = CLAYFRACTION_DEFAULT
1057        !Config Desc  = default fraction of clay
1058        !Config If    = OK_SECHIBA
1059        !Config Def   = 0.2
1060        !Config Help  =
1061        !Config Units = [-]   
1062        CALL getin_p('CLAYFRACTION_DEFAULT',clayfraction_default)
1063        !
1064        !Config Key   = MIN_VEGFRAC
1065        !Config Desc  = Minimal fraction of mesh a vegetation type can occupy
1066        !Config If    = OK_SECHIBA
1067        !Config Def   = 0.001
1068        !Config Help  =
1069        !Config Units = [-] 
1070        CALL getin_p('MIN_VEGFRAC',min_vegfrac)
1071        !
1072        !Config Key   = STEMPDIAG_BID
1073        !Config Desc  = only needed for an initial LAI if there is no restart file
1074        !Config If    = OK_SECHIBA
1075        !Config Def   = 280.
1076        !Config Help  =
1077        !Config Units = [K]
1078        CALL getin_p('STEMPDIAG_BID',stempdiag_bid)
1079        !
1080        !Config Key   = LSCALE_LCC_NOBIO
1081        !Config Desc  = Scale new land cover maps to match the nobio fraction of the current one.
1082        !Config If    = LAND_USE
1083        !Config Def   = n
1084        !Config Help  = This scales every pixel on new land cover maps to match the nobio fraction
1085        !               of the current map.  The reason for this is to avoid crashes in land cover
1086        !               change due to small differences in nobio fractions.  CAUTION: This flag should
1087        !               only be used if you have created and/or checked your land cover maps to
1088        !               make sure the nobio fraction does not change!
1089        !Config Units = [FLAG]   
1090        CALL getin_p('LSCALE_LCC_NOBIO',lscale_lcc_nobio)
1091        !
1092        !Config Key   = LIGNORE_LCC_STOPS
1093        !Config Desc  = Ignore a few STOP statements related to land cover change.
1094        !Config If    = LAND_USE
1095        !Config Def   = n
1096        !Config Help  = If this is set to TRUE, a few error messages which would ordinarly produce
1097        !               program exists just produce warnings and the code continues.  This is only
1098        !               to be used in some very specific circumstances (for example, between
1099        !               an analyical and transient spinup where land cover maps have changed slightly).
1100        !               If you didn't add this option yourself, you probably shouldn't be using it.
1101        CALL getin_p('LIGNORE_LCC_STOPS',lignore_lcc_stops)
1102        !
1103        !Config Key   = ALBEDO_TYPE
1104        !Config Desc  = Specify the albedo type used if not using the standard
1105        !Config Def   = standard
1106        !Config If    = OK_ALBEDO
1107        !Config Help  = There are currently two albedo models supported
1108        !Config         'standard' : The standard scheme, with a preset value 
1109        !Config         'pinty' : The scheme of Pinty et al 2006, which feedsback into the model
1110        !Config                   and is a two stream method
1111        !Config Units = [-]
1112        !
1113        albedo_type = 'standard'
1114        ! If the DOFOCO flag is on, we have a specific albedo type.
1115        IF(active_flags%ok_dofoco)THEN
1116           ! Note that nothing will be written to the used_run_def because getin_p is not used
1117           albedo_type = 'pinty'
1118           WRITE(numout,*) "OK_DOFOCO flag has been set.  Ignoring albedo_type in the run.def.  Using ALBEDO_TYPE=pinty."
1119        ELSE
1120            CALL getin_p('ALBEDO_TYPE',albedo_type)
1121        ENDIF
1122        SELECTCASE (albedo_type)
1123        CASE ('standard', 'Standard','STANDARD')
1124           albedo_type = 'standard'
1125        CASE ('pinty','Pinty','PINTY')
1126           albedo_type = 'pinty'
1127        CASE DEFAULT
1128           WRITE(numout,*) "Unsupported albedo type. Choose between standard and pinty."
1129           CALL ipslerr_p(3,'constantes.f90','intsurf_config','','')
1130        ENDSELECT
1131        WRITE(numout,*) "Albedo type being used : ",albedo_type
1132        !
1133        !Config Key   = DO_NEW_SNOW_ALBEDO
1134        !Config Desc  = Use the snow albedo calculation from CLM3
1135        !Config Def   = n
1136        !Config If    = OK_SECHIBA
1137        !Config Help  =
1138        !Config Units = [-]
1139        !
1140        do_new_snow_albedo = .FALSE.
1141        ! If the DOFOCO flag is on, the old snow albedo is not consistent.
1142        IF(active_flags%ok_dofoco)THEN
1143           ! Note that nothing will be written to the used_run_def because getin_p is not used
1144           do_new_snow_albedo = .TRUE.
1145           WRITE(numout,*) "OK_DOFOCO flag has been set.  Ignoring do_new_snow_albedo in the run.def.  Using DO_NEW_SNOW_ALBEDO=Y."
1146        ELSE
1147           CALL getin_p('DO_NEW_SNOW_ALBEDO', do_new_snow_albedo)
1148        ENDIF
1149        WRITE(numout,*) "Using the new snow albedo? : ",do_new_snow_albedo
1150
1151
1152        !
1153        !Config Key  = ALBEDO_OPT_STEP_SIZE_MIN
1154        !Config Desc = Minimum step size for albedo n-layer optimization (arbitrary)
1155        !Config Def   = 0.000001
1156        !Config If   = ALBEDO_TYPE == Pinty
1157        !Config Help  =
1158        !Config Units = [-]
1159        !
1160        step_size_min=0.000001_r_std
1161        CALL getin_p('ALBEDO_OPT_STEP_SIZE_MIN',step_size_min) 
1162        WRITE(numout,*) 'Minimum step size for albedo n-layer optimization: ',step_size_min
1163
1164        !
1165        !Config Key  = ALBEDO_OPT_STEP_SIZE_SCALE
1166        !Config Desc = The scale factor for the step size in the albedo n-layer optimization (arbitrary)
1167        !Config Def   = 0.5
1168        !Config If   = ALBEDO_TYPE == Pinty
1169        !Config Help  =
1170        !Config Units = [-]
1171        !
1172        step_size_scale=0.5_r_std
1173        CALL getin_p('ALBEDO_OPT_STEP_SIZE_SCALE',step_size_scale) 
1174        WRITE(numout,*) 'The scale factor for the step size in the albedo n-layer optimization (arbitrary): ',step_size_scale
1175
1176        !
1177        !Config Key  = ALBEDO_OPT_CONVERENCE_LIMIT
1178        !Config Desc = The value of the optimization function below which we say the process has converged (arbitrary)
1179        !Config If   = ALBEDO_TYPE == Pinty
1180        !Config Def   = 0.00000001
1181        !Config Help  =
1182        !Config Units = [-]
1183        !
1184        converged_limit=0.00000001_r_std
1185        CALL getin_p('ALBEDO_OPT_CONVERENCE_LIMIT',converged_limit) 
1186        WRITE(numout,*) 'The value of the optimization function below which we say the process has converged: ',converged_limit
1187
1188        !
1189        !Config Key  = ALBEDO_OPT_NSTEPS_MAX
1190        !Config Desc = Maximum number of optimization steps tried for albedo n-layer optimization (arbitrary)
1191        !Config If   = ALBEDO_TYPE == Pinty
1192        !Config Def   = 10
1193        !Config Help  =
1194        !Config Units = [-]
1195        !
1196        max_steps=10_i_std
1197        CALL getin_p('ALBEDO_OPT_NSTEPS_MAX',max_steps) 
1198        WRITE(numout,*) 'Maximum number of optimization steps tried for albedo n-layer optimization (arbitrary): ',max_steps
1199
1200        !
1201        !Config Key  = LAIEFF_SOLAR_ANGLE
1202        !Config Desc = The solar zenith angle used in the calculation of the effective LAI.  Pinty recommends a value of 60 degrees.
1203        !Config If   = ALBEDO_TYPE == Pinty
1204        !Config Def   = 60
1205        !Config Help  =
1206        !Config Units = [degrees]
1207        !
1208        laieff_solar_angle=60.0_r_std
1209        CALL getin_p('LAIEFF_SOLAR_ANGLE',laieff_solar_angle) 
1210        WRITE(numout,*) 'Maximum number of optimization steps tried for albedo n-layer optimization [degrees]: ',laieff_solar_angle
1211        laieff_solar_angle=laieff_solar_angle/180.0_r_std*pi ! convert to radians
1212
1213        !
1214        !Config Key  = LAIEFF_ZERO_CUTOFF
1215        !Config Desc = This is an arbitrary cutoff to make sure we don't pass zero values of crown diameter and trunk diameter
1216        !              to a subroutine that will choke on them
1217        !Config If   = ALBEDO_TYPE == Pinty
1218        !Config Def   = 0.0000001
1219        !Config Help  =
1220        !Config Units = [-]
1221        !
1222        laieff_zero_cutoff=0.0000001_r_std
1223        CALL getin_p('LAIEFF_ZERO_CUTOFF',laieff_zero_cutoff) 
1224        WRITE(numout,*) 'A minimum threshold for trunk and crown diameters for numerical stability: ',laieff_zero_cutoff
1225
1226
1227
1228       laieff_set_value_upper=0.5_r_std
1229       laieff_set_value_lower=0.5_r_std
1230        CALL getin_p('LAIEFF_SET_VALUE_LOWER',laieff_set_value_lower) 
1231        CALL getin_p('LAIEFF_SET_VALUE_UPPER',laieff_set_value_upper) 
1232!!$        WRITE(numout,*) 'Testing: ',laieff_set_value_upper
1233!!$        WRITE(numout,*) 'Testing: ',laieff_set_value_lower
1234       laieff_theta=0.01_r_std
1235        CALL getin_p('LAIEFF_THETA',laieff_theta) 
1236!!$        WRITE(numout,*) 'Testing here too: ',laieff_theta
1237
1238        first_call =.FALSE.
1239
1240
1241
1242     ENDIF
1243     
1244 
1245
1246   END SUBROUTINE config_sechiba_parameters
1247!
1248!=
1249!
1250
1251!! ================================================================================================================================
1252!! SUBROUTINE   : config_co2_parameters
1253!!
1254!>\BRIEF        This subroutine reads in the configuration file all the parameters
1255!! needed when OK_CO2 is set to true. (ie : when the photosynthesis is activated)
1256!!
1257!! DESCRIPTION  : None
1258!!
1259!! RECENT CHANGE(S): None
1260!!
1261!! MAIN OUTPUT VARIABLE(S): None
1262!!
1263!! REFERENCE(S) :
1264!!
1265!! FLOWCHART    :
1266!! \n
1267!_ ================================================================================================================================
1268
1269   SUBROUTINE config_co2_parameters
1270     
1271     IMPLICIT NONE
1272
1273     !! 0. Variables and parameters declaration
1274
1275     !! 0.4 Local variables
1276     
1277     LOGICAL, SAVE ::  first_call = .TRUE.      !! To keep first call trace (true/false)
1278!$OMP THREADPRIVATE(first_call)
1279
1280!_ ================================================================================================================================
1281     
1282     IF (first_call) THEN
1283       
1284        !
1285        !Config Key   = LAI_LEVEL_DEPTH
1286        !Config Desc  =
1287        !Config If    = OK_CO2
1288        !Config Def   = 0.15
1289        !Config Help  =
1290        !Config Units = [-] 
1291        CALL getin_p('LAI_LEVEL_DEPTH',lai_level_depth)
1292        !
1293        !Config Key   = Oi
1294        !Config Desc  = Intercellular oxygen partial pressure
1295        !Config If    = OK_CO2
1296        !Config Def   = 210000.
1297        !Config Help  = See Legend of Figure 6 of Yin et al. (2009)
1298        !Config Units = [ubar]   
1299        CALL getin_p('Oi',Oi) 
1300
1301        !Config Key   = THRESHOLD_C13_ASSIM
1302        !Config Desc  = If assimilation falls below this threshold
1303        !               the delta_c13 is set to zero
1304        !Config If    = OK_C13, OK_CO2
1305        !Config Def   = 0.01
1306        !Config Help  =
1307        !Config Units = [-] 
1308        CALL getin_p('THRESHOLD_C13_ASSIM',threshold_c13_assim)
1309
1310        !Config Key   = C13_A
1311        !Config Desc  = Coefficient for fractionation occurring
1312        !               due to diffusion in air
1313        !Config If    = OK_C13, OK_CO2
1314        !Config Def   = 0.01
1315        !Config Help  =
1316        !Config Units = [-] 
1317        CALL getin_p('C13_A',c13_a)
1318
1319        !Config Key   = C13_B
1320        !Config Desc  = Coefficient for fractionation caused by
1321        !               carboxylation
1322        !Config If    = OK_C13, OK_CO2
1323        !Config Def   = 0.01
1324        !Config Help  =
1325        !Config Units = [-] 
1326        CALL getin_p('C13_B',c13_b)
1327
1328        first_call = .FALSE.
1329       
1330     ENDIF
1331     
1332   END SUBROUTINE config_co2_parameters
1333!
1334!=
1335!
1336
1337!! ================================================================================================================================
1338!! SUBROUTINE   : config_stomate_parameters
1339!!
1340!>\BRIEF        This subroutine reads in the configuration file all the parameters
1341!! needed when stomate is activated (ie : when OK_STOMATE is set to true).
1342!!
1343!! DESCRIPTION  : None
1344!!
1345!! RECENT CHANGE(S): None
1346!!
1347!! MAIN OUTPUT VARIABLE(S):
1348!!
1349!! REFERENCE(S) :
1350!!
1351!! FLOWCHART    :
1352!! \n
1353!_ ================================================================================================================================
1354
1355   SUBROUTINE config_stomate_parameters
1356     
1357    IMPLICIT NONE
1358   
1359    !! 0. Variables and parameters declaration
1360
1361    !! 0.4 Local variables   
1362
1363    LOGICAL, SAVE ::  first_call = .TRUE.  !! To keep first call trace (true/false)
1364!$OMP THREADPRIVATE(first_call)
1365
1366!_ ================================================================================================================================
1367   
1368    IF(first_call) THEN
1369       
1370       !
1371       ! debug setting
1372       !
1373       !Config Key   = TEST_PFT
1374       !Config Desc  = pft for which extra output is written to the out_execution file
1375       !Config If    = OK_STOMATE
1376       !Config Def   = 6
1377       !Config Help  =
1378       !Config Units = [-]   
1379       CALL getin_p('TEST_PFT',test_pft)   
1380
1381       !
1382       ! debug setting
1383       !
1384       !Config Key   = TEST_GRID
1385       !Config Desc  = grid cell for which extra output is written to the out_execution file
1386       !Config If    = OK_STOMATE
1387       !Config Def   = 1
1388       !Config Help  =
1389       !Config Units = [-]
1390       test_grid=1
1391       CALL getin_p('TEST_GRID',test_grid)   
1392
1393       !-
1394       ! constraints_parameters
1395       !-
1396       !
1397       !Config Key   = TOO_LONG
1398       !Config Desc  = longest sustainable time without regeneration (vernalization)
1399       !Config If    = OK_STOMATE
1400       !Config Def   = 5.
1401       !Config Help  =
1402       !Config Units = [days]   
1403       CALL getin_p('TOO_LONG',too_long)
1404
1405       !-
1406       ! fire parameters
1407       !-
1408       !
1409       !Config Key   = TAU_FIRE
1410       !Config Desc  = Time scale for memory of the fire index (days). Validated for one year in the DGVM.
1411       !Config If    = OK_STOMATE
1412       !Config Def   = 30.
1413       !Config Help  =
1414       !Config Units = [days]   
1415       CALL getin_p('TAU_FIRE',tau_fire)
1416       !
1417       !Config Key   = LITTER_CRIT
1418       !Config Desc  = Critical litter quantity for fire
1419       !Config If    = OK_STOMATE
1420       !Config Def   = 200.
1421       !Config Help  =
1422       !Config Units = [gC/m^2] 
1423       CALL getin_p('LITTER_CRIT',litter_crit)
1424       !
1425       !Config Key   = FIRE_RESIST_LIGNIN
1426       !Config Desc  =
1427       !Config If    = OK_STOMATE
1428       !Config Def   = 0.5
1429       !Config Help  =
1430       !Config Units = [-] 
1431       CALL getin_p('FIRE_RESIST_LIGNIN',fire_resist_lignin)
1432       !
1433       !
1434       !Config Key   = CO2FRAC
1435       !Config Desc  = What fraction of a burned plant compartment goes into the atmosphere
1436       !Config If    = OK_STOMATE
1437       !Config Def   = 0.95, 0.95, 0., 0.3, 0., 0., 0.95, 0.95, 0.95
1438       !Config Help  =
1439       !Config Units = [-] 
1440       CALL getin_p('CO2FRAC',co2frac)
1441       !
1442       !Config Key   = BCFRAC_COEFF
1443       !Config Desc  =
1444       !Config If    = OK_STOMATE
1445       !Config Def   = 0.3, 1.3, 88.2
1446       !Config Help  =
1447       !Config Units = [-] 
1448       CALL getin_p('BCFRAC_COEFF',bcfrac_coeff)
1449       !
1450       !Config Key   = FIREFRAC_COEFF
1451       !Config Desc  =
1452       !Config If    = OK_STOMATE
1453       !Config Def   = 0.45, 0.8, 0.6, 0.13
1454       !Config Help  =
1455       !Config Units = [-]   
1456       CALL getin_p('FIREFRAC_COEFF',firefrac_coeff)
1457
1458       !-
1459       ! windfall parameters
1460       !-
1461       
1462       ! NOTE: COMMENTS NEED TO BE FILLED.
1463
1464       !Config Key   = ONE_THIRD
1465       !Config Desc  = This value is used on multiple occasions in stomate_windfall.f90
1466       !Config If    = OK_STOMATE
1467       !Config Def   = 0.333
1468       !Config Help  =
1469       !Config Units = [unitless]   
1470       CALL getin_p('ONE_THIRD',one_third)
1471       
1472       !Config Key   = ONE_THIRD
1473       !Config Desc  = This value is used on multiple occasions in stomate_windfall.f90
1474       !Config If    = OK_STOMATE
1475       !Config Def   = 0.333
1476       !Config Help  =
1477       !Config Units = [unitless]   
1478       CALL getin_p('DBH_HEIGHT_STANDARD',dbh_height_standard)
1479       
1480       !Config Key   = ONE_THIRD
1481       !Config Desc  = This value is used on multiple occasions in stomate_windfall.f90
1482       !Config If    = OK_STOMATE
1483       !Config Def   = 0.333
1484       !Config Help  =
1485       !Config Units = [unitless]   
1486       CALL getin_p('DBH_HEIGHT_STUMP',dbh_height_stump)
1487       
1488       !Config Key   = ONE_THIRD
1489       !Config Desc  = This value is used on multiple occasions in stomate_windfall.f90
1490       !Config If    = OK_STOMATE
1491       !Config Def   = 0.333
1492       !Config Help  =
1493       !Config Units = [unitless]   
1494       CALL getin_p('SNOW_DENSITY',snow_density)
1495       
1496       !Config Key   = ONE_THIRD
1497       !Config Desc  = This value is used on multiple occasions in stomate_windfall.f90
1498       !Config If    = OK_STOMATE
1499       !Config Def   = 0.333
1500       !Config Help  =
1501       !Config Units = [unitless]   
1502       CALL getin_p('CLEAR_CUT_MAX',clear_cut_max)
1503       
1504       !Config Key   = ONE_THIRD
1505       !Config Desc  = This value is used on multiple occasions in stomate_windfall.f90
1506       !Config If    = OK_STOMATE
1507       !Config Def   = 0.333
1508       !Config Help  =
1509       !Config Units = [unitless]   
1510       CALL getin_p('C_SURFACE',c_surface)
1511       
1512       !Config Key   = ONE_THIRD
1513       !Config Desc  = This value is used on multiple occasions in stomate_windfall.f90
1514       !Config If    = OK_STOMATE
1515       !Config Def   = 0.333
1516       !Config Help  =
1517       !Config Units = [unitless]   
1518       CALL getin_p('C_DRAG',c_drag)
1519       
1520       !Config Key   = ONE_THIRD
1521       !Config Desc  = This value is used on multiple occasions in stomate_windfall.f90
1522       !Config If    = OK_STOMATE
1523       !Config Def   = 0.333
1524       !Config Help  =
1525       !Config Units = [unitless]   
1526       CALL getin_p('C_DISPLACEMENT',c_displacement)
1527             
1528       !Config Key   = ONE_THIRD
1529       !Config Desc  = This value is used on multiple occasions in stomate_windfall.f90
1530       !Config If    = OK_STOMATE
1531       !Config Def   = 0.333
1532       !Config Help  =
1533       !Config Units = [unitless]   
1534       CALL getin_p('C_ROUGHNESS',c_roughness)
1535             
1536       !Config Key   = ONE_THIRD
1537       !Config Desc  = This value is used on multiple occasions in stomate_windfall.f90
1538       !Config If    = OK_STOMATE
1539       !Config Def   = 0.333
1540       !Config Help  =
1541       !Config Units = [unitless]   
1542       CALL getin_p('AIR_DENSITY',air_density)
1543             
1544       !Config Key   = ONE_THIRD
1545       !Config Desc  = This value is used on multiple occasions in stomate_windfall.f90
1546       !Config If    = OK_STOMATE
1547       !Config Def   = 0.333
1548       !Config Help  =
1549       !Config Units = [unitless]   
1550       CALL getin_p('F_CROWN_WEIGHT',f_crown_weight)
1551       
1552
1553
1554       !-
1555       ! gap parameters (+ lpj_const_mort)
1556       !-
1557       !
1558       !Config Key   = AVAILABILITY_FACT
1559       !Config Desc  =
1560       !Config If    = OK_STOMATE, resource-limited allocation
1561       !Config Def   = 0.1
1562       !Config Help  =
1563       !Config Units = [-]   
1564       CALL getin_p('AVAILABILITY_FACT', availability_fact) 
1565       !
1566       !Config Key   = REF_GREFF
1567       !Config Desc  = Asymptotic maximum mortality rate
1568       !Config If    = OK_STOMATE, resource-limited allocation
1569       !Config Def   = 0.035
1570       !Config Help  = Set asymptotic maximum mortality rate from Sitch 2003
1571       !Config         (they use 0.01) (year^{-1})
1572       !Config Units = [1/year] 
1573       CALL getin_p('REF_GREFF',ref_greff)
1574
1575       !-
1576       ! growth_res_limitation
1577       !-
1578       !
1579       !Config Key   = OK_MINRES
1580       !Config Desc  = Do we try to reach a minimum reservoir even if we are severely stressed?
1581       !Config If    = OK_STOMATE
1582       !Config Def   = y
1583       !Config Help  =
1584       !Config Units = [FLAG]
1585       CALL getin_p('OK_MINRES',ok_minres)
1586       !
1587       !Config Key   = RESERVE_TIME_TREE
1588       !Config Desc  = maximum time during which reserve is used (trees)
1589       !Config If    = OK_STOMATE
1590       !Config Def   = 30.
1591       !Config Help  =
1592       !Config Units = [days]   
1593       CALL getin_p('RESERVE_TIME_TREE',reserve_time_tree)
1594       !
1595       !Config Key   = RESERVE_TIME_GRASS
1596       !Config Desc  = maximum time during which reserve is used (grasses)
1597       !Config If    = OK_STOMATE
1598       !Config Def   = 20.
1599       !Config Help  =
1600       !Config Units = [days]   
1601       CALL getin_p('RESERVE_TIME_GRASS',reserve_time_grass)
1602       !
1603       !Config Key   = F_FRUIT
1604       !Config Desc  = Standard fruit allocation
1605       !Config If    = OK_STOMATE
1606       !Config Def   = 0.1
1607       !Config Help  =
1608       !Config Units = [-]   
1609       CALL getin_p('F_FRUIT',f_fruit)
1610       !
1611       !Config Key   = ALLOC_SAP_ABOVE_GRASS
1612       !Config Desc  = fraction of sapwood allocation above ground
1613       !Config If    = OK_STOMATE
1614       !Config Def   = 1.0
1615       !Config Help  =
1616       !Config Units = [-]   
1617       CALL getin_p('ALLOC_SAP_ABOVE_GRASS',alloc_sap_above_grass)
1618       !
1619       !Config Key   = MIN_LTOLSR
1620       !Config Desc  = extrema of leaf allocation fraction
1621       !Config If    = OK_STOMATE
1622       !Config Def   = 0.2
1623       !Config Help  =
1624       !Config Units = [-]   
1625       CALL getin_p('MIN_LTOLSR',min_LtoLSR)
1626       !
1627       !Config Key   = MAX_LTOLSR
1628       !Config Desc  = extrema of leaf allocation fraction
1629       !Config If    = OK_STOMATE
1630       !Config Def   = 0.5
1631       !Config Help  =
1632       !Config Units = [-]   
1633       CALL getin_p('MAX_LTOLSR',max_LtoLSR)
1634       !
1635       !Config Key   = Z_NITROGEN
1636       !Config Desc  = scaling depth for nitrogen limitation
1637       !Config If    = OK_STOMATE
1638       !Config Def   = 0.2
1639       !Config Help  =
1640       !Config Units = [m] 
1641       CALL getin_p('Z_NITROGEN',z_nitrogen)
1642       !
1643       !Config Key   = NLIM_TREF
1644       !Config Desc  =
1645       !Config If    = OK_STOMATE
1646       !Config Def   = 25.
1647       !Config Help  =
1648       !Config Units = [C] 
1649       CALL getin_p('NLIM_TREF',Nlim_tref)
1650
1651       !-
1652       ! growth_fun_all
1653       !-
1654       !Config Key   = NCIRC
1655       !Config Desc  = Number of basal area classes in allocation scheme
1656       !               circ classes could be considered as cohorts within a stand
1657       !Config If    = OK_STOMATE, functional allocation
1658       !Config Def   = 2
1659       !Config Help  =
1660       !Config Units = [-]
1661       ncirc = 2
1662       CALL getin_p('NCIRC',ncirc) 
1663
1664       !Config Key   = NAGEC
1665       !Config Desc  = Number of age classes in forestry and lcchange
1666       !               age classes could be considered age classes across stands in the same pixel
1667       !Config If    = OK_STOMATE, forestry and/or lcchange
1668       !Config Def   = 1
1669       !Config Help  =
1670       !Config Units = [-]
1671       nagec = 1
1672       CALL getin_p('NAGEC',nagec) 
1673       !
1674       !Config Key   = MIN_WATER_STRESS
1675       !Config Desc  = Minimal value for wstress_fac
1676       !Config If    = OK_STOMATE, functional allocation
1677       !Config Def   = 0.1
1678       !Config Help  =
1679       !Config Units = [-] 
1680       CALL getin_p('MIN_WATER_STRESS',min_water_stress)
1681       !
1682       !Config Key   = MAX_DELTA_KF
1683       !Config Desc  = Maximum change in KF from one time step to another
1684       !Config If    = OK_STOMATE, functional allocation
1685       !Config Def   = 0.1
1686       !Config Help  =
1687       !Config Units = [m] 
1688       CALL getin_p('MAX_DELTA_KF',max_delta_KF)
1689       !
1690       !Config Key   = MAINT_FROM_LABILE
1691       !Config Desc  = Maintenance respiration should be positive. In case it is
1692       !               very low use ::maint_from_labile of the active labile carbon
1693       !               pool (gC m-2 dt-1)
1694       !Config If    = OK_STOMATE, functional allocation
1695       !Config Def   = 0.2
1696       !Config Help  =
1697       !Config Units = [-] 
1698       CALL getin_p('MAINT_FROM_LABILE',maint_from_labile)
1699       !
1700       !Config Key   = MAINT_FROM_GPP
1701       !Config Desc  = Some carbon needs to remain to support the growth, hence,
1702       !               respiration will be limited. In this case resp_maint
1703       !               (gC m-2 dt-1) should not be more than 80% (::maint_from_gpp)
1704       !               of the GPP (gC m-2 s-1)
1705       !Config If    = OK_STOMATE, functional allocation
1706       !Config Def   = 0.8
1707       !Config Help  =
1708       !Config Units = [-] 
1709       CALL getin_p('MAINT_FROM_GPP',maint_from_gpp)
1710       !
1711       !Config Key   = SYNC_THRESHOLD
1712       !Config Desc  = The threshold value for a warning when we sync biomass
1713       !Config If    = OK_STOMATE, functional allocation
1714       !Config Def   = 0.1
1715       !Config Help  =
1716       !Config Units = [-] 
1717       CALL getin_p('SYNC_THRESHOLD',sync_threshold)
1718   
1719       !-
1720       ! data parameters
1721       !-
1722       !
1723       !Config Key   = PRECIP_CRIT
1724       !Config Desc  = minimum precip
1725       !Config If    = OK_STOMATE
1726       !Config Def   = 100.
1727       !Config Help  =
1728       !Config Units = [mm/year] 
1729       CALL getin_p('PRECIP_CRIT',precip_crit)
1730       !
1731       !Config Key   = GDD_CRIT_ESTAB
1732       !Config Desc  = minimum gdd for establishment of saplings
1733       !Config If    = OK_STOMATE
1734       !Config Def   = 150.
1735       !Config Help  =
1736       !Config Units = [-] 
1737       CALL getin_p('GDD_CRIT_ESTAB',gdd_crit_estab)
1738        !
1739       !Config Key   = FPC_CRIT
1740       !Config Desc  = critical fpc, needed for light competition and establishment
1741       !Config If    = OK_STOMATE
1742       !Config Def   = 0.95
1743       !Config Help  =
1744       !Config Units = [-] 
1745       CALL getin_p('FPC_CRIT',fpc_crit)
1746       !
1747       !Config Key   = ALPHA_GRASS
1748       !Config Desc  = sapling characteristics : alpha's
1749       !Config If    = OK_STOMATE
1750       !Config Def   = 0.5
1751       !Config Help  =
1752       !Config Units = [-]   
1753       CALL getin_p('ALPHA_GRASS',alpha_grass)
1754       !
1755       !Config Key   = ALPHA_TREE
1756       !Config Desc  = sapling characteristics : alpha's
1757       !Config If    = OK_STOMATE
1758       !Config Def   = 1.
1759       !Config Help  =
1760       !Config Units = [-]   
1761       CALL getin_p('ALPHA_TREE',alpha_tree)
1762       !
1763!!$       !Config Key   = STRUCT_TO_LEAVES
1764!!$       !Config Desc  = Allocate C to structural carbon i.e. leave stems, tubers, ...
1765!!$       !Config If    = OK_STOMATE
1766!!$       !Config Def   = 0.05
1767!!$       !Config Help  =
1768!!$       !Config Units = [-]   
1769!!$       CALL getin_p('STRUCT_TO_LEAVES',struct_to_leaves)
1770       
1771       !-
1772       !
1773       !Config Key   = TAU_HUM_MONTH
1774       !Config Desc  = time scales for phenology and other processes
1775       !Config If    = OK_STOMATE
1776       !Config Def   = 20.
1777       !Config Help  =
1778       !Config Units = [days] 
1779       CALL getin_p('TAU_HUM_MONTH',tau_hum_month)
1780       !
1781       !Config Key   = TAU_HUM_WEEK
1782       !Config Desc  = time scales for phenology and other processes
1783       !Config If    = OK_STOMATE
1784       !Config Def   = 7.
1785       !Config Help  =
1786       !Config Units = [days]   
1787       CALL getin_p('TAU_HUM_WEEK',tau_hum_week)
1788       !
1789       !Config Key   = TAU_T2M_MONTH
1790       !Config Desc  = time scales for phenology and other processes
1791       !Config If    = OK_STOMATE
1792       !Config Def   = 20.
1793       !Config Help  =
1794       !Config Units = [days]     
1795       CALL getin_p('TAU_T2M_MONTH',tau_t2m_month)
1796       !
1797       !Config Key   = TAU_T2M_WEEK
1798       !Config Desc  = time scales for phenology and other processes
1799       !Config If    = OK_STOMATE
1800       !Config Def   = 7.
1801       !Config Help  =
1802       !Config Units = [days]   
1803       CALL getin_p('TAU_T2M_WEEK',tau_t2m_week)
1804       !
1805       !Config Key   = TAU_TSOIL_MONTH
1806       !Config Desc  = time scales for phenology and other processes
1807       !Config If    = OK_STOMATE
1808       !Config Def   = 20.
1809       !Config Help  =
1810       !Config Units = [days]     
1811       CALL getin_p('TAU_TSOIL_MONTH',tau_tsoil_month)
1812       !
1813       !Config Key   = TAU_SOILHUM_MONTH
1814       !Config Desc  = time scales for phenology and other processes
1815       !Config If    = OK_STOMATE
1816       !Config Def   = 20.
1817       !Config Help  =
1818       !Config Units = [days]   
1819       CALL getin_p('TAU_SOILHUM_MONTH',tau_soilhum_month)
1820       !
1821       !Config Key   = TAU_GPP_WEEK
1822       !Config Desc  = time scales for phenology and other processes
1823       !Config If    = OK_STOMATE
1824       !Config Def   = 7.
1825       !Config Help  =
1826       !Config Units = [days]   
1827       CALL getin_p('TAU_GPP_WEEK',tau_gpp_week)
1828       !
1829       !Config Key   = TAU_GDD
1830       !Config Desc  = time scales for phenology and other processes
1831       !Config If    = OK_STOMATE
1832       !Config Def   = 40.
1833       !Config Help  =
1834       !Config Units = [days]   
1835       CALL getin_p('TAU_GDD',tau_gdd)
1836       !
1837       !Config Key   = TAU_NGD
1838       !Config Desc  = time scales for phenology and other processes
1839       !Config If    = OK_STOMATE
1840       !Config Def   = 50.
1841       !Config Help  =
1842       !Config Units = [days]   
1843       CALL getin_p('TAU_NGD',tau_ngd)
1844       !
1845       !Config Key   = COEFF_TAU_LONGTERM
1846       !Config Desc  = time scales for phenology and other processes
1847       !Config If    = OK_STOMATE
1848       !Config Def   = 3.
1849       !Config Help  =
1850       !Config Units = [days]   
1851       CALL getin_p('COEFF_TAU_LONGTERM',coeff_tau_longterm)
1852       !-
1853       !
1854       !Config Key   = BM_SAPL_CARBRES
1855       !Config Desc  =
1856       !Config If    = OK_STOMATE
1857       !Config Def   = 5.
1858       !Config Help  =
1859       !Config Units = [-]   
1860       CALL getin_p('BM_SAPL_CARBRES',bm_sapl_carbres)
1861       !
1862       !Config Key   = BM_SAPL_SAPABOVE
1863       !Config Desc  =
1864       !Config If    = OK_STOMATE
1865       !Config Def   = 0.5
1866       !Config Help  =
1867       !Config Units = [-]   
1868       CALL getin_p('BM_SAPL_SAPABOVE',bm_sapl_sapabove)
1869       !
1870       !Config Key   = BM_SAPL_HEARTABOVE
1871       !Config Desc  =
1872       !Config If    = OK_STOMATE
1873       !Config Def   = 2.
1874       !Config Help  =
1875       !Config Units = [-]   
1876       CALL getin_p('BM_SAPL_HEARTABOVE',bm_sapl_heartabove)
1877       !
1878       !Config Key   = BM_SAPL_HEARTBELOW
1879       !Config Desc  =
1880       !Config If    = OK_STOMATE
1881       !Config Def   = 2.
1882       !Config Help  =
1883       !Config Units = [-]   
1884       CALL getin_p('BM_SAPL_HEARTBELOW',bm_sapl_heartbelow)
1885       !
1886       !Config Key   = INIT_SAPL_MASS_LEAF_NAT
1887       !Config Desc  =
1888       !Config If    = OK_STOMATE
1889       !Config Def   = 0.1
1890       !Config Help  =
1891       !Config Units = [-]   
1892       CALL getin_p('INIT_SAPL_MASS_LEAF_NAT',init_sapl_mass_leaf_nat)
1893       !
1894       !Config Key   = INIT_SAPL_MASS_LEAF_AGRI
1895       !Config Desc  =
1896       !Config If    = OK_STOMATE
1897       !Config Def   = 1.
1898       !Config Help  =
1899       !Config Units = [-]   
1900       CALL getin_p('INIT_SAPL_MASS_LEAF_AGRI',init_sapl_mass_leaf_agri)
1901       !
1902       !Config Key   = INIT_SAPL_MASS_CARBRES
1903       !Config Desc  =
1904       !Config If    = OK_STOMATE
1905       !Config Def   = 5.
1906       !Config Help  =
1907       !Config Units = [-]   
1908       CALL getin_p('INIT_SAPL_MASS_CARBRES',init_sapl_mass_carbres)
1909       !
1910       !Config Key   = INIT_SAPL_MASS_ROOT
1911       !Config Desc  =
1912       !Config If    = OK_STOMATE
1913       !Config Def   = 0.1
1914       !Config Help  =
1915       !Config Units = [-]   
1916       CALL getin_p('INIT_SAPL_MASS_ROOT',init_sapl_mass_root)
1917       !
1918       !Config Key   = INIT_SAPL_MASS_FRUIT
1919       !Config Desc  =
1920       !Config If    = OK_STOMATE
1921       !Config Def   = 0.3
1922       !Config Help  =
1923       !Config Units = [-]   
1924       CALL getin_p('INIT_SAPL_MASS_FRUIT',init_sapl_mass_fruit)
1925       !
1926       !Config Key   = CN_SAPL_INIT
1927       !Config Desc  =
1928       !Config If    = OK_STOMATE
1929       !Config Def   = 0.5
1930       !Config Help  =
1931       !Config Units = [-]   
1932       CALL getin_p('CN_SAPL_INIT',cn_sapl_init)
1933       !
1934       !Config Key   = MIGRATE_TREE
1935       !Config Desc  =
1936       !Config If    = OK_STOMATE
1937       !Config Def   = 10000.
1938       !Config Help  =
1939       !Config Units = [m/year]   
1940       CALL getin_p('MIGRATE_TREE',migrate_tree)
1941       !
1942       !Config Key   = MIGRATE_GRASS
1943       !Config Desc  =
1944       !Config If    = OK_STOMATE
1945       !Config Def   = 10000.
1946       !Config Help  =
1947       !Config Units = [m/year]   
1948       CALL getin_p('MIGRATE_GRASS',migrate_grass)
1949       !
1950       !replaced by a calculation of lai_tagret
1951       !Config Key   = LAI_INITMIN_TREE
1952       !Config Desc  =
1953       !Config If    = OK_STOMATE
1954       !Config Def   = 0.3
1955       !Config Help  =
1956       !Config Units = [m^2/m^2] 
1957       CALL getin_p('LAI_INITMIN_TREE',lai_initmin_tree)
1958       !
1959       !Config Key   = LAI_INITMIN_GRASS
1960       !Config Desc  =
1961       !Config If    = OK_STOMATE
1962       !Config Def   = 0.1
1963       !Config Help  =
1964       !Config Units = [m^2/m^2]   
1965       CALL getin_p('LAI_INITMIN_GRASS',lai_initmin_grass)
1966       !
1967       !Config Key   = DIA_COEFF
1968       !Config Desc  =
1969       !Config If    = OK_STOMATE
1970       !Config Def   = 4., 0.5
1971       !Config Help  =
1972       !Config Units = [-]   
1973       CALL getin_p('DIA_COEFF',dia_coeff)
1974       !
1975       !Config Key   = MAXDIA_COEFF
1976       !Config Desc  =
1977       !Config If    = OK_STOMATE
1978       !Config Def   = 100., 0.01
1979       !Config Help  =
1980       !Config Units = [-]   
1981       CALL getin_p('MAXDIA_COEFF',maxdia_coeff)
1982       !
1983       !Config Key   = BM_SAPL_LEAF
1984       !Config Desc  =
1985       !Config If    = OK_STOMATE
1986       !Config Def   = 4., 4., 0.8, 5.
1987       !Config Help  =
1988       !Config Units = [-] 
1989       CALL getin_p('BM_SAPL_LEAF',bm_sapl_leaf)
1990
1991       !-
1992       ! litter parameters
1993       !-
1994       !
1995       !Config Key   = METABOLIC_REF_FRAC
1996       !Config Desc  =
1997       !Config If    = OK_STOMATE
1998       !Config Def   = 0.85 
1999       !Config Help  =
2000       !Config Units = [-]
2001       CALL getin_p('METABOLIC_REF_FRAC',metabolic_ref_frac)
2002       !
2003       !Config Key   = Z_DECOMP
2004       !Config Desc  = scaling depth for soil activity
2005       !Config If    = OK_STOMATE
2006       !Config Def   = 0.2
2007       !Config Help  =
2008       !Config Units = [m]   
2009       CALL getin_p('Z_DECOMP',z_decomp)
2010       !
2011       !Config Key   = CN
2012       !Config Desc  = C/N ratio
2013       !Config If    = OK_STOMATE
2014       !Config Def   = 40., 40., 40., 40., 40., 40., 40., 40.
2015       !Config Help  =
2016       !Config Units = [-] 
2017       CALL getin_p('CN',CN)
2018       !
2019       !Config Key   = LC
2020       !Config Desc  = Lignine/C ratio of the different plant parts
2021       !Config If    = OK_STOMATE
2022       !Config Def   = 0.22, 0.35, 0.35, 0.35, 0.35, 0.22, 0.22, 0.22
2023       !Config Help  =
2024       !Config Units = [-]   
2025       CALL getin_p('LC',LC)
2026       !
2027       !Config Key   = FRAC_SOIL_STRUCT_AA
2028       !Config Desc  = frac_soil(istructural,iactive,iabove)
2029       !Config If    = OK_STOMATE
2030       !Config Def   = 0.55
2031       !Config Help  =
2032       !Config Units = [-]
2033       CALL getin_p('FRAC_SOIL_STRUCT_AA',frac_soil_struct_aa)
2034       !
2035       !Config Key   = FRAC_SOIL_STRUCT_A
2036       !Config Desc  = frac_soil(istructural,iactive,ibelow)
2037       !Config If    = OK_STOMATE
2038       !Config Def   = 0.45
2039       !Config Help  =
2040       !Config Units = [-]
2041       CALL getin_p('FRAC_SOIL_STRUCT_AB',frac_soil_struct_ab)
2042       !
2043       !Config Key   = FRAC_SOIL_STRUCT_SA
2044       !Config Desc  = frac_soil(istructural,islow,iabove)
2045       !Config If    = OK_STOMATE
2046       !Config Def   = 0.7 
2047       !Config Help  =
2048       !Config Units = [-]   
2049       CALL getin_p('FRAC_SOIL_STRUCT_SA',frac_soil_struct_sa)
2050       !
2051       !Config Key   = FRAC_SOIL_STRUCT_SB
2052       !Config Desc  = frac_soil(istructural,islow,ibelow)
2053       !Config If    = OK_STOMATE
2054       !Config Def   = 0.7 
2055       !Config Help  =
2056       !Config Units = [-]   
2057       CALL getin_p('FRAC_SOIL_STRUCT_SB',frac_soil_struct_sb)
2058       !
2059       !Config Key   = FRAC_SOIL_METAB_AA
2060       !Config Desc  = frac_soil(imetabolic,iactive,iabove)
2061       !Config If    = OK_STOMATE
2062       !Config Def   = 0.45
2063       !Config Help  =
2064       !Config Units = [-]   
2065       CALL getin_p('FRAC_SOIL_METAB_AA',frac_soil_metab_aa)
2066       !
2067       !Config Key   = FRAC_SOIL_METAB_AB
2068       !Config Desc  = frac_soil(imetabolic,iactive,ibelow)
2069       !Config If    = OK_STOMATE
2070       !Config Def   = 0.45 
2071       !Config Help  =
2072       !Config Units = [-]   
2073       CALL getin_p('FRAC_SOIL_METAB_AB',frac_soil_metab_ab)
2074       !
2075       !
2076       !Config Key   = METABOLIC_LN_RATIO
2077       !Config Desc  =
2078       !Config If    = OK_STOMATE
2079       !Config Def   = 0.018 
2080       !Config Help  =
2081       !Config Units = [-]   
2082       CALL getin_p('METABOLIC_LN_RATIO',metabolic_LN_ratio) 
2083       !
2084       !Config Key   = TAU_METABOLIC
2085       !Config Desc  =
2086       !Config If    = OK_STOMATE
2087       !Config Def   = 0.066
2088       !Config Help  =
2089       !Config Units = [days]
2090       CALL getin_p('TAU_METABOLIC',tau_metabolic)
2091       !
2092       !Config Key   = TAU_STRUCT
2093       !Config Desc  =
2094       !Config If    = OK_STOMATE
2095       !Config Def   = 0.245
2096       !Config Help  =
2097       !Config Units = [days]
2098       CALL getin_p('TAU_STRUCT',tau_struct)
2099       !
2100       !Config Key   = TAU_WOODY
2101       !Config Desc  =
2102       !Config If    = OK_STOMATE
2103       !Config Def   = 0.75
2104       !Config Help  =
2105       !Config Units = [days]
2106       CALL getin_p('TAU_WOODY',tau_woody)
2107       !
2108       !Config Key   = SOIL_Q10
2109       !Config Desc  =
2110       !Config If    = OK_STOMATE
2111       !Config Def   = 0.69 (=ln2)
2112       !Config Help  =
2113       !Config Units = [-]
2114       CALL getin_p('SOIL_Q10',soil_Q10)
2115       !
2116       !Config Key   = TSOIL_REF
2117       !Config Desc  =
2118       !Config If    = OK_STOMATE
2119       !Config Def   = 30.
2120       !Config Help  =
2121       !Config Units = [C]   
2122       CALL getin_p('TSOIL_REF',tsoil_ref)
2123       !
2124       !Config Key   = LITTER_STRUCT_COEF
2125       !Config Desc  =
2126       !Config If    = OK_STOMATE
2127       !Config Def   = 3.
2128       !Config Help  =
2129       !Config Units = [-]   
2130       CALL getin_p('LITTER_STRUCT_COEF',litter_struct_coef)
2131       !
2132       !Config Key   = MOIST_COEFF
2133       !Config Desc  =
2134       !Config If    = OK_STOMATE
2135       !Config Def   = -1.1, 2.4, -0.29
2136       !Config Help  = Coefficients of the quadratic function determining
2137       !Config         the moisture control factor controling heterotrophic
2138       !Config         respiration.
2139       !Config Units = [-]   
2140       CALL getin_p('MOIST_COEFF',moist_coeff)
2141       !
2142       !Config Key   = MOISTCONT_MIN
2143       !Config Desc  =
2144       !Config If    = OK_STOMATE
2145       !Config Def   = 0.25
2146       !Config Help  = Minimum value of the moisture control factor
2147       !Config         controling heterotrophic respiration.
2148       !Config Units = [-]   
2149       CALL getin_p("MOISTCONT_MIN",moistcont_min)
2150
2151       !-
2152       ! lpj parameters
2153       !-
2154       !
2155       !Config Key   = FRAC_TURNOVER_DAILY
2156       !Config Desc  =
2157       !Config If    = OK_STOMATE
2158       !Config Def   = 0.55
2159       !Config Help  =
2160       !Config Units = [-]
2161       CALL getin_p('FRAC_TURNOVER_DAILY',frac_turnover_daily)   
2162
2163       !-
2164       ! npp parameters
2165       !-
2166       !
2167       !Config Key   = TAX_MAX
2168       !Config Desc  = maximum fraction of allocatable biomass used for maintenance respiration
2169       !Config If    = OK_STOMATE, OK_FUNCTIONAL_ALLOCATION = N
2170       !Config Def   = 0.8
2171       !Config Help  =
2172       !Config Units = [-]   
2173       CALL getin_p('TAX_MAX',tax_max) 
2174
2175       !-
2176       ! phenology parameters
2177       !-
2178       !
2179       !Config Key   = ALWAYS_INIT
2180       !Config Desc  = take carbon from atmosphere if carbohydrate reserve too small?
2181       !Config If    = OK_STOMATE
2182       !Config Def   = n
2183       !Config Help  =
2184       !Config Units = [-]   
2185       CALL getin_p('ALWAYS_INIT',always_init)
2186       !
2187       !Config Key   = MIN_GROWTHINIT_TIME
2188       !Config Desc  = minimum time since last beginning of a growing season
2189       !Config If    = OK_STOMATE
2190       !Config Def   = 300.
2191       !Config Help  =
2192       !Config Units = [days] 
2193       CALL getin_p('MIN_GROWTHINIT_TIME',min_growthinit_time)
2194       !
2195       !Config Key   = MOIAVAIL_ALWAYS_TREE
2196       !Config Desc  = moisture availability above which moisture tendency doesn't matter
2197       !Config If    = OK_STOMATE
2198       !Config Def   = 1.0
2199       !Config Help  =
2200       !Config Units = [-]   
2201       CALL getin_p('MOIAVAIL_ALWAYS_TREE',moiavail_always_tree)
2202       !
2203       !Config Key   = MOIAVAIL_ALWAYS_GRASS
2204       !Config Desc  = moisture availability above which moisture tendency doesn't matter
2205       !Config If    = OK_STOMATE
2206       !Config Def   = 0.6
2207       !Config Help  =
2208       !Config Units = [-]   
2209       CALL getin_p('MOIAVAIL_ALWAYS_GRASS',moiavail_always_grass)
2210       !
2211       !Config Key   = T_ALWAYS_ADD
2212       !Config Desc  = monthly temp. above which temp. tendency doesn't matter
2213       !Config If    = OK_STOMATE
2214       !Config Def   = 10.
2215       !Config Help  =
2216       !Config Units = [C]   
2217       CALL getin_p('T_ALWAYS_ADD',t_always_add)
2218       !
2219       !
2220       !Config Key   = GDDNCD_REF
2221       !Config Desc  =
2222       !Config If    = OK_STOMATE
2223       !Config Def   = 603.
2224       !Config Help  =
2225       !Config Units = [-]   
2226       CALL getin_p('GDDNCD_REF',gddncd_ref)
2227       !
2228       !Config Key   = GDDNCD_CURVE
2229       !Config Desc  =
2230       !Config If    = OK_STOMATE
2231       !Config Def   = 0.0091
2232       !Config Help  =
2233       !Config Units = [-] 
2234       CALL getin_p('GDDNCD_CURVE',gddncd_curve)
2235       !
2236       !Config Key   = GDDNCD_OFFSET
2237       !Config Desc  =
2238       !Config If    = OK_STOMATE
2239       !Config Def   = 64.
2240       !Config Help  =
2241       !Config Units = [-] 
2242       CALL getin_p('GDDNCD_OFFSET',gddncd_offset)
2243       !-
2244       ! prescribe parameters
2245       !-
2246       !
2247       !Config Key   = BM_SAPL_RESCALE
2248       !Config Desc  =
2249       !Config If    = OK_STOMATE
2250       !Config Def   = 40.
2251       !Config Help  =
2252       !Config Units = [-] 
2253       CALL getin_p('BM_SAPL_RESCALE',bm_sapl_rescale)
2254
2255       !-
2256       ! respiration parameters
2257       !-
2258       !
2259       !Config Key   = MAINT_RESP_MIN_VMAX
2260       !Config Desc  =
2261       !Config If    = OK_STOMATE
2262       !Config Def   = 0.3
2263       !Config Help  =
2264       !Config Units = [-] 
2265       CALL getin_p('MAINT_RESP_MIN_VMAX',maint_resp_min_vmax) 
2266       !
2267       !Config Key   = MAINT_RESP_COEFF
2268       !Config Desc  =
2269       !Config If    = OK_STOMATE
2270       !Config Def   = 1.4
2271       !Config Help  =
2272       !Config Units = [-]
2273       CALL getin_p('MAINT_RESP_COEFF',maint_resp_coeff)
2274       !
2275       !Config Key   = MAINT_RESP_C
2276       !Config Desc  = Offset coefficient
2277       !Config If    = OK_STOMATE
2278       !Config Def   = 1.
2279       !Config Help  = Offset of the relationship between temperature and
2280       !Config         maintenance respiration
2281       !Config Units = [-]
2282       CALL getin_p("MAINT_RESP_C",maint_resp_c)
2283
2284       !-
2285       ! soilcarbon parameters
2286       !-
2287       !
2288       !Config Key   = FRAC_CARB_AP
2289       !Config Desc  = frac carb coefficients from active pool: depends on clay content
2290       !Config if    = OK_STOMATE
2291       !Config Def   = 0.004
2292       !Config Help  = fraction of the active pool going into the passive pool
2293       !Config Units = [-]
2294       CALL getin_p('FRAC_CARB_AP',frac_carb_ap) 
2295       !
2296       !Config Key   = FRAC_CARB_SA
2297       !Config Desc  = frac_carb_coefficients from slow pool
2298       !Config if    = OK_STOMATE
2299       !Config Def   = 0.42
2300       !Config Help  = fraction of the slow pool going into the active pool
2301       !Config Units = [-]
2302       CALL getin_p('FRAC_CARB_SA',frac_carb_sa)
2303       !
2304       !Config Key   = FRAC_CARB_SP
2305       !Config Desc  = frac_carb_coefficients from slow pool
2306       !Config if    = OK_STOMATE
2307       !Config Def   = 0.03
2308       !Config Help  = fraction of the slow pool going into the passive pool
2309       !Config Units = [-]
2310       CALL getin_p('FRAC_CARB_SP',frac_carb_sp)
2311       !
2312       !Config Key   = FRAC_CARB_PA
2313       !Config Desc  = frac_carb_coefficients from passive pool
2314       !Config if    = OK_STOMATE
2315       !Config Def   = 0.45
2316       !Config Help  = fraction of the passive pool going into the active pool
2317       !Config Units = [-]
2318       CALL getin_p('FRAC_CARB_PA',frac_carb_pa)
2319       !
2320       !Config Key   = FRAC_CARB_PS
2321       !Config Desc  = frac_carb_coefficients from passive pool
2322       !Config if    = OK_STOMATE
2323       !Config Def   = 0.0
2324       !Config Help  = fraction of the passive pool going into the slow pool
2325       !Config Units = [-]
2326       CALL getin_p('FRAC_CARB_PS',frac_carb_ps)
2327       !
2328       !Config Key   = ACTIVE_TO_PASS_CLAY_FRAC
2329       !Config Desc  =
2330       !Config if    = OK_STOMATE
2331       !Config Def   = 0.68 
2332       !Config Help  =
2333       !Config Units = [-]
2334       CALL getin_p('ACTIVE_TO_PASS_CLAY_FRAC',active_to_pass_clay_frac)
2335       !
2336       !Config Key   = CARBON_TAU_IACTIVE
2337       !Config Desc  = residence times in carbon pools
2338       !Config if    = OK_STOMATE
2339       !Config Def   = 0.149
2340       !Config Help  =
2341       !Config Units =  [days]
2342       CALL getin_p('CARBON_TAU_IACTIVE',carbon_tau_iactive)
2343       !
2344       !Config Key   = CARBON_TAU_ISLOW
2345       !Config Desc  = residence times in carbon pools
2346       !Config if    = OK_STOMATE
2347       !Config Def   = 5.48
2348       !Config Help  =
2349       !Config Units = [days]
2350       CALL getin_p('CARBON_TAU_ISLOW',carbon_tau_islow)
2351       !
2352       !Config Key   = CARBON_TAU_IPASSIVE
2353       !Config Desc  = residence times in carbon pools
2354       !Config if    = OK_STOMATE
2355       !Config Def   = 241.
2356       !Config Help  = residence time in the passive pool
2357       !Config Units = [days]
2358       CALL getin_p('CARBON_TAU_IPASSIVE',carbon_tau_ipassive)
2359       !
2360       !Config Key   = FLUX_TOT_COEFF
2361       !Config Desc  =
2362       !Config if    = OK_STOMATE
2363       !Config Def   = 1.2, 1.4,.75
2364       !Config Help  =
2365       !Config Units = [days]
2366       CALL getin_p('FLUX_TOT_COEFF',flux_tot_coeff)
2367
2368       !-
2369       ! turnover parameters
2370       !-
2371       !
2372       !Config Key   = NEW_TURNOVER_TIME_REF
2373       !Config Desc  =
2374       !Config If    = OK_STOMATE
2375       !Config Def   = 20.
2376       !Config Help  =
2377       !Config Units = [days] 
2378       CALL getin_p('NEW_TURNOVER_TIME_REF',new_turnover_time_ref)
2379       !
2380       !Config Key   = DT_TURNOVER_TIME
2381       !Config Desc  =
2382       !Config If    = OK_STOMATE
2383       !Config Def   = 10.
2384       !Config Help  =
2385       !Config Units = [days] 
2386       CALL getin_p('DT_TURNOVER_TIME',dt_turnover_time)
2387       !
2388       !Config Key   = LEAF_AGE_CRIT_TREF
2389       !Config Desc  = Mean critical leaf life time
2390       !Config If    = OK_STOMATE
2391       !Config Def   = 20.
2392       !Config Help  =
2393       !Config Units = [days] 
2394       CALL getin_p('LEAF_AGE_CRIT_TREF',leaf_age_crit_tref)
2395       !
2396       !Config Key   = LEAF_AGE_CRIT_COEFF
2397       !Config Desc  =
2398       !Config If    = OK_STOMATE
2399       !Config Def   = 1.5, 0.75, 10.
2400       !Config Help  =
2401       !Config Units = [-]
2402       CALL getin_p('LEAF_AGE_CRIT_COEFF',leaf_age_crit_coeff)
2403
2404       !-
2405       ! vmax parameters
2406       !-
2407       !
2408       !Config Key   = VMAX_OFFSET
2409       !Config Desc  = offset (minimum relative vcmax)
2410       !Config If    = OK_STOMATE
2411       !Config Def   = 0.3
2412       !Config Help  = offset (minimum vcmax/vmax_opt)
2413       !Config Units = [-] 
2414       CALL getin_p('VMAX_OFFSET',vmax_offset)
2415       !
2416       !Config Key   = LEAFAGE_FIRSTMAX
2417       !Config Desc  = leaf age at which vmax attains vcmax_opt (in fraction of critical leaf age)
2418       !Config If    = OK_STOMATE
2419       !Config Def   = 0.03
2420       !Config Help  = relative leaf age at which vmax attains vcmax_opt
2421       !Config Units = [-]
2422       CALL getin_p('LEAFAGE_FIRSTMAX',leafage_firstmax)
2423       !
2424       !Config Key   = LEAFAGE_LASTMAX
2425       !Config Desc  = leaf age at which vmax falls below vcmax_opt (in fraction of critical leaf age)
2426       !Config If    = OK_STOMATE
2427       !Config Def   = 0.5
2428       !Config Help  = relative leaf age at which vmax falls below vcmax_opt
2429       !Config Units = [-] 
2430       CALL getin_p('LEAFAGE_LASTMAX',leafage_lastmax)
2431       !
2432       !Config Key   = LEAFAGE_OLD
2433       !Config Desc  = leaf age at which vmax attains its minimum (in fraction of critical leaf age)
2434       !Config If    = OK_STOMATE
2435       !Config Def   = 1.
2436       !Config Help  = relative leaf age at which vmax attains its minimum
2437       !Config Units = [-] 
2438       CALL getin_p('LEAFAGE_OLD',leafage_old)
2439
2440       !-
2441       ! season parameters
2442       !-
2443       !
2444       !Config Key   = GPPFRAC_DORMANCE
2445       !Config Desc  = rapport maximal GPP/GGP_max pour dormance
2446       !Config If    = OK_STOMATE
2447       !Config Def   = 0.2
2448       !Config Help  =
2449       !Config Units = [-]
2450       CALL getin_p('GPPFRAC_DORMANCE',gppfrac_dormance)
2451       !
2452       !Config Key   = TAU_CLIMATOLOGY
2453       !Config Desc  = tau for "climatologic variables
2454       !Config If    = OK_STOMATE
2455       !Config Def   = 20
2456       !Config Help  =
2457       !Config Units = [days]
2458       CALL getin_p('TAU_CLIMATOLOGY',tau_climatology)
2459       !
2460       !Config Key   = HVC1
2461       !Config Desc  = parameters for herbivore activity
2462       !Config If    = OK_STOMATE
2463       !Config Def   = 0.019
2464       !Config Help  =
2465       !Config Units = [-] 
2466       CALL getin_p('HVC1',hvc1)
2467       !
2468       !Config Key   = HVC2
2469       !Config Desc  = parameters for herbivore activity
2470       !Config If    = OK_STOMATE
2471       !Config Def   = 1.38
2472       !Config Help  =
2473       !Config Units = [-] 
2474       CALL getin_p('HVC2',hvc2)
2475       !
2476       !Config Key   = LEAF_FRAC_HVC
2477       !Config Desc  = parameters for herbivore activity
2478       !Config If    = OK_STOMATE
2479       !Config Def   = 0.33
2480       !Config Help  =
2481       !Config Units = [-]
2482       CALL getin_p('LEAF_FRAC_HVC',leaf_frac_hvc)
2483       !
2484       !Config Key   = TLONG_REF_MAX
2485       !Config Desc  = maximum reference long term temperature
2486       !Config If    = OK_STOMATE
2487       !Config Def   = 303.1
2488       !Config Help  =
2489       !Config Units = [K] 
2490       CALL getin_p('TLONG_REF_MAX',tlong_ref_max)
2491       !
2492       !Config Key   = TLONG_REF_MIN
2493       !Config Desc  = minimum reference long term temperature
2494       !Config If    = OK_STOMATE
2495       !Config Def   = 253.1
2496       !Config Help  =
2497       !Config Units = [K] 
2498       CALL getin_p('TLONG_REF_MIN',tlong_ref_min)
2499       !
2500       !Config Key   = TUNE_WATERSTRESS
2501       !Config Desc  = Tuning parameter when calculating ::wstress_fac from ::moiavail_daily
2502       !Config If    = OK_STOMATE, functional_allocation
2503       !Config Def   = 2
2504       !Config Help  =
2505       !Config Units = [-]
2506       CALL getin_p('TUNE_WATERSTRESS',tune_waterstress)
2507       !
2508       !Config Key   = NCD_MAX_YEAR
2509       !Config Desc  =
2510       !Config If    = OK_STOMATE
2511       !Config Def   = 3.
2512       !Config Help  = NCD : Number of Chilling Days
2513       !Config Units = [days]
2514       CALL getin_p('NCD_MAX_YEAR',ncd_max_year)
2515       !
2516       !Config Key   = GDD_THRESHOLD
2517       !Config Desc  =
2518       !Config If    = OK_STOMATE
2519       !Config Def   = 5.
2520       !Config Help  = GDD : Growing-Degree-Day
2521       !Config Units = [K]
2522       CALL getin_p('GDD_THRESHOLD',gdd_threshold)
2523       !
2524       !Config Key   = GREEN_AGE_EVER
2525       !Config Desc  =
2526       !Config If    = OK_STOMATE
2527       !Config Def   = 2.
2528       !Config Help  =
2529       !Config Units = [-] 
2530       CALL getin_p('GREEN_AGE_EVER',green_age_ever)
2531       !
2532       !Config Key   = GREEN_AGE_DEC
2533       !Config Desc  =
2534       !Config If    = OK_STOMATE
2535       !Config Def   = 0.5
2536       !Config Help  =
2537       !Config Units = [-]
2538       CALL getin_p('GREEN_AGE_DEC',green_age_dec)
2539       !
2540       !Config Key   = NGD_MIN_DORMANCE
2541       !Config Desc  = Minimum length (days) of the dormance period
2542       !               for species with the ngd phenology type
2543       !Config If    = OK_STOMATE
2544       !Config Def   = 90.
2545       !Config Help  =
2546       !Config Units = [days]
2547       CALL getin_p('NGD_MIN_DORMANCE',ngd_min_dormance)
2548       
2549       !-
2550       ! growth_fun_all
2551       !-
2552       !Config Key   = BLYPASS_CC_BUG
2553       !Config Desc  = There is a bug somewhere which allows the circumference classes to
2554       !               deviate from monotonically increasing order, which can cause a problem.
2555       !               Setting this to TRUE disables the check for this condition and impliments
2556       !               a small patch for the one problem which has manifested.  This needs to
2557       !               be found.
2558       !Config If    = OK_STOMATE, functional allocation
2559       !Config Def   = FALSE
2560       !Config Help  =
2561       !Config Units = [-]
2562       lbypass_cc = .FALSE.
2563       CALL getin_p('BYPASS_CC_BUG',lbypass_cc) 
2564
2565       first_call = .FALSE.
2566       
2567    ENDIF
2568   
2569  END SUBROUTINE config_stomate_parameters
2570!
2571!=
2572!
2573!! ================================================================================================================================
2574!! SUBROUTINE   : config_forest_manage_parameters
2575!!
2576!>\BRIEF        This subroutine reads in the configuration file all the parameters
2577!! needed when forest management is activated (ie : when FOREST_MANAGEMENT is set to true).
2578!!
2579!! DESCRIPTION  : None
2580!!
2581!! RECENT CHANGE(S): None
2582!!
2583!! MAIN OUTPUT VARIABLE(S):
2584!!
2585!! REFERENCE(S) :
2586!!
2587!! FLOWCHART    :
2588!! \n
2589!_ ================================================================================================================================
2590
2591   SUBROUTINE config_forest_manage_parameters
2592     
2593    IMPLICIT NONE
2594   
2595    !! 0. Variables and parameters declaration
2596
2597    !! 0.4 Local variables   
2598
2599    LOGICAL, SAVE ::  first_call = .TRUE.  !! To keep first call trace (true/false)
2600!$OMP THREADPRIVATE(first_call)
2601
2602!_ ================================================================================================================================
2603   
2604    IF(first_call) THEN
2605       
2606       !Config Key   = BAV_F
2607       !Config Desc  =
2608       !Config If    = FOREST_MANAGEMENT 
2609       !Config Def   = 0
2610       !Config Help  =
2611       !Config Units =
2612       bavard_f=0
2613       CALL getin_p ('BAV_F',bavard_f)
2614
2615       !! 2.1 Load parameters
2616
2617       !Config Key   = SS_SIGMA
2618       !Config Desc  =
2619       !Config If    = FOREST_MANAGEMENT
2620       !Config Def   =
2621       !Config Help  =
2622       !Config Units =
2623       CALL getin_p ('SS_SIGMA',ss_sigma) 
2624       !
2625       !Config Key   = FAKE
2626       !Config Desc  =
2627       !Config If    = FOREST_MANAGEMENT
2628       !Config Def   =
2629       !Config Help  =
2630       !Config Units =
2631       CALL getin_p ('FAKE',fake)
2632       !
2633       !Config Key   = EARLY_CUT
2634       !Config Desc  =
2635       !Config If    = FOREST_MANAGEMENT
2636       !Config Def   =
2637       !Config Help  =
2638       !Config Units =
2639       CALL getin_p ('EARLY_CUT',early_cut)
2640       !
2641       !Config Key   = CLEARFIRST
2642       !Config Desc  =
2643       !Config If    = FOREST_MANAGEMENT 
2644       !Config Def   =
2645       !Config Help  =
2646       !Config Units =
2647       CALL getin_p ('CLEARFIRST',clearfirst)
2648       !
2649       !Config Key   = ITINERARY
2650       !Config Desc  =
2651       !Config If    = FOREST_MANAGEMENT 
2652       !Config Def   =
2653       !Config Help  =
2654       !Config Units =
2655       CALL getin_p ('ITINERARY',itinerary)
2656       !
2657       !Config Key   = AGE_TARGET_DEF
2658       !Config Desc  =
2659       !Config If    = FOREST_MANAGEMENT 
2660       !Config Def   =
2661       !Config Help  =
2662       !Config Units =
2663       CALL getin_p('AGE_TARGET_DEF',age_target_def)
2664       !
2665       !Config Key   = NTREES_PROFIT
2666       !Config Desc  =
2667       !Config If    = FOREST_MANAGEMENT 
2668       !Config Def   = 100
2669       !Config Help  =
2670       !Config Units = (number of trees)
2671       ntrees_profit=200
2672       CALL getin_p('NTREES_PROFIT',ntrees_profit)
2673
2674       ! Sensitivity analysis
2675       !
2676       !Config Key   = SS_PIPE_DENSITY
2677       !Config Desc  =
2678       !Config If    = FOREST_MANAGEMENT 
2679       !Config Def   =
2680       !Config Help  =
2681       !Config Units =
2682       CALL getin_p('SS_PIPE_DENSITY',ss_pipe_density)
2683
2684       !Config Key   = SS_LAMBDA
2685       !Config Desc  =
2686       !Config If    = FOREST_MANAGEMENT 
2687       !Config Def   =
2688       !Config Help  =
2689       !Config Units =
2690       CALL getin_p('SS_LAMBDA',ss_lambda)
2691
2692       !Config Key   = SS_CIRC_BM
2693       !Config Desc  =
2694       !Config If    = FOREST_MANAGEMENT 
2695       !Config Def   =
2696       !Config Help  =
2697       !Config Units =
2698       CALL getin_p('SS_CIRC_BM',ss_circ_bm)
2699
2700       !Config Key   = SS_HEIGHT_CIRC
2701       !Config Desc  =
2702       !Config If    = FOREST_MANAGEMENT 
2703       !Config Def   =
2704       !Config Help  =
2705       !Config Units =
2706       CALL getin_p('SS_HEIGHT_CIRC',ss_height_circ)
2707
2708       !Config Key   = SS_MIN_CIRC_INIT
2709       !Config Desc  =
2710       !Config If    =
2711       !Config Def   =
2712       !Config Help  =
2713       !Config Units =
2714       CALL getin_p('SS_MIN_CIRC_INIT',ss_min_circ_init)
2715
2716       !Config Key   = SS_P_MAX
2717       !Config Desc  =
2718       !Config If    = FOREST_MANAGEMENT 
2719       !Config Def   =
2720       !Config Help  =
2721       !Config Units =
2722       CALL getin_p('SS_P_MAX',ss_p_max)
2723
2724       !Config Key   = SS_TH_STRAT 
2725       !Config Desc  =
2726       !Config If    = FOREST_MANAGEMENT 
2727       !Config Def   =
2728       !Config Help  =
2729       !Config Units =
2730       CALL getin_p('SS_TH_STRAT',ss_th_strat)
2731
2732       !Config Key   = SS_TAU_SPREAD
2733       !Config Desc  =
2734       !Config If    = FOREST_MANAGEMENT
2735       !Config Def   =
2736       !Config Help  =
2737       !Config Units =
2738       CALL getin_p('SS_TAU_SPREAD',ss_tau_spread)
2739
2740       !Config Key   = SS_SELFTH_CURVE
2741       !Config Desc  =
2742       !Config If    = FOREST_MANAGEMENT 
2743       !Config Def   =
2744       !Config Help  =
2745       !Config Units =
2746       CALL getin_p('SS_SELFTH_CURVE',ss_selfth_curve)
2747       
2748       !
2749       ! these parameters were initially found in the clearcut routine,
2750       ! but I moved them here for externalization
2751       !
2752       !Config Key   = FRAC_SHOOT_INIT
2753       !Config Desc  =
2754       !Config If    = FOREST_MANAGEMENT 
2755       !Config Def   =
2756       !Config Help  =
2757       !Config Units =
2758       frac_shoot_init = un/1.4_r_std
2759       CALL getin_p('FRAC_SHOOT_INIT',frac_shoot_init)
2760
2761       !Config Key   = MIN_CIRC_INIT
2762       !Config Desc  =
2763       !Config If    = FOREST_MANAGEMENT 
2764       !Config Def   =
2765       !Config Help  =
2766       !Config Units = cm
2767       min_circ_init = un*pi
2768       CALL getin_p('MIN_CIRC_INIT',min_circ_init)
2769
2770       !Config Key   = RDI_LIMIT_UPPER
2771       !Config Desc  = Replace yield relationship by this values in case inconsistencies
2772       !               exist between the fitted self-tinning and fitted yield relationships         
2773       !Config If    = OK_STOMATE, functional allocation
2774       !Config Def   = 0.9
2775       !Config Help  =
2776       !Config Units = [-]
2777       rdi_limit_upper = 0.9
2778       CALL getin_p('RDI_LIMIT_UPPER',rdi_limit_upper)
2779
2780       !Config Key   = NDIA_HARVEST
2781       !Config Desc  = Number of basal area classes in allocation scheme
2782       !Config If    = OK_STOMATE, functional allocation
2783       !Config Def   = 5
2784       !Config Help  =
2785       !Config Units = [-]
2786       ndia_harvest = 5
2787       CALL getin_p('NDIA_HARVEST',ndia_harvest)
2788
2789       !Config Key   = MAX_HARVEST_DIA
2790       !Config Desc  = The maximum diamter of tree [m] which can be harvested.  Notice that we
2791       !               will create a class that is one size larger than this to make sure
2792       !               we keep track of all the wood.
2793       !Config If    = OK_STOMATE, functional allocation
2794       !Config Def   = 1.0
2795       !Config Help  =
2796       !Config Units = [-]
2797       max_harvest_dia = un
2798       CALL getin_p('MAX_HARVEST_DIA',max_harvest_dia) 
2799
2800       !Config Key   = N_PAI
2801       !Config Desc  = Number of years used for the calculation of the periodic annual increment
2802       !Config If    = OK_STOMATE, functional allocation
2803       !Config Def   = 5
2804       !Config Help  =
2805       !Config Units = [-]
2806       n_pai=5
2807       CALL getin_p('N_PAI',n_pai)
2808
2809       ! Check to see if we are interested in using a litter demand map
2810       ! to remove litter from forest PFTs and put it into agricultural
2811       ! PFTs.  This simulations the practice of litter raking.
2812       !Config Key   = USE_LITTER_RAKING
2813       !Config Desc  =
2814       !Config If    = OK_STOMATE
2815       !Config Def   = N
2816       !Config Help  =
2817       !Config Units =
2818       use_litter_raking=.FALSE.
2819       CALL getin_p('USE_LITTER_RAKING',use_litter_raking)
2820
2821       ! We need to have the option to read the forest management
2822       ! strategy from a map (NetCDF file).  If this option is
2823       ! equal to Y, we will overwrite the forest_managed_forced
2824       ! option above, so you should be careful to only use one
2825       ! or the other. 
2826       !Config Key   = READ_FM_MAP
2827       !Config Desc  =
2828       !Config If    = OK_STOMATE
2829       !Config Def   = N
2830       !Config Help  =
2831       !Config Units =
2832       lread_fm_map=.FALSE.
2833       CALL getin_p('READ_FM_MAP',lread_fm_map)
2834
2835       ! Sometimes it's a good idea to change species after
2836       ! a clearcut on managed forest.  If this flag is true,
2837       ! we do this.  If not, the same PFT is always replanted.
2838       !Config Key   = LCHANGE_SPECIES
2839       !Config Desc  =
2840       !Config If    = OK_STOMATE
2841       !Config Def   = N
2842       !Config Help  =
2843       !Config Units =
2844       lchange_species=.FALSE.
2845       CALL getin_p('LCHANGE_SPECIES',lchange_species)
2846
2847       ! If we change the species after a clearcut, do we want to
2848       ! read the new PFT from a map?
2849       !Config Key   = READ_SPECIES_CHANGE_MAP
2850       !Config Desc  =
2851       !Config If    = OK_STOMATE
2852       !Config Def   = N
2853       !Config Help  =
2854       !Config Units =
2855       lread_species_change_map=.FALSE.
2856       CALL getin_p('READ_SPECIES_CHANGE_MAP',lread_species_change_map)
2857
2858       ! If we don't read the new species from a map, we will use veget_max
2859       ! instead. So we will replant with the current species. This will
2860       ! only happen if species_change_force equals -9999. If
2861       ! species_change_force has a different value in the run.def that
2862       ! value will be used. Note that species_change_force is intended for
2863       ! testing and debugging.
2864       !Config Key   = SPECIES_CHANGE_FORCE
2865       !Config Desc  =
2866       !Config If    = OK_STOMATE
2867       !Config Def   = 1
2868       !Config Help  =
2869       !Config Units =
2870       species_change_force=-9999
2871       CALL getin_p('SPECIES_CHANGE_FORCE',species_change_force)
2872
2873       ! If we change the species after a clearcut, do we want to
2874       ! read the new FM strategy from a map?
2875       !Config Key   = READ_DESIRED_FM_MAP
2876       !Config Desc  =
2877       !Config If    = OK_STOMATE, LCHANGE_SPECIES
2878       !Config Def   = N
2879       !Config Help  =
2880       !Config Units =
2881       lread_desired_fm_map=.FALSE.
2882       CALL getin_p('READ_DESIRED_FM_MAP',lread_desired_fm_map)
2883
2884       ! If we don't read the new speciesFM strategies from a map, we
2885       ! will force it with this variable.
2886       !Config Key   = FM_CHANGE_FORCE
2887       !Config Desc  =
2888       !Config If    = OK_STOMATE, LCHANGE_SPECIES
2889       !Config Def   = 1
2890       !Config Help  =
2891       !Config Units =
2892       species_change_force=1
2893       CALL getin_p('FM_CHANGE_FORCE',fm_change_force)
2894
2895       first_call = .FALSE.
2896       
2897    ENDIF
2898   
2899  END SUBROUTINE config_forest_manage_parameters
2900
2901!
2902! =
2903!
2904
2905!! ================================================================================================================================
2906!! SUBROUTINE   : config_dgvm_parameters
2907!!
2908!>\BRIEF        This subroutine reads in the configuration file all the parameters
2909!! needed when the DGVM model is activated (ie : when ok_dgvm is set to true).
2910!!
2911!! DESCRIPTION  : None
2912!!
2913!! RECENT CHANGE(S): None
2914!!
2915!! MAIN OUTPUT VARIABLE(S):
2916!!
2917!! REFERENCE(S) :
2918!!
2919!! FLOWCHART    :
2920!! \n
2921!_ ================================================================================================================================
2922
2923  SUBROUTINE config_dgvm_parameters   
2924   
2925    IMPLICIT NONE
2926   
2927    !! 0. Variables and parameters declaration
2928
2929    !! 0.4 Local variables
2930
2931    LOGICAL, SAVE ::  first_call = .TRUE.         !! To keep first call trace (true/false)
2932!$OMP THREADPRIVATE(first_call)
2933
2934!_ ================================================================================================================================   
2935
2936    IF(first_call) THEN
2937 
2938       !-
2939       ! establish parameters
2940       !-
2941       !
2942       !Config Key   = ESTAB_MAX_TREE
2943       !Config Desc  = Maximum tree establishment rate
2944       !Config If    = OK_DGVM
2945       !Config Def   = 0.12
2946       !Config Help  =
2947       !Config Units = [-]   
2948       CALL getin_p('ESTAB_MAX_TREE',estab_max_tree)
2949       !
2950       !Config Key   = ESTAB_MAX_GRASS
2951       !Config Desc  = Maximum grass establishment rate
2952       !Config If    = OK_DGVM
2953       !Config Def   = 0.12
2954       !Config Help  =
2955       !Config Units = [-] 
2956       CALL getin_p('ESTAB_MAX_GRASS',estab_max_grass)
2957       !
2958       !Config Key   = ESTABLISH_SCAL_FACT
2959       !Config Desc  =
2960       !Config If    = OK_DGVM
2961       !Config Def   = 5.
2962       !Config Help  =
2963       !Config Units = [-]
2964       CALL getin_p('ESTABLISH_SCAL_FACT',establish_scal_fact)
2965       !
2966       !Config Key   = MAX_TREE_COVERAGE
2967       !Config Desc  =
2968       !Config If    = OK_DGVM
2969       !Config Def   = 0.98
2970       !Config Help  =
2971       !Config Units = [-]
2972       CALL getin_p('MAX_TREE_COVERAGE',max_tree_coverage)
2973       !
2974       !Config Key   = IND_0_ESTAB
2975       !Config Desc  =
2976       !Config If    = OK_DGVM
2977       !Config Def   = 0.2
2978       !Config Help  =
2979       !Config Units = [-] 
2980       CALL getin_p('IND_0_ESTAB',ind_0_estab)
2981
2982       !-
2983       ! light parameters
2984       !-
2985       !
2986       !Config Key   = ANNUAL_INCREASE
2987       !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)?
2988       !Config If    = OK_DGVM
2989       !Config Def   = y
2990       !Config Help  =
2991       !Config Units = [FLAG]
2992       CALL getin_p('ANNUAL_INCREASE',annual_increase)
2993       !
2994       !Config Key   = MIN_COVER
2995       !Config Desc  = For trees, minimum fraction of crown area occupied
2996       !Config If    = OK_DGVM
2997       !Config Def   = 0.05
2998       !Config Help  =
2999       !Config Units = [-] 
3000       CALL getin_p('MIN_COVER',min_cover)
3001
3002       !-
3003       ! pftinout parameters
3004       !
3005       !Config Key   = IND_0
3006       !Config Desc  = initial density of individuals
3007       !Config If    = OK_DGVM
3008       !Config Def   = 0.02
3009       !Config Help  =
3010       !Config Units = [-] 
3011       CALL getin_p('IND_0',ind_0)
3012       !
3013       !Config Key   = MIN_AVAIL
3014       !Config Desc  = minimum availability
3015       !Config If    = OK_DGVM
3016       !Config Def   = 0.01
3017       !Config Help  =
3018       !Config Units = [-] 
3019       CALL getin_p('MIN_AVAIL',min_avail)
3020       !
3021       !Config Key   = RIP_TIME_MIN
3022       !Config Desc  =
3023       !Config If    = OK_DGVM
3024       !Config Def   = 1.25
3025       !Config Help  =
3026       !Config Units = [year] 
3027       CALL getin_p('RIP_TIME_MIN',RIP_time_min)
3028       !
3029       !Config Key   = NPP_LONGTERM_INIT
3030       !Config Desc  =
3031       !Config If    = OK_DGVM
3032       !Config Def   = 10.
3033       !Config Help  =
3034       !Config Units = [gC/m^2/year]
3035       CALL getin_p('NPP_LONGTERM_INIT',npp_longterm_init)
3036       !
3037       !Config Key   = EVERYWHERE_INIT
3038       !Config Desc  =
3039       !Config If    = OK_DGVM
3040       !Config Def   = 0.05
3041       !Config Help  =
3042       !Config Units = [-]
3043       CALL getin_p('EVERYWHERE_INIT',everywhere_init)
3044       
3045       first_call = .FALSE.
3046       
3047    ENDIF
3048   
3049   
3050  END SUBROUTINE config_dgvm_parameters
3051
3052
3053END MODULE constantes
Note: See TracBrowser for help on using the repository browser.