SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
wet_leaves_frac.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 wet_leaves_frac(PWRM, PVEG, PWRMAX_CF, PZ0, PLAI, PWRMAX, PDELTA)
7 ! ############################################################################
8 !
9 !!**** *WET_LEAVES_FRAC*
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 !
15 !!** METHOD
16 !! ------
17 !
18 !
19 !! EXTERNAL
20 !! --------
21 !!
22 !!
23 !! IMPLICIT ARGUMENTS
24 !! ------------------
25 !!
26 !!
27 !!
28 !! REFERENCE
29 !! ---------
30 !!
31 !!
32 !! AUTHOR
33 !! ------
34 !!
35 !! S. Belair * Meteo-France *
36 !!
37 !! MODIFICATIONS
38 !! -------------
39 !! Original 13/03/95
40 !! (A.Boone) 11/26/98 Option for PDELTA: forested vs default surface
41 !! B. Decharme 2008 Add optional maximum value for the fraction of the foliage covered by intercepted water
42 !-------------------------------------------------------------------------------
43 !
44 !* 0. DECLARATIONS
45 ! ------------
46 !
47 USE modd_surf_atm, ONLY : xdelta_max
48 !
49 !
50 USE yomhook ,ONLY : lhook, dr_hook
51 USE parkind1 ,ONLY : jprb
52 !
53 IMPLICIT NONE
54 !
55 !* 0.1 declarations of arguments
56 !
57 !
58 REAL, DIMENSION(:), INTENT(IN) :: pwrm
59 ! PWRM = liquid water retained on the foliage
60 ! of the vegetation
61 !
62 REAL, DIMENSION(:), INTENT(IN) :: pveg, pwrmax_cf, plai, pz0
63 ! PVEG = vegetation fraction
64 ! PLAI = leaf area index
65 ! PWRMAX_CF = coefficient for maximum water interception
66 ! storage capacity on the vegetation (kg/m2)
67 ! PZ0 = roughness length
68 !
69 !
70 REAL, DIMENSION(:), INTENT(OUT) :: pwrmax
71 ! PWRMAX = maximum equivalent water content
72 ! in the vegetation canopy
73 !
74 REAL, DIMENSION(:), INTENT(OUT) :: pdelta
75 ! PDELTA = fraction of the foliage covered
76 ! by intercepted water
77 !
78 !
79 !
80 !* 0.2 declarations of local variables
81 !
82 !
83 !
84 REAL, DIMENSION(SIZE(PVEG)) :: zcoef, &
85 ! ZCOEF = work array
86  zwr, &
87 ! Interception reservoir limited by WRMAX
88  zdelta_low, &
89 ! ZDELTA_LOW = fraction of the foliage covered
90 ! by intercepted water for low vegetation
91  zdelta_high
92 REAL(KIND=JPRB) :: zhook_handle
93 ! ZDELTA_HIGH = fraction of the foliage covered
94 ! by intercepted water for high vegetation
95 
96 !-------------------------------------------------------------------------------
97 !
98 IF (lhook) CALL dr_hook('WET_LEAVES_FRAC',0,zhook_handle)
99 pdelta(:) = 0.
100 !
101 !* 2. FRACTION OF THE FOLIAGE COVERED BY INTERCEPTED WATER (DELTA)
102 ! ------------------------------------------------------------
103 !
104 ! first calculate the maximum value of
105 ! equivalent water content in the
106 ! vegetation canopy
107 !
108 pwrmax(:) = pwrmax_cf(:) * pveg(:) * plai(:)
109 !
110 zwr(:) = min(pwrm(:),pwrmax(:))
111 !
112 WHERE (pveg(:)>0. .AND. pwrmax>0.)
113 !* calculate 'DELTA'
114 !
115 !* 2.1 Low vegetation, Deardorff (1978) formulmation:
116 ! ---------------------------------------------
117 !
118  zdelta_low(:) = ( zwr(:)/pwrmax(:) )**(2./3.)
119 !
120 !* 2.2 High vegetation, Manzi (1993) formulmation:
121 ! ------------------------------------------
122 !
123 ! Manzi (1993) [see also Delire et al. JGR 1997]
124 ! The dynamic vegetation roughness length
125 ! is used to determine which formulation
126 ! for 'DELTA' is used. This formulation
127 ! was calibrated for ARME (tropical forrest)
128 ! and so is used for forest canopies. It
129 ! results in 'smeared' (time and amplitude)
130 ! evaporation from interception relative to
131 ! that using Deardorff (above).
132 !
133  zcoef(:) = 1. + 2.*plai(:)
134 !
135  zdelta_high(:) = zwr(:)/( (1.-zcoef(:))*zwr(:) + zcoef(:)*pwrmax(:) )
136 !
137 !
138 !* 2.3 Ponderation between low and high vegetation (min and max thresholds: z0 of 0.5m and 1m)
139 ! ------------------------------------------
140 !
141  zcoef(:) = max(min(2.*pz0(:)-1. ,1.),0.)
142 !
143  pdelta(:) = (1.-zcoef(:)) * zdelta_low(:) + zcoef(:) * zdelta_high(:)
144 !
145 END WHERE
146 !
147 pdelta(:) = min(xdelta_max,pdelta(:))
148 IF (lhook) CALL dr_hook('WET_LEAVES_FRAC',1,zhook_handle)
149 !
150 !-------------------------------------------------------------------------------
151 !
152 END SUBROUTINE wet_leaves_frac
subroutine wet_leaves_frac(PWRM, PVEG, PWRMAX_CF, PZ0, PLAI, PWRMAX, PDELTA)