SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
veg_height_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 !
10 !
11  FUNCTION veg_height_from_lai_0d(PLAI,PH_TREE,PVEGTYPE,OAGRI_TO_GRASS) RESULT(PH_VEG)
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, DIMENSION(SIZE(PVEGTYPE)) :: ph_veg ! vegetation height
19 !
20 END FUNCTION veg_height_from_lai_0d
21 !
22 !
23  FUNCTION veg_height_from_lai_1d(PLAI,PH_TREE,PVEGTYPE,OAGRI_TO_GRASS) RESULT(PH_VEG)
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(PVEGTYPE,1),SIZE(PVEGTYPE,2)) :: ph_veg ! vegetation height
31 !
32 END FUNCTION veg_height_from_lai_1d
33 !
34 !
35  FUNCTION veg_height_from_lai_2d(PLAI,PH_TREE,PVEGTYPE,OAGRI_TO_GRASS) RESULT(PH_VEG)
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(PVEGTYPE,1),SIZE(PVEGTYPE,2),SIZE(PVEGTYPE,3)) :: ph_veg ! vegetation height
43 !
44 END FUNCTION veg_height_from_lai_2d
45 !
46  FUNCTION veg_height_from_lai_patch(PLAI,PH_TREE,PVEGTYPE,OAGRI_TO_GRASS) RESULT(PH_VEG)
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(PVEGTYPE)) :: ph_veg ! vegetation height
54 !
55 END FUNCTION veg_height_from_lai_patch
56 !
57 END INTERFACE
58 !
59 END MODULE modi_veg_height_from_lai
60 !
61 
62 ! ###########################################################
63  FUNCTION veg_height_from_lai_0d(PLAI,PH_TREE,PVEGTYPE,OAGRI_TO_GRASS) RESULT(PH_VEG)
64 ! ###########################################################
65 !!
66 !! PURPOSE
67 !! -------
68 !
69 ! Calculates vegetation height 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. Samuelsson 02/2012 MEB
98 !!
99 !-------------------------------------------------------------------------------
100 !
101 !* 0. DECLARATIONS
102 ! ------------
103 !
104 USE modd_surf_par, ONLY : xundef
105 USE modd_data_cover_par, ONLY : nvt_no, nvt_rock, nvt_snow, nvt_park, &
106  nvt_tebd, nvt_bone, nvt_trbe, nvt_trbd, &
107  nvt_tebe, nvt_tene, nvt_bobd, nvt_bond, &
108  nvt_shrb, nvt_c3, nvt_c4, nvt_irr, &
109  nvt_gras, nvt_bogr, nvt_trog
110 USE modd_treedrag, ONLY : ltreedrag
111 !
112 USE yomhook ,ONLY : lhook, dr_hook
113 USE parkind1 ,ONLY : jprb
114 !
115 IMPLICIT NONE
116 !
117 !* 0.1 declarations of arguments
118 !
119 REAL, INTENT(IN) :: plai ! Leaf area Index
120 REAL, INTENT(IN) :: ph_tree ! height of trees
121 REAL, DIMENSION(:), INTENT(IN) :: pvegtype ! type of vegetation
122 LOGICAL, INTENT(IN) :: oagri_to_grass
123 !
124 REAL, DIMENSION(SIZE(PVEGTYPE)) :: ph_veg ! vegetation height
125 !
126 !* 0.2 declarations of local variables
127 !
128 REAL :: zallen_h ! Allen formula for height
129 REAL :: zlai ! LAI for vegetated areas
130 !
131 REAL :: zavg_h ! averaged height
132 REAL :: zzref ! reference height
133 !
134 INTEGER :: jtype ! loop counter
135 REAL(KIND=JPRB) :: zhook_handle
136 !-----------------------------------------------------------------
137 !
138 IF (lhook) CALL dr_hook('MODI_VEG_HEIGHT_FROM_LAI:VEG_HEIGHT_FROM_LAI_0D',0,zhook_handle)
139 !
140 !-----------------------------------------------------------------
141 !
142 zlai = plai
143 IF ( pvegtype(nvt_no ) + pvegtype(nvt_rock) + pvegtype(nvt_snow) < 1.) THEN
144  zlai = plai / (1.-pvegtype(nvt_no)-pvegtype(nvt_rock)-pvegtype(nvt_snow))
145 END IF
146 !
147 zallen_h = 0.
148 IF ( plai /= xundef) THEN
149  zallen_h = exp((zlai-3.5)/(1.3))
150 END IF
151 !
152 ph_veg(nvt_park) = zlai / 6. ! irr. grassland
153 IF (ltreedrag) THEN
154  ph_veg(nvt_tebd) = zlai / 6. ! forest
155  ph_veg(nvt_bone) = zlai / 6. ! forest
156  ph_veg(nvt_trbe) = zlai / 6. ! forest
157  ph_veg(nvt_trbd) = zlai / 6. ! forest
158  ph_veg(nvt_tebe) = zlai / 6. ! forest
159  ph_veg(nvt_tene) = zlai / 6. ! forest
160  ph_veg(nvt_bobd) = zlai / 6. ! forest
161  ph_veg(nvt_bond) = zlai / 6. ! forest
162  ph_veg(nvt_shrb) = zlai / 6. ! forest
163 ELSE
164  ph_veg(nvt_tebd) = ph_tree ! forest
165  ph_veg(nvt_bone) = ph_tree ! forest
166  ph_veg(nvt_trbe) = ph_tree ! forest
167  ph_veg(nvt_trbd) = ph_tree ! forest
168  ph_veg(nvt_tebe) = ph_tree ! forest
169  ph_veg(nvt_tene) = ph_tree ! forest
170  ph_veg(nvt_bobd) = ph_tree ! forest
171  ph_veg(nvt_bond) = ph_tree ! forest
172  ph_veg(nvt_shrb) = ph_tree ! forest
173 END IF
174 ph_veg(nvt_gras) = zlai / 6. ! grassland
175 ph_veg(nvt_bogr) = zlai / 6. ! boreal grassland
176 ph_veg(nvt_trog) = zlai / 6. ! tropical grassland
177 IF(oagri_to_grass)THEN
178  ph_veg(nvt_c3 ) = zlai / 6.
179  ph_veg(nvt_c4 ) = zlai / 6.
180  ph_veg(nvt_irr ) = zlai / 6.
181 ELSE
182  ph_veg(nvt_c3 ) = min(1. , zallen_h ) ! cultures
183  ph_veg(nvt_c4 ) = min(2.5, zallen_h ) ! C4 types
184  ph_veg(nvt_irr ) = min(2.5, zallen_h ) ! irrigated crops (as C4)
185 ENDIF
186 ph_veg(nvt_no ) = 0.1 ! no vegetation (smooth)
187 ph_veg(nvt_rock) = 1. ! no vegetation (rocks)
188 ph_veg(nvt_snow) = 0.01 ! no vegetation (snow)
189 !
190 ph_veg(:) = max(ph_veg(:),0.001)
191 !
192 IF (lhook) CALL dr_hook('MODI_VEG_HEIGHT_FROM_LAI:VEG_HEIGHT_FROM_LAI_0D',1,zhook_handle)
193 !-----------------------------------------------------------------
194 !
195 END FUNCTION veg_height_from_lai_0d
196 !
197 ! ###########################################################
198  FUNCTION veg_height_from_lai_1d(PLAI,PH_TREE,PVEGTYPE,OAGRI_TO_GRASS) RESULT(PH_VEG)
199 ! ###########################################################
200 !!
201 !! PURPOSE
202 !! -------
203 !
204 ! Calculates vegetation height from leaf
205 ! area index and type of vegetation
206 ! (most of types; forest and vineyards; grassland)
207 !
208 !!** METHOD
209 !! ------
210 !!
211 !! EXTERNAL
212 !! --------
213 !! none
214 !!
215 !! IMPLICIT ARGUMENTS
216 !! ------------------
217 !!
218 !! none
219 !!
220 !! REFERENCE
221 !! ---------
222 !!
223 !!
224 !! AUTHOR
225 !! ------
226 !!
227 !! V. Masson and A. Boone * Meteo-France *
228 !!
229 !! MODIFICATIONS
230 !! -------------
231 !! Original 25/03/99
232 !!
233 !-------------------------------------------------------------------------------
234 !
235 !* 0. DECLARATIONS
236 ! ------------
237 !
238 USE modd_surf_par, ONLY : xundef
239 USE modd_data_cover_par, ONLY : nvt_no, nvt_rock, nvt_snow, nvt_park, &
240  nvt_tebd, nvt_bone, nvt_trbe, nvt_trbd, &
241  nvt_tebe, nvt_tene, nvt_bobd, nvt_bond, &
242  nvt_shrb, nvt_c3, nvt_c4, nvt_irr, &
243  nvt_gras, nvt_bogr, nvt_trog
244 USE modd_treedrag, ONLY : ltreedrag
245 !
246 USE yomhook ,ONLY : lhook, dr_hook
247 USE parkind1 ,ONLY : jprb
248 !
249 IMPLICIT NONE
250 !
251 !* 0.1 declarations of arguments
252 !
253 REAL, DIMENSION(:), INTENT(IN) :: plai ! Leaf area Index
254 REAL, DIMENSION(:), INTENT(IN) :: ph_tree ! height of trees
255 REAL, DIMENSION(:,:), INTENT(IN) :: pvegtype ! type of vegetation
256 LOGICAL, INTENT(IN) :: oagri_to_grass
257 !
258 REAL, DIMENSION(SIZE(PVEGTYPE,1),SIZE(PVEGTYPE,2)) :: ph_veg ! vegetation height
259 !
260 !* 0.2 declarations of local variables
261 !
262 REAL, DIMENSION(SIZE(PLAI)) :: zallen_h ! Allen formula for height
263 REAL, DIMENSION(SIZE(PLAI)) :: zlai ! LAI for vegetated areas
264 !
265 REAL, DIMENSION(SIZE(PLAI)) :: zavg_h ! averaged height
266 REAL :: zzref ! reference height
267 !
268 INTEGER :: jtype ! loop counter
269 REAL(KIND=JPRB) :: zhook_handle
270 !-----------------------------------------------------------------
271 !
272 IF (lhook) CALL dr_hook('MODI_VEG_HEIGHT_FROM_LAI:VEG_HEIGHT_FROM_LAI_1D',0,zhook_handle)
273 !
274 !-----------------------------------------------------------------
275 !
276 ph_veg(:,:) = xundef
277 !
278 zlai(:) = plai(:)
279 WHERE ( pvegtype(:,nvt_no ) + pvegtype(:,nvt_rock) + pvegtype(:,nvt_snow) < 1.)
280  zlai(:) = plai(:) / (1.-pvegtype(:,nvt_no)-pvegtype(:,nvt_rock)-pvegtype(:,nvt_snow))
281 END WHERE
282 !
283 zallen_h(:) = 0.
284 WHERE (plai(:) /= xundef)
285  zallen_h(:) = exp((zlai(:)-3.5)/(1.3))
286 END WHERE
287 !
288 !
289 ph_veg(:,nvt_park) = zlai(:) / 6. ! irr. grassland
290 IF (ltreedrag) THEN
291  ph_veg(:,nvt_tebd) = zlai(:) / 6. ! forest
292  ph_veg(:,nvt_bone) = zlai(:) / 6. ! forest
293  ph_veg(:,nvt_trbe) = zlai(:) / 6. ! forest
294  ph_veg(:,nvt_trbd) = zlai(:) / 6. ! forest
295  ph_veg(:,nvt_tebe) = zlai(:) / 6. ! forest
296  ph_veg(:,nvt_tene) = zlai(:) / 6. ! forest
297  ph_veg(:,nvt_bobd) = zlai(:) / 6. ! forest
298  ph_veg(:,nvt_bond) = zlai(:) / 6. ! forest
299  ph_veg(:,nvt_shrb) = zlai(:) / 6. ! forest
300 ELSE
301  ph_veg(:,nvt_tebd) = ph_tree(:) ! forest
302  ph_veg(:,nvt_bone) = ph_tree(:) ! forest
303  ph_veg(:,nvt_trbe) = ph_tree(:) ! forest
304  ph_veg(:,nvt_trbd) = ph_tree(:) ! forest
305  ph_veg(:,nvt_tebe) = ph_tree(:) ! forest
306  ph_veg(:,nvt_tene) = ph_tree(:) ! forest
307  ph_veg(:,nvt_bobd) = ph_tree(:) ! forest
308  ph_veg(:,nvt_bond) = ph_tree(:) ! forest
309  ph_veg(:,nvt_shrb) = ph_tree(:) ! forest
310 END IF
311 ph_veg(:,nvt_gras) = zlai(:) / 6. ! grassland
312 ph_veg(:,nvt_bogr) = zlai(:) / 6. ! boreal grassland
313 ph_veg(:,nvt_trog) = zlai(:) / 6. ! tropical grassland
314 IF(oagri_to_grass)THEN
315  ph_veg(:,nvt_c3 ) = zlai(:) / 6.
316  ph_veg(:,nvt_c4 ) = zlai(:) / 6.
317  ph_veg(:,nvt_irr ) = zlai(:) / 6.
318 ELSE
319  ph_veg(:,nvt_c3 ) = min(1. , zallen_h(:) ) ! cultures
320  ph_veg(:,nvt_c4 ) = min(2.5, zallen_h(:) ) ! C4 types
321  ph_veg(:,nvt_irr ) = min(2.5, zallen_h(:) ) ! irrigated crops (as C4)
322 ENDIF
323 ph_veg(:,nvt_no ) = 0.1 ! no vegetation (smooth)
324 ph_veg(:,nvt_rock) = 1. ! no vegetation (rocks)
325 ph_veg(:,nvt_snow) = 0.01 ! no vegetation (snow)
326 !
327 ph_veg(:,:) = max(ph_veg(:,:),0.001)
328 !
329 IF (lhook) CALL dr_hook('MODI_VEG_HEIGHT_FROM_LAI:VEG_HEIGHT_FROM_LAI_1D',1,zhook_handle)
330 !-----------------------------------------------------------------
331 !
332 END FUNCTION veg_height_from_lai_1d
333 !
334 ! ###########################################################
335  FUNCTION veg_height_from_lai_2d(PLAI,PH_TREE,PVEGTYPE,OAGRI_TO_GRASS) RESULT(PH_VEG)
336 ! ###########################################################
337 !!
338 !! PURPOSE
339 !! -------
340 !
341 ! Calculates vegetation height from leaf
342 ! area index and type of vegetation
343 ! (most of types; forest and vineyards; grassland)
344 !
345 !!** METHOD
346 !! ------
347 !!
348 !! EXTERNAL
349 !! --------
350 !! none
351 !!
352 !! IMPLICIT ARGUMENTS
353 !! ------------------
354 !!
355 !! none
356 !!
357 !! REFERENCE
358 !! ---------
359 !!
360 !!
361 !! AUTHOR
362 !! ------
363 !!
364 !! V. Masson and A. Boone * Meteo-France *
365 !!
366 !! MODIFICATIONS
367 !! -------------
368 !! Original 25/03/99
369 !!
370 !-------------------------------------------------------------------------------
371 !
372 !* 0. DECLARATIONS
373 ! ------------
374 !
375 USE modd_data_cover_par, ONLY : nvt_no, nvt_rock, nvt_snow, nvt_park, &
376  nvt_tebd, nvt_bone, nvt_trbe, nvt_trbd, &
377  nvt_tebe, nvt_tene, nvt_bobd, nvt_bond, &
378  nvt_shrb, nvt_c3, nvt_c4, nvt_irr, &
379  nvt_gras, nvt_bogr, nvt_trog
380 USE modd_surf_par, ONLY : xundef
381 USE modd_treedrag, ONLY : ltreedrag
382 !
383 USE yomhook ,ONLY : lhook, dr_hook
384 USE parkind1 ,ONLY : jprb
385 !
386 IMPLICIT NONE
387 !
388 !* 0.1 declarations of arguments
389 !
390 REAL, DIMENSION(:,:), INTENT(IN) :: plai ! Leaf area Index
391 REAL, DIMENSION(:,:), INTENT(IN) :: ph_tree ! height of trees
392 REAL, DIMENSION(:,:,:), INTENT(IN) :: pvegtype ! type of vegetation
393 LOGICAL, INTENT(IN) :: oagri_to_grass
394 !
395 REAL, DIMENSION(SIZE(PVEGTYPE,1),SIZE(PVEGTYPE,2),SIZE(PVEGTYPE,3)) :: ph_veg ! vegetation height
396 !
397 !* 0.2 declarations of local variables
398 !
399 
400 REAL, DIMENSION(SIZE(PLAI,1),SIZE(PLAI,2)) :: zallen_h ! Allen formula for height
401 REAL, DIMENSION(SIZE(PLAI,1),SIZE(PLAI,2)) :: zlai ! LAI for vegetated areas
402 !
403 REAL, DIMENSION(SIZE(PLAI,1),SIZE(PLAI,2)) :: zavg_h ! averaged height
404 REAL :: zzref ! reference height
405 !
406 INTEGER :: jtype ! loop counter
407 REAL(KIND=JPRB) :: zhook_handle
408 !-----------------------------------------------------------------
409 !
410 IF (lhook) CALL dr_hook('MODI_VEG_HEIGHT_FROM_LAI:VEG_HEIGHT_FROM_LAI_2D',0,zhook_handle)
411 !
412 !-----------------------------------------------------------------
413 !
414 ph_veg(:,:,:)=xundef
415 !
416 zlai(:,:) = plai(:,:)
417 WHERE ( pvegtype(:,:,nvt_no ) + pvegtype(:,:,nvt_rock) + pvegtype(:,:,nvt_snow) < 1.)
418  zlai(:,:) = plai(:,:) / (1.-pvegtype(:,:,nvt_no)-pvegtype(:,:,nvt_rock)-pvegtype(:,:,nvt_snow))
419 END WHERE
420 !
421 zallen_h(:,:) = 0.
422 WHERE(plai(:,:)/=xundef)
423  zallen_h(:,:) = exp((zlai(:,:)-3.5)/(1.3))
424 END WHERE
425 !
426 !
427 ph_veg(:,:,nvt_park) = zlai(:,:) / 6. ! irr. grassland
428 IF (ltreedrag) THEN
429  ph_veg(:,:,nvt_tebd) = zlai(:,:) / 6. ! forest
430  ph_veg(:,:,nvt_bone) = zlai(:,:) / 6. ! forest
431  ph_veg(:,:,nvt_trbe) = zlai(:,:) / 6. ! forest
432  ph_veg(:,:,nvt_trbd) = zlai(:,:) / 6. ! forest
433  ph_veg(:,:,nvt_tebe) = zlai(:,:) / 6. ! forest
434  ph_veg(:,:,nvt_tene) = zlai(:,:) / 6. ! forest
435  ph_veg(:,:,nvt_bobd) = zlai(:,:) / 6. ! forest
436  ph_veg(:,:,nvt_bond) = zlai(:,:) / 6. ! forest
437  ph_veg(:,:,nvt_shrb) = zlai(:,:) / 6. ! forest
438 ELSE
439  ph_veg(:,:,nvt_tebd) = ph_tree(:,:) ! forest
440  ph_veg(:,:,nvt_bone) = ph_tree(:,:) ! forest
441  ph_veg(:,:,nvt_trbe) = ph_tree(:,:) ! forest
442  ph_veg(:,:,nvt_trbd) = ph_tree(:,:) ! forest
443  ph_veg(:,:,nvt_tebe) = ph_tree(:,:) ! forest
444  ph_veg(:,:,nvt_tene) = ph_tree(:,:) ! forest
445  ph_veg(:,:,nvt_bobd) = ph_tree(:,:) ! forest
446  ph_veg(:,:,nvt_bond) = ph_tree(:,:) ! forest
447  ph_veg(:,:,nvt_shrb) = ph_tree(:,:) ! forest
448 END IF
449 ph_veg(:,:,nvt_gras) = zlai(:,:) / 6. ! grassland
450 ph_veg(:,:,nvt_bogr) = zlai(:,:) / 6. ! boreal grassland
451 ph_veg(:,:,nvt_trog) = zlai(:,:) / 6. ! tropical grassland
452 IF(oagri_to_grass)THEN
453  ph_veg(:,:,nvt_c3 ) = zlai(:,:) / 6.
454  ph_veg(:,:,nvt_c4 ) = zlai(:,:) / 6.
455  ph_veg(:,:,nvt_irr ) = zlai(:,:) / 6.
456 ELSE
457  ph_veg(:,:,nvt_c3 ) = min(1. , zallen_h(:,:) ) ! cultures
458  ph_veg(:,:,nvt_c4 ) = min(2.5, zallen_h(:,:) ) ! C4 types
459  ph_veg(:,:,nvt_irr ) = min(2.5, zallen_h(:,:) ) ! irrigated crops (as C4)
460 ENDIF
461 ph_veg(:,:,nvt_no ) = 0.1 ! no vegetation (smooth)
462 ph_veg(:,:,nvt_rock) = 1. ! no vegetation (rocks)
463 ph_veg(:,:,nvt_snow) = 0.01 ! no vegetation (snow)
464 !
465 ph_veg(:,:,:) = max(ph_veg(:,:,:),0.001)
466 !
467 IF (lhook) CALL dr_hook('MODI_VEG_HEIGHT_FROM_LAI:VEG_HEIGHT_FROM_LAI_2D',1,zhook_handle)
468 !-----------------------------------------------------------------
469 !
470 END FUNCTION veg_height_from_lai_2d
471 !
472 !
473 !
474 ! ###########################################################
475  FUNCTION veg_height_from_lai_patch(PLAI,PH_TREE,PVEGTYPE,OAGRI_TO_GRASS) RESULT(PH_VEG)
476 ! ###########################################################
477 !!
478 !! PURPOSE
479 !! -------
480 !
481 ! Calculates vegetation height from leaf
482 ! area index and type of vegetation for each patch
483 ! (most of types; forest and vineyards; grassland)
484 !
485 !!** METHOD
486 !! ------
487 !!
488 !! EXTERNAL
489 !! --------
490 !! none
491 !!
492 !! IMPLICIT ARGUMENTS
493 !! ------------------
494 !!
495 !! none
496 !!
497 !! REFERENCE
498 !! ---------
499 !!
500 !!
501 !! AUTHOR
502 !! ------
503 !! F.Solmon
504 !! V. Masson and A. Boone * Meteo-France *
505 !!
506 !! MODIFICATIONS
507 !! -------------
508 !! Original 25/03/99
509 !!
510 !-------------------------------------------------------------------------------
511 !
512 !* 0. DECLARATIONS
513 ! ------------
514 !
515 USE modd_data_cover_par, ONLY : nvt_no, nvt_rock, nvt_snow, nvt_park, &
516  nvt_tebd, nvt_bone, nvt_trbe, nvt_trbd, &
517  nvt_tebe, nvt_tene, nvt_bobd, nvt_bond, &
518  nvt_shrb, nvt_c3, nvt_c4, nvt_irr, &
519  nvt_gras, nvt_bogr, nvt_trog
520 USE modd_surf_par, ONLY : xundef
521 USE modd_treedrag, ONLY : ltreedrag
522 !
523 USE yomhook ,ONLY : lhook, dr_hook
524 USE parkind1 ,ONLY : jprb
525 !
526 IMPLICIT NONE
527 !
528 !* 0.1 declarations of arguments
529 !
530 REAL, DIMENSION(:), INTENT(IN) :: plai ! Leaf area Index
531 REAL, DIMENSION(:), INTENT(IN) :: ph_tree ! height of trees
532 REAL, DIMENSION(:), INTENT(IN) :: pvegtype ! type of vegetation
533 LOGICAL, INTENT(IN) :: oagri_to_grass
534 !
535 REAL, DIMENSION(SIZE(PVEGTYPE)) :: ph_veg ! vegetation height
536 !
537 !* 0.2 declarations of local variables
538 !
539 REAL, DIMENSION(SIZE(PLAI)) :: zallen_h ! Allen formula for height
540 REAL(KIND=JPRB) :: zhook_handle
541 !-----------------------------------------------------------------
542 !
543 IF (lhook) CALL dr_hook('MODI_VEG_HEIGHT_FROM_LAI:VEG_HEIGHT_FROM_LAI_PATCH',0,zhook_handle)
544 !
545 !
546 !-----------------------------------------------------------------
547 !
548 ph_veg(:) = xundef
549 !
550 WHERE (plai(:)/= xundef)
551  zallen_h(:) = exp((plai(:)-3.5)/(1.3))
552 END WHERE
553 !
554 !
555 IF (pvegtype(nvt_park)>0.) ph_veg(nvt_park) = plai(nvt_park) / 6. ! irr. grasslands
556 IF (ltreedrag) THEN
557  IF (pvegtype(nvt_tebd)>0.) ph_veg(nvt_tebd) = plai(nvt_tebd) / 6. ! broadleaf forest
558  IF (pvegtype(nvt_bone)>0.) ph_veg(nvt_bone) = plai(nvt_bone) / 6. ! coniferous forest
559  IF (pvegtype(nvt_trbe)>0.) ph_veg(nvt_trbe) = plai(nvt_trbe) / 6. ! euqatorial forest
560  IF (pvegtype(nvt_trbd)>0.) ph_veg(nvt_trbd) = plai(nvt_trbd) / 6. ! broadleaf forest
561  IF (pvegtype(nvt_tebe)>0.) ph_veg(nvt_tebe) = plai(nvt_tebe) / 6. ! coniferous forest
562  IF (pvegtype(nvt_tene)>0.) ph_veg(nvt_tene) = plai(nvt_tene) / 6. ! euqatorial forest
563  IF (pvegtype(nvt_bobd)>0.) ph_veg(nvt_bobd) = plai(nvt_bobd) / 6. ! broadleaf forest
564  IF (pvegtype(nvt_bond)>0.) ph_veg(nvt_bond) = plai(nvt_bond) / 6. ! coniferous forest
565  IF (pvegtype(nvt_shrb)>0.) ph_veg(nvt_shrb) = plai(nvt_shrb) / 6. ! euqatorial forest
566 ELSE
567  IF (pvegtype(nvt_tebd)>0.) ph_veg(nvt_tebd) = ph_tree(nvt_tebd) ! broadleaf forest
568  IF (pvegtype(nvt_bone)>0.) ph_veg(nvt_bone) = ph_tree(nvt_bone) ! coniferous forest
569  IF (pvegtype(nvt_trbe)>0.) ph_veg(nvt_trbe) = ph_tree(nvt_trbe) ! euqatorial forest
570  IF (pvegtype(nvt_trbd)>0.) ph_veg(nvt_trbd) = ph_tree(nvt_trbd) ! broadleaf forest
571  IF (pvegtype(nvt_tebe)>0.) ph_veg(nvt_tebe) = ph_tree(nvt_tebe) ! coniferous forest
572  IF (pvegtype(nvt_tene)>0.) ph_veg(nvt_tene) = ph_tree(nvt_tene) ! euqatorial forest
573  IF (pvegtype(nvt_bobd)>0.) ph_veg(nvt_bobd) = ph_tree(nvt_bobd) ! broadleaf forest
574  IF (pvegtype(nvt_bond)>0.) ph_veg(nvt_bond) = ph_tree(nvt_bond) ! coniferous forest
575  IF (pvegtype(nvt_shrb)>0.) ph_veg(nvt_shrb) = ph_tree(nvt_shrb) ! euqatorial forest
576 END IF
577 IF (pvegtype(nvt_gras)>0.) ph_veg(nvt_gras) = plai(nvt_gras) / 6. ! grassland
578 IF (pvegtype(nvt_bogr)>0.) ph_veg(nvt_bogr) = plai(nvt_bogr) / 6. ! boreal grassland
579 IF (pvegtype(nvt_trog)>0.) ph_veg(nvt_trog) = plai(nvt_trog) / 6. ! tropical grassland
580 IF(oagri_to_grass)THEN
581  IF (pvegtype(nvt_c3 )>0.) ph_veg(nvt_c3 ) = plai(nvt_c3) / 6. ! cultures
582  IF (pvegtype(nvt_c4 )>0.) ph_veg(nvt_c4 ) = plai(nvt_c4) / 6. ! C4 types
583  IF (pvegtype(nvt_irr )>0.) ph_veg(nvt_irr ) = plai(nvt_irr) / 6. ! irrigated crops (as C4)
584 ELSE
585  IF (pvegtype(nvt_c3 )>0.) ph_veg(nvt_c3 ) = min(1. , zallen_h(nvt_c3) ) ! cultures
586  IF (pvegtype(nvt_c4 )>0.) ph_veg(nvt_c4 ) = min(2.5, zallen_h(nvt_c4) ) ! C4 types
587  IF (pvegtype(nvt_irr )>0.) ph_veg(nvt_irr ) = min(2.5, zallen_h(nvt_irr) ) ! irrigated crops (as C4)
588 ENDIF
589 IF (pvegtype(nvt_no )>0.) ph_veg(nvt_no ) = 0.1 ! no vegetation (smooth)
590 IF (pvegtype(nvt_rock)>0.) ph_veg(nvt_rock) = 1. ! no vegetation (rocks)
591 IF (pvegtype(nvt_snow)>0.) ph_veg(nvt_snow) = 0.01 ! no vegetation (snow)
592 !
593 ph_veg(:) = max(ph_veg(:),0.001)
594 
595 !
596 IF (lhook) CALL dr_hook('MODI_VEG_HEIGHT_FROM_LAI:VEG_HEIGHT_FROM_LAI_PATCH',1,zhook_handle)
597 !
598 END FUNCTION veg_height_from_lai_patch
599 !
real function, dimension(size(pvegtype, 1), size(pvegtype, 2)) veg_height_from_lai_1d(PLAI, PH_TREE, PVEGTYPE, OAGRI_TO_GRASS)
real function, dimension(size(pvegtype, 1), size(pvegtype, 2), size(pvegtype, 3)) veg_height_from_lai_2d(PLAI, PH_TREE, PVEGTYPE, OAGRI_TO_GRASS)
real function, dimension(size(pvegtype)) veg_height_from_lai_patch(PLAI, PH_TREE, PVEGTYPE, OAGRI_TO_GRASS)
real function, dimension(size(pvegtype)) veg_height_from_lai_0d(PLAI, PH_TREE, PVEGTYPE, OAGRI_TO_GRASS)