SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
hydro_veg.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 hydro_veg(HRAIN, PTSTEP, PMUF, PRR, PLEV, PLETR, &
7  pveg, ppsnv, pwr, pwrmax, ppg, pdrip, &
8  prrveg, plvtt )
9 ! #####################################################################
10 !
11 !!**** *HYDRO_VEG*
12 !!
13 !! PURPOSE
14 !! -------
15 !
16 ! Calculates the evolution of the liquid water retained in the vegetation
17 ! canopy (Wr). Also determine the runoff from the canopy that reaches the
18 ! ground (Mahfouf et al. 1995). This routine take into account the spatially
19 ! exponential distribution of precip introduced by Entekhabi and Eagleson (1989).
20 !
21 !
22 !!** METHOD
23 !! ------
24 !
25 !! EXTERNAL
26 !! --------
27 !!
28 !! none
29 !!
30 !! IMPLICIT ARGUMENTS
31 !! ------------------
32 !!
33 !! USE MODD_CST
34 !!
35 !! REFERENCE
36 !! ---------
37 !!
38 !! Noilhan and Planton (1989)
39 !! Belair (1995)
40 !! Mahfouf et al. 1995
41 !! Decharme and Douville (2006)
42 !!
43 !! AUTHOR
44 !! ------
45 !!
46 !! S. Belair * Meteo-France *
47 !!
48 !! MODIFICATIONS
49 !! -------------
50 !!
51 !! Original 14/03/95
52 !! 31/08/98 (V. Masson and F. Habets) add Dumenil et Todini
53 !! runoff scheme
54 !! 31/08/98 (V. Masson and A. Boone) add the third soil-water
55 !! reservoir (WG3,D3)
56 !! 31/05/04 (B. Decharme) add the rainfall spatial distribution
57 !! 2008 (B. Decharme) add the dripping rate as new diag
58 !! 11/2009 (S.Senesi) returns precipitation intercepted by
59 ! the vegetation
60 !! 07/2011 (B. Decharme) delete SGH for very fine precipitation
61 !! 09/2012 (B. Decharme) Computation efficiency for HRAIN=='SGH'
62 !! 10/2012 (B. Decharme) PPG intent(out)
63 !
64 !-------------------------------------------------------------------------------
65 !
66 !* 0. DECLARATIONS
67 ! ------------
68 !
69 USE modd_sgh_par, ONLY : x001
70 !
71 USE yomhook ,ONLY : lhook, dr_hook
72 USE parkind1 ,ONLY : jprb
73 !
74 IMPLICIT NONE
75 !
76 !* 0.1 declarations of arguments
77 !
78  CHARACTER(LEN=*), INTENT(IN) :: hrain ! Rainfall spatial distribution
79  ! 'DEF' = No rainfall spatial distribution
80  ! 'SGH' = Rainfall exponential spatial distribution
81  !
82 !
83 REAL, INTENT(IN) :: ptstep
84 ! timestep of the integration
85 !
86 REAL, DIMENSION(:), INTENT(IN) :: prr, plev, pletr, pmuf, plvtt
87 ! PRR = rain rate
88 ! PLEV = latent heat of evaporation over vegetation
89 ! PLETR = evapotranspiration of the vegetation
90 ! PMUF = fraction of the grid cell reached by the precipitation
91 ! PLVTT = latent heat of vaporization (J/kg)
92 !
93 REAL, DIMENSION(:), INTENT(IN) :: pveg, pwrmax
94 ! PVEG = fraction of vegetation
95 ! PWRMAX = maximum equivalent water content
96 ! in the vegetation canopy
97 !
98 REAL, DIMENSION(:), INTENT(IN) :: ppsnv
99 ! PPSNV = vegetation covered by snow
100 !
101 REAL, DIMENSION(:), INTENT(INOUT) :: pwr
102 ! PWR = liquid water retained on the foliage
103 ! of the vegetation at time 't+dt'
104 !
105 REAL, DIMENSION(:), INTENT(OUT) :: ppg,pdrip
106 ! PPG = total water reaching the ground
107 ! PDRIP = Dripping from the vegetation
108 REAL, DIMENSION(:), INTENT(OUT) :: prrveg
109 ! PRRVEG = Precip. intercepted by vegetation (kg/m2/s)
110 !
111 !
112 !* 0.2 declarations of local variables
113 !
114 REAL, DIMENSION(SIZE(PVEG)) :: zer
115 ! ZER = evaporation rate from the canopy
116 !
117 REAL, DIMENSION(SIZE(PVEG)) :: zwr ! for time stability scheme
118 !
119 REAL, DIMENSION(SIZE(PVEG)) :: zruir, zruir2 ! dripping from the vegetation
120 !
121 REAL :: zlim
122 !
123 REAL(KIND=JPRB) :: zhook_handle
124 !
125 !-------------------------------------------------------------------------------
126 !
127 IF (lhook) CALL dr_hook('HYDRO_VEG',0,zhook_handle)
128 zruir(:) = 0.
129 zruir2(:) = 0.
130 pdrip(:) = 0.
131 zwr(:) = 0.
132 !
133 !* 1. EVOLUTION OF THE EQUIVALENT WATER CONTENT Wr
134 ! --------------------------------------------
135 !
136 !evaporation rates
137 !
138 zer(:) = (plev(:)-pletr(:)) / plvtt(:)
139 !
140 !intercepted rainfall rate
141 !
142 prrveg(:) = pveg(:) * (1.-ppsnv(:)) * prr(:)
143 !
144 !evolution of the intercepted water
145 !(if we don't consider the runoff)
146 !
147 pwr(:) = pwr(:) - ptstep * (zer(:) - prrveg(:))
148 !
149 !When Wr < 0, the direct evaporation
150 !(i.e., EV-ETR) removes too much
151 !liquid water from the vegetation
152 !reservoir. This is considered as
153 !negative runoff, and it is stocked
154 !in ZRUIR2.
155 !
156 zruir2(:) = min(0.,pwr(:)/ptstep)
157 !
158 !Wr must be positive
159 !
160 pwr(:) = max(0., pwr(:))
161 !
162 IF(hrain=='SGH')THEN
163 !
164 !* 2. SPATIALLY EXPONENTIAL DISTRIBUTION OF PRECIPITATION
165 ! ---------------------------------------------------
166 !
167 !
168 ! Subgrid dripping from Wr
169 !
170  zlim=x001/ptstep
171 !
172  WHERE(prrveg(:)>zlim.AND.pwr(:)>0.0)
173  zruir(:) = prrveg(:)*exp(pmuf(:)*(pwr(:)-pwrmax(:))/(prrveg(:)*ptstep))
174  zruir(:) = min(zruir(:),pwr(:)/ptstep)
175  ENDWHERE
176 !
177  IF(ptstep>300.)THEN
178 !
179 ! if the isba time step is coarser than 5min, the "prediction/correction" method is applied
180 ! to Wr using the predicted Wr* at the end of the time step for time numerical stability
181 !
182  zwr(:) = pwr(:)-ptstep*zruir(:)
183  zruir(:) = 0.0
184 !
185 ! if the dripping is too big, the "prediction/correction" method is applied to Wr using
186 ! the predicted Wr* at the midle of the time step for time numerical stability
187 ! (<=> Runge-Kutta order 1 rang 1)
188 !
189  WHERE(prrveg(:)>zlim.AND.zwr(:)<=0.0)
190  zruir(:) = prrveg(:)*exp(pmuf(:)*(pwr(:)-pwrmax(:))/(prrveg(:)*ptstep/2.))
191  zruir(:) = min(zruir(:),pwr(:)/(ptstep/2.))
192  zwr(:) = pwr(:)-ptstep*zruir(:)/2.
193  zruir(:) = 0.0
194  ENDWHERE
195 !
196 ! Calculate the corrected dripping from the predicted Wr*
197 !
198  WHERE(prrveg(:)>zlim.AND.zwr(:)>0.0)
199  zruir(:) = prrveg(:)*exp(pmuf(:)*(zwr(:)-pwrmax(:))/(prrveg(:)*ptstep))
200  zruir(:) = min(zruir(:),pwr(:)/ptstep)
201  ENDWHERE
202 !
203  ENDIF
204 !
205  pwr(:) = pwr(:)-ptstep*zruir(:)
206 !
207 ! As previously Wr must be positive (numerical artefact)
208 !
209  zruir2(:) = zruir2(:) + min(0.,pwr(:)/ptstep)
210  pwr(:) = max( 0., pwr(:) )
211 !
212 ! Wr must be smaller then Wrmax
213 ! Then if Wr remain > Wrmax, there is runoff
214 !
215  zruir(:) = zruir(:) + max(0., (pwr(:) - pwrmax(:)) / ptstep )
216 !
217 ELSE
218 !
219 ! if Wr > Wrmax, there is runoff
220 !
221  zruir(:) = max(0., (pwr(:) - pwrmax(:)) / ptstep )
222 !
223 ENDIF
224 !
225 !Wr must be smaller then Wrmax
226 !
227 pwr(:) = min(pwr(:), pwrmax(:))
228 !
229 !
230 !* 3. LIQUID WATER REACHING THE GROUND Pg
231 ! -----------------------------------
232 !
233 !Thus, the rate of liquid water reaching the ground is the
234 !precipitation plus the vegetation runoff (we also consider the
235 !negative runoff).
236 !
237 ppg(:) = (1.-pveg(:)*(1-ppsnv(:))) * prr(:) + zruir(:) + zruir2(:)
238 !
239 pdrip(:) = zruir(:) + zruir2(:)
240 IF (lhook) CALL dr_hook('HYDRO_VEG',1,zhook_handle)
241 
242 !
243 !-------------------------------------------------------------------------------
244 !
245 END SUBROUTINE hydro_veg
subroutine hydro_veg(HRAIN, PTSTEP, PMUF, PRR, PLEV, PLETR, PVEG, PPSNV, PWR, PWRMAX, PPG, PDRIP, PRRVEG, PLVTT)
Definition: hydro_veg.F90:6