source: branches/publications/ORCHIDEE-GMv3.2/ORCHIDEE/src_parameters/control.f90 @ 5816

Last change on this file since 5816 was 5816, checked in by jinfeng.chang, 5 years ago

copy ORCHIDEE-GMv3.2 for publication

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