SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
modd_teb_garden_pgdn.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_TEB_GARDEN - 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. Lemonsu *Meteo France*
25 !!
26 !! MODIFICATIONS
27 !! -------------
28 !! Original 01/2011
29 !! V. Masson 06/2013 splits module in 4
30 !!
31 !-------------------------------------------------------------------------------
32 !
33 !* 0. DECLARATIONS
34 ! ------------
35 !
36 !
37 USE yomhook ,ONLY : lhook, dr_hook
38 USE parkind1 ,ONLY : jprb
39 !
40 IMPLICIT NONE
41 
42 !-------------------------------------------------------------------------------
44 !-------------------------------------------------------------------------------
45 !
46 ! Mask and number of grid elements containing patches/tiles:
47 !
48  REAL, POINTER, DIMENSION(:,:) :: XVEGTYPE ! fraction of each vegetation type for
49 ! ! each grid mesh (-)
50 !-------------------------------------------------------------------------------
51 !
52 ! Averaged Surface radiative parameters:
53 !
54  REAL, POINTER, DIMENSION(:) :: XALBNIR_DRY ! dry soil near-infra-red albedo (-)
55  REAL, POINTER, DIMENSION(:) :: XALBVIS_DRY ! dry soil visible albedo (-)
56  REAL, POINTER, DIMENSION(:) :: XALBUV_DRY ! dry soil UV albedo (-)
57  REAL, POINTER, DIMENSION(:) :: XALBNIR_WET ! wet soil near-infra-red albedo (-)
58  REAL, POINTER, DIMENSION(:) :: XALBVIS_WET ! wet soil visible albedo (-)
59  REAL, POINTER, DIMENSION(:) :: XALBUV_WET ! wet soil UV albedo (-)
60  REAL, POINTER, DIMENSION(:) :: XALBNIR_SOIL ! soil near-infra-red albedo (-)
61  REAL, POINTER, DIMENSION(:) :: XALBVIS_SOIL ! soil visible albedo (-)
62  REAL, POINTER, DIMENSION(:) :: XALBUV_SOIL ! soil UV albedo (-)
63 !
64 !-------------------------------------------------------------------------------
65 !
66 ! Input Parameters, per patch:
67 !
68 ! - vegetation + bare soil:
69 !
70  REAL, POINTER, DIMENSION(:) :: XZ0_O_Z0H ! ratio of surface roughness lengths
71 ! ! (momentum to heat) (-)
72 !
73 ! - vegetation:
74 !
75  REAL, POINTER, DIMENSION(:) :: XALBNIR_VEG ! vegetation near-infra-red albedo (-)
76  REAL, POINTER, DIMENSION(:) :: XALBVIS_VEG ! vegetation visible albedo (-)
77  REAL, POINTER, DIMENSION(:) :: XALBUV_VEG ! vegetation UV albedo (-)
78 !
79 ! - vegetation: default option (Jarvis) and general parameters:
80 !
81  REAL, POINTER, DIMENSION(:) :: XWRMAX_CF ! coefficient for maximum water
82 ! ! interception
83 ! ! storage capacity on the vegetation (-)
84  REAL, POINTER, DIMENSION(:) :: XRSMIN ! minimum stomatal resistance (s/m)
85  REAL, POINTER, DIMENSION(:) :: XGAMMA ! coefficient for the calculation
86 ! ! of the surface stomatal
87 ! ! resistance
88  REAL, POINTER, DIMENSION(:) :: XCV ! vegetation thermal inertia coefficient (K m2/J)
89  REAL, POINTER, DIMENSION(:) :: XRGL ! maximum solar radiation
90 ! ! usable in photosynthesis (W/m2)
91  REAL, POINTER, DIMENSION(:,:) :: XROOTFRAC ! root fraction profile ('DIF' option)
92 !
93 !-------------------------------------------------------------------------------
94 !
95 ! - vegetation: Ags parameters ('AGS', 'LAI', 'AST', 'LST', 'NIT', 'NCB' options)
96 !
97 ! REAL, DIMENSION(3) :: XABC ! abscissa needed for integration
98  REAL, POINTER, DIMENSION(:) :: XABC ! abscissa needed for integration
99 ! ! of net assimilation and stomatal
100 ! ! conductance over canopy depth (-)
101 ! REAL, DIMENSION(3) :: XPOI ! Gaussian weights for integration
102  REAL, POINTER, DIMENSION(:) :: XPOI ! Gaussian weights for integration
103 ! ! of net assimilation and stomatal
104 ! ! conductance over canopy depth (-)
105  REAL, POINTER, DIMENSION(:) :: XBSLAI ! ratio d(biomass)/d(lai) (kg/m2)
106  REAL, POINTER, DIMENSION(:) :: XLAIMIN ! minimum LAI (Leaf Area Index) (m2/m2)
107  REAL, POINTER, DIMENSION(:) :: XSEFOLD ! e-folding time for senescence (s)
108  REAL, POINTER, DIMENSION(:) :: XH_TREE ! height of trees (m)
109  REAL, POINTER, DIMENSION(:) :: XANF ! total assimilation over canopy (
110  REAL, POINTER, DIMENSION(:) :: XANMAX ! maximum photosynthesis rate (
111  REAL, POINTER, DIMENSION(:) :: XFZERO ! ideal value of F, no photo-
112 ! ! respiration or saturation deficit (
113  REAL, POINTER, DIMENSION(:) :: XEPSO ! maximum initial quantum use
114 ! ! efficiency (mg J-1 PAR)
115  REAL, POINTER, DIMENSION(:) :: XGAMM ! CO2 conpensation concentration (ppm)
116  REAL, POINTER, DIMENSION(:) :: XQDGAMM ! Log of Q10 function for CO2 conpensation
117 ! ! concentration (-)
118  REAL, POINTER, DIMENSION(:) :: XGMES ! mesophyll conductance (m s-1)
119  REAL, POINTER, DIMENSION(:) :: XRE25 ! Ecosystem respiration parameter (kg/kg.m.s-1)
120  REAL, POINTER, DIMENSION(:) :: XQDGMES ! Log of Q10 function for mesophyll conductance (-)
121  REAL, POINTER, DIMENSION(:) :: XT1GMES ! reference temperature for computing
122 ! ! compensation concentration function for
123 ! ! mesophyll conductance: minimum
124 ! ! temperature (K)
125  REAL, POINTER, DIMENSION(:) :: XT2GMES ! reference temperature for computing
126 ! ! compensation concentration function for
127 ! ! mesophyll conductance: maximum
128 ! ! temperature (K)
129  REAL, POINTER, DIMENSION(:) :: XAMAX ! leaf photosynthetic capacity (mg m-2 s-1)
130  REAL, POINTER, DIMENSION(:) :: XQDAMAX ! Log of Q10 function for leaf photosynthetic
131 ! ! capacity (-)
132  REAL, POINTER, DIMENSION(:) :: XT1AMAX ! reference temperature for computing
133 ! ! compensation concentration function for
134 ! ! leaf photosynthetic capacity: minimum
135 ! ! temperature (K)
136  REAL, POINTER, DIMENSION(:) :: XT2AMAX ! reference temperature for computing
137 ! ! compensation concentration function for
138 ! ! leaf photosynthetic capacity: maximum
139 ! ! temperature (K)
140 !
141 
142 !-------------------------------------------------------------------------------
143 !
144 ! - vegetation: Ags Stress parameters ('AST', 'LST', 'NIT', 'NCB' options)
145 !
146  LOGICAL, POINTER, DIMENSION(:) :: LSTRESS ! vegetation response type to water
147 ! ! stress (true:defensive false:offensive) (-)
148  REAL, POINTER, DIMENSION(:) :: XF2I ! critical normilized soil water
149 ! ! content for stress parameterisation
150  REAL, POINTER, DIMENSION(:) :: XGC ! cuticular conductance (m s-1)
151  REAL, POINTER, DIMENSION(:) :: XAH ! coefficients for herbaceous water stress
152 ! ! response (offensive or defensive) (log(mm/s))
153  REAL, POINTER, DIMENSION(:) :: XBH ! coefficients for herbaceous water stress
154 ! ! response (offensive or defensive) (-)
155  REAL, POINTER, DIMENSION(:) :: XDMAX ! maximum air saturation deficit
156 ! ! tolerate by vegetation (kg/kg)
157 !
158 !-------------------------------------------------------------------------------
159 !
160 ! - vegetation: Ags Nitrogen-model parameters ('NIT', 'NCB' option)
161 !
162  REAL, POINTER, DIMENSION(:) :: XCE_NITRO ! leaf aera ratio sensitivity to
163 ! ! nitrogen concentration (m2/kg)
164  REAL, POINTER, DIMENSION(:) :: XCF_NITRO ! lethal minimum value of leaf area
165 ! ! ratio (m2/kg)
166  REAL, POINTER, DIMENSION(:) :: XCNA_NITRO ! nitrogen concentration of active
167 ! ! biomass (kg/kg)
168  REAL, POINTER, DIMENSION(:) :: XBSLAI_NITRO ! biomass/LAI ratio from nitrogen
169 ! ! decline theory (kg/m2)
170 !
171 !-------------------------------------------------------------------------------
172 !
173 ! - soil: primary parameters
174 !
175  REAL, POINTER, DIMENSION(:,:) :: XSAND ! sand fraction (-)
176  REAL, POINTER, DIMENSION(:,:) :: XCLAY ! clay fraction (-)
177  REAL, POINTER, DIMENSION(:) :: XRUNOFFB ! sub-grid surface runoff slope parameter (-)
178  REAL, POINTER, DIMENSION(:) :: XWDRAIN ! continuous drainage parameter (-)
179  REAL, POINTER, DIMENSION(:) :: XTAUICE ! soil freezing characteristic timescale (s)
180  REAL, POINTER, DIMENSION(:) :: XGAMMAT ! 'Force-Restore' timescale when using a
181 ! ! prescribed lower boundary temperature (1/days)
182  REAL, POINTER, DIMENSION(:,:) :: XDG ! soil layer thicknesses (m)
183 ! ! NOTE: in Force-Restore mode, the
184 ! ! uppermost layer thickness is superficial
185 ! ! and is only explicitly used for soil
186 ! ! water phase changes (m)
187  REAL, POINTER, DIMENSION(:) :: XRUNOFFD ! depth over which sub-grid runoff is
188 ! ! computed: in Force-Restore this is the
189 ! ! total soil column ('2-L'), or root zone
190 ! ! ('3-L'). For the 'DIF' option, it can
191 ! ! be any depth within soil column (m)
192 !
193  REAL, POINTER, DIMENSION(:,:) :: XSOILWGHT ! ISBA-DIF: weights for vertical
194  REAL, POINTER, DIMENSION(:,:) :: XDZG ! soil layers thicknesses (DIF option)
195  REAL, POINTER, DIMENSION(:,:) :: XDZDIF ! distance between consecuative layer mid-points (DIF option)
196 !
197  INTEGER, POINTER, DIMENSION(:) :: NWG_LAYER ! Number of soil moisture layers for DIF
198  REAL, POINTER, DIMENSION(:) :: XDROOT ! effective root depth for DIF (m)
199  REAL, POINTER, DIMENSION(:) :: XDG2 ! root depth for DIF as 3-L (m)
200 !-------------------------------------------------------------------------------
201 !
202 ! - soil: Secondary parameters: hydrology
203 !
204  REAL, POINTER, DIMENSION(:) :: XC1SAT ! 'Force-Restore' C1 coefficient at
205 ! ! saturation (-)
206  REAL, POINTER, DIMENSION(:) :: XC2REF ! 'Force-Restore' reference value of C2 (-)
207  REAL, POINTER, DIMENSION(:,:) :: XC3 ! 'Force-Restore' C3 drainage coefficient (m)
208  REAL, POINTER, DIMENSION(:) :: XC4B ! 'Force-Restore' sub-surface vertical
209 ! ! diffusion coefficient (slope parameter) (-)
210  REAL, POINTER, DIMENSION(:) :: XC4REF ! 'Force-Restore' sub-surface vertical
211 ! ! diffusion coefficient (-)
212  REAL, POINTER, DIMENSION(:) :: XACOEF ! 'Force-Restore' surface vertical
213 ! ! diffusion coefficient (-)
214  REAL, POINTER, DIMENSION(:) :: XPCOEF ! 'Force-Restore' surface vertical
215 ! ! diffusion coefficient (-)
216  REAL, POINTER, DIMENSION(:,:) :: XWFC ! field capacity volumetric water content
217 ! ! profile (m3/m3)
218  REAL, POINTER, DIMENSION(:,:) :: XWWILT ! wilting point volumetric water content
219 ! ! profile (m3/m3)
220  REAL, POINTER, DIMENSION(:,:) :: XWSAT ! porosity profile (m3/m3)
221  REAL, POINTER, DIMENSION(:,:) :: XBCOEF ! soil water CH78 b-parameter (-)
222  REAL, POINTER, DIMENSION(:,:) :: XCONDSAT ! hydraulic conductivity at saturation (m/s)
223  REAL, POINTER, DIMENSION(:,:) :: XMPOTSAT ! matric potential at saturation (m)
224 !
225 !-------------------------------------------------------------------------------
226 !
227 ! - soil: Secondary parameters: thermal
228 !
229  REAL, POINTER, DIMENSION(:) :: XCGSAT ! soil thermal inertia coefficient at
230 ! ! saturation (K m2/J)
231  REAL, POINTER, DIMENSION(:,:) :: XHCAPSOIL ! soil heat capacity (J/K/m3)
232  REAL, POINTER, DIMENSION(:,:) :: XCONDDRY ! soil dry thermal conductivity (W/m/K)
233  REAL, POINTER, DIMENSION(:,:) :: XCONDSLD ! soil solids thermal conductivity (W/m/K)
234  REAL, POINTER, DIMENSION(:) :: XTDEEP ! prescribed deep soil temperature
235 ! ! (optional) (K)
236  REAL, POINTER, DIMENSION(:) :: XPCPS
237  REAL, POINTER, DIMENSION(:) :: XPLVTT
238  REAL, POINTER, DIMENSION(:) :: XPLSTT
239 !-------------------------------------------------------------------------------
240 !
241 ! - SGH scheme
242 !
243  REAL, POINTER, DIMENSION(:) :: XD_ICE !depth of the soil column for the calculation
244 ! of the frozen soil fraction (m)
245  REAL, POINTER, DIMENSION(:) :: XKSAT_ICE !hydraulic conductivity at saturation
246 ! over frozen area (m s-1)
247 !-------------------------------------------------------------------------------
248 !
249 ! Type of vegetation (simplification of vegetation charaterization)
250  CHARACTER(LEN=4) :: CTYPE_HVEG ! type of high vegetation
251  CHARACTER(LEN=4) :: CTYPE_LVEG ! type of low vegetation
252  CHARACTER(LEN=4) :: CTYPE_NVEG ! type of bare soil (no vegetation)
253 !-------------------------------------------------------------------------------
254 !
255 END TYPE teb_garden_pgd_t
256 !
257 
258 
259 
260  CONTAINS
261 
262 !
263 
264 
265 !
266 
267 SUBROUTINE teb_garden_pgd_init(YTEB_GARDEN_PGD)
268 TYPE(teb_garden_pgd_t), INTENT(INOUT) :: yteb_garden_pgd
269 REAL(KIND=JPRB) :: zhook_handle
270 IF (lhook) CALL dr_hook("MODD_TEB_GARDEN_PGD_N:TEB_GARDEN_PGD_INIT",0,zhook_handle)
271  nullify(yteb_garden_pgd%XVEGTYPE)
272  nullify(yteb_garden_pgd%XALBNIR_DRY)
273  nullify(yteb_garden_pgd%XALBVIS_DRY)
274  nullify(yteb_garden_pgd%XALBUV_DRY)
275  nullify(yteb_garden_pgd%XALBNIR_WET)
276  nullify(yteb_garden_pgd%XALBVIS_WET)
277  nullify(yteb_garden_pgd%XALBUV_WET)
278  nullify(yteb_garden_pgd%XALBNIR_SOIL)
279  nullify(yteb_garden_pgd%XALBVIS_SOIL)
280  nullify(yteb_garden_pgd%XALBUV_SOIL)
281  nullify(yteb_garden_pgd%XZ0_O_Z0H)
282  nullify(yteb_garden_pgd%XALBNIR_VEG)
283  nullify(yteb_garden_pgd%XALBVIS_VEG)
284  nullify(yteb_garden_pgd%XALBUV_VEG)
285  nullify(yteb_garden_pgd%XWRMAX_CF)
286  nullify(yteb_garden_pgd%XRSMIN)
287  nullify(yteb_garden_pgd%XGAMMA)
288  nullify(yteb_garden_pgd%XCV)
289  nullify(yteb_garden_pgd%XRGL)
290  nullify(yteb_garden_pgd%XROOTFRAC)
291  nullify(yteb_garden_pgd%XBSLAI)
292  nullify(yteb_garden_pgd%XLAIMIN)
293  nullify(yteb_garden_pgd%XSEFOLD)
294  nullify(yteb_garden_pgd%XH_TREE)
295  nullify(yteb_garden_pgd%XANF)
296  nullify(yteb_garden_pgd%XANMAX)
297  nullify(yteb_garden_pgd%XFZERO)
298  nullify(yteb_garden_pgd%XEPSO)
299  nullify(yteb_garden_pgd%XGAMM)
300  nullify(yteb_garden_pgd%XQDGAMM)
301  nullify(yteb_garden_pgd%XGMES)
302  nullify(yteb_garden_pgd%XRE25)
303  nullify(yteb_garden_pgd%XQDGMES)
304  nullify(yteb_garden_pgd%XT1GMES)
305  nullify(yteb_garden_pgd%XT2GMES)
306  nullify(yteb_garden_pgd%XAMAX)
307  nullify(yteb_garden_pgd%XQDAMAX)
308  nullify(yteb_garden_pgd%XT1AMAX)
309  nullify(yteb_garden_pgd%XT2AMAX)
310  nullify(yteb_garden_pgd%LSTRESS)
311  nullify(yteb_garden_pgd%XF2I)
312  nullify(yteb_garden_pgd%XGC)
313  nullify(yteb_garden_pgd%XAH)
314  nullify(yteb_garden_pgd%XBH)
315  nullify(yteb_garden_pgd%XDMAX)
316  nullify(yteb_garden_pgd%XCE_NITRO)
317  nullify(yteb_garden_pgd%XCF_NITRO)
318  nullify(yteb_garden_pgd%XCNA_NITRO)
319  nullify(yteb_garden_pgd%XBSLAI_NITRO)
320  nullify(yteb_garden_pgd%XSAND)
321  nullify(yteb_garden_pgd%XCLAY)
322  nullify(yteb_garden_pgd%XRUNOFFB)
323  nullify(yteb_garden_pgd%XWDRAIN)
324  nullify(yteb_garden_pgd%XTAUICE)
325  nullify(yteb_garden_pgd%XGAMMAT)
326  nullify(yteb_garden_pgd%XDG)
327  nullify(yteb_garden_pgd%XRUNOFFD)
328  nullify(yteb_garden_pgd%XSOILWGHT)
329  nullify(yteb_garden_pgd%XDZG)
330  nullify(yteb_garden_pgd%XDZDIF)
331  nullify(yteb_garden_pgd%NWG_LAYER)
332  nullify(yteb_garden_pgd%XDROOT)
333  nullify(yteb_garden_pgd%XDG2)
334  nullify(yteb_garden_pgd%XPCPS)
335  nullify(yteb_garden_pgd%XPLVTT)
336  nullify(yteb_garden_pgd%XPLSTT)
337  nullify(yteb_garden_pgd%XC1SAT)
338  nullify(yteb_garden_pgd%XC2REF)
339  nullify(yteb_garden_pgd%XC3)
340  nullify(yteb_garden_pgd%XC4B)
341  nullify(yteb_garden_pgd%XC4REF)
342  nullify(yteb_garden_pgd%XACOEF)
343  nullify(yteb_garden_pgd%XPCOEF)
344  nullify(yteb_garden_pgd%XWFC)
345  nullify(yteb_garden_pgd%XWWILT)
346  nullify(yteb_garden_pgd%XWSAT)
347  nullify(yteb_garden_pgd%XBCOEF)
348  nullify(yteb_garden_pgd%XCONDSAT)
349  nullify(yteb_garden_pgd%XMPOTSAT)
350  nullify(yteb_garden_pgd%XCGSAT)
351  nullify(yteb_garden_pgd%XHCAPSOIL)
352  nullify(yteb_garden_pgd%XCONDDRY)
353  nullify(yteb_garden_pgd%XCONDSLD)
354  nullify(yteb_garden_pgd%XTDEEP)
355  nullify(yteb_garden_pgd%XD_ICE)
356  nullify(yteb_garden_pgd%XKSAT_ICE)
357  nullify(yteb_garden_pgd%XABC)
358  nullify(yteb_garden_pgd%XPOI)
359 yteb_garden_pgd%CTYPE_HVEG=' '
360 yteb_garden_pgd%CTYPE_LVEG=' '
361 yteb_garden_pgd%CTYPE_NVEG=' '
362 IF (lhook) CALL dr_hook("MODD_TEB_GARDEN_PGD_N:TEB_GARDEN_PGD_INIT",1,zhook_handle)
363 END SUBROUTINE teb_garden_pgd_init
364 
365 
366 END MODULE modd_teb_garden_pgd_n
subroutine teb_garden_pgd_init(YTEB_GARDEN_PGD)