source: tags/ORCHIDEE_4_1/ORCHIDEE/src_parameters/control.f90 @ 7852

Last change on this file since 7852 was 7534, checked in by josefine.ghattas, 2 years ago

Merged changset 7337 and 7338 from ORCHIDEE_2_2 into the trunk, see ticket #821:

Simplification of soil texture processing, cf ticket #416: when using the Zobler map, the soil parameters are no more taken from 3-value "FAO" vectors in constantes_soil_var.f90, but from 13-value USDA vectors, owing to a pointer fao2usda.

No change in results but the variable njsc which changed order.

File size: 43.7 KB
Line 
1! =================================================================================================================================
2! MODULE       : control
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE      : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF        "control" module contains subroutines to initialize run time control parameters.
10!!
11!!\n DESCRIPTION:
12!!
13!! SVN          :
14!! $HeadURL:
15!! $Date: 
16!! $Revision:
17!! \n
18!_ ================================================================================================================================
19
20MODULE control
21 
22  USE constantes_soil
23  USE constantes_var
24  USE pft_parameters
25  USE vertical_soil
26
27  IMPLICIT NONE
28
29CONTAINS
30!! ================================================================================================================================
31!! SUBROUTINE   : control_initialize
32!!
33!>\BRIEF        This subroutine reads the configuration flags which control the behaviour of the model
34!!              This subroutine was previsouly named intsurf_config and located in intersurf module.
35!!
36!! DESCRIPTION  : None
37!!
38!! RECENT CHANGE(S): None
39!!
40!! MAIN OUTPUT VARIABLE(S): None
41!!
42!! REFERENCE(S) : None
43!!
44!! FLOWCHART    : None
45!! \n
46!_ ================================================================================================================================
47
48  SUBROUTINE control_initialize
49
50    IMPLICIT NONE
51   
52    LOGICAL                                    :: conflict              !! Check whether there are conflicts
53    LOGICAL                                    :: temp                  !! Temp to check for conflicts 
54    INTEGER(i_std)                             :: jv                    !! Local index variable
55    INTEGER(i_std)                             :: ier                   !! Error handeling
56    LOGICAL                                    :: hydrol_cwrr_test      !! Temporary test variable
57    LOGICAL                                    :: ok_co2_test           !! Temporary test variable
58    LOGICAL                                    :: ok_explicitsnow_test  !! Temporary test variable
59    ! control initialisation with sechiba
60    ok_sechiba = .TRUE.
61
62    ! Start reading options from parameter file
63    !
64    !Config key   = NC_RESTART_COMPRESSION
65    !Config Desc  = Restart netcdf outputs file are written in compression mode
66    !Config If    =
67    !Config Def   = n
68    !Config Help  = This flag allows the user to decide if the restart netcdf
69    !Config         output files are compressed by default 
70    !Config Units = [FLAG]
71    !
72    nc_restart_compression = .TRUE.
73    CALL getin_p('NC_RESTART_COMPRESSION', nc_restart_compression)
74    WRITE(numout,*) "Netcdf restart compression is : ", nc_restart_compression
75
76    !Config Key   = SOILTYPE_CLASSIF
77    !Config Desc  = Type of classification used for the map of soil types
78    !Config Def   = zobler
79    !Config If    = !IMPOSE_VEG
80    !Config Help  = The classification used in the file that we use here
81    !Config         There are three classification supported: 
82    !Config         Zobler (7 converted to 3) and USDA (12)
83    !Config Units = [-]
84    !
85    soil_classif = 'zobler'
86    CALL getin_p('SOILTYPE_CLASSIF',soil_classif)
87    SELECTCASE (soil_classif)
88    CASE ('zobler','none')
89       nscm = nscm_usda ! owing to the fao2usda pointer
90    CASE ('usda')
91       nscm = nscm_usda
92    CASE DEFAULT
93       WRITE(numout,*) "Unsupported soil type classification: soil_classif=",soil_classif
94       WRITE(numout,*) "Choose between zobler, usda and none according to the map"
95       CALL ipslerr(3,'control_initialize','Bad choice of soil_classif',&
96            'Choose between zobler, usda and none','')
97    ENDSELECT
98    WRITE(numout,*)'soil_classif,nscm', soil_classif, nscm
99
100    !Config Key   = ENERGY_CONTROL
101    !Config Desc  = A flag that controls severeal other flags related to  the energy budget
102    !Config Desc    scheme (enerbil or multi-layer energy budget) and water stress.
103    !Config Def   = 1
104    !Config If    = OK_SECHIBA
105    !Config Help  = Flag that automatically controls several other flags related
106    !Config Help    to multi-layering (1/2/3/4/5).
107    !Config Help    1 - DEFAULT uses the enerbil module in combination with the
108    !Config Help    hydraulic architecture (ok_hydrol_arch and ok_gs_feedback
109    !Config Help    true, while ok_mleb and ok_impose_canopy_structure are set
110    !Config Help    to false). Uses a dynamic approach to bare soil thus
111    !Config Help    ok_bare_soil_new = false
112    !Config Help    2 - option to use enerbil module and original water stress
113    !Config Help    (not hydraulic architecture). Uses a dynamic approach to bare soil thus
114    !Config Help    ok_bare_soil_new = false
115    !Config Help    3 - The energy budget is calculated using the multi-layer
116    !Config Help    energy scheme with a single laye: ok_hydrol_arch,
117    !Config Help    ok_gs_feedback, ok_impose_canopy_structure and ok_mleb all
118    !Config Help    TRUE, but The energy budget is only calculated for a single
119    !Config Help    layer (jnlvls is 1,jnlvls_under is 0,jnlvls_canopy is 1,jnlvls_over is 0).
120    !Config Help    No mleb output, ok_mleb_history_file is set to FALSE. Uses a
121    !Config Help    dynamic approach to bare soil thus ok_bare_soil_new = false
122    !Config Help    4 - multi-layer energy budget: ok_hydrol_arch, ok_gs_feedback
123    !Config Help    and ok_mleb all TRUE. ok_impose_canopy_structure is False, and the
124    !Config Help    energy budget is calculated for multiple layers
125    !Config Help    (jnlvls is 29,jnlvls_under is 10,jnlvls_canopy is 10,jnlvls_over is 9).   
126    !Config Help    No mleb output, ok_mleb_history_file is set to  FALSE. Uses an ecological
127    !Config Help    approach to bare soil thus ok_bare_soil_new = true
128    !Config Help    5 - user specific: user specific settings for these
129    !Config Help    controls and layers as defined in the run.def by the user.
130    !Config Units = [FLAG]
131    ENERGY_CONTROL = 1 
132    CALL getin_p('ENERGY_CONTROL', ENERGY_CONTROL)
133
134    ! set flags according to the ENERGY_CONTROL flag.
135    IF( ENERGY_CONTROL .EQ. 1) THEN  ! DEFAULT
136
137       ok_hydrol_arch = .TRUE.
138       ok_gs_feedback = .TRUE.
139       ok_mleb = .FALSE.
140       ok_impose_can_structure = .FALSE.
141       ok_mleb_history_file = .FALSE.
142       ok_bare_soil_new = .FALSE.
143
144       ! Search for possible conflicts
145       conflict = .FALSE.
146       temp = ok_hydrol_arch
147       CALL getin_p('OK_HYDROL_ARCH', temp)
148       IF (ok_hydrol_arch .NEQV. temp) conflict = .TRUE.
149       temp = ok_gs_feedback
150       CALL getin_p('OK_GS_FEEDBACK', temp)
151       IF (ok_gs_feedback .NEQV. temp) conflict = .TRUE.
152       temp = ok_mleb
153       CALL getin_p('OK_MLEB', temp)
154       IF (ok_mleb .NEQV. temp) conflict = .TRUE.
155       temp = ok_impose_can_structure
156       CALL getin_p('OK_IMPOSE_CAN_STRUCTURE', temp)
157       IF (ok_impose_can_structure .NEQV. temp) conflict = .TRUE.
158       temp = ok_mleb_history_file
159       CALL getin_p('OK_MLEB_HISTORY_FILE', temp)
160       IF (ok_mleb_history_file .NEQV. temp) conflict = .TRUE.
161       IF (conflict) THEN
162          CALL ipslerr(2,'control_initialize', &
163               'Some of the parameter values set in the', &
164               'run.def or set as a default are overwritten by the',&
165               'values implied by the ENERGY_CONTROL flag')
166       ENDIF
167
168    ELSEIF( ENERGY_CONTROL .EQ. 2 ) THEN  ! enerbil module
169
170       WRITE(numout,*) 'ENERGY_CONTROL=2 is set. '
171       WRITE(numout,*) 'enerbil module will be used and no of the options in mleb and hydrol_arch will be used'
172       ok_hydrol_arch = .FALSE.
173       ok_gs_feedback = .FALSE.
174       ok_mleb = .FALSE.
175       ok_impose_can_structure = .FALSE.
176       ok_mleb_history_file = .FALSE.
177       ok_bare_soil_new = .FALSE.
178
179    ELSEIF( ENERGY_CONTROL .EQ. 3 ) THEN  ! single layer multi-layer energy scheme
180
181       ok_hydrol_arch = .TRUE.
182       ok_gs_feedback = .TRUE.
183       ok_mleb = .TRUE.
184       ok_impose_can_structure = .TRUE.
185       ok_mleb_history_file = .FALSE.
186       ok_bare_soil_new = .FALSE.
187
188       ! Search for possible conflicts
189       conflict = .FALSE.
190       temp = ok_hydrol_arch
191       CALL getin_p('OK_HYDROL_ARCH', temp)
192       IF (ok_hydrol_arch .NEQV. temp) conflict = .TRUE.
193       temp = ok_gs_feedback
194       CALL getin_p('OK_GS_FEEDBACK', temp)
195       IF (ok_gs_feedback .NEQV. temp) conflict = .TRUE.
196       temp = ok_mleb
197       CALL getin_p('OK_MLEB', temp)
198       IF (ok_mleb .NEQV. temp) conflict = .TRUE.
199       temp = ok_impose_can_structure
200       CALL getin_p('OK_IMPOSE_CAN_STRUCTURE', temp)
201       IF (ok_impose_can_structure .NEQV. temp) conflict = .TRUE.
202       temp = ok_mleb_history_file
203       CALL getin_p('OK_MLEB_HISTORY_FILE', temp)
204       IF (ok_mleb_history_file .NEQV. temp) conflict = .TRUE.
205       IF (conflict) THEN
206          CALL ipslerr(2,'control_initialize', &
207               'Some of the parameter values set in the', &
208               'run.def or set as a default are overwritten by the',&
209               'values implied by the ENERGY_CONTROL flag')
210       ENDIF
211
212    ELSEIF( ENERGY_CONTROL .EQ. 4 ) THEN  ! multi-layer
213
214       ok_hydrol_arch = .TRUE.
215       ok_gs_feedback = .TRUE.
216       ok_mleb = .TRUE.
217       ok_impose_can_structure = .FALSE.
218       ok_mleb_history_file = .FALSE.
219       ok_bare_soil_new = .TRUE.
220
221       ! Search for possible conflicts
222       conflict = .FALSE.
223       temp = ok_hydrol_arch
224       CALL getin_p('OK_HYDROL_ARCH', temp)
225       IF (ok_hydrol_arch .NEQV. temp) conflict = .TRUE.
226       temp = ok_gs_feedback
227       CALL getin_p('OK_GS_FEEDBACK', temp)
228       IF (ok_gs_feedback .NEQV. temp) conflict = .TRUE.
229       temp = ok_mleb
230       CALL getin_p('OK_MLEB', temp)
231       IF (ok_mleb .NEQV. temp) conflict = .TRUE.
232       temp = ok_impose_can_structure
233       CALL getin_p('OK_IMPOSE_CAN_STRUCTURE', temp)
234       IF (ok_impose_can_structure .NEQV. temp) conflict = .TRUE.
235       temp = ok_mleb_history_file
236       CALL getin_p('OK_MLEB_HISTORY_FILE', temp)
237       IF (ok_mleb_history_file .NEQV. temp) conflict = .TRUE.
238       IF (conflict) THEN
239          CALL ipslerr(2,'control_initialize', &
240               'Some of the parameter values set in the', &
241               'run.def or set as a default are overwritten by the',&
242               'values implied by the ENERGY_CONTROL flag')
243       ENDIF
244
245    ELSEIF( ENERGY_CONTROL .EQ. 5 ) THEN 
246
247       !Config Key   = OK_HYDROL_ARCH
248       !Config Desc  = Activates the hydraulic architecture
249       !Config If    = OK_SECHIBA
250       !Config Def   = y
251       !Config Help  = Flag that activates the hydraulic architecture routine (true/false)
252       !Config Help    The trunk version of ORCHIDEE (false) uses soil water as a
253       !Config Help    proxy for water stress and applies the stress to Vcmax.
254       !Config Help    When set to true the hydraulic architecture of the vegetation
255       !Config Help    is accounted for to calculate the amount of water that
256       !Config Help    can be transported through the plant given the soil and leaf
257       !Config Help    potential and the conductivities of the roots, wood and
258       !Config Help    leaves. Water supply through the plant is compared against
259       !Config Help    the atmospheric demand for water. If the supply is smaller
260       !Config Help    then the demand, the plant experiences water stress and the
261       !Config Help    stomata will be closed (water stress is now on gs rather
262       !Config Help    than Vcmax). Note that whether stomatal regulation is used or
263       !Config Help    not is controled by a separate flag: ok_gs_feedback.
264       !Config Units = [FLAG]
265       ok_hydrol_arch = .TRUE.
266       CALL getin_p('OK_HYDROL_ARCH', ok_hydrol_arch)
267       !
268       !Config Key   = OK_GS_FEEDBACK
269       !Config Desc  = Debug option for OK_HYDROL_ARCH 
270       !Config If    = OK_SECHIBA, OK_HYDROL_ARCH
271       !Config Def   = y
272       !Config Help  = Flag that activates water stress on stomata (true/false)
273       !Config Help    This flag is for debugging only! It allows developers
274       !Config Help    to calculate GPP without any water stress. If the model is
275       !Config Help    used in production mode and ok_hydrol_arch is true this
276       !Config Help    flag should be true as well.
277       !Config Units = [FLAG]
278       ok_gs_feedback = .TRUE.
279       CALL getin_p('OK_GS_FEEDBACK', ok_gs_feedback)
280       !
281       !Config Key   = OK_MLEB
282       !Config Desc  = Activate multi-layer energy budget 
283       !Config If    = OK_SECHIBA
284       !Config Def   = y
285       !Config Help  = Flag that activates the multilayer energy budget (true/false)
286       !Config Help    The model uses 10 (default) canopy layers to calculate
287       !Config Help    the albedo, transmittance, absorbance and GPP. These canopy
288       !Config Help    layers can be combined with 10 (default) layers below and
289       !Config Help    10 layers above the canopy to calculate the energy budget
290       !Config Help    (ok_mleb is y). If set to no, this flag will make the model
291       !Config Help    use 10 layers for the canopy albedo, transmittance,
292       !Config Help    absorbance and GPP and just a single layer for the energy
293       !Config Help    budget.
294       !Config Units = [FLAG]
295       ok_mleb = .FALSE.
296       CALL getin_p('OK_MLEB', ok_mleb)
297       !
298       !+++CHECK+++
299       ! This may no longer be needed. One could get the same functionality
300       ! by reading an biomass map in shechiba (lai_map) and not using stomate.
301       !Config Key   = OK_IMPOSE_CAN_STRUCTURE
302       !Config Desc  = Debug option for OK_MLEB
303       !Config If    = OK_SECHIBA, OK_MLEB
304       !Config Def   = n
305       !Config Help  = This flag is for debugging only! It allows developers
306       !Config Help    to use a prescribed canopy structure rather then the
307       !Config Help    structure calculate by ORCHIDEE. The flag activates the
308       !Config Help    sections of code which directly link the energy budget
309       !Config Help    scheme to the the size and LAI profile of the canopy for the
310       !Config Help    respective PFT and age class that is calculated in stomate,
311       !Config Help    for the albedo. If set to TRUE and the multi-layer budget
312       !Config Help    is activated the model takes LAI profile information and
313       !Config Help    canopy level heights from the run.def. If set to FALSE, and
314       !Config Help    and the multi-layer energy budget is used the profile
315       !Config Help    infomation and canopy levels heights comes from the
316       !Config Help    PGap-based processes for calculation of stand profile
317       !Config Help    information in stomate.
318       !Config Units = [FLAG]
319       ok_impose_can_structure = .FALSE.
320       CALL getin_p('OK_IMPOSE_CAN_STRUCTURE', ok_impose_can_structure)
321       !++++++++++
322       !
323       !Config Key   = MLEB_NETCDF_FLAG
324       !Config Desc  = Debug option for OK_MLEB
325       !Config If    = OK_SECHIBA, OK_MLEB
326       !Config Def   = n
327       !Config Help  = Flag that controls the writing of an output file with the
328       !Config Help    multi-layer energy simulations (true/false). Note that this
329       !Config Help    a large file and writing it slows down the code.
330       !Config Units = [FLAG]
331       ok_mleb_history_file = .FALSE.
332       CALL getin_p('OK_MLEB_HISTORY_FILE', ok_mleb_history_file)
333
334       !Config Key   = OK_BARE_SOIL_NEW
335       !Config Desc  = Flag that controls the view on and calculation of bare soil
336       !Config If    = OK_SECHIBA or OK_STOMATE
337       !Config Def   = FALSE
338       !Config Help  = Choose between the two options to calculate the bare soil.
339       !Config         False uses the classic view: gaps within a canopy should be treated
340       !Config         as bare soil. True uses the ecological view: gaps within a canopy are
341       !Config         part of the ecosystem and should be treated as such.
342       !Config Units = [FLAG]
343       ok_bare_soil_new = .FALSE.
344       CALL getin_p('OK_BARE_SOIL_NEW', ok_bare_soil_new) 
345
346    ELSE
347       WRITE(numout,*) 'Current setting of ENERGY_CONTROL is not implemanted, ENERGY_CONTROL=',ENERGY_CONTROL
348       CALL ipslerr_p(3,'control_initialize',&
349            'ENERGY_CONTROL can only have integer values from 1-4', '','')
350    ENDIF ! (ENERGY_CONTROL)
351
352    ! Share the final settings with the user
353    WRITE(numout,*) 'ENERGY_CONTROL is activated', ENERGY_CONTROL
354    WRITE(numout,*) 'OK_HYDROL_ARCH is activated, ',ok_hydrol_arch
355    WRITE(numout,*) 'OK_GS_FEEDBACK is activated, ',ok_gs_feedback   
356    WRITE(NUmout,*) 'OK_MLEB is activated', ok_mleb
357    WRITE(numout,*) 'OK_IMPOSE_CAN_STRUCTURE is activated', ok_impose_can_structure
358    WRITE(numout,*) 'OK_MLEB_HISTORY_FILE is activated',ok_mleb_history_file
359    WRITE(numout,*) 'OK_BARE_SOIL_NEW is activated',ok_bare_soil_new
360   
361    ! Final consistency check of the settings
362    IF (ok_hydrol_arch .AND. ok_gs_feedback)THEN
363
364       ! This is the default set-up for running hydraulic architecture
365       ! in production mode. Using full functionality
366       WRITE(numout,*) 'Hydraulic architecture, stomatal feedback'
367       WRITE(numout,*) 'and the energy budget are (re)calculated'
368
369    ELSEIF (.NOT. ok_hydrol_arch .AND. ok_gs_feedback) THEN
370
371       ! The debug options should not be used. Not clear whether
372       ! the user want to use hydraulic architecture or not
373       WRITE(numout,*) 'Hydraulic architecture is not used'
374       WRITE(numout,*) 'but the debug option was set to TRUE'
375       WRITE(numout,*) 'Not clear whether you want to use '
376       WRITE(numout,*) 'hydraulic architecture or not'
377       CALL ipslerr(3,'control.f90 - run.def',&
378            'setting for stomatal feedback was in conflict with',&
379            'the setting of hydraulic architecture','')
380
381    ELSEIF (ok_hydrol_arch .AND. .NOT.ok_gs_feedback) THEN
382
383       ! Warning
384       CALL ipslerr(2,'control.f90 - hydraulic architecture',&
385            'is run in DEBUG mode',&
386            'stomatal feedback is not used','')
387
388    ENDIF
389
390    IF (ok_mleb .AND. ok_impose_can_structure) THEN
391
392       ! Warning
393       CALL ipslerr(2,'control.f90 - multi-layer energy budget',&
394            'is run in debug mode',&
395            'The canopy structure is fixed and imposed','')
396
397    ELSEIF (ok_mleb .AND. .NOT.ok_mleb_history_file) THEN
398   
399       ! Warning
400       CALL ipslerr(2,'control.f90 - multi-layer energy budget',&
401            'There won be any output files for the multi-layer energy budget',&
402            'If this is not intended, change the run.def','')
403
404    ELSEIF ((.NOT.ok_mleb .AND. ok_impose_can_structure) .OR. &
405         (.NOT.ok_mleb .AND. ok_mleb_history_file)) THEN
406       
407       ! The debug options should not be used. Not clear whether
408       ! the user want to use hydraulic architecture or not
409       WRITE(numout,*) 'The multi-layer energy budget is not used'
410       WRITE(numout,*) 'Debug options are set to FALSE'
411       CALL ipslerr(3,'control.f90 - run.def',&
412            'inconsistent settings of de debug options',&
413            'because the multi-level enery budget itself is not used','')
414
415    ENDIF
416
417    !Config Key   = RIVER_ROUTING
418    !Config Desc  = Decides if we route the water or not
419    !Config If    = OK_SECHIBA
420    !Config Def   = y
421    !Config Help  = This flag allows the user to decide if the runoff
422    !Config         and drainage should be routed to the ocean
423    !Config         and to downstream grid boxes.
424    !Config Units = [FLAG]
425    river_routing = .TRUE.
426    CALL getin_p('RIVER_ROUTING', river_routing)
427    IF (printlev>=1) WRITE(numout,*) "RIVER routing is activated : ",river_routing
428
429    ! Control for the option HYDROL_CWRR which is not longer existing in the model.
430    ! Check here if in run.def HYDROL_CWRR=n. If that's the case then stop the model and ask the user to remove the flag from run.def
431    hydrol_cwrr_test = .TRUE.
432    CALL getin_p('HYDROL_CWRR', hydrol_cwrr_test)
433    IF (.NOT. hydrol_cwrr_test) THEN
434       CALL ipslerr_p(3,'control_initialize',&
435            'HYDROL_CWRR=n is set in run.def but this option does not exist any more in ORCHIDEE', &
436            'Choisnel hydrolology has been removed and CWRR is now the only hydrology module in ORCHIDEE',&
437            'Remove parameter HYDROL_CWRR from run.def')
438    END IF
439
440    !Config Key   = DO_IRRIGATION
441    !Config Desc  = Should we compute an irrigation flux
442    !Config If    = RIVER_ROUTING
443    !Config Def   = n
444    !Config Help  = This parameters allows the user to ask the model
445    !Config         to compute an irigation flux. This performed for the
446    !Config         on very simple hypothesis. The idea is to have a good
447    !Config         map of irrigated areas and a simple function which estimates
448    !Config         the need to irrigate.
449    !Config Units = [FLAG]
450    do_irrigation = .FALSE.
451    IF ( river_routing ) CALL getin_p('DO_IRRIGATION', do_irrigation)
452   
453    !Config Key   = DO_FLOODPLAINS
454    !Config Desc  = Should we include floodplains
455    !Config If    = RIVER_ROUTING
456    !Config Def   = n
457    !Config Help  = This parameters allows the user to ask the model
458    !Config         to take into account the flood plains and return
459    !Config         the water into the soil moisture. It then can go
460    !Config         back to the atmopshere. This tried to simulate
461    !Config         internal deltas of rivers.
462    !Config Units = [FLAG] 
463    do_floodplains = .FALSE.
464    IF ( river_routing ) CALL getin_p('DO_FLOODPLAINS', do_floodplains)
465
466    !Config Key   = OK_SOIL_CARBON_DISCRETIZATION
467    !Config Desc  = Activate soil carbon vertical discretization
468    !Config If    = OK_STOMATE
469    !Config Def   = FALSE
470    !Config Help  = Activate soil carbon scheme with vertical discretization and vertical transport of carbon
471    !Config Units = [FLAG]
472    ok_soil_carbon_discretization=.FALSE.
473    CALL getin_p('OK_SOIL_CARBON_DISCRETIZATION', ok_soil_carbon_discretization)
474
475    !Config Key   = OK_VESSEL_MORTALITY
476    !Config Desc  = Activate death and recovery of vegetation following hydraulic failure.
477    !Config If    = OK_STOMATE
478    !Config Def   = FALSE
479    !Config Help  = Activate death and recovery of vegetation following hydraulic failure.
480    !Config Units = [FLAG]
481    ok_vessel_mortality=.FALSE.
482    CALL getin_p('OK_VESSEL_MORTALITY', ok_vessel_mortality)
483
484
485    ! Control of option OK_EXPLICITSNOW which is not longer existing in the model.
486    ! Check here if in run.def OK_EXPLICITSNOW=n. If that's the case then stop the model and ask the user to remove the flag from run.def.
487    ok_explicitsnow_test = .TRUE.
488    CALL getin_p('OK_EXPLICITSNOW', ok_explicitsnow_test)
489    IF (.NOT. ok_explicitsnow_test) THEN
490       CALL ipslerr_p(3,'control_initialize',&
491            'OK_EXPLICITSNOW=n is set in run.def but this option does not exist any more in ORCHIDEE', &
492            'Explicit snow scheme is now always used in ORCHIDEE.',&
493            'Remove parameter OK_EXPLICITSNOW from run.def')
494    END IF
495
496    !
497    !Config Key   = STOMATE_OK_STOMATE
498    !Config Desc  = Activate STOMATE?
499    !Config If    = OK_SECHIBA
500    !Config Def   = y
501    !Config Help  = set to TRUE if STOMATE is to be activated
502    !Config Units = [FLAG]
503    !
504    ok_stomate = .TRUE.
505    CALL getin_p('STOMATE_OK_STOMATE',ok_stomate)
506    IF (printlev>=1) WRITE(numout,*) 'STOMATE is activated: ',ok_stomate
507
508    ! Control for the option STOMATE_OK_CO2 which is not longer existing in the model.
509    ! Check here if in run.def STOMATE_OK_CO2=n. If that's the case then stop the model and ask the user to remove the flag from run.def
510    ok_co2_test = .TRUE.
511    CALL getin_p('STOMATE_OK_CO2', ok_co2_test)
512    IF (.NOT. ok_co2_test) THEN
513       CALL ipslerr_p(3,'control_initialize',&
514            'STOMATE_OK_CO2=n is set in run.def but this option does not exist any more in ORCHIDEE', &
515            'Calculation of beta coefficient using Jarvis formulation has been removed and Farquar formulation is now always used',&
516            'Remove parameter STOMATE_OK_CO2 from run.def')
517    END IF
518
519   
520    !Config Key   = DO_WOOD_HARVEST
521    !Config Desc  = Activate Wood Harvest ?
522    !Config If    = OK_STOMATE
523    !Config Def   = n
524    !Config Help  = set to TRUE if a prescribed amount of wood is to be harvested.
525    !Config         Note that this approach is different from the forest management
526    !Config         in which the management strategy is read from a map and the model
527    !Config         left to calculate the thinnings and the harvest.
528    !Config Units = [FLAG]
529    do_wood_harvest = .FALSE.
530    CALL getin_p('DO_WOOD_HARVEST',do_wood_harvest)
531
532    !
533    !Config Key   = STOMATE_OK_NCYCLE
534    !Config Desc  = Activate dynamic N cycle
535    !Config If    = OK_STOMATE
536    !Config Def   = y
537    !Config Help  = set to TRUE if N cycle is to be activated
538    !Config Units = [FLAG]
539    ok_ncycle = .TRUE. 
540    CALL getin_p('STOMATE_OK_NCYCLE',ok_ncycle) 
541    WRITE(numout,*) 'N cycle is activated: ',ok_ncycle 
542
543    !
544    !Config Key   = STOMATE_IMPOSE_CN
545    !Config Desc  = Impose the CN ratio of leaves
546    !Config If    = OK_STOMATE
547    !Config Def   = n
548    !Config Help  = set to TRUE if IMPOSE_CN is to be activated
549    !Config Units = [FLAG]
550    impose_cn = .FALSE. 
551    CALL getin_p('STOMATE_IMPOSE_CN',impose_cn) 
552    WRITE(numout,*) 'CN ratio is imposed: ',impose_cn 
553    !
554    !Config Key   = RESET_IMPOSE_CN
555    !Config Desc  = Reset the CN ratio of leaves
556    !Config If    = OK_STOMATE
557    !Config Def   = n
558    !Config Help  = set to TRUE if RESET_IMPOSE_CN is to be activated
559    !Config Units = [FLAG] 
560    reset_impose_cn = .FALSE. 
561    CALL getin_p('RESET_IMPOSE_CN',reset_impose_cn) 
562    WRITE(numout,*) 'CN ratio is reset: ',reset_impose_cn 
563    !
564    !Config Key   = STOMATE_READ_CN
565    !Config Desc  = Read the CN ratio of leaves
566    !Config If    = OK_STOMATE
567    !Config Def   = n
568    !Config Help  = set to TRUE if IMPOSE_CN is to be activated read
569    !Config Units = [FLAG]
570    !
571    read_cn = .FALSE. 
572    CALL getin_p('STOMATE_READ_CN',read_cn) 
573    WRITE(numout,*) 'CN ratio is read: ',read_cn 
574    !
575    !
576    !Config Key   = STOMATE_OK_DGVM
577    !Config Desc  = Activate DGVM?
578    !Config If    = OK_STOMATE
579    !Config Def   = n
580    !Config Help  = set to TRUE if DGVM is to be activated
581    !Config Units = [FLAG]
582    ok_dgvm = .FALSE.
583    CALL getin_p('STOMATE_OK_DGVM',ok_dgvm)
584    IF ( ok_dgvm ) THEN
585       CALL ipslerr(3,'control_initialize', &
586            'All calls to DGVM have been commented. See ticket 504 before retoring the DGVM.',&
587            'Remember that stomate now uses only veget_max but the DGVM may require rescaled veget_max (previously veget_cov_max)',&
588            'This still needs to be changed before activation STOMATE_OK_DGVM')
589    ENDIF
590
591    !Config Key   = CHEMISTRY_BVOC
592    !Config Desc  = Activate calculations for BVOC
593    !Config If    = OK_SECHIBA
594    !Config Def   = n
595    !Config Help  = set to TRUE if biogenic emissions calculation is to be activated
596    !Config Units = [FLAG]
597   
598    ok_bvoc = .FALSE.
599    CALL getin_p('CHEMISTRY_BVOC', ok_bvoc)
600    IF (printlev>=1) WRITE(numout,*) 'Biogenic emissions: ', ok_bvoc
601
602    IF ( ok_bvoc ) THEN
603       ok_leafage         = .TRUE. 
604       ok_radcanopy       = .TRUE. 
605       ok_multilayer      = .TRUE.
606       ok_pulse_NOx       = .TRUE.
607       ok_bbgfertil_NOx   = .TRUE.
608       ok_cropsfertil_NOx = .TRUE.
609    ELSE
610       ok_leafage         = .FALSE. 
611       ok_radcanopy       = .FALSE. 
612       ok_multilayer      = .FALSE.
613       ok_pulse_NOx       = .FALSE.
614       ok_bbgfertil_NOx   = .FALSE.
615       ok_cropsfertil_NOx = .FALSE.
616    ENDIF
617    !
618    !Config Key   = CHEMISTRY_LEAFAGE
619    !Config Desc  = Activate LEAFAGE?
620    !Config If    = CHEMISTRY_BVOC
621    !Config Def   = n
622    !Config Help  = set to TRUE if biogenic emissions calculation takes leaf age into account
623    !Config Units = [FLAG]
624    !
625    CALL getin_p('CHEMISTRY_LEAFAGE', ok_leafage)
626    IF (printlev>=1) WRITE(numout,*) 'Leaf Age: ', ok_leafage
627   
628    !Config Key   = CANOPY_EXTINCTION
629    !Config Desc  = Use canopy radiative transfer model?
630    !Config If    = CHEMISTRY_BVOC
631    !Config Def   = n
632    !Config Help  = set to TRUE if canopy radiative transfer model is used for biogenic emissions
633    !Config Units = [FLAG]
634    !
635    CALL getin_p('CANOPY_EXTINCTION', ok_radcanopy)
636    IF (printlev>=1) WRITE(numout,*) 'Canopy radiative transfer model: ', ok_radcanopy
637   
638    !Config Key   = CANOPY_MULTILAYER
639    !Config Desc  = Use canopy radiative transfer model with multi-layers
640    !Config If    = CANOPY_EXTINCTION
641    !Config Def   = n
642    !Config Help  = set to TRUE if canopy radiative transfer model is with
643    !Config         multiple layers. DO NOT CONFUSE with the settings for the
644    !Config         multi-layer energy budget. 
645    !Config Units = [FLAG]
646    !
647    CALL getin_p('CANOPY_MULTILAYER', ok_multilayer)
648    IF (printlev>=1) WRITE(numout,*) 'Multi-layer Canopy model: ', ok_multilayer
649   
650    !Config Key   = NOx_RAIN_PULSE
651    !Config Desc  = Calculate NOx emissions with pulse?
652    !Config If    = CHEMISTRY_BVOC
653    !Config Def   = n
654    !Config Help  = set to TRUE if NOx rain pulse is taken into account
655    !Config Units = [FLAG]
656    !
657    CALL getin_p('NOx_RAIN_PULSE', ok_pulse_NOx)
658    IF (printlev>=1) WRITE(numout,*) 'Rain NOx pulsing: ', ok_pulse_NOx
659   
660    !Config Key   = NOx_BBG_FERTIL
661    !Config Desc  = Calculate NOx emissions with bbg fertilizing effect?
662    !Config If    = CHEMISTRY_BVOC
663    !Config Def   = n
664    !Config Help  = set to TRUE if NOx emissions are calculated with bbg effect
665    !Config         Fertil effect of bbg on NOx soil emissions
666    !Config Units = [FLAG]
667    !
668    CALL getin_p('NOx_BBG_FERTIL', ok_bbgfertil_NOx)
669    IF (printlev>=1) WRITE(numout,*) 'NOx bbg fertil effect: ', ok_bbgfertil_NOx
670   
671    !Config Key   = NOx_FERTILIZERS_USE
672    !Config Desc  = Calculate NOx emissions with fertilizers use?
673    !Config If    = CHEMISTRY_BVOC
674    !Config Def   = n
675    !Config Help  = set to TRUE if NOx emissions are calculated with fertilizers use
676    !Config         Fertilizers use effect on NOx soil emissions 
677    !Config Units = [FLAG]
678    !
679    CALL getin_p('NOx_FERTILIZERS_USE', ok_cropsfertil_NOx)
680    IF (printlev>=1) WRITE(numout,*) 'NOx Fertilizers use: ', ok_cropsfertil_NOx
681    !Config Key  = Is CO2 impact on BVOC accounted for using Possell 2005 ?
682    !Config Desc = In this case we use Possell 2005 parameterisation
683    !Config Desc = to take into account the impact of CO2 on biogenic emissions for
684    !Config Desc = isoprene
685    !Config Def  = n
686    !Config Help = set to TRUE if Possell parameterisation has to be considered for the CO2 impact
687    !
688    ok_co2bvoc_poss = .FALSE.
689    CALL getin_p('CO2_FOR_BVOC_POSSELL', ok_co2bvoc_poss)
690    IF (printlev>=1) WRITE(numout,*) 'CO2 impact on BVOC - Possell parameterisation: ', ok_co2bvoc_poss
691    !
692    !Config Key  = Is CO2 impact on BVOC accounted for using Wilkinson 2009 ?
693    !Config Desc = In this case we use Wilkinson 2009 parameterisation
694    !Config Desc = to take into account the impact of CO2 on biogenic emissions for
695    !Config Desc = isoprene
696    !Config Def  = n
697    !Config Help = set to TRUE if Wilkinson parameterisation has to be considered for the CO2 impact
698    !
699    ok_co2bvoc_wilk = .FALSE.
700    CALL getin_p('CO2_FOR_BVOC_WILKINSON', ok_co2bvoc_wilk)
701    IF (printlev>=1) WRITE(numout,*) 'CO2 impact on BVOC - Wilkinson parameterisation: ', ok_co2bvoc_wilk
702    !
703    ! control initialisation with sechiba
704    !
705    !Config Key  = Is CO2 impact on BVOC accounted for using Wilkinson 2009 ?
706    !Config Desc = In this case we use Wilkinson 2009 parameterisation
707    !Config Desc = to take into account the impact of CO2 on biogenic emissions for
708    !Config Desc = isoprene
709    !Config Def  = FALSE
710    !Config Help = set to TRUE if Wilkinson parameterisation has to be considered for the CO2 impact
711    !
712    ok_co2bvoc_wilk = .FALSE.
713    CALL getin_p('CO2_FOR_BVOC_WILKINSON', ok_co2bvoc_wilk)
714    WRITE(*,*) 'CO2 impact on BVOC - Wilkinson parameterisation: ', ok_co2bvoc_wilk
715    !
716    !+++CHECK+++
717    ! No longer in CN but still in CN.CAN
718    !Config Key  = CONSTANT_MORTALITY
719    !Config Desc = Assume constant prescribed mortality or calculate &
720    !              mortality as a function of last year's NPP
721    !Config If   = OK_STOMATE
722    !Config Def  = TRUE
723    !Config Help = set to TRUE if constant mortality is to be assumed
724    ok_constant_mortality = .TRUE.
725    CALL getin_p('CONSTANT_MORTALITY',ok_constant_mortality)
726    WRITE(numout,*) 'MORTALITY is assumed to be constant ',&
727         '(instead of being a function of vigor): ', &
728         ok_constant_mortality
729    !+++++++++++
730   
731    !
732    !Config Key   = OK_READ_FM_MAP
733    !Config Desc  = Read the forest management strategy from a map 
734    !Config If    = OK_STOMATE
735    !Config Def   = FALSE
736    !Config Help  = We need to have the option to read the forest
737    !               management strategy from a map (NetCDF file). 
738    !               If this option is equal to TRUE, we will overwrite
739    !               the forest_managed_forced option, so you should be
740    !               careful to only use one or the other.
741    !Config Units = [FLAG]
742    ok_read_fm_map=.FALSE.
743    CALL getin_p('OK_READ_FM_MAP',ok_read_fm_map)
744   
745    !
746    !Config Key   = OK_READ_SP_CLEARCUT_MAP
747    !Config Desc  = Read a map prescribing whether a pxiel and PFT gets
748    !               clearcut during spinup 
749    !Config If    = OK_STOMATE
750    !Config Def   = FALSE
751    !Config Help  = We need this option to create the spatial heterogeneity
752    !               in forest age during spinup to mimic stochastic occurrence
753    !               natural disturbance events that lead to complete forest
754    !               regneration. This is also to break up the synchrony in
755    !               biomass growth during spinup for different pixels.
756    !Config Units = [FLAG]
757    ok_read_sp_clearcut_map = .FALSE.
758    CALL getin_p('OK_READ_SP_CLEARCUT_MAP',ok_read_sp_clearcut_map)
759
760    !Config Key   = OK_SPECIES_CHANGE
761    !Config Desc  = Change species after a stand replacing disturbance
762    !Config If    = OK_STOMATE
763    !Config Def   = FALSE
764    !Config Help  = Sometimes it's a good idea to change species
765    !               after a clearcut on managed forest.  If this
766    !               flag is true, we do this. If not, the same PFT
767    !               is always replanted.
768    !Config Units = [FLAG]
769    ok_change_species=.FALSE.
770    CALL getin_p('OK_CHANGE_SPECIES',ok_change_species)
771   
772    !Config Key   = READ_SPECIES_CHANGE_MAP
773    !Config Desc  = Read the new tree species from a species map
774    !Config If    = OK_STOMATE
775    !Config Def   = FALSE
776    !Config Help  = If we change the species after a clearcut, do we
777    !               want to read the new PFT from a map?
778    !Config Units = [FLAG]
779    ok_read_species_change_map=.FALSE.
780    CALL getin_p('OK_READ_SPECIES_CHANGE_MAP',ok_read_species_change_map)
781   
782    !Config Key   = OK_READ_DESIRED_FM_MAP
783    !Config Desc  = Read the new FM strategu from a map
784    !Config If    = OK_STOMATE, OK_CHANGE_SPECIES
785    !Config Def   = FALSE
786    !Config Help  = If we change the forest management after a clearcut, do
787    !               we want to read the new FM strategy from a map?
788    !Config Units = [FLAG]
789    ok_read_desired_fm_map=.FALSE.
790    CALL getin_p('OK_READ_DESIRED_FM_MAP',ok_read_desired_fm_map)
791   
792    !Config Key   = OK_LITTER_RAKING
793    !Config Desc  = Activite litter raking
794    !Config If    = OK_STOMATE
795    !Config Def   = FALSE
796    !Config Help  = Check to see if we are interested in using a litter
797    !               demand map to remove litter from forest PFTs and put
798    !               it into agricultural PFTs. This simulations the
799    !               practice of litter raking.
800    !Config Units = [FLAG]
801    ok_litter_raking=.FALSE.
802    CALL getin_p('OK_LITTER_RAKING',ok_litter_raking)
803       
804    !Config Key   = OK_DIMENSIONAL_PRODUCT_USE
805    !Config Desc  = Product pools are based on the dimensions of the harvest
806    !Config If    = OK_STOMATE
807    !Config Def   = TRUE
808    !Config Help  = Once the wood is harvested (through management or
809    !               LCC) it ends up in wood product pools. Two options were
810    !               implemeted: (1) the product use and the longevity, of the
811    !               product pools depend on the dimensions of the harvest. (2) the
812    !               dimensions are ignored and the wood is used according
813    !               to fixed ratios.
814    !Config Units = [FLAG]
815    ok_dimensional_product_use=.FALSE.
816    CALL getin_p('DIMENSIONAL_PRODUCT_USE',ok_dimensional_product_use)
817
818    !Config Key   = FORCED_CLEAR_CUT
819    !Config Desc  = Use to force a clear cut at a specific year during a simulation.
820    !Config If    = OK_STOMATE
821    !Config Def   = FALSE
822    !Config Help  = Use to force a clear cut at a specific year during a simulation.
823    !               This parameter is used by the ENSEMBLE runs to ensure
824    !               that the age of the simulated forest matches the age of
825    !               the observations
826    !Config Units = year
827    forced_clear_cut= .FALSE.
828    CALL getin_p('FORCED_CLEAR_CUT',forced_clear_cut)
829
830    ! Check for consistency
831    IF (ok_change_species .AND. ok_litter_raking)THEN
832
833       ! There is no obvious conflict in combining species change
834       ! and litter raking but it was never tested. Better not to
835       ! combine these settings
836       WRITE(numout,*) 'ERROR - conflicting settings in run.def'
837       WRITE(numout,*) 'Trying to jointly use litter raking and species change'
838       WRITE(numout,*) 'This should be tested first'
839       CALL ipslerr(3,'ERROR: run.def',&
840            'ERROR - Trying to use litter raking',&
841            'at the same time of species change',&
842            'The code was not developed or tested for this combination')       
843    ENDIF
844   
845   
846    IF ( ok_dgvm ) THEN
847
848       ok_stomate = .TRUE.
849       CALL ipslerr(2,'control_initialize', &
850            'If you want to use the DGVM you need STOMATE',&
851            'activating the flag OK_STOMATE',&
852            'We set OK_STOMATE to TRUE to ensure consistency')
853    ENDIF
854
855    IF ( ok_dgvm ) ok_stomate = .TRUE.
856    IF ( ok_multilayer .AND. .NOT.(ok_radcanopy) ) THEN
857
858       ok_radcanopy  = .TRUE.
859       IF (printlev>=1) WRITE(numout,*) 'You want to use the multilayer model without activating the flag CANOPY_EXTINCTION'
860       IF (printlev>=1) WRITE(numout,*) 'We set CANOPY_EXTINCTION to TRUE to ensure consistency'
861    ENDIF
862
863    !
864    !Config Key   = OK_C13
865    !Config Desc  = Calculate C13 fractionation
866    !Config If    = OK_SECHIBA
867    !Config Def   = FALSE
868    !Config Help  = set to TRUE if C13 is to be calculated. C13 is
869    !               calculated for leaf photosynthesis only.
870    !Config Units = [FLAG]
871    ok_c13 = .FALSE.
872    CALL getin_p('OK_C13', ok_c13)
873    WRITE(numout,*) 'C13 fractionation is calculated: ', ok_c13
874
875!    IF(ok_c13) THEN
876!       CALL ipslerr(3,'control.f90 - ok_c13',&
877!            'There is a problem with leaf_ci recalculation after water stress',&
878!            'It is not recommended to use c13 simulation until fixing that.','')   
879!    ENDIF
880
881
882    !
883    !Config Key  = OK_WINDTHROW
884    !Config Desc = Activate windthrow
885    !Config If   = OK_STOMATE
886    !Config Def  = FALSE
887    !Config Help = Set to TRUE if storm damage needs to be accounted for. Calculates
888    !              PFT-specific critical wind speeds and subsequent tree mortality from
889    !              storm damage (stem breakage and uprooting)
890    !Config Units = [FLAG]
891    ok_windthrow = .FALSE.
892    CALL getin_p('OK_WINDTHROW',ok_windthrow) 
893    WRITE(numout,*) 'Windthrow is activated: ',ok_windthrow
894    !
895    !Config Key  = OK_PEST
896    !Config Desc = Calculate pest outbreaks.
897    !Config Def  = FALSE
898    !Config If   = OK_STOMATE
899    !Config Help = Set to TRUE if pest outbreaks need to be accounted for. For the moment
900    !              the only pest ORCHIDEE can account for are bark beetle outbreaks. The
901    !              parameters are biased toward bark beetles of Norway spruce. This is a
902    !              a general flag. The pft-specific parameter beetle_pft controls whether
903    !              tree mortality from beetle attacks needs to be calculated.
904    !Config Units = [FLAG]
905    ok_pest = .FALSE.
906    CALL getin_p('OK_PEST',ok_pest)
907    WRITE(numout,*) 'Pest outbreak is activated: ',ok_pest
908
909    !Config Key  = OK_PHENO
910    !Config Desc = Calculate lai and phenology.
911    !Config Def  = TRUE
912    !Config If   = OK_STOMATE
913    !Config Help = This flag is used to switch between a calculated and prescribed lai
914    !              It seems that with the new way LAI is prescribed, the flag is no
915    !              longer needed. Clean when prescribed LAI is working again.
916    !Config Units = [FLAG]
917    ok_pheno = .TRUE.
918    CALL getin_p('OK_PHENO',ok_pheno)
919    WRITE(numout,*) 'Phenology is activated: ',ok_pheno
920
921    ok_wlsk = .FALSE.
922    CALL getin_p('OK_WLSK',ok_wlsk)
923    WRITE(numout,*) 'local writing: ',ok_wlsk
924    !
925    ! Configuration : number of PFTs and parameters
926    !
927
928    ! 1. Number of PFTs defined by the user
929
930    !Config Key   = NVM
931    !Config Desc  = number of PFTs 
932    !Config If    = OK_SECHIBA or OK_STOMATE
933    !Config Def   = 13
934    !Config Help  = The number of vegetation types define by the user
935    !Config Units = [-]
936    !
937    CALL getin_p('NVM',nvm)
938    IF (printlev>=1) WRITE(numout,*) 'The number of pfts used by the model is : ', nvm
939
940    ! 2. Should we read the parameters in the run.def file ?
941
942    !Config Key   = IMPOSE_PARAM
943    !Config Desc  = Do you impose the values of the parameters?
944    !Config if    = OK_SECHIBA or OK_STOMATE
945    !Config Def   = y
946    !Config Help  = This flag can deactivate the reading of some parameters.
947    !               Useful if you want to use the standard values without commenting
948    !               the run.def
949    !Config Units = [FLAG]
950    !
951    CALL getin_p('IMPOSE_PARAM',impose_param)
952
953
954    !! Initialize vertical discretization
955    !! Case CWRR : All initialization is done in the vertical module
956    !! Calculate ngrnd and nslm
957    CALL vertical_soil_init
958
959    ! 3. Allocate and intialize the pft parameters
960
961    CALL pft_parameters_main()
962
963    ! 4. Activation sub-models of ORCHIDEE
964
965    CALL activate_sub_models()
966
967    ! 5. Vegetation configuration
968
969    CALL veget_config
970
971    ! 6. Read the parameters in the run.def file  according the flags
972
973    IF (impose_param ) THEN
974       CALL config_pft_parameters
975    ENDIF
976
977    IF ( ok_sechiba ) THEN
978       IF (impose_param ) THEN
979          IF (printlev>=2) WRITE(numout,*)'In control_initialize: call config_sechiba_parameters and config_sechiba_pft_parameters'
980          CALL config_sechiba_parameters
981          CALL config_sechiba_pft_parameters()
982       ENDIF
983    ENDIF
984
985
986    !! Initialize variables in constantes_soil
987    CALL config_soil_parameters()
988
989
990    !! Coherence check for depth of thermosoil for long term simulation where soil thermal inertia matters
991    !! ok_freeze_thermix is defined in config_soil_parameters
992    IF (ok_freeze_thermix .AND. zmaxt < 11) THEN
993       WRITE(numout,*) 'ERROR : Incoherence between ok_freeze_thermix activated and soil depth too small. '
994       WRITE(numout,*) 'Here a soil depth of ', zmaxt, 'm is used for the soil thermodynamics'
995       WRITE(numout,*) 'Set DEPTH_MAX_T=11 or higher in run.def parameter file or deactivate soil freezing'
996       CALL ipslerr_p(3,'control_initialize','Too shallow soil chosen for the thermodynamic for soil freezing', &
997            'Adapt run.def with at least DEPTH_MAX=11','')
998    END IF
999       
1000    IF ( impose_param ) THEN
1001       IF (printlev>=2) WRITE(numout,*)'In control_initialize: call config_co2_parameters'
1002       CALL config_co2_parameters
1003    ENDIF
1004       
1005    IF ( ok_stomate ) THEN
1006       IF ( impose_param ) THEN
1007          IF (printlev>=2) WRITE(numout,*)'In control_initialize: &
1008              & call config_stomate_parameters'
1009          CALL config_stomate_parameters
1010          CALL config_stomate_pft_parameters
1011       ENDIF
1012    ENDIF
1013   
1014    IF ( ok_dgvm ) THEN
1015       IF ( impose_param ) THEN
1016          IF (printlev>=2) WRITE(numout,*)'In control_initialize: &
1017             & call config_dgvm_parameters'
1018          CALL config_dgvm_parameters
1019       ENDIF
1020    ENDIF   
1021  END SUBROUTINE control_initialize
1022 
1023END MODULE control
Note: See TracBrowser for help on using the repository browser.