source: branches/publications/ORCHIDEE_gmd-2018-261/src_parameters/control.f90

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