source: branches/publications/ORCHIDEE-ICE_SurfaceMassBalance/src_parameters/control.f90 @ 8398

Last change on this file since 8398 was 7396, checked in by christophe.dumas, 2 years ago

New 3 layer ice scheme on ice-sheet area that can be activated via the OK_ICE_SHEET flag

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