SURFEX v8.1
General documentation of Surfex
drag.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 drag(HISBA, HSNOW_ISBA, HCPSURF, PTSTEP, PTG, PWG, PWGI, &
7  PEXNS, PEXNA, PTA, PVMOD, PQA, PRR, PSR, PPS, PRS, &
8  PVEG, PZ0, PZ0EFF, PZ0H, PWFC, PWSAT, PPSNG, PPSNV, &
9  PZREF, PUREF, PDIRCOSZW, PDELTA, PF5, PRA, PCH, PCD, &
10  PCDN, PRI, PHUG, PHUGI, PHV, PHU, PCPS, PQS, PFFG, &
11  PFFV, PFF, PFFG_NOSNOW, PFFV_NOSNOW, PLEG_DELTA, &
12  PLEGI_DELTA, PWR, PRHOA, PLVTT, PQSAT )
13 ! ############################################################################
14 !
15 !!**** *DRAG*
16 !!
17 !! PURPOSE
18 !! -------
19 !
20 ! Calculates the drag coefficients for heat and momentum transfers
21 ! over ground (i.e., Ch and Cd).
22 !
23 !
24 !!** METHOD
25 !! ------
26 !
27 ! 1) computes hu, hv, and delta
28 !
29 ! 2) use this to find qsoil, the grid-averaged relative humidity
30 ! of the soil
31 !
32 ! 3) calculates the Richardson's number
33 !
34 ! 4) find the transfer and resistance coefficients Ch, Cd, and Ra
35 !
36 !! EXTERNAL
37 !! --------
38 !!
39 !! IMPLICIT ARGUMENTS
40 !! ------------------
41 !!
42 !! USE MODD_CST
43 !!
44 !!
45 !! REFERENCE
46 !! ---------
47 !!
48 !! Mascart et al. (1995)
49 !! Belair (1995)
50 !!
51 !! AUTHOR
52 !! ------
53 !!
54 !! S. Belair * Meteo-France *
55 !!
56 !! MODIFICATIONS
57 !! -------------
58 !! Original 13/03/95
59 !! (J.Stein) 15/11/95 use the potential temperature to compute Ri
60 !! and PVMOD instead of ZVMOD
61 !! (P.Lacarrere)15/03/96 replace * PEXNS by / PEXNS
62 !! (V.Masson) 22/12/97 computation of z0eff after snow treatment
63 !! (V.Masson) 05/10/98 clear routine
64 !! (A.Boone) 11/26/98 Option for PDELTA: forested vs default surface
65 !! (V.Masson) 01/03/03 Puts PDELTA in another routine
66 !! (P.LeMoigne) 28/07/05 dependance on qs for cp
67 !! (P.LeMoigne) 09/02/06 z0h and snow
68 !! (P.LeMoigne) 09/01/08 limitation of Ri
69 !! (B.Decharme) 01/05/08 optional limitation of Ri
70 !! (B.Decharme) 03/06/08 flooding scheme
71 !! (A.Boone) 03/15/10 Add delta fnctions to force LEG ans LEGI=0
72 !! when hug(i)Qsat < Qa and Qsat > Qa
73 !! (A.Boone) 21/11/11 Add Rs_max limit for dry conditions with Etv
74 !! (B. Decharme) 09/12 limitation of Ri in surface_ri.F90
75 !! (C. Ardilouze) 09/13 Halstead coef set to 0 for very low values
76 !! (B. Decharme) 03/16 Bug in limitation of Er for Interception reservoir
77 !-------------------------------------------------------------------------------
78 !
79 !* 0. DECLARATIONS
80 ! ------------
81 !
82 USE modd_csts, ONLY : xpi, xcpd, xcpv
83 USE modd_isba_par, ONLY : xwgmin, xrs_max
86 !
87 USE modi_surface_ri
88 USE modi_surface_aero_cond
89 USE modi_surface_cd
90 USE modi_surface_cdch_1darp
91 USE modi_wind_threshold
92 !
93 USE mode_thermos
94 !
95 !
96 USE yomhook ,ONLY : lhook, dr_hook
97 USE parkind1 ,ONLY : jprb
98 !
99 IMPLICIT NONE
100 !
101 !* 0.1 declarations of arguments
102 !
103 !
104  CHARACTER(LEN=*), INTENT(IN) :: HISBA ! type of ISBA version:
105 ! ! '2-L' (default)
106 ! ! '3-L'
107 ! ! 'DIF'
108  CHARACTER(LEN=*), INTENT(IN) :: HSNOW_ISBA ! 'DEF' = Default F-R snow scheme
109 ! ! (Douville et al. 1995)
110 ! ! '3-L' = 3-L snow scheme (option)
111 ! ! (Boone and Etchevers 2000)
112  CHARACTER(LEN=*), INTENT(IN) :: HCPSURF ! option for specific heat Cp:
113 ! ! 'DRY' = dry Cp
114 ! ! 'HUM' = Cp as a function of qs
115 !
116 REAL, INTENT(IN) :: PTSTEP ! timestep of ISBA (not split time step)
117 !
118 REAL, DIMENSION(:), INTENT(IN) :: PTG, PWG, PWGI, PEXNS
119 ! PTG = surface temperature
120 ! PWG = near-surface volumetric water content
121 ! PWGI = near-surface frozen volumetric water content
122 ! PEXNS = Exner function at the surface
123 !
124 REAL, DIMENSION(:), INTENT(IN) :: PEXNA, PTA, PVMOD, PQA, PRR, PSR, PPS
125 ! PEXNA= Exner function
126 ! near surface atmospheric variables
127 ! PTA = 2m temperature
128 ! PVMOD = module of the horizontal wind
129 ! NOTE it should be input as >= 1. (m)
130 ! PQA = specific humidity
131 ! PPS = surface pressure
132 ! PRR = rain rate
133 ! PSR = snow rate
134 !
135 REAL, DIMENSION(:), INTENT(IN) :: PRS, PVEG, PZ0, PZ0H, PZ0EFF
136 REAL, DIMENSION(:), INTENT(IN) :: PWFC, PWSAT, PPSNG, PPSNV, PZREF, PUREF
137 ! PRS = stomatal resistance
138 ! PVEG = vegetation fraction
139 ! PZ0 = roughness length for momentum
140 ! PZ0H = roughness length for heat
141 ! PZ0EFF= effective roughness length
142 ! PWFC = field capacity volumetric water content
143 ! PWSAT = volumetric water content at saturation
144 ! PPSNG = fraction of the bare ground covered
145 ! by snow
146 ! PPSNV = fraction of the vegetation covered
147 ! by snow
148 ! PZREF = reference height of the first
149 ! atmospheric level
150 ! PUREF = reference height of the wind
151 ! NOTE this is different from ZZREF
152 ! ONLY in stand-alone/forced mode,
153 ! NOT when coupled to a model (MesoNH)
154 !
155 REAL, DIMENSION(:), INTENT(INOUT) :: PDELTA
156 ! PDELTA = fraction of the foliage covered
157 ! by intercepted water
158 REAL, DIMENSION(:), INTENT(IN) :: PF5
159 ! PF5 = water stress function for Hv
160 REAL, DIMENSION(:), INTENT(IN) :: PDIRCOSZW
161 ! Cosinus of the angle between the normal to the surface and the vertical
162 REAL, DIMENSION(:), INTENT(INOUT) :: PRA
163 ! aerodynamic surface resistance
164 REAL, DIMENSION(:), INTENT(INOUT) :: PCPS
165 ! specific heat at surface
166 !
167 REAL, DIMENSION(:), INTENT(OUT) :: PCH, PCD, PCDN, PRI
168 ! PCH = drag coefficient for heat
169 ! PCD = drag coefficient for momentum
170 ! PCDN= neutral drag coefficient for momentum
171 ! PRI = Richardson number
172 !
173 REAL, DIMENSION(:), INTENT(OUT) :: PHUG, PHUGI, PHV, PHU, PQS, PLEG_DELTA, PLEGI_DELTA
174 ! PHUG = ground relative humidity
175 ! PHUGI = ground (ice) relative humidity
176 ! PHV = Halstead coefficient
177 ! PHU = relative humidity at the surface
178 ! PQS = humidity at surface
179 ! PLEG_DELTA = soil evaporation delta fn
180 ! PLEGI_DELTA = soil sublimation delta fn
181 !
182 REAL, DIMENSION(:), INTENT(IN) :: PFFV, PFF, PFFG, PFFG_NOSNOW, PFFV_NOSNOW
183 ! PFFG = Floodplain fraction over ground
184 ! PFFV = Floodplain fraction over vegetation
185 ! PFF = Floodplain fraction at the surface
186 !
187 REAL, DIMENSION(:), INTENT(IN) :: PWR, PRHOA, PLVTT
188 ! PWR = liquid water retained on the foliage
189 ! PRHOA = near-ground air density
190 ! PLVTT = Vaporization heat
191 !
192 REAL, DIMENSION(:), INTENT(OUT), OPTIONAL :: PQSAT
193 ! PQSAT = specific humidity at saturation
194 !
195 !* 0.2 declarations of local variables
196 !
197 REAL, PARAMETER :: ZHVLIM = 1.e-12 ! set halstead coef to 0 at this limit
198 !
199 REAL, DIMENSION(SIZE(PTG)) :: ZQSAT, &
200 ! ZQSAT = specific humidity at saturation
201  zac, &
202 ! ZAC = aerodynamical conductance
203  zwfc, &
204 ! ZWFC = field capacity in presence of ice
205  zvmod, &
206 ! ZVMOD = wind modulus with minimum threshold
207  zfp, &
208 ! ZFP = working variable
209  zzhv, &
210 ! ZZHV = condensation delta fn for Hv
211  zrrcor
212 ! ZRRCOR = correction of CD, CH, CDN due to moist-gustiness
213 !
214 REAL(KIND=JPRB) :: ZHOOK_HANDLE
215 !-------------------------------------------------------------------------------
216 !
217 !* 0. Initialization:
218 ! ---------------
219 !
220 IF (lhook) CALL dr_hook('DRAG',0,zhook_handle)
221 pch(:) =0.
222 pcd(:) =0.
223 phug(:) =0.
224 phugi(:) =0.
225 phv(:) =0.
226 phu(:) =0.
227 !
228 zqsat(:) =0.
229 zwfc(:) =0.
230 pri(:) =0.
231 !
232 zvmod = wind_threshold(pvmod,puref)
233 !
234 zqsat(:) = qsat(ptg(:),pps(:))
235 !
236 IF(PRESENT(pqsat))pqsat(:)=zqsat(:)
237 !
238 !-------------------------------------------------------------------------------
239 !
240 !* 1. RELATIVE HUMIDITY OF THE GROUND HU
241 ! ----------------------------------
242 !
243 ! this relative humidity is related to
244 ! the superficial soil moisture and the
245 ! field capacity of the ground
246 !
247 !
248 zwfc(:) = pwfc(:)*(pwsat(:)-pwgi(:))/pwsat(:)
249 !
250 phug(:) = 0.5 * ( 1.-cos(xpi*min((pwg(:)-xwgmin) /zwfc(:),1.)) )
251 
252 zwfc(:) = pwfc(:)*max(xwgmin, pwsat(:)-pwg(:))/pwsat(:)
253 !
254 phugi(:) = 0.5 * ( 1.-cos(xpi*min(pwgi(:)/zwfc(:),1.)) )
255 !
256 !
257 ! there is a specific treatment for dew
258 ! (see Mahfouf and Noilhan, jam, 1991)
259 ! when hu*qsat < qa, there are two
260 ! possibilities
261 !
262 ! a) low-level air is dry, i.e.,
263 ! qa < qsat
264 !
265 ! NOTE the additional delta fn's
266 ! here are needed owing to linearization
267 ! of Qsat in the surface energy budget.
268 !
269 pleg_delta(:) = 1.0
270 plegi_delta(:) = 1.0
271 WHERE ( phug*zqsat < pqa .AND. zqsat > pqa )
272  phug(:) = pqa(:) / zqsat(:)
273  pleg_delta(:) = 0.0
274 END WHERE
275 WHERE ( phugi*zqsat < pqa .AND. zqsat > pqa )
276  phugi(:) = pqa(:) / zqsat(:)
277  plegi_delta(:) = 0.0
278 END WHERE
279 !
280 ! b) low-level air is humid, i.e.,
281 ! qa >= qsat
282 !
283 WHERE ( phug*zqsat < pqa .AND. zqsat <= pqa )
284  phug(:) = 1.0
285 END WHERE
286 WHERE ( phugi*zqsat < pqa .AND. zqsat <= pqa )
287  phugi(:) = 1.0
288 END WHERE
289 !
290 !-------------------------------------------------------------------------------
291 !
292 !* 3. HALSTEAD COEFFICIENT (RELATIVE HUMIDITY OF THE VEGETATION)
293 ! ----------------------------------------------------------
294 !
295 zzhv(:) = max(0.,sign(1.,zqsat(:)-pqa(:))) ! condensation on foilage if = 1
296 !
297 phv(:) = pdelta(:) + (1.- pdelta(:))* &
298  ( pra(:) + prs(:)*(1.0 - zzhv(:)) )* &
299  ( (1/(pra(:)+prs(:))) - (zzhv(:)*(1.-pf5(:))/(pra(:)+xrs_max)) )
300 !
301 WHERE(phv(:)<zhvlim)
302  phv(:)=0.0
303 ENDWHERE
304 !
305 !-------------------------------------------------------------------------------
306 !
307 !* 4. GRID-AVERAGED HUMIDITY OF THE SURFACE
308 ! -------------------------------------
309 !
310 IF(hsnow_isba == '3-L' .OR. hsnow_isba == 'CRO' .OR. hisba == 'DIF')THEN
311 !
312 ! For explicit snow, humidity HERE only over snow-free region:
313 !
314  pqs(:) =( (1.-pveg(:))*(1.-pffg_nosnow(:))*(pwg(:) /(pwg(:)+pwgi(:)))*phug(:) &
315  + (1.-pveg(:))*(1.-pffg_nosnow(:))*(pwgi(:)/(pwg(:)+pwgi(:)))*phugi(:) &
316  + pveg(:) *(1.-pffv_nosnow(:))* phv(:) &
317  + ((1.-pveg(:))*pffg_nosnow(:)+pveg(:)*pffv_nosnow(:)))*zqsat(:) &
318  + pveg(:) *(1.-pffv_nosnow(:))*(1.-phv(:))*pqa(:)
319 !
320 ELSE
321 !
322  pqs(:) =( (1.-pveg(:))*(1.-ppsng(:)-pffg(:))*(pwg(:) /(pwg(:)+pwgi(:)))*phug(:) &
323  + (1.-pveg(:))*(1.-ppsng(:)-pffg(:))*(pwgi(:)/(pwg(:)+pwgi(:)))*phugi(:) &
324  + (1.-pveg(:))* ppsng(:) &
325  + pveg(:) *(1.-ppsnv(:)-pffv(:))*phv(:) &
326  + pveg(:) * ppsnv(:) &
327  + pff(:) )*zqsat(:) &
328  + pveg(:) *(1.-ppsnv(:)-pffv(:))*(1.-phv(:))*pqa(:)
329 !
330 ENDIF
331 !
332 phu(:) = pqs(:)/zqsat(:)
333 !
334 !-------------------------------------------------------------------------------
335 !
336 !* 5. SPECIFIC HEAT OF THE SURFACE
337 ! ----------------------------
338 !
339 IF (hcpsurf=='DRY') THEN
340  pcps(:) = xcpd
341 ELSEIF(.NOT.lcpl_arp)THEN
342  pcps(:) = xcpd + ( xcpv - xcpd ) * pqa(:)
343 ENDIF
344 !
345 !-------------------------------------------------------------------------------
346 !
347 !* 6. COMPUTATION OF RESISTANCE AND DRAG COEFFICIENT
348 ! ----------------------------------------------
349 !
350  CALL surface_ri(ptg, pqs, pexns, pexna, pta, pqa, &
351  pzref, puref, pdircoszw, pvmod, pri )
352 !
353 !-------------------------------------------------------------------------------
354 !
355 !* 6.5 LIMITATION OF RICHARDSON NUMBER
356 ! -------------------------------
357 !
358 !Now done directly in SURFACE_RI subroutine
359 !
360 !-------------------------------------------------------------------------------
361 !* 7.0 DRAG COEFFICIENT FOR HEAT AND MOMENTUM TRANSFERS
362 ! -------------------------------------------------
363 !
364 IF (ldrag_coef_arp) THEN
365 
366  CALL surface_cdch_1darp(pzref, pz0eff, pz0h, zvmod, pta, ptg, &
367  pqa, pqs, pcd, pcdn, pch )
368  pra(:) = 1. / ( pch(:) * zvmod(:) )
369 
370 ELSE
371 
372 !
373 !* 7.1 SURFACE AERODYNAMIC RESISTANCE FOR HEAT TRANSFERS
374 ! -------------------------------------------------
375 !
376  CALL surface_aero_cond(pri, pzref, puref, zvmod, pz0, pz0h, zac, pra, pch)
377 !
378 !-------------------------------------------------------------------------------
379 !
380 !* 7.2 DRAG COEFFICIENT FOR MOMENTUM TRANSFERS
381 ! ---------------------------------------
382 !
383 !
384  CALL surface_cd(pri, pzref, puref, pz0eff, pz0h, pcd, pcdn)
385 !
386 ENDIF
387 !
388 !-------------------------------------------------------------------------------
389 !
390 !* 8. CORRECTION DUE TO MOIST GUSTINESS
391 ! ---------------------------------
392 !
393 IF (lrrgust_arp) THEN
394 
395  zfp(:)=max(0.0,prr(:)+psr(:))
396  zrrcor(:)=sqrt(1.0+((((zfp(:)/(zfp(:)+xrrscale))**xrrgamma)*xutilgust)**2) &
397  /(pcd(:)*zvmod(:)**2))
398 
399  pcd = pcd * zrrcor
400  pch = pch * zrrcor
401  pcdn = pcdn * zrrcor
402 
403 ENDIF
404 !
405 !-------------------------------------------------------------------------------
406 !
407 !
408 !* 9. HALSTEAD COEFFICIENT (WITH THE NEW VALUES OF PRA)
409 ! ----------------------------------------------------------
410 !
411 !
412 phv(:) = pdelta(:) + (1.- pdelta(:))* &
413  ( pra(:) + prs(:)*(1.0 - zzhv(:)) )* &
414  ( (1/(pra(:)+prs(:))) - (zzhv(:)*(1.-pf5(:))/(pra(:)+xrs_max)) )
415 !
416  CALL limit_ler(pdelta)
417 !
418 WHERE(phv(:)<zhvlim)
419  phv(:)=0.0
420 ENDWHERE
421 !
422 IF (lhook) CALL dr_hook('DRAG',1,zhook_handle)
423 !
424 !-------------------------------------------------------------------------------
425 !
426 CONTAINS
427 !
428 !-------------------------------------------------------------------------------
429 !
430 SUBROUTINE limit_ler(PDELTA)
431 !
432 IMPLICIT NONE
433 !
434 !* 0.1 declarations of arguments
435 !
436 REAL, DIMENSION(:), INTENT(INOUT) :: PDELTA
437 !
438 !
439 !* 0.2 declarations of local variables
440 !
441 REAL, DIMENSION(SIZE(PDELTA)) :: ZPSNV
442 REAL, DIMENSION(SIZE(PDELTA)) :: ZLEV
443 REAL, DIMENSION(SIZE(PDELTA)) :: ZLETR
444 REAL, DIMENSION(SIZE(PDELTA)) :: ZLECOEF
445 REAL, DIMENSION(SIZE(PDELTA)) :: ZER
446 REAL, DIMENSION(SIZE(PDELTA)) :: ZRRVEG
447 REAL, DIMENSION(SIZE(PDELTA)) :: ZWR_DELTA
448 !
449 REAL(KIND=JPRB) :: ZHOOK_HANDLE
450 !
451 IF (lhook) CALL dr_hook('DRAG:LIMIT_LER',0,zhook_handle)
452 !
453 !-------------------------------------------------------------------------------
454 !
455 !* 1. Initialization:
456 ! ---------------
457 !
458 IF(hsnow_isba == '3-L' .OR. hsnow_isba == 'CRO' .OR. hisba == 'DIF')THEN
459  zlecoef(:) = (1.0-ppsnv(:)-pffv(:))
460  zpsnv(:) = 0.0
461 ELSE
462  zlecoef(:) = 1.0
463  zpsnv(:) = ppsnv(:)+pffv(:)
464 ENDIF
465 !
466 !
467 !* 2. Interception reservoir consistency:
468 ! -----------------------------------
469 !
470 ! In DRAG, we use the timestep of ISBA (PTSTEP) and not the split time step (ZTSTEP)
471 ! because diagnostic canopy evaporation (Er) must be consistent with PWR to
472 ! limit negative dripping in hydro_veg
473 !
474 zlev(:) = prhoa(:) * plvtt(:) * pveg(:) * (1-zpsnv(:)) * phv(:) * (zqsat(:) - pqa(:)) / pra(:)
475 !
476 zletr(:) = zzhv(:) * prhoa(:) * (1. - pdelta(:)) * plvtt(:) * pveg(:) *(1-zpsnv(:)) &
477  * (zqsat(:) - pqa(:)) * ( (1/(pra(:) + prs(:))) - ((1.-pf5(:))/(pra(:) + xrs_max)) )
478 !
479 zer(:)=ptstep*(zlev(:)-zletr(:))*zlecoef(:)/plvtt(:)
480 !
481 zrrveg(:) = ptstep*pveg(:)*(1.-ppsnv(:))*prr(:)
482 !
483 zwr_delta(:)=1.0
484 !
485 WHERE( zzhv(:)>0.0 .AND. zer(:)/=0.0 .AND. (pwr(:)+zrrveg(:))<zer(:) )
486 !
487  zwr_delta(:) = max(0.01,min(1.0,(pwr(:)+zrrveg(:))/zer(:)))
488 !
489  pdelta(:) = pdelta(:) * zwr_delta(:)
490 !
491  phv(:) = pdelta(:) + (1.- pdelta(:))*( pra(:) + prs(:)*(1.0 - zzhv(:)) )* &
492  ( (1/(pra(:)+prs(:))) - (zzhv(:)*(1.-pf5(:))/(pra(:)+xrs_max)) )
493 !
494 ENDWHERE
495 !
496 IF (lhook) CALL dr_hook('DRAG:LIMIT_LER',1,zhook_handle)
497 !
498 END SUBROUTINE limit_ler
499 !
500 !-------------------------------------------------------------------------------
501 !
502 END SUBROUTINE drag
real, save xcpd
Definition: modd_csts.F90:63
real function, dimension(size(pwind)) wind_threshold(PWIND, PUREF)
subroutine surface_ri(PTG, PQS, PEXNS, PEXNA, PTA, PQA, PZREF, PUREF, PDIRCOSZW, PVMOD, PRI)
Definition: surface_ri.F90:8
real, save xpi
Definition: modd_csts.F90:43
logical lrrgust_arp
subroutine surface_aero_cond(PRI, PZREF, PUREF, PVMOD, PZ0, PZ0H, PAC, PRA, PCH)
integer, parameter jprb
Definition: parkind1.F90:32
subroutine limit_ler(PDELTA)
Definition: drag.F90:431
real, save xcpv
Definition: modd_csts.F90:63
subroutine surface_cd(PRI, PZREF, PUREF, PZ0EFF, PZ0H, PCD, PCDN)
Definition: surface_cd.F90:8
logical lhook
Definition: yomhook.F90:15
subroutine surface_cdch_1darp(PZREF, PZ0EFF, PZ0H, PVMOD, PTA, PTG, PQA, PQS, PCD, PCDN, PCH)
logical ldrag_coef_arp
subroutine drag(HISBA, HSNOW_ISBA, HCPSURF, PTSTEP, PTG, PWG, PWGI, PEXNS, PEXNA, PTA, PVMOD, PQA, PRR, PSR, PPS, PRS, PVEG, PZ0, PZ0EFF, PZ0H, PWFC, PWSAT, PPSNG, PPSNV, PZREF, PUREF, PDIRCOSZW, PDELTA, PF5, PRA, PCH, PCD, PCDN, PRI, PHUG, PHUGI, PHV, PHU, PCPS, PQS, PFFG, PFFV, PFF, PFFG_NOSNOW, PFFV_NOSNOW, PLEG_DELTA, PLEGI_DELTA, PWR, PRHOA, PLVTT, PQSAT)
Definition: drag.F90:13