source: branches/publications/ORCHIDEE-LEAK-r5919/src_parameters/control.f90 @ 5925

Last change on this file since 5925 was 4207, checked in by ronny.lauerwald, 7 years ago

fixed bugs with no-swamp, and no-routing, cleaned code

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