source: branches/publications/ORCHIDEE-PEAT_r5488/src_parameters/control.f90 @ 5491

Last change on this file since 5491 was 5080, checked in by chunjing.qiu, 6 years ago

soil freezing, soil moisture, fwet bugs fixed

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