source: tags/ORCHIDEE_2_0/ORCHIDEE/src_parameters/control.f90 @ 6392

Last change on this file since 6392 was 4962, checked in by josefine.ghattas, 6 years ago

Updated default values as have been decided for version ORCHIDEE 2.0 and to be used for CMIP6. See ticket #414

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