SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
z0v_from_lai.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 INTERFACE z0v_from_lai
10 !
11  FUNCTION z0v_from_lai_0d(PLAI,PH_TREE,PVEGTYPE,OAGRI_TO_GRASS) RESULT(PZ0)
12 !
13 REAL, INTENT(IN) :: plai ! Leaf area Index
14 REAL, INTENT(IN) :: ph_tree ! height of trees
15 REAL, DIMENSION(:), INTENT(IN) :: pvegtype ! type of vegetation
16 LOGICAL, INTENT(IN) :: oagri_to_grass
17 !
18 REAL :: pz0 ! vegetation roughness
19 !
20 END FUNCTION z0v_from_lai_0d
21 !
22 !
23  FUNCTION z0v_from_lai_1d(PLAI,PH_TREE,PVEGTYPE,OAGRI_TO_GRASS) RESULT(PZ0)
24 !
25 REAL, DIMENSION(:), INTENT(IN) :: plai ! Leaf area Index
26 REAL, DIMENSION(:), INTENT(IN) :: ph_tree ! height of trees
27 REAL, DIMENSION(:,:), INTENT(IN) :: pvegtype ! type of vegetation
28 LOGICAL, INTENT(IN) :: oagri_to_grass
29 !
30 REAL, DIMENSION(SIZE(PLAI)) :: pz0 ! vegetation roughness
31 !
32 END FUNCTION z0v_from_lai_1d
33 !
34 !
35  FUNCTION z0v_from_lai_2d(PLAI,PH_TREE,PVEGTYPE,OAGRI_TO_GRASS) RESULT(PZ0)
36 !
37 REAL, DIMENSION(:,:), INTENT(IN) :: plai ! Leaf area Index
38 REAL, DIMENSION(:,:), INTENT(IN) :: ph_tree ! height of trees
39 REAL, DIMENSION(:,:,:), INTENT(IN) :: pvegtype ! type of vegetation
40 LOGICAL, INTENT(IN) :: oagri_to_grass
41 !
42 REAL, DIMENSION(SIZE(PLAI,1),SIZE(PLAI,2)) :: pz0 ! vegetation roughness
43 !
44 END FUNCTION z0v_from_lai_2d
45 !
46  FUNCTION z0v_from_lai_patch(PLAI,PH_TREE,PVEGTYPE,OAGRI_TO_GRASS) RESULT(PZ0)
47 !
48 REAL, DIMENSION(:), INTENT(IN) :: plai ! Leaf area Index
49 REAL, DIMENSION(:), INTENT(IN) :: ph_tree ! height of trees
50 REAL, DIMENSION(:), INTENT(IN) :: pvegtype ! type of vegetation
51 LOGICAL, INTENT(IN) :: oagri_to_grass
52 !
53 REAL, DIMENSION(SIZE(PLAI)) :: pz0 ! vegetation roughness
54 !
55 END FUNCTION z0v_from_lai_patch
56 !
57 END INTERFACE
58 !
59 END MODULE modi_z0v_from_lai
60 !
61 
62 ! ###########################################################
63  FUNCTION z0v_from_lai_0d(PLAI,PH_TREE,PVEGTYPE,OAGRI_TO_GRASS) RESULT(PZ0)
64 ! ###########################################################
65 !!
66 !! PURPOSE
67 !! -------
68 !
69 ! Calculates vegetation roughness from leaf
70 ! area index and type of vegetation
71 ! (most of types; forest and vineyards; grassland)
72 !
73 !!** METHOD
74 !! ------
75 !!
76 !! EXTERNAL
77 !! --------
78 !! none
79 !!
80 !! IMPLICIT ARGUMENTS
81 !! ------------------
82 !!
83 !! none
84 !!
85 !! REFERENCE
86 !! ---------
87 !!
88 !!
89 !! AUTHOR
90 !! ------
91 !!
92 !! V. Masson and A. Boone * Meteo-France *
93 !!
94 !! MODIFICATIONS
95 !! -------------
96 !! Original 25/03/99
97 !! P. Aumond 10/10/2009 Because drag force applied in atmospheric
98 !! model, Z0tree -> z0grass
99 !! R. Alkama 05/2012 : Extantion from 12 to 19 vegtypes
100 !-------------------------------------------------------------------------------
101 !
102 !* 0. DECLARATIONS
103 ! ------------
104 !
105 USE modd_surf_par, ONLY : xundef
106 USE modd_data_cover_par, ONLY : nvt_no, nvt_rock, nvt_snow, nvt_tebd, &
107  nvt_bone, nvt_trbe, nvt_c3, nvt_c4, &
108  nvt_irr, nvt_gras, nvt_trog,nvt_park, &
109  nvt_trbd, nvt_tebe, nvt_tene, nvt_bobd, &
110  nvt_bond, nvt_bogr, nvt_shrb
112 !
113 USE yomhook ,ONLY : lhook, dr_hook
114 USE parkind1 ,ONLY : jprb
115 !
116 IMPLICIT NONE
117 !
118 !* 0.1 declarations of arguments
119 !
120 REAL, INTENT(IN) :: plai ! Leaf area Index
121 REAL, INTENT(IN) :: ph_tree ! height of trees
122 REAL, DIMENSION(:), INTENT(IN) :: pvegtype ! type of vegetation
123 LOGICAL, INTENT(IN) :: oagri_to_grass
124 !
125 REAL :: pz0 ! vegetation roughness
126 !
127 !* 0.2 declarations of local variables
128 !
129 REAL :: zallen_h ! Allen formula for height
130 REAL :: zlai ! LAI for vegetated areas
131 !
132 REAL, DIMENSION(SIZE(PVEGTYPE)) :: zh_veg ! height for each type
133 REAL :: zavg_h ! averaged height
134 REAL :: zzref ! reference height
135 !
136 INTEGER :: jtype ! loop counter
137 REAL(KIND=JPRB) :: zhook_handle
138 !-----------------------------------------------------------------
139 !
140 IF (lhook) CALL dr_hook('MODI_Z0V_FROM_LAI:Z0V_FROM_LAI_0D',0,zhook_handle)
141 !
142 zh_veg(:) = veg_height_from_lai(plai,ph_tree,pvegtype,oagri_to_grass)
143 !
144 zzref = 10.
145 zavg_h = 0.
146 DO jtype=1,SIZE(pvegtype)
147  zavg_h = zavg_h + pvegtype(jtype) / (log(0.13*zh_veg(jtype)/zzref))**2
148 END DO
149 zavg_h = max(zavg_h,0.00001)
150 
151 zavg_h = zzref / 0.13 * exp(-1./sqrt(zavg_h))
152 !
153 pz0 = max(0.001, 0.13*zavg_h)
154 IF (lhook) CALL dr_hook('MODI_Z0V_FROM_LAI:Z0V_FROM_LAI_0D',1,zhook_handle)
155 !
156 !-----------------------------------------------------------------
157 !
158 END FUNCTION z0v_from_lai_0d
159 !
160 ! ###########################################################
161  FUNCTION z0v_from_lai_1d(PLAI,PH_TREE,PVEGTYPE,OAGRI_TO_GRASS) RESULT(PZ0)
162 ! ###########################################################
163 !!
164 !! PURPOSE
165 !! -------
166 !
167 ! Calculates vegetation roughness from leaf
168 ! area index and type of vegetation
169 ! (most of types; forest and vineyards; grassland)
170 !
171 !!** METHOD
172 !! ------
173 !!
174 !! EXTERNAL
175 !! --------
176 !! none
177 !!
178 !! IMPLICIT ARGUMENTS
179 !! ------------------
180 !!
181 !! none
182 !!
183 !! REFERENCE
184 !! ---------
185 !!
186 !!
187 !! AUTHOR
188 !! ------
189 !!
190 !! V. Masson and A. Boone * Meteo-France *
191 !!
192 !! MODIFICATIONS
193 !! -------------
194 !! Original 25/03/99
195 !!
196 !-------------------------------------------------------------------------------
197 !
198 !* 0. DECLARATIONS
199 ! ------------
200 !
201 USE modd_surf_par, ONLY : xundef
202 USE modd_data_cover_par, ONLY : nvt_no, nvt_rock, nvt_snow, nvt_tebd, &
203  nvt_bone, nvt_trbe, nvt_c3, nvt_c4, &
204  nvt_irr, nvt_gras, nvt_trog,nvt_park, &
205  nvt_trbd, nvt_tebe, nvt_tene, nvt_bobd, &
206  nvt_bond, nvt_bogr, nvt_shrb
208 !
209 USE yomhook ,ONLY : lhook, dr_hook
210 USE parkind1 ,ONLY : jprb
211 !
212 IMPLICIT NONE
213 !
214 !* 0.1 declarations of arguments
215 !
216 REAL, DIMENSION(:), INTENT(IN) :: plai ! Leaf area Index
217 REAL, DIMENSION(:), INTENT(IN) :: ph_tree ! height of trees
218 REAL, DIMENSION(:,:), INTENT(IN) :: pvegtype ! type of vegetation
219 LOGICAL, INTENT(IN) :: oagri_to_grass
220 !
221 REAL, DIMENSION(SIZE(PLAI)) :: pz0 ! vegetation roughness
222 !
223 !* 0.2 declarations of local variables
224 !
225 REAL, DIMENSION(SIZE(PLAI)) :: zallen_h ! Allen formula for height
226 REAL, DIMENSION(SIZE(PLAI)) :: zlai ! LAI for vegetated areas
227 !
228 REAL, DIMENSION(SIZE(PLAI),SIZE(PVEGTYPE,2)) :: zh_veg ! height for each type
229 REAL, DIMENSION(SIZE(PLAI)) :: zavg_h ! averaged height
230 REAL :: zzref ! reference height
231 !
232 INTEGER :: jtype ! loop counter
233 REAL(KIND=JPRB) :: zhook_handle
234 !-----------------------------------------------------------------
235 !
236 IF (lhook) CALL dr_hook('MODI_Z0V_FROM_LAI:Z0V_FROM_LAI_1D',0,zhook_handle)
237 zh_veg(:,:) = veg_height_from_lai(plai,ph_tree,pvegtype,oagri_to_grass)
238 !
239 zzref = 10.
240 zavg_h(:) = 0.
241 DO jtype=1,SIZE(pvegtype,2)
242  zavg_h(:) = zavg_h(:) + pvegtype(:,jtype) / (log(0.13*zh_veg(:,jtype)/zzref))**2
243 END DO
244 
245 zavg_h = max(zavg_h,0.00001)
246 
247 zavg_h(:) = zzref / 0.13 * exp(-1./sqrt(zavg_h(:)))
248 !
249 pz0(:) = max(0.001, 0.13*zavg_h(:))
250 IF (lhook) CALL dr_hook('MODI_Z0V_FROM_LAI:Z0V_FROM_LAI_1D',1,zhook_handle)
251 !-----------------------------------------------------------------
252 !
253 END FUNCTION z0v_from_lai_1d
254 !
255 ! ###########################################################
256  FUNCTION z0v_from_lai_2d(PLAI,PH_TREE,PVEGTYPE,OAGRI_TO_GRASS) RESULT(PZ0)
257 ! ###########################################################
258 !!
259 !! PURPOSE
260 !! -------
261 !
262 ! Calculates vegetation roughness from leaf
263 ! area index and type of vegetation
264 ! (most of types; forest and vineyards; grassland)
265 !
266 !!** METHOD
267 !! ------
268 !!
269 !! EXTERNAL
270 !! --------
271 !! none
272 !!
273 !! IMPLICIT ARGUMENTS
274 !! ------------------
275 !!
276 !! none
277 !!
278 !! REFERENCE
279 !! ---------
280 !!
281 !!
282 !! AUTHOR
283 !! ------
284 !!
285 !! V. Masson and A. Boone * Meteo-France *
286 !!
287 !! MODIFICATIONS
288 !! -------------
289 !! Original 25/03/99
290 !!
291 !-------------------------------------------------------------------------------
292 !
293 !* 0. DECLARATIONS
294 ! ------------
295 !
296 USE modd_data_cover_par, ONLY : nvt_no, nvt_rock, nvt_snow, nvt_tebd, &
297  nvt_bone, nvt_trbe, nvt_c3, nvt_c4, &
298  nvt_irr, nvt_gras, nvt_trog,nvt_park, &
299  nvt_trbd, nvt_tebe, nvt_tene, nvt_bobd, &
300  nvt_bond, nvt_bogr, nvt_shrb
301 USE modd_surf_par, ONLY : xundef
303 !
304 USE yomhook ,ONLY : lhook, dr_hook
305 USE parkind1 ,ONLY : jprb
306 !
307 IMPLICIT NONE
308 !
309 !* 0.1 declarations of arguments
310 !
311 REAL, DIMENSION(:,:), INTENT(IN) :: plai ! Leaf area Index
312 REAL, DIMENSION(:,:), INTENT(IN) :: ph_tree ! height of trees
313 REAL, DIMENSION(:,:,:), INTENT(IN) :: pvegtype ! type of vegetation
314 LOGICAL, INTENT(IN) :: oagri_to_grass
315 !
316 REAL, DIMENSION(SIZE(PLAI,1),SIZE(PLAI,2)) :: pz0 ! vegetation roughness
317 !
318 !* 0.2 declarations of local variables
319 !
320 
321 REAL, DIMENSION(SIZE(PLAI,1),SIZE(PLAI,2)) :: zallen_h ! Allen formula for height
322 REAL, DIMENSION(SIZE(PLAI,1),SIZE(PLAI,2)) :: zlai ! LAI for vegetated areas
323 !
324 REAL, DIMENSION(SIZE(PLAI,1),SIZE(PLAI,2),SIZE(PVEGTYPE,3)) :: zh_veg ! height for each type
325 REAL, DIMENSION(SIZE(PLAI,1),SIZE(PLAI,2)) :: zavg_h ! averaged height
326 REAL :: zzref ! reference height
327 !
328 INTEGER :: jtype ! loop counter
329 REAL(KIND=JPRB) :: zhook_handle
330 !-----------------------------------------------------------------
331 !
332 IF (lhook) CALL dr_hook('MODI_Z0V_FROM_LAI:Z0V_FROM_LAI_2D',0,zhook_handle)
333 zh_veg(:,:,:) = veg_height_from_lai(plai,ph_tree,pvegtype,oagri_to_grass)
334 !
335 zzref = 10.
336 zavg_h(:,:) = 0.
337 DO jtype=1,SIZE(pvegtype,3)
338  zavg_h(:,:) = zavg_h(:,:) + pvegtype(:,:,jtype) / (log(0.13*zh_veg(:,:,jtype)/zzref))**2
339 END DO
340 zavg_h(:,:) = max(zavg_h(:,:),0.00001)
341 zavg_h(:,:) = zzref / 0.13 * exp(-1./sqrt(zavg_h(:,:)))
342 !
343 pz0(:,:) = max(0.001, 0.13*zavg_h(:,:))
344 !
345 WHERE (plai(:,:) == xundef)
346  pz0(:,:) = xundef
347 END WHERE
348 IF (lhook) CALL dr_hook('MODI_Z0V_FROM_LAI:Z0V_FROM_LAI_2D',1,zhook_handle)
349 !-----------------------------------------------------------------
350 !
351 END FUNCTION z0v_from_lai_2d
352 !
353 !
354 !
355 ! ###########################################################
356  FUNCTION z0v_from_lai_patch(PLAI,PH_TREE,PVEGTYPE,OAGRI_TO_GRASS) RESULT(PZ0)
357 ! ###########################################################
358 !!
359 !! PURPOSE
360 !! -------
361 !
362 ! Calculates vegetation roughness from leaf
363 ! area index and type of vegetation for each patch
364 ! (most of types; forest and vineyards; grassland)
365 !
366 !!** METHOD
367 !! ------
368 !!
369 !! EXTERNAL
370 !! --------
371 !! none
372 !!
373 !! IMPLICIT ARGUMENTS
374 !! ------------------
375 !!
376 !! none
377 !!
378 !! REFERENCE
379 !! ---------
380 !!
381 !!
382 !! AUTHOR
383 !! ------
384 !! F.Solmon
385 !! V. Masson and A. Boone * Meteo-France *
386 !!
387 !! MODIFICATIONS
388 !! -------------
389 !! Original 25/03/99
390 !!
391 !-------------------------------------------------------------------------------
392 !
393 !* 0. DECLARATIONS
394 ! ------------
395 !
396 USE modd_data_cover_par, ONLY : nvt_no, nvt_rock, nvt_snow, nvt_tebd, &
397  nvt_bone, nvt_trbe, nvt_c3, nvt_c4, &
398  nvt_irr, nvt_gras, nvt_trog,nvt_park, &
399  nvt_trbd, nvt_tebe, nvt_tene, nvt_bobd, &
400  nvt_bond, nvt_bogr, nvt_shrb
401 USE modd_surf_par, ONLY : xundef
403 !
404 USE yomhook ,ONLY : lhook, dr_hook
405 USE parkind1 ,ONLY : jprb
406 !
407 IMPLICIT NONE
408 !
409 !* 0.1 declarations of arguments
410 !
411 REAL, DIMENSION(:), INTENT(IN) :: plai ! Leaf area Index
412 REAL, DIMENSION(:), INTENT(IN) :: ph_tree ! height of trees
413 REAL, DIMENSION(:), INTENT(IN) :: pvegtype ! type of vegetation
414 LOGICAL, INTENT(IN) :: oagri_to_grass
415 !
416 REAL, DIMENSION(SIZE(PLAI)) :: pz0 ! vegetation roughness
417 !
418 !* 0.2 declarations of local variables
419 !
420 REAL, DIMENSION(SIZE(PLAI)) :: zallen_h ! Allen formula for height
421 !
422 REAL, DIMENSION(SIZE(PLAI)) :: zh_veg ! height for each type
423 REAL(KIND=JPRB) :: zhook_handle
424 !-----------------------------------------------------------------
425 !
426 IF (lhook) CALL dr_hook('MODI_Z0V_FROM_LAI:Z0V_FROM_LAI_PATCH',0,zhook_handle)
427 zh_veg(:) = veg_height_from_lai(plai,ph_tree,pvegtype,oagri_to_grass)
428 !
429 pz0(:) = max(0.001, 0.13*zh_veg(:)) ! rugosite pour chaque vegtype
430 !-----------------------------------------------------------------
431 !
432 WHERE (plai(:) == xundef)
433  pz0(:) = xundef
434 END WHERE
435 IF (lhook) CALL dr_hook('MODI_Z0V_FROM_LAI:Z0V_FROM_LAI_PATCH',1,zhook_handle)
436 !
437 !
438 END FUNCTION z0v_from_lai_patch
439 !
real function, dimension(size(plai, 1), size(plai, 2)) z0v_from_lai_2d(PLAI, PH_TREE, PVEGTYPE, OAGRI_TO_GRASS)
real function, dimension(size(plai)) z0v_from_lai_patch(PLAI, PH_TREE, PVEGTYPE, OAGRI_TO_GRASS)
real function z0v_from_lai_0d(PLAI, PH_TREE, PVEGTYPE, OAGRI_TO_GRASS)
real function, dimension(size(plai)) z0v_from_lai_1d(PLAI, PH_TREE, PVEGTYPE, OAGRI_TO_GRASS)