source: branches/publications/ORCHIDEE_2.2_r7266/ORCHIDEE/src_parameters/control.f90 @ 7541

Last change on this file since 7541 was 7541, checked in by fabienne.maignan, 2 years ago
  1. Zhang publication on coupling factor
File size: 16.8 KB
Line 
1! =================================================================================================================================
2! MODULE       : control
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.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
49
50    IMPLICIT NONE
51   
52    INTEGER(i_std)                             :: jv                    !! Local index variable
53    INTEGER(i_std)                             :: ier                   !! Error handeling
54    LOGICAL                                    :: hydrol_cwrr_test      !! Temporary test variable
55    LOGICAL                                    :: ok_co2_test           !! Temporary test variable
56    LOGICAL                                    :: ok_explicitsnow_test  !! Temporary test variable
57    ! Start reading options from parameter file
58
59    !Config Key   = SOILTYPE_CLASSIF
60    !Config Desc  = Type of classification used for the map of soil types
61    !Config Def   = zobler
62    !Config If    = !IMPOSE_VEG
63    !Config Help  = The classification used in the file that we use here
64    !Config         There are three classification supported: 
65    !Config         Zobler (7 converted to 3) and USDA (12)
66    !Config Units = [-]
67    !
68    !-tdo- Suivant le type de classification utilisee pour le sol, on adapte nscm
69    soil_classif = 'zobler'
70    CALL getin_p('SOILTYPE_CLASSIF',soil_classif)
71    SELECTCASE (soil_classif)
72    CASE ('zobler','none')
73       nscm = nscm_fao
74    CASE ('usda')
75       nscm = nscm_usda
76    CASE DEFAULT
77       WRITE(numout,*) "Unsupported soil type classification: soil_classif=",soil_classif
78       WRITE(numout,*) "Choose between zobler, usda and none according to the map"
79       CALL ipslerr_p(3,'control_initialize','Bad choice of soil_classif','Choose between zobler, usda and none','')
80    ENDSELECT
81
82
83    !Config Key   = RIVER_ROUTING
84    !Config Desc  = Decides if we route the water or not
85    !Config If    = OK_SECHIBA
86    !Config Def   = y
87    !Config Help  = This flag allows the user to decide if the runoff
88    !Config         and drainage should be routed to the ocean
89    !Config         and to downstream grid boxes.
90    !Config Units = [FLAG]
91    !
92    river_routing = .TRUE.
93    CALL getin_p('RIVER_ROUTING', river_routing)
94    IF (printlev>=1) WRITE(numout,*) "RIVER routing is activated : ",river_routing
95
96    ! Control for the option HYDROL_CWRR which is not longer existing in the model.
97    ! Check here if in run.def HYDROL_CWRR=n. If that's the case then stop the model and ask the user to remove the flag from run.def
98    hydrol_cwrr_test = .TRUE.
99    CALL getin_p('HYDROL_CWRR', hydrol_cwrr_test)
100    IF (.NOT. hydrol_cwrr_test) THEN
101       CALL ipslerr_p(3,'control_initialize',&
102            'HYDROL_CWRR=n is set in run.def but this option does not exist any more in ORCHIDEE', &
103            'Choisnel hydrolology has been removed and CWRR is now the only hydrology module in ORCHIDEE',&
104            'Remove parameter HYDROL_CWRR from run.def')
105    END IF
106
107    !Config Key   = DO_IRRIGATION
108    !Config Desc  = Should we compute an irrigation flux
109    !Config If    = RIVER_ROUTING
110    !Config Def   = n
111    !Config Help  = This parameters allows the user to ask the model
112    !Config         to compute an irigation flux. This performed for the
113    !Config         on very simple hypothesis. The idea is to have a good
114    !Config         map of irrigated areas and a simple function which estimates
115    !Config         the need to irrigate.
116    !Config Units = [FLAG]
117    !
118    do_irrigation = .FALSE.
119    IF ( river_routing ) CALL getin_p('DO_IRRIGATION', do_irrigation)
120    !
121    !Config Key   = DO_FLOODPLAINS
122    !Config Desc  = Should we include floodplains
123    !Config If    = RIVER_ROUTING
124    !Config Def   = n
125    !Config Help  = This parameters allows the user to ask the model
126    !Config         to take into account the flood plains and return
127    !Config         the water into the soil moisture. It then can go
128    !Config         back to the atmopshere. This tried to simulate
129    !Config         internal deltas of rivers.
130    !Config Units = [FLAG] 
131    !
132    do_floodplains = .FALSE.
133    IF ( river_routing ) CALL getin_p('DO_FLOODPLAINS', do_floodplains)
134
135
136    ! Control of option OK_EXPLICITSNOW which is not longer existing in the model.
137    ! Check here if in run.def OK_EXPLICITSNOW=n. If that's the case then stop the model and ask the user to remove the flag from run.def.
138    ok_explicitsnow_test = .TRUE.
139    CALL getin_p('OK_EXPLICITSNOW', ok_explicitsnow_test)
140    IF (.NOT. ok_explicitsnow_test) THEN
141       CALL ipslerr_p(3,'control_initialize',&
142            'OK_EXPLICITSNOW=n is set in run.def but this option does not exist any more in ORCHIDEE', &
143            'Explicit snow scheme is now always used in ORCHIDEE.',&
144            'Remove parameter OK_EXPLICITSNOW from run.def')
145    END IF
146
147
148
149    !
150    !Config Key   = STOMATE_OK_STOMATE
151    !Config Desc  = Activate STOMATE?
152    !Config If    = OK_SECHIBA
153    !Config Def   = y
154    !Config Help  = set to TRUE if STOMATE is to be activated
155    !Config Units = [FLAG]
156    !
157    ok_stomate = .TRUE.
158    CALL getin_p('STOMATE_OK_STOMATE',ok_stomate)
159    IF (printlev>=1) WRITE(numout,*) 'STOMATE is activated: ',ok_stomate
160
161    ! Control for the option STOMATE_OK_CO2 which is not longer existing in the model.
162    ! Check here if in run.def STOMATE_OK_CO2=n. If that's the case then stop the model and ask the user to remove the flag from run.def
163    ok_co2_test = .TRUE.
164    CALL getin_p('STOMATE_OK_CO2', ok_co2_test)
165    IF (.NOT. ok_co2_test) THEN
166       CALL ipslerr_p(3,'control_initialize',&
167            'STOMATE_OK_CO2=n is set in run.def but this option does not exist any more in ORCHIDEE', &
168            'Calculation of beta coefficient using Jarvis formulation has been removed and Farquar formulation is now always used',&
169            'Remove parameter STOMATE_OK_CO2 from run.def')
170    END IF
171   
172
173    !                                                                                                                             
174    !Config Key   = DO_WOOD_HARVEST
175    !Config Desc  = Activate Wood Harvest ?
176    !Config If    = OK_STOMATE
177    !Config Def   = y
178    !Config Help  = set to TRUE if wood is harvested
179    !Config Units = [FLAG]
180    do_wood_harvest = .TRUE.
181    CALL getin_p('DO_WOOD_HARVEST',do_wood_harvest)
182
183    !
184    !Config Key   = STOMATE_OK_DGVM
185    !Config Desc  = Activate DGVM?
186    !Config If    = OK_STOMATE
187    !Config Def   = n
188    !Config Help  = set to TRUE if DGVM is to be activated
189    !Config Units = [FLAG]
190    !
191    ok_dgvm = .FALSE.
192    CALL getin_p('STOMATE_OK_DGVM',ok_dgvm)
193    !
194    !Config Key   = CHEMISTRY_BVOC
195    !Config Desc  = Activate calculations for BVOC
196    !Config If    = OK_SECHIBA
197    !Config Def   = n
198    !Config Help  = set to TRUE if biogenic emissions calculation is to be activated
199    !Config Units = [FLAG]
200    !
201    ok_bvoc = .FALSE.
202    CALL getin_p('CHEMISTRY_BVOC', ok_bvoc)
203    IF (printlev>=1) WRITE(numout,*) 'Biogenic emissions: ', ok_bvoc
204
205    IF ( ok_bvoc ) THEN
206       ok_leafage         = .TRUE. 
207       ok_radcanopy       = .TRUE. 
208       ok_multilayer      = .TRUE.
209       ok_pulse_NOx       = .TRUE.
210       ok_bbgfertil_NOx   = .TRUE.
211       ok_cropsfertil_NOx = .TRUE.
212    ELSE
213       ok_leafage         = .FALSE. 
214       ok_radcanopy       = .FALSE. 
215       ok_multilayer      = .FALSE.
216       ok_pulse_NOx       = .FALSE.
217       ok_bbgfertil_NOx   = .FALSE.
218       ok_cropsfertil_NOx = .FALSE.
219    ENDIF
220    !
221    !Config Key   = CHEMISTRY_LEAFAGE
222    !Config Desc  = Activate LEAFAGE?
223    !Config If    = CHEMISTRY_BVOC
224    !Config Def   = n
225    !Config Help  = set to TRUE if biogenic emissions calculation takes leaf age into account
226    !Config Units = [FLAG]
227    !
228    CALL getin_p('CHEMISTRY_LEAFAGE', ok_leafage)
229    IF (printlev>=1) WRITE(numout,*) 'Leaf Age: ', ok_leafage
230    !
231    !Config Key   = CANOPY_EXTINCTION
232    !Config Desc  = Use canopy radiative transfer model?
233    !Config If    = CHEMISTRY_BVOC
234    !Config Def   = n
235    !Config Help  = set to TRUE if canopy radiative transfer model is used for biogenic emissions
236    !Config Units = [FLAG]
237    !
238    CALL getin_p('CANOPY_EXTINCTION', ok_radcanopy)
239    IF (printlev>=1) WRITE(numout,*) 'Canopy radiative transfer model: ', ok_radcanopy
240    !
241    !Config Key   = CANOPY_MULTILAYER
242    !Config Desc  = Use canopy radiative transfer model with multi-layers
243    !Config If    = CANOPY_EXTINCTION
244    !Config Def   = n
245    !Config Help  = set to TRUE if canopy radiative transfer model is with multiple layers
246    !Config Units = [FLAG]
247    !
248    CALL getin_p('CANOPY_MULTILAYER', ok_multilayer)
249    IF (printlev>=1) WRITE(numout,*) 'Multi-layer Canopy model: ', ok_multilayer
250    !
251    !Config Key   = NOx_RAIN_PULSE
252    !Config Desc  = Calculate NOx emissions with pulse?
253    !Config If    = CHEMISTRY_BVOC
254    !Config Def   = n
255    !Config Help  = set to TRUE if NOx rain pulse is taken into account
256    !Config Units = [FLAG]
257    !
258    CALL getin_p('NOx_RAIN_PULSE', ok_pulse_NOx)
259    IF (printlev>=1) WRITE(numout,*) 'Rain NOx pulsing: ', ok_pulse_NOx
260    !
261    !Config Key   = NOx_BBG_FERTIL
262    !Config Desc  = Calculate NOx emissions with bbg fertilizing effect?
263    !Config If    = CHEMISTRY_BVOC
264    !Config Def   = n
265    !Config Help  = set to TRUE if NOx emissions are calculated with bbg effect
266    !Config         Fertil effect of bbg on NOx soil emissions
267    !Config Units = [FLAG]
268    !
269    CALL getin_p('NOx_BBG_FERTIL', ok_bbgfertil_NOx)
270    IF (printlev>=1) WRITE(numout,*) 'NOx bbg fertil effect: ', ok_bbgfertil_NOx
271    !
272    !Config Key   = NOx_FERTILIZERS_USE
273    !Config Desc  = Calculate NOx emissions with fertilizers use?
274    !Config If    = CHEMISTRY_BVOC
275    !Config Def   = n
276    !Config Help  = set to TRUE if NOx emissions are calculated with fertilizers use
277    !Config         Fertilizers use effect on NOx soil emissions 
278    !Config Units = [FLAG]
279    !
280    CALL getin_p('NOx_FERTILIZERS_USE', ok_cropsfertil_NOx)
281    IF (printlev>=1) WRITE(numout,*) 'NOx Fertilizers use: ', ok_cropsfertil_NOx
282    !Config Key  = Is CO2 impact on BVOC accounted for using Possell 2005 ?
283    !Config Desc = In this case we use Possell 2005 parameterisation
284    !Config Desc = to take into account the impact of CO2 on biogenic emissions for
285    !Config Desc = isoprene
286    !Config Def  = n
287    !Config Help = set to TRUE if Possell parameterisation has to be considered for the CO2 impact
288    !
289    ok_co2bvoc_poss = .FALSE.
290    CALL getin_p('CO2_FOR_BVOC_POSSELL', ok_co2bvoc_poss)
291    IF (printlev>=1) WRITE(numout,*) 'CO2 impact on BVOC - Possell parameterisation: ', ok_co2bvoc_poss
292    !
293    !Config Key  = Is CO2 impact on BVOC accounted for using Wilkinson 2009 ?
294    !Config Desc = In this case we use Wilkinson 2009 parameterisation
295    !Config Desc = to take into account the impact of CO2 on biogenic emissions for
296    !Config Desc = isoprene
297    !Config Def  = n
298    !Config Help = set to TRUE if Wilkinson parameterisation has to be considered for the CO2 impact
299    !
300    ok_co2bvoc_wilk = .FALSE.
301    CALL getin_p('CO2_FOR_BVOC_WILKINSON', ok_co2bvoc_wilk)
302    IF (printlev>=1) WRITE(numout,*) 'CO2 impact on BVOC - Wilkinson parameterisation: ', ok_co2bvoc_wilk
303   
304    !
305    ! control initialisation with sechiba
306    !
307    ok_sechiba = .TRUE.
308    !
309    !
310    ! Ensure consistency
311    !
312    IF ( ok_dgvm ) ok_stomate = .TRUE.
313    IF ( ok_multilayer .AND. .NOT.(ok_radcanopy) ) THEN
314       ok_radcanopy  = .TRUE.
315       IF (printlev>=1) WRITE(numout,*) 'You want to use the multilayer model without activating the flag CANOPY_EXTINCTION'
316       IF (printlev>=1) WRITE(numout,*) 'We set CANOPY_EXTINCTION to TRUE to ensure consistency'
317    ENDIF
318
319
320
321    !
322    ! Here we need the same initialisation as above
323    !
324    ok_pheno = .TRUE.
325
326    !
327    ! Configuration : number of PFTs and parameters
328    !
329
330    ! 1. Number of PFTs defined by the user
331
332    !Config Key   = NVM
333    !Config Desc  = number of PFTs 
334    !Config If    = OK_SECHIBA or OK_STOMATE
335    !Config Def   = 13
336    !Config Help  = The number of vegetation types define by the user
337    !Config Units = [-]
338    !
339    CALL getin_p('NVM',nvm)
340    IF (printlev>=1) WRITE(numout,*) 'The number of pfts used by the model is : ', nvm
341
342    ! 2. Should we read the parameters in the run.def file ?
343
344    !Config Key   = IMPOSE_PARAM
345    !Config Desc  = Do you impose the values of the parameters?
346    !Config if    = OK_SECHIBA or OK_STOMATE
347    !Config Def   = y
348    !Config Help  = This flag can deactivate the reading of some parameters.
349    !               Useful if you want to use the standard values without commenting the run.def
350    !Config Units = [FLAG]
351    !
352    CALL getin_p('IMPOSE_PARAM',impose_param)
353
354
355    !! Initialize vertical discretization
356    !! Case CWRR : All initialization is done in the vertical module
357    !! Calculate ngrnd and nslm
358    CALL vertical_soil_init
359
360    ! 3. Allocate and intialize the pft parameters
361
362    CALL pft_parameters_main()
363
364    ! 4. Activation sub-models of ORCHIDEE
365
366    CALL activate_sub_models()
367
368    ! 5. Vegetation configuration
369
370    CALL veget_config
371
372    ! 6. Read the parameters in the run.def file  according the flags
373
374    IF (impose_param ) THEN
375       CALL config_pft_parameters
376    ENDIF
377
378    IF ( ok_sechiba ) THEN
379       IF (impose_param ) THEN
380          IF (printlev>=2) WRITE(numout,*)'In control_initialize: call config_sechiba_parameters and config_sechiba_pft_parameters'
381          CALL config_sechiba_parameters
382          CALL config_sechiba_pft_parameters()
383       ENDIF
384    ENDIF
385
386
387    !! Initialize variables in constantes_soil
388    CALL config_soil_parameters()
389
390
391    !! Coherence check for depth of thermosoil for long term simulation where soil thermal inertia matters
392    !! ok_freeze_thermix is defined in config_soil_parameters
393    IF (ok_freeze_thermix .AND. zmaxt < 11) THEN
394       WRITE(numout,*) 'ERROR : Incoherence between ok_freeze_thermix activated and soil depth too small. '
395       WRITE(numout,*) 'Here a soil depth of ', zmaxt, 'm is used for the soil thermodynamics'
396       WRITE(numout,*) 'Set DEPTH_MAX_T=11 or higher in run.def parameter file or deactivate soil freezing'
397       CALL ipslerr_p(3,'control_initialize','Too shallow soil chosen for the thermodynamic for soil freezing', &
398            'Adapt run.def with at least DEPTH_MAX=11','')
399    END IF
400       
401    ! Define diaglev as the depth of the bottom of each layer
402    ! diaglev defines the vertical axes for the variables transmitted from sechiba
403    ! to stomate (stempdiag, shumdiag).
404    ALLOCATE(diaglev(nslm), stat=ier)
405    IF (ier /= 0) CALL ipslerr_p(3,'control_initialize','Pb in allocation of diaglev','','')
406
407    ! Get diaglev from module vertical for CWRR
408    ! We take the top nslm (number of layer in CWRR) layer of the thermodynamics
409    ! for the diagnostics. The layers in the hydrology and the thermodynamics are
410    ! placed a the same depth (the top nslm layers) but the upper boundary condition
411    ! is simpler in the thermodynamics.
412    diaglev=zlt(1:nslm)
413    IF (printlev>=2) WRITE(numout,*) 'In control_initialize, diaglev = ',diaglev
414
415    IF ( impose_param ) THEN
416       IF (printlev>=2) WRITE(numout,*)'In control_initialize: call config_co2_parameters'
417       CALL config_co2_parameters
418    ENDIF
419       
420    IF ( ok_stomate ) THEN
421       IF ( impose_param ) THEN
422          IF (printlev>=2) WRITE(numout,*)'In control_initialize: call config_stomate_parameters and config_stomate_pft_parameters'
423          CALL config_stomate_parameters
424          CALL config_stomate_pft_parameters
425       ENDIF
426    ENDIF
427   
428    IF ( ok_dgvm ) THEN
429       IF ( impose_param ) THEN
430          IF (printlev>=2) WRITE(numout,*)'In control_initialize: call config_dgvm_parameters'
431          CALL config_dgvm_parameters
432       ENDIF
433    ENDIF   
434  END SUBROUTINE control_initialize
435 
436END MODULE control
Note: See TracBrowser for help on using the repository browser.