SURFEX v8.1
General documentation of Surfex
modd_isba_optionsn.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 !##################
7 !##################
8 !
9 !!**** *MODD_ISBA - declaration of packed surface parameters for ISBA scheme
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 !!
15 !!** IMPLICIT ARGUMENTS
16 !! ------------------
17 !! None
18 !!
19 !! REFERENCE
20 !! ---------
21 !!
22 !! AUTHOR
23 !! ------
24 !! A. Boone *Meteo France*
25 !!
26 !! MODIFICATIONS
27 !! -------------
28 !! Original 20/09/02
29 !! A.L. Gibelin 04/2009 : BIOMASS and RESP_BIOMASS arrays
30 !! A.L. Gibelin 04/2009 : TAU_WOOD for NCB option
31 !! A.L. Gibelin 05/2009 : Add carbon spinup
32 !! A.L. Gibelin 06/2009 : Soil carbon variables for CNT option
33 !! A.L. Gibelin 07/2009 : Suppress RDK and transform GPP as a diagnostic
34 !! A.L. Gibelin 07/2009 : Suppress PPST and PPSTF as outputs
35 !! P. Samuelsson 02/2012 : MEB
36 !!
37 !-------------------------------------------------------------------------------
38 !
39 !* 0. DECLARATIONS
40 ! ------------
41 !
42 USE yomhook ,ONLY : lhook, dr_hook
43 USE parkind1 ,ONLY : jprb
44 !
45 IMPLICIT NONE
46 !
47 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
48 !
49 TYPE ISba_options_t
50 !
51 ! * General PGD options
52 !
53 LOGICAL :: lecoclimap ! T: parameters computed from ecoclimap
54 ! ! F: they are read in the file
55 !
56 LOGICAL :: lpar ! T: parameters computed from ecoclimap
57 ! ! F: they are read in the file
58 !
59 INTEGER :: npatch ! maximum number of sub-tiles (patches)
60 ! ! used at any grid point within a
61 ! ! natural surface fraction
62 INTEGER :: nground_layer ! number of ground layers
63 !
64  CHARACTER(LEN=3) :: cisba ! type of ISBA version:
65 ! ! '2-L' (default)
66 ! ! '3-L'
67 ! ! 'DIF'
68  CHARACTER(LEN=4) :: cpedotf ! NOTE: Only used when HISBA = DIF
69 ! ! 'CH78' = Clapp and Hornberger 1978 for BC (Default)
70 ! ! 'CO84' = Cosby et al. 1988 for BC
71  CHARACTER(LEN=3) :: cphoto ! type of photosynthesis
72 ! ! 'NON'
73 ! ! 'AST'
74 ! ! 'NIT'
75 ! ! 'NCB'
76 !
77 REAL, POINTER, DIMENSION(:) :: xsoilgrid ! Soil layer grid as reference for DIF
78 !
79 LOGICAL :: ltr_ml ! new radiative transfert
80 !
81 REAL :: xrm_patch ! threshold to remove little fractions of patches
82 !
83 LOGICAL :: lsocp ! Soil organic carbon profile data
84 LOGICAL :: lcti ! Topographic index data
85 LOGICAL :: lperm ! Permafrost distribution data
86 LOGICAL :: lnof
87 !
88 ! Type of vegetation (simplification of vegetation charaterization)
89 !
90  CHARACTER(LEN=4) :: ctype_hveg ! type of high vegetation
91  CHARACTER(LEN=4) :: ctype_lveg ! type of low vegetation
92  CHARACTER(LEN=4) :: ctype_nveg ! type of bare soil (no vegetation)
93  CHARACTER(LEN=5) :: ctyp_cov ! type of green roof
94 !
95 ! * AGS and Carbon PGD options
96 !
97 INTEGER :: nnbiomass ! number of biomass pools
98 INTEGER :: nnlitter ! number of litter pools
99 INTEGER :: nnlittlevs ! number of litter levels
100 INTEGER :: nnsoilcarb ! number of soil carbon pools
101 !
102 ! * PGD MEB OPTIONS
103 !
104 LOGICAL, POINTER, DIMENSION(:) :: lmeb_patch ! Vector with T/F values
105  ! True = treat patch with multi-energy balance
106  ! False = treat patch with classical ISBA
107 LOGICAL :: lforc_measure ! True = Forcing data from observations
108 ! ! False = Forcing data from atmospheric model (default)
109 LOGICAL :: lmeb_litter ! Activate Litter
110 LOGICAL :: lmeb_gndres ! Activate Ground Resistance
111 !
112 ! * General PREP options
113 !
114 LOGICAL :: lcanopy ! T: SBL scheme within the canopy
115 ! ! F: no atmospheric layers below forcing level
116 !
117 ! * Carbon PREP options
118  CHARACTER(LEN=3) :: crespsl ! Soil respiration
119 ! ! 'DEF' = Default: Norman (1992)
120 ! ! 'PRM' = New Parameterization
121 ! ! 'CNT' = CENTURY model (Gibelin 2007)
122 !
123 !
124 ! * General MODEL options
125 !
126  CHARACTER(LEN=4) :: cc1dry ! C1 formulation for dry soils
127 ! ! 'DEF ' = DEFault: Giard-Bazile formulation
128 ! ! 'GB93' = Giordani 1993, Braud 1993
129 ! ! discontinuous at WILT
130  CHARACTER(LEN=4) :: cscond ! Thermal conductivity
131 ! ! 'DEF ' = DEFault: NP89 implicit method
132 ! ! 'PL98' = Peters-Lidard et al. 1998 used
133 ! ! for explicit computation of CG
134  CHARACTER(LEN=3) :: csoilfrz ! soil freezing-physics option
135 ! ! 'DEF' = Default (Boone et al. 2000;
136 ! ! Giard and Bazile 2000)
137 ! ! 'LWT' = Phase changes as above,
138 ! ! but relation between unfrozen
139 ! ! water and temperature considered
140  CHARACTER(LEN=4) :: cdifsfcond ! Mulch effects
141 ! ! 'MLCH' = include the insulating effect of
142 ! ! leaf litter/mulch on the surf. thermal cond.
143 ! ! 'DEF ' = no mulch effect
144 ! NOTE: Only used when YISBA = DIF
145  CHARACTER(LEN=3) :: csnowres ! Turbulent exchanges over snow
146 ! ! 'DEF' = Default: Louis (ISBA)
147 ! ! 'RIL' = Maximum Richardson number limit
148 ! ! for stable conditions ISBA-SNOW3L
149 ! ! turbulent exchange option
150  CHARACTER(LEN=4) :: calbedo ! albedo type
151 ! ! 'DRY '
152 ! ! 'EVOL'
153 ! ! 'WET '
154 ! ! 'USER'
155 ! NOTE that when using the YISBA='DIF' multi-layer soil option,
156 ! the 'LWT' method is used. It is only an option
157 ! when using the force-restore soil method ('2-L' or '3-L')
158  CHARACTER(LEN=3) :: ccpsurf ! specific heat at surface
159 ! ! 'DRY' = default value (dry Cp)
160 ! ! 'HUM' = Cp as a fct of specific humidity
161 !
162 REAL :: xout_tstep ! ISBA output writing time step
163 REAL :: xtstep ! ISBA time step
164 REAL :: xcgmax ! maximum soil heat capacity
165 REAL :: xcdrag ! drag coefficient in canopy
166 !
167 LOGICAL :: lglacier ! True = Over permanent snow and ice,
168 ! initialise WGI=WSAT,
169 ! Hsnow>=10m and allow 0.8<SNOALB<0.85
170  ! False = No specific treatment
171 LOGICAL :: lcanopy_drag ! T: drag activated in SBL scheme within the canopy
172 ! ! F: no drag activated in SBL atmospheric layers
173 LOGICAL :: lvegupd ! True = update vegetation parameters every decade
174 LOGICAL :: lpertsurf ! True = apply random perturbations for ensemble prediction
175  ! False = no random perturbation (default)
176 !
177 !
178 ! * SGH model options
179 !
180 ! - Adjustable physical parameters
181 !
182 INTEGER :: nlayer_hort
183 INTEGER :: nlayer_dun
184 !
185 ! - Sub-grid hydrology and vertical hydrology
186 !
187  CHARACTER(LEN=4) :: crunoff ! surface runoff formulation
188 ! ! 'WSAT'
189 ! ! 'DT92'
190 ! ! 'SGH ' Topmodel
191 !
192  CHARACTER(LEN=3) :: cksat ! ksat
193 ! ! 'DEF' = default value
194 ! ! 'SGH' = profil exponentiel
195 !
196 LOGICAL :: lsoc ! soil organic carbon effect
197 ! ! False = default value
198 ! ! True = soil SOC profil
199 !
200  CHARACTER(LEN=3) :: crain ! Rainfall spatial distribution
201  ! 'DEF' = No rainfall spatial distribution
202  ! 'SGH' = Rainfall exponential spatial distribution
203  !
204 !
205  CHARACTER(LEN=3) :: chort ! Horton runoff
206  ! 'DEF' = no Horton runoff
207  ! 'SGH' = Horton runoff
208 !
209 ! * AGS and carbon options
210 !
211 LOGICAL :: lnitro_dilu ! nitrogen dilution fct of CO2 (Calvet et al. 2008)
212  ! False = keep vegetation parameters constant in time
213 !
214 LOGICAL :: lspinupcarbs ! T: do the soil carb spinup, F: no
215 LOGICAL :: lspinupcarbw ! T: do the wood carb spinup, F: no
216 REAL :: xspinmaxs ! max number of times CARBON_SOIL subroutine is
217  ! called for each timestep in simulation during
218  ! acceleration procedure number
219 REAL :: xspinmaxw ! max number of times the wood is accelerated
220 REAL :: xco2_start ! Pre-industrial CO2 concentration
221 REAL :: xco2_end ! Begin-transient CO2 concentration
222 INTEGER :: nnbyearspins ! nbr years needed to reaches soil equilibrium
223 INTEGER :: nnbyearspinw ! nbr years needed to reaches wood equilibrium
224 INTEGER :: nnbyearsold ! nbr years executed at curent time step
225 INTEGER :: nspins ! number of times the soil is accelerated
226 INTEGER :: nspinw ! number of times the wood is accelerated
227 !
228 LOGICAL :: lagri_to_grass ! During soil carbon spinup with ISBA-CC,
229  ! grass parameters are attributed to all agricultural PFT
230 !
231 ! * Snow model options
232 !
233 LOGICAL :: lsnowdrift, lsnowdrift_sublim ! Logicals for snowdrift and sublimation
234 
235 LOGICAL :: lsnow_abs_zenith ! if True modify solar absorption as a function of solar zenithal angle
236  ! (physically wrong but better results in polar regions when CSNOWRAD=B92)
237 ! Scheme of snow metamorphism (Crocus)
238  CHARACTER(3) :: csnowmetamo ! B92 (historical version, Brun et al 92), C13, T07, F06 (see Carmagnola et al 2014)
239 !
240 ! radiative transfer scheme in snow (Crocus)
241  CHARACTER(3) :: csnowrad ! B92 (historical version, Brun et al 92), TAR, TA1, TA2 (see Libois et al 2013)
242 !
243 ! * Other options
244 !
245 LOGICAL :: lflood ! Activation of the flooding scheme
246 LOGICAL :: lwtd ! Activation of Water table depth coupling
247 LOGICAL :: lcpl_rrm ! Activation of the coupling
248 !
249 LOGICAL :: ltemp_arp ! True = time-varying force-restore soil temperature (as in ARPEGE)
250  ! False = No time-varying force-restore soil temperature (Default
251 INTEGER :: ntemplayer_arp ! Number of force-restore soil temperature layer, including Ts (Default = 4)
252  ! Only used if LTEMP_ARP=True
253 REAL, POINTER, DIMENSION(:) :: xsodelx ! Pulsation for each layer (Only used if LTEMP_ARP=True)
254 !
255 END TYPE isba_options_t
256 !
257 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
258 !
259 CONTAINS
260 
261 SUBROUTINE isba_options_init(IO)
262 TYPE(isba_options_t), INTENT(INOUT) :: IO
263 REAL(KIND=JPRB) :: ZHOOK_HANDLE
264 IF (lhook) CALL dr_hook("MODD_ISBA_OPTIONS_N:ISBA_OPTIONS_INIT",0,zhook_handle)
265 !
266 NULLIFY(io%XSOILGRID)
267 NULLIFY(io%LMEB_PATCH)
268 !
269 io%CTYPE_HVEG=' '
270 io%CTYPE_LVEG=' '
271 io%CTYPE_NVEG=' '
272 io%CTYP_COV=' '
273 io%LPAR=.false.
274 io%LECOCLIMAP=.false.
275 io%NPATCH=0
276 io%NGROUND_LAYER=0
277 io%CISBA=' '
278 io%CPEDOTF=' '
279 io%CPHOTO=' '
280 io%LTR_ML=.false.
281 io%XRM_PATCH=0.0
282 io%LSOCP=.false.
283 io%LCTI=.false.
284 io%LPERM=.false.
285 io%LNOF=.false.
286 io%NNBIOMASS=0
287 io%NNLITTER=0
288 io%NNLITTLEVS=0
289 io%NNSOILCARB=0
290 io%LFORC_MEASURE=.false.
291 io%LMEB_LITTER=.false.
292 io%LMEB_GNDRES=.false.
293 !
294 io%LCANOPY=.false.
295 io%CRESPSL=' '
296 !
297 io%CC1DRY=' '
298 io%CSCOND=' '
299 io%CSOILFRZ=' '
300 io%CDIFSFCOND=' '
301 io%CSNOWRES=' '
302 io%CALBEDO=' '
303 io%CCPSURF=' '
304 io%XOUT_TSTEP=0.
305 io%XTSTEP=0.
306 io%XCGMAX=0.
307 io%XCDRAG=0.
308 io%LGLACIER=.false.
309 io%LCANOPY_DRAG=.false.
310 io%LVEGUPD=.false.
311 io%LPERTSURF=.false.
312 io%NLAYER_HORT=0
313 io%NLAYER_DUN=0
314 io%CRUNOFF=' '
315 io%CKSAT=' '
316 io%CRAIN=' '
317 io%CHORT=' '
318 io%LSOC=.false.
319 io%LNITRO_DILU=.false.
320 io%LSPINUPCARBS=.false.
321 io%LSPINUPCARBW=.false.
322 io%XSPINMAXS=0.
323 io%XSPINMAXW=0.
324 io%XCO2_START=0.
325 io%XCO2_END=0.
326 io%NNBYEARSPINS=0
327 io%NNBYEARSPINW=0
328 io%NNBYEARSOLD=0
329 io%NSPINS=1
330 io%NSPINW=1
331 io%LAGRI_TO_GRASS=.false.
332 io%LSNOWDRIFT=.true.
333 io%LSNOWDRIFT_SUBLIM=.false.
334 io%LSNOW_ABS_ZENITH=.false.
335 io%CSNOWMETAMO='B92'
336 io%CSNOWRAD='B92'
337 io%LFLOOD=.false.
338 io%LWTD=.false.
339 io%LCPL_RRM=.false.
340 io%LTEMP_ARP=.false.
341 io%NTEMPLAYER_ARP=0
342 !
343 IF (lhook) CALL dr_hook("MODD_ISBA_OPTIONS_N:ISBA_OPTIONS_INIT",1,zhook_handle)
344 END SUBROUTINE isba_options_init
345 
346 END MODULE modd_isba_options_n
subroutine isba_options_init(IO)
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15