source: branches/ORCHIDEE_3_CMIP6/ORCHIDEE/src_parameters/control.f90 @ 7599

Last change on this file since 7599 was 6482, checked in by josefine.ghattas, 4 years ago

Make sugar loading the only option to deal with excess labile and reserve pools. Flag OK_SUGAR_LOADING has been removed. No change in results. Decision taken by N. Vuichard and S. Luyssaert

File size: 18.5 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    INTEGER(i_std)                             :: jv                    !! Local index variable
53    INTEGER(i_std)                             :: ier                   !! Error handeling
54    LOGICAL                                    :: hydrol_cwrr_test      !! Temporary test variable
55    LOGICAL                                    :: ok_co2_test           !! Temporary test variable
56    LOGICAL                                    :: ok_explicitsnow_test  !! Temporary test variable
57    ! Start reading options from parameter file
58    !
59    !Config key   = NC_RESTART_COMPRESSION
60    !Config Desc  = Restart netcdf outputs file are written in compression mode
61    !Config If    =
62    !Config Def   = n
63    !Config Help  = This flag allows the user to decide if the restart netcdf
64    !Config         output files are compressed by default 
65    !Config Units = [FLAG]
66    !
67    nc_restart_compression = .TRUE.
68    CALL getin_p('NC_RESTART_COMPRESSION', nc_restart_compression)
69    WRITE(numout,*) "Netcdf restart compression is : ", nc_restart_compression
70
71    !Config Key   = SOILTYPE_CLASSIF
72    !Config Desc  = Type of classification used for the map of soil types
73    !Config Def   = zobler
74    !Config If    = !IMPOSE_VEG
75    !Config Help  = The classification used in the file that we use here
76    !Config         There are three classification supported: 
77    !Config         Zobler (7 converted to 3) and USDA (12)
78    !Config Units = [-]
79    !
80    !-tdo- Suivant le type de classification utilisee pour le sol, on adapte nscm
81    soil_classif = 'zobler'
82    CALL getin_p('SOILTYPE_CLASSIF',soil_classif)
83    SELECTCASE (soil_classif)
84    CASE ('zobler','none')
85       nscm = nscm_fao
86    CASE ('usda')
87       nscm = nscm_usda
88    CASE DEFAULT
89       WRITE(numout,*) "Unsupported soil type classification: soil_classif=",soil_classif
90       WRITE(numout,*) "Choose between zobler, usda and none according to the map"
91       CALL ipslerr_p(3,'control_initialize','Bad choice of soil_classif','Choose between zobler, usda and none','')
92    ENDSELECT
93
94
95    !Config Key   = RIVER_ROUTING
96    !Config Desc  = Decides if we route the water or not
97    !Config If    = OK_SECHIBA
98    !Config Def   = y
99    !Config Help  = This flag allows the user to decide if the runoff
100    !Config         and drainage should be routed to the ocean
101    !Config         and to downstream grid boxes.
102    !Config Units = [FLAG]
103    !
104    river_routing = .TRUE.
105    CALL getin_p('RIVER_ROUTING', river_routing)
106    IF (printlev>=1) WRITE(numout,*) "RIVER routing is activated : ",river_routing
107
108    ! Control for the option HYDROL_CWRR which is not longer existing in the model.
109    ! 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
110    hydrol_cwrr_test = .TRUE.
111    CALL getin_p('HYDROL_CWRR', hydrol_cwrr_test)
112    IF (.NOT. hydrol_cwrr_test) THEN
113       CALL ipslerr_p(3,'control_initialize',&
114            'HYDROL_CWRR=n is set in run.def but this option does not exist any more in ORCHIDEE', &
115            'Choisnel hydrolology has been removed and CWRR is now the only hydrology module in ORCHIDEE',&
116            'Remove parameter HYDROL_CWRR from run.def')
117    END IF
118
119    !Config Key   = DO_IRRIGATION
120    !Config Desc  = Should we compute an irrigation flux
121    !Config If    = RIVER_ROUTING
122    !Config Def   = n
123    !Config Help  = This parameters allows the user to ask the model
124    !Config         to compute an irigation flux. This performed for the
125    !Config         on very simple hypothesis. The idea is to have a good
126    !Config         map of irrigated areas and a simple function which estimates
127    !Config         the need to irrigate.
128    !Config Units = [FLAG]
129    !
130    do_irrigation = .FALSE.
131    IF ( river_routing ) CALL getin_p('DO_IRRIGATION', do_irrigation)
132    !
133    !Config Key   = DO_FLOODPLAINS
134    !Config Desc  = Should we include floodplains
135    !Config If    = RIVER_ROUTING
136    !Config Def   = n
137    !Config Help  = This parameters allows the user to ask the model
138    !Config         to take into account the flood plains and return
139    !Config         the water into the soil moisture. It then can go
140    !Config         back to the atmopshere. This tried to simulate
141    !Config         internal deltas of rivers.
142    !Config Units = [FLAG] 
143    !
144    do_floodplains = .FALSE.
145    IF ( river_routing ) CALL getin_p('DO_FLOODPLAINS', do_floodplains)
146
147
148    !Config Key   = OK_SOIL_CARBON_DISCRETIZATION
149    !Config Desc  = Activate soil carbon vertical discretization
150    !Config If    = OK_STOMATE
151    !Config Def   = FALSE
152    !Config Help  = Activate soil carbon scheme with vertical discretization and vertical transport of carbon
153    !Config Units = [FLAG]
154    ok_soil_carbon_discretization=.FALSE.
155    CALL getin_p('OK_SOIL_CARBON_DISCRETIZATION', ok_soil_carbon_discretization)
156
157
158    ! Control of option OK_EXPLICITSNOW which is not longer existing in the model.
159    ! 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.
160    ok_explicitsnow_test = .TRUE.
161    CALL getin_p('OK_EXPLICITSNOW', ok_explicitsnow_test)
162    IF (.NOT. ok_explicitsnow_test) THEN
163       CALL ipslerr_p(3,'control_initialize',&
164            'OK_EXPLICITSNOW=n is set in run.def but this option does not exist any more in ORCHIDEE', &
165            'Explicit snow scheme is now always used in ORCHIDEE.',&
166            'Remove parameter OK_EXPLICITSNOW from run.def')
167    END IF
168
169
170
171    !
172    !Config Key   = STOMATE_OK_STOMATE
173    !Config Desc  = Activate STOMATE?
174    !Config If    = OK_SECHIBA
175    !Config Def   = y
176    !Config Help  = set to TRUE if STOMATE is to be activated
177    !Config Units = [FLAG]
178    !
179    ok_stomate = .TRUE.
180    CALL getin_p('STOMATE_OK_STOMATE',ok_stomate)
181    IF (printlev>=1) WRITE(numout,*) 'STOMATE is activated: ',ok_stomate
182
183    ! Control for the option STOMATE_OK_CO2 which is not longer existing in the model.
184    ! 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
185    ok_co2_test = .TRUE.
186    CALL getin_p('STOMATE_OK_CO2', ok_co2_test)
187    IF (.NOT. ok_co2_test) THEN
188       CALL ipslerr_p(3,'control_initialize',&
189            'STOMATE_OK_CO2=n is set in run.def but this option does not exist any more in ORCHIDEE', &
190            'Calculation of beta coefficient using Jarvis formulation has been removed and Farquar formulation is now always used',&
191            'Remove parameter STOMATE_OK_CO2 from run.def')
192    END IF
193   
194
195    !                                                                                                                             
196    !Config Key   = DO_WOOD_HARVEST
197    !Config Desc  = Activate Wood Harvest ?
198    !Config If    = OK_STOMATE
199    !Config Def   = y
200    !Config Help  = set to TRUE if wood is harvested
201    !Config Units = [FLAG]
202    do_wood_harvest = .TRUE.
203    CALL getin_p('DO_WOOD_HARVEST',do_wood_harvest)
204
205    !
206    !Config Key   = STOMATE_OK_NCYCLE
207    !Config Desc  = Activate dynamic N cycle
208    !Config If    = OK_STOMATE
209    !Config Def   = y
210    !Config Help  = set to TRUE if N cycle is to be activated
211    !Config Units = [FLAG]
212    !
213    ok_ncycle = .TRUE. 
214    CALL getin_p('STOMATE_OK_NCYCLE',ok_ncycle) 
215    WRITE(numout,*) 'N cycle is activated: ',ok_ncycle 
216    !
217    !Config Key   = STOMATE_IMPOSE_CN
218    !Config Desc  = Impose the CN ratio of leaves
219    !Config If    = OK_STOMATE
220    !Config Def   = n
221    !Config Help  = set to TRUE if IMPOSE_CN is to be activated
222    !Config Units = [FLAG]
223    !
224    impose_cn = .FALSE. 
225    CALL getin_p('STOMATE_IMPOSE_CN',impose_cn) 
226    WRITE(numout,*) 'CN ratio is imposed: ',impose_cn 
227    !Config Key   = RESET_IMPOSE_CN
228    !Config Desc  = Reset the CN ratio of leaves
229    !Config If    = OK_STOMATE
230    !Config Def   = n
231    !Config Help  = set to TRUE if RESET_IMPOSE_CN is to be activated
232    !Config Units = [FLAG]
233    !
234    reset_impose_cn = .FALSE. 
235    CALL getin_p('RESET_IMPOSE_CN',reset_impose_cn) 
236    WRITE(numout,*) 'CN ratio is reset: ',reset_impose_cn 
237    !
238    !Config Key   = STOMATE_READ_CN
239    !Config Desc  = Read the CN ratio of leaves
240    !Config If    = OK_STOMATE
241    !Config Def   = n
242    !Config Help  = set to TRUE if IMPOSE_CN is to be activated read
243    !Config Units = [FLAG]
244    !
245    read_cn = .FALSE. 
246    CALL getin_p('STOMATE_READ_CN',read_cn) 
247    WRITE(numout,*) 'CN ratio is read: ',read_cn 
248    !
249    !
250    !Config Key   = STOMATE_OK_DGVM
251    !Config Desc  = Activate DGVM?
252    !Config If    = OK_STOMATE
253    !Config Def   = n
254    !Config Help  = set to TRUE if DGVM is to be activated
255    !Config Units = [FLAG]
256    !
257    ok_dgvm = .FALSE.
258    CALL getin_p('STOMATE_OK_DGVM',ok_dgvm)
259    !
260    !Config Key   = CHEMISTRY_BVOC
261    !Config Desc  = Activate calculations for BVOC
262    !Config If    = OK_SECHIBA
263    !Config Def   = n
264    !Config Help  = set to TRUE if biogenic emissions calculation is to be activated
265    !Config Units = [FLAG]
266    !
267    ok_bvoc = .FALSE.
268    CALL getin_p('CHEMISTRY_BVOC', ok_bvoc)
269    IF (printlev>=1) WRITE(numout,*) 'Biogenic emissions: ', ok_bvoc
270
271    IF ( ok_bvoc ) THEN
272       ok_leafage         = .TRUE. 
273       ok_radcanopy       = .TRUE. 
274       ok_multilayer      = .TRUE.
275       ok_pulse_NOx       = .TRUE.
276       ok_bbgfertil_NOx   = .TRUE.
277       ok_cropsfertil_NOx = .TRUE.
278    ELSE
279       ok_leafage         = .FALSE. 
280       ok_radcanopy       = .FALSE. 
281       ok_multilayer      = .FALSE.
282       ok_pulse_NOx       = .FALSE.
283       ok_bbgfertil_NOx   = .FALSE.
284       ok_cropsfertil_NOx = .FALSE.
285    ENDIF
286    !
287    !Config Key   = CHEMISTRY_LEAFAGE
288    !Config Desc  = Activate LEAFAGE?
289    !Config If    = CHEMISTRY_BVOC
290    !Config Def   = n
291    !Config Help  = set to TRUE if biogenic emissions calculation takes leaf age into account
292    !Config Units = [FLAG]
293    !
294    CALL getin_p('CHEMISTRY_LEAFAGE', ok_leafage)
295    IF (printlev>=1) WRITE(numout,*) 'Leaf Age: ', ok_leafage
296    !
297    !Config Key   = CANOPY_EXTINCTION
298    !Config Desc  = Use canopy radiative transfer model?
299    !Config If    = CHEMISTRY_BVOC
300    !Config Def   = n
301    !Config Help  = set to TRUE if canopy radiative transfer model is used for biogenic emissions
302    !Config Units = [FLAG]
303    !
304    CALL getin_p('CANOPY_EXTINCTION', ok_radcanopy)
305    IF (printlev>=1) WRITE(numout,*) 'Canopy radiative transfer model: ', ok_radcanopy
306    !
307    !Config Key   = CANOPY_MULTILAYER
308    !Config Desc  = Use canopy radiative transfer model with multi-layers
309    !Config If    = CANOPY_EXTINCTION
310    !Config Def   = n
311    !Config Help  = set to TRUE if canopy radiative transfer model is with multiple layers
312    !Config Units = [FLAG]
313    !
314    CALL getin_p('CANOPY_MULTILAYER', ok_multilayer)
315    IF (printlev>=1) WRITE(numout,*) 'Multi-layer Canopy model: ', ok_multilayer
316    !
317    !Config Key   = NOx_RAIN_PULSE
318    !Config Desc  = Calculate NOx emissions with pulse?
319    !Config If    = CHEMISTRY_BVOC
320    !Config Def   = n
321    !Config Help  = set to TRUE if NOx rain pulse is taken into account
322    !Config Units = [FLAG]
323    !
324    CALL getin_p('NOx_RAIN_PULSE', ok_pulse_NOx)
325    IF (printlev>=1) WRITE(numout,*) 'Rain NOx pulsing: ', ok_pulse_NOx
326    !
327    !Config Key   = NOx_BBG_FERTIL
328    !Config Desc  = Calculate NOx emissions with bbg fertilizing effect?
329    !Config If    = CHEMISTRY_BVOC
330    !Config Def   = n
331    !Config Help  = set to TRUE if NOx emissions are calculated with bbg effect
332    !Config         Fertil effect of bbg on NOx soil emissions
333    !Config Units = [FLAG]
334    !
335    CALL getin_p('NOx_BBG_FERTIL', ok_bbgfertil_NOx)
336    IF (printlev>=1) WRITE(numout,*) 'NOx bbg fertil effect: ', ok_bbgfertil_NOx
337    !
338    !Config Key   = NOx_FERTILIZERS_USE
339    !Config Desc  = Calculate NOx emissions with fertilizers use?
340    !Config If    = CHEMISTRY_BVOC
341    !Config Def   = n
342    !Config Help  = set to TRUE if NOx emissions are calculated with fertilizers use
343    !Config         Fertilizers use effect on NOx soil emissions 
344    !Config Units = [FLAG]
345    !
346    CALL getin_p('NOx_FERTILIZERS_USE', ok_cropsfertil_NOx)
347    IF (printlev>=1) WRITE(numout,*) 'NOx Fertilizers use: ', ok_cropsfertil_NOx
348    !Config Key  = Is CO2 impact on BVOC accounted for using Possell 2005 ?
349    !Config Desc = In this case we use Possell 2005 parameterisation
350    !Config Desc = to take into account the impact of CO2 on biogenic emissions for
351    !Config Desc = isoprene
352    !Config Def  = n
353    !Config Help = set to TRUE if Possell parameterisation has to be considered for the CO2 impact
354    !
355    ok_co2bvoc_poss = .FALSE.
356    CALL getin_p('CO2_FOR_BVOC_POSSELL', ok_co2bvoc_poss)
357    IF (printlev>=1) WRITE(numout,*) 'CO2 impact on BVOC - Possell parameterisation: ', ok_co2bvoc_poss
358    !
359    !Config Key  = Is CO2 impact on BVOC accounted for using Wilkinson 2009 ?
360    !Config Desc = In this case we use Wilkinson 2009 parameterisation
361    !Config Desc = to take into account the impact of CO2 on biogenic emissions for
362    !Config Desc = isoprene
363    !Config Def  = n
364    !Config Help = set to TRUE if Wilkinson parameterisation has to be considered for the CO2 impact
365    !
366    ok_co2bvoc_wilk = .FALSE.
367    CALL getin_p('CO2_FOR_BVOC_WILKINSON', ok_co2bvoc_wilk)
368    IF (printlev>=1) WRITE(numout,*) 'CO2 impact on BVOC - Wilkinson parameterisation: ', ok_co2bvoc_wilk
369
370    !
371    ! control initialisation with sechiba
372    !
373    ok_sechiba = .TRUE.
374    !
375    !
376    ! Ensure consistency
377    !
378    IF ( ok_dgvm ) ok_stomate = .TRUE.
379    IF ( ok_multilayer .AND. .NOT.(ok_radcanopy) ) THEN
380       ok_radcanopy  = .TRUE.
381       IF (printlev>=1) WRITE(numout,*) 'You want to use the multilayer model without activating the flag CANOPY_EXTINCTION'
382       IF (printlev>=1) WRITE(numout,*) 'We set CANOPY_EXTINCTION to TRUE to ensure consistency'
383    ENDIF
384
385
386
387    !
388    ! Here we need the same initialisation as above
389    !
390    ok_pheno = .TRUE.
391
392    !
393    ! Configuration : number of PFTs and parameters
394    !
395
396    ! 1. Number of PFTs defined by the user
397
398    !Config Key   = NVM
399    !Config Desc  = number of PFTs 
400    !Config If    = OK_SECHIBA or OK_STOMATE
401    !Config Def   = 13
402    !Config Help  = The number of vegetation types define by the user
403    !Config Units = [-]
404    !
405    CALL getin_p('NVM',nvm)
406    IF (printlev>=1) WRITE(numout,*) 'The number of pfts used by the model is : ', nvm
407
408    ! 2. Should we read the parameters in the run.def file ?
409
410    !Config Key   = IMPOSE_PARAM
411    !Config Desc  = Do you impose the values of the parameters?
412    !Config if    = OK_SECHIBA or OK_STOMATE
413    !Config Def   = y
414    !Config Help  = This flag can deactivate the reading of some parameters.
415    !               Useful if you want to use the standard values without commenting the run.def
416    !Config Units = [FLAG]
417    !
418    CALL getin_p('IMPOSE_PARAM',impose_param)
419
420
421    !! Initialize vertical discretization
422    !! Case CWRR : All initialization is done in the vertical module
423    !! Calculate ngrnd and nslm
424    CALL vertical_soil_init
425
426    ! 3. Allocate and intialize the pft parameters
427
428    CALL pft_parameters_main()
429
430    ! 4. Activation sub-models of ORCHIDEE
431
432    CALL activate_sub_models()
433
434    ! 5. Vegetation configuration
435
436    CALL veget_config
437
438    ! 6. Read the parameters in the run.def file  according the flags
439
440    IF (impose_param ) THEN
441       CALL config_pft_parameters
442    ENDIF
443
444    IF ( ok_sechiba ) THEN
445       IF (impose_param ) THEN
446          IF (printlev>=2) WRITE(numout,*)'In control_initialize: call config_sechiba_parameters and config_sechiba_pft_parameters'
447          CALL config_sechiba_parameters
448          CALL config_sechiba_pft_parameters()
449       ENDIF
450    ENDIF
451
452
453    !! Initialize variables in constantes_soil
454    CALL config_soil_parameters()
455
456
457    !! Coherence check for depth of thermosoil for long term simulation where soil thermal inertia matters
458    !! ok_freeze_thermix is defined in config_soil_parameters
459    IF (ok_freeze_thermix .AND. zmaxt < 11) THEN
460       WRITE(numout,*) 'ERROR : Incoherence between ok_freeze_thermix activated and soil depth too small. '
461       WRITE(numout,*) 'Here a soil depth of ', zmaxt, 'm is used for the soil thermodynamics'
462       WRITE(numout,*) 'Set DEPTH_MAX_T=11 or higher in run.def parameter file or deactivate soil freezing'
463       CALL ipslerr_p(3,'control_initialize','Too shallow soil chosen for the thermodynamic for soil freezing', &
464            'Adapt run.def with at least DEPTH_MAX=11','')
465    END IF
466       
467    IF ( impose_param ) THEN
468       IF (printlev>=2) WRITE(numout,*)'In control_initialize: call config_co2_parameters'
469       CALL config_co2_parameters
470    ENDIF
471       
472    IF ( ok_stomate ) THEN
473       IF ( impose_param ) THEN
474          IF (printlev>=2) WRITE(numout,*)'In control_initialize: call config_stomate_parameters and config_stomate_pft_parameters'
475          CALL config_stomate_parameters
476          CALL config_stomate_pft_parameters
477       ENDIF
478    ENDIF
479   
480    IF ( ok_dgvm ) THEN
481       IF ( impose_param ) THEN
482          IF (printlev>=2) WRITE(numout,*)'In control_initialize: call config_dgvm_parameters'
483          CALL config_dgvm_parameters
484       ENDIF
485    ENDIF   
486  END SUBROUTINE control_initialize
487 
488END MODULE control
Note: See TracBrowser for help on using the repository browser.