source: branches/publications/ORCHIDEE-MUSLE-r6129/src_parameters/control.f90 @ 7346

Last change on this file since 7346 was 6128, checked in by haicheng.zhang, 5 years ago

New: ORCHIDEE_MUSLE modified on 20190722 by Haicheng Zhang

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