source: branches/publications/ORCHIDEE_gmd_2018_MICT-LEAK/src_parameters/control.f90 @ 7862

Last change on this file since 7862 was 4977, checked in by simon.bowring, 7 years ago

Currently running (13/02/2018) version includes all necessarily changes to include DOC in MICT code... further parametrisation necessary to equate soil pools with those of normal forcesoil restarts

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