SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
disph_for_meb.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 !####################################################################
6  SUBROUTINE disph_for_meb(PCHIL,PLAIV,PLW,PH_VEG,PZREF,PZ0_MEBV,PDISPH)
7 !
8 ! typical values for nordic forest:
9 ! PH_VEG = 15 m
10 ! PCHIL = 0.12
11 ! PLW = 0.02 m
12 !
13 !!**** *DISPH_FOR_MEB*
14 !!
15 !! PURPOSE
16 !! -------
17 !
18 ! Calculates the displacement height, (PDISPH)
19 ! Only used for double energy balance
20 !
21 !
22 !!** METHOD
23 !! ------
24 !!
25 !! REFERENCE
26 !! ---------
27 !!
28 !!
29 !! AUTHOR
30 !! ------
31 !!
32 !! P. Samuelsson/S.Gollvik * SMHI *
33 !!
34 !! MODIFICATIONS
35 !! -------------
36 !! Original 12/2010
37 !!
38 !-------------------------------------------------------------------------------
39 !
40 !* 0. DECLARATIONS
41 ! ------------
42 !
43 USE modd_csts, ONLY : xpi
44 USE modd_isba_par, ONLY : xlimh
45 !
46 USE yomhook ,ONLY : lhook, dr_hook
47 USE parkind1 ,ONLY : jprb
48 !
49 IMPLICIT NONE
50 !
51 !* 0.1 declarations of arguments
52 !
53 REAL, DIMENSION(:), INTENT(IN) :: pchil, plaiv, plw, ph_veg, pzref,pz0_mebv
54 ! PCHIL = Ross-Goudriaan leaf angle distr
55 ! PLAIV = leaf area index
56 ! PLW = leaf width
57 ! PH_VEG = height of the vegetation
58 ! PZREF = height of the lowest model layer
59 ! PZ0_MEBV = momentum roughness for canopy
60 !
61 REAL, DIMENSION(:), INTENT(OUT) :: pdisph
62 ! PDISPH = displacement height
63 !
64 !* 0.2 declarations of local variables
65 !
66 REAL, DIMENSION(SIZE(PLAIV)) :: zreveg, zcd
67 !
68 REAL(KIND=JPRB) :: zhook_handle
69 !
70 !* 0.3 declarations of local parameters
71 !
72 REAL, PARAMETER :: zul = 1. ! typical windspeed within the foliage
73 REAL, PARAMETER :: zny = 0.15e-04 ! kinematic viscosity for air
74 REAL, PARAMETER :: zfrtop = 0.95 ! maximumi displacement heightfraction
75 ! of vegetation top
76 !
77 !---------------------------------------------------------------------------------
78 !
79 !* 0. Initialization:
80 ! ---------------
81 !
82 IF (lhook) CALL dr_hook('DISPH_FOR_MEB',0,zhook_handle)
83 !
84 pdisph(:) = 0.
85 !
86 ! Reynolds number:
87 !
88 zreveg(:) = zul*plw(:)/zny
89 !
90 !
91 ! Eq. B7, Sellers et.al. 1996:
92 !
93 zcd(:) = 0.
94 !
95 WHERE(zreveg>0.)
96  zcd(:) =1.328*2./sqrt(zreveg(:)) + 0.45*((1.-pchil(:))/xpi)**1.6
97 END WHERE
98 !
99 ! Dispacement height, Eq. 20, Choudhury and Monteith, 1988:
100 !
101 pdisph(:) = 1.1*ph_veg(:)*alog(1.+(zcd(:)*plaiv(:))**0.25)
102 !
103 ! SAFE! Displacement height + PZREF + XLIMH >= PH_VEG
104 !
105 pdisph(:) = max(pdisph(:),ph_veg(:)+xlimh-pzref(:))
106 pdisph(:) = min(pdisph(:),ph_veg(:)*zfrtop)
107 !
108 ! SAFE assure that PH_VEG-DISPH > PZ0_MEBV+0.01 (see surface_air_meb)
109 pdisph(:)=min(pdisph(:),ph_veg(:)-pz0_mebv(:)-0.01)
110 !
111 IF (lhook) CALL dr_hook('DISPH_FOR_MEB',1,zhook_handle)
112 !
113 END SUBROUTINE disph_for_meb
subroutine disph_for_meb(PCHIL, PLAIV, PLW, PH_VEG, PZREF, PZ0_MEBV, PDISPH)