source: branches/ORCHIDEE_2_2/ORCHIDEE/src_parameters/control.f90 @ 7475

Last change on this file since 7475 was 7475, checked in by josefine.ghattas, 2 years ago

Update orchidee.default using the tool create_orchidee_defalut.sh tool. Note that manual modifications in orchidee.default are overwritten. Reported some of the changes done previously in orchidee.default to the fortran source code. Note also that all sections in !Config must be there to have the tool working. Therfore added some missing !Config If lines.

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