/[lmdze]/trunk/phylmd/Interface_surf/hbtm.f90
ViewVC logotype

Contents of /trunk/phylmd/Interface_surf/hbtm.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 346 - (show annotations)
Mon Dec 9 20:15:29 2019 UTC (4 years, 5 months ago) by guez
File size: 13365 byte(s)
Rename block to `my_block` in procedure `CLOUDS_GNO` because block is
a Fortran keyword.

Remove computation of palpbla in procedure sw. It was not used nor
output. (Not used nor output either in LMDZ.)

In procedure physiq, define `d_[uv]_con` and add them to `[uv]_seri`
only if `conv_Emanuel`. Thus, we do not need to initialize
`d_[uv]_con` to 0, we do not have to save them and we do not add 0 to
`[uv]_seri`.

In procedure physiq, no need to initialize rnebcon to 0, it is defined
by phyetat0 afterwards.

Check that `iflag_cldcon` is between - 2 and 3.

1 module HBTM_m
2
3 IMPLICIT none
4
5 contains
6
7 SUBROUTINE HBTM(paprs, pplay, t2m, q2m, ustar, flux_t, flux_q, u, v, t, q, &
8 pblh, cape, EauLiq, ctei, pblT, therm, plcl)
9
10 ! D'apr\'es Holstag et Boville et Troen et Mahrt
11 ! JAS 47 BLM
12
13 ! Algorithme th\'ese Anne Mathieu. Crit\'ere d'entra\^inement
14 ! Peter Duynkerke (JAS 50). Written by: Anne MATHIEU and Alain
15 ! LAHELLEC, 22nd November 1999.
16
17 ! Modifications : d\'ecembre 99 passage th \`a niveau plus bas. Voir fixer
18 ! la prise du th \`a z/Lambda = -.2 (max Ray)
19 ! Autre algorithme : entra\^inement ~ Theta + v =constante
20 ! mais comment ? The ?
21 ! On peut fixer q \`a 0.7 qsat (cf. non adiabatique) d'où T2 et The2.
22 ! Voir aussi KE pblh = niveau The_e ou l = env.
23
24 ! Adaptation \`a LMDZ version coupl\'ee. Pour le moment on fait
25 ! passer en argument les grandeurs de surface : flux, t, q2m. On
26 ! va utiliser syst\'ematiquement les grandeurs \`a 2 m mais on
27 ! garde la possibilit\'e de changer si besoin (jusqu'\`a pr\'esent
28 ! la forme de HB avec le premier niveau mod\`ele \'etait
29 ! conserv\'ee).
30
31 USE dimphy, ONLY: klev, klon
32 USE suphec_m, ONLY: rcpd, rd, retv, rg, rkappa, rtt
33 USE yoethf_m, ONLY: r2es, rvtmp2
34 USE fcttre, ONLY: foeew
35
36 ! Arguments:
37
38 ! pression a inter-couche (Pa)
39 REAL, intent(in):: paprs(klon, klev+1)
40 ! pression au milieu de couche (Pa)
41 REAL, intent(in):: pplay(klon, klev)
42 REAL, intent(in):: t2m(klon) ! temperature a 2 m
43 ! q a 2 et 10m
44 REAL, intent(in):: q2m(klon)
45 REAL, intent(in):: ustar(:) ! (knon)
46 REAL, intent(in):: flux_t(:), flux_q(:) ! (knon) flux à la surface
47 REAL, intent(in):: u(:, :) ! (knon, klev) vitesse U (m/s)
48 REAL, intent(in):: v(:, :) ! (knon, klev) vitesse V (m/s)
49 REAL, intent(in):: t(:, :) ! (knon, klev) temperature (K)
50 REAL, intent(in):: q(:, :) ! (knon, klev) vapeur d'eau (kg/kg)
51
52 REAL, intent(out):: pblh(:) ! (knon)
53 ! Cape du thermique
54 REAL Cape(klon)
55 ! Eau liqu integr du thermique
56 REAL EauLiq(klon)
57 ! Critere d'instab d'entrainmt des nuages de
58 REAL ctei(klon)
59 REAL pblT(klon)
60 ! thermal virtual temperature excess
61 REAL therm(klon)
62 REAL plcl(klon)
63
64 ! Local:
65
66 INTEGER knon ! nombre de points a calculer
67 INTEGER isommet
68 ! limite max sommet pbl
69 PARAMETER (isommet=klev)
70 REAL vk
71 ! Von Karman => passer a .41 ! cf U.Olgstrom
72 PARAMETER (vk=0.35)
73 REAL ricr
74 PARAMETER (ricr=0.4)
75 ! a
76 REAL onet
77 PARAMETER (onet=1.0/3.0)
78 REAL zkmin
79 PARAMETER (zkmin=0.01)
80 REAL betam
81 ! pour Phim / h dans la S.L stable
82 PARAMETER (betam=15.0)
83 ! z/OBL<>1
84 REAL sffrac
85 ! S.L. = z/h < .1
86 PARAMETER (sffrac=0.1)
87 REAL binm
88 PARAMETER (binm=betam*sffrac)
89
90 REAL q_star, t_star
91 ! Lambert correlations T' q' avec T* q*
92 REAL b1, b2, b212, b2sr
93 PARAMETER (b1=70., b2=20.)
94
95 REAL z(klon, klev)
96
97 REAL zref
98 ! Niveau de ref a 2m peut eventuellement
99 PARAMETER (zref=2.)
100 ! etre choisi a 10m
101
102 INTEGER i, k
103 REAL zxt
104 ! surface kinematic heat flux [mK/s]
105 REAL khfs(klon)
106 ! sfc kinematic constituent flux [m/s]
107 REAL kqfs(klon)
108 ! surface virtual heat flux
109 REAL heatv(klon)
110 ! bulk Richardon no. mais en Theta_v
111 REAL rhino(klon, klev)
112 ! pts w/unstbl pbl (positive virtual ht flx)
113 LOGICAL unstbl(klon)
114 LOGICAL check(klon) ! Richardson number > critical
115 ! flag de prolongerment cape pour pt Omega
116 LOGICAL omegafl(klon)
117
118 ! Monin-Obukhov lengh
119 REAL obklen(klon)
120
121 REAL zdu2
122 ! Algorithme thermique
123 REAL s(klon, klev) ! [P/Po]^Kappa milieux couches
124 ! total water of thermal
125 REAL qT_th(klon)
126 ! T thermique niveau precedent
127 REAL qsatbef(klon)
128 ! le thermique est sature
129 LOGICAL Zsat(klon)
130 REAL zthvd, zthvu, qqsat
131 REAL t2
132
133 ! inverse phi function for momentum
134 REAL phiminv(klon)
135 ! turbulent velocity scale for momentum
136 REAL wm(klon)
137 ! current level height + one level up
138 REAL zp(klon)
139 REAL zcor
140
141 REAL pblmin
142
143 !-----------------------------------------------------------------
144
145 knon = size(pblh)
146
147 ! initialisations
148 q_star = 0
149 t_star = 0
150
151 b212=sqrt(b1*b2)
152 b2sr=sqrt(b2)
153
154 ! Calculer les hauteurs de chaque couche
155 ! (geopotentielle Int_dp/ro = Int_[Rd.T.dp/p] z = geop/g)
156 ! pourquoi ne pas utiliser Phi/RG ?
157 DO i = 1, knon
158 z(i, 1) = RD * t(i, 1) / (0.5*(paprs(i, 1)+pplay(i, 1))) &
159 * (paprs(i, 1)-pplay(i, 1)) / RG
160 s(i, 1) = (pplay(i, 1)/paprs(i, 1))**RKappa
161 ENDDO
162 ! s(k) = [pplay(k)/ps]^kappa
163 ! + + + + + + + + + pplay <-> s(k) t dp=pplay(k-1)-pplay(k)
164 ! ----------------- paprs <-> sig(k)
165 ! + + + + + + + + + pplay <-> s(k-1)
166 ! + + + + + + + + + pplay <-> s(1) t dp=paprs-pplay z(1)
167 ! ----------------- paprs <-> sig(1)
168
169 DO k = 2, klev
170 DO i = 1, knon
171 z(i, k) = z(i, k-1) &
172 + RD * 0.5*(t(i, k-1)+t(i, k)) / paprs(i, k) &
173 * (pplay(i, k-1)-pplay(i, k)) / RG
174 s(i, k) = (pplay(i, k) / paprs(i, 1))**RKappa
175 ENDDO
176 ENDDO
177
178 ! Determination des grandeurs de surface
179 DO i = 1, knon
180 ! Niveau de ref choisi a 2m
181 zxt = t2m(i)
182
183 ! convention >0 vers le bas ds lmdz
184 khfs(i) = - flux_t(i)*zxt*Rd / (RCPD*paprs(i, 1))
185 kqfs(i) = - flux_q(i)*zxt*Rd / paprs(i, 1)
186 ! verifier que khfs et kqfs sont bien de la forme w'l'
187 heatv(i) = khfs(i) + 0.608*zxt*kqfs(i)
188 ! a comparer aussi aux sorties de clqh : flux_T/RoCp et flux_q/RoLv
189 ! Theta et qT du thermique sans exces (interpolin vers surf)
190 ! chgt de niveau du thermique (jeudi 30/12/1999)
191 ! (interpolation lineaire avant integration phi_h)
192 qT_th(i) = q2m(i)
193 ENDDO
194
195 DO i = 1, knon
196 ! Global Richardson
197 rhino(i, 1) = 0.0
198 check(i) = .TRUE.
199 ! on initialise pblh a l'altitude du 1er niv
200 pblh(i) = z(i, 1)
201 plcl(i) = 6000.
202 ! Lambda = -u*^3 / (alpha.g.kvon.<w'Theta'v>
203 obklen(i) = -t(i, 1)*ustar(i)**3/(RG*vk*heatv(i))
204 ENDDO
205
206 ! PBL height calculation: Search for level of pbl. Scan upward
207 ! until the Richardson number between the first level and the
208 ! current level exceeds the "critical" value. (bonne idee Nu de
209 ! separer le Ric et l'exces de temp du thermique)
210 DO k = 2, isommet
211 DO i = 1, knon
212 IF (check(i)) THEN
213 ! pourquoi / niveau 1 (au lieu du sol) et le terme en u*^2 ?
214 zdu2 = u(i, k)**2+v(i, k)**2
215 zdu2 = max(zdu2, 1.0e-20)
216 ! Theta_v environnement
217 zthvd=t(i, k)/s(i, k)*(1.+RETV*q(i, k))
218
219 ! therm Theta_v sans exces (avec hypothese fausse de H&B, sinon,
220 ! passer par Theta_e et virpot)
221 zthvu = T2m(i)*(1.+RETV*qT_th(i))
222 ! Le Ri par Theta_v
223 ! On a nveau de ref a 2m ???
224 rhino(i, k) = (z(i, k)-zref)*RG*(zthvd-zthvu) &
225 /(zdu2*0.5*(zthvd+zthvu))
226
227 IF (rhino(i, k).GE.ricr) THEN
228 pblh(i) = z(i, k-1) + (z(i, k-1)-z(i, k)) * &
229 (ricr-rhino(i, k-1))/(rhino(i, k-1)-rhino(i, k))
230 ! test04
231 pblh(i) = pblh(i) + 100.
232 pblT(i) = t(i, k-1) + (t(i, k)-t(i, k-1)) * &
233 (pblh(i)-z(i, k-1))/(z(i, k)-z(i, k-1))
234 check(i) = .FALSE.
235 ENDIF
236 ENDIF
237 ENDDO
238 ENDDO
239
240 ! Set pbl height to maximum value where computation exceeds number of
241 ! layers allowed
242 DO i = 1, knon
243 if (check(i)) pblh(i) = z(i, isommet)
244 ENDDO
245
246 ! Improve estimate of pbl height for the unstable points.
247 ! Find unstable points (sensible heat flux is upward):
248 DO i = 1, knon
249 IF (heatv(i) > 0.) THEN
250 unstbl(i) = .TRUE.
251 check(i) = .TRUE.
252 ELSE
253 unstbl(i) = .FALSE.
254 check(i) = .FALSE.
255 ENDIF
256 ENDDO
257
258 ! For the unstable case, compute velocity scale and the
259 ! convective temperature excess:
260 DO i = 1, knon
261 IF (check(i)) THEN
262 phiminv(i) = (1.-binm*pblh(i)/obklen(i))**onet
263
264 ! CALCUL DE wm
265 ! Ici on considerera que l'on est dans la couche de surf jusqu'a 100
266 ! On prend svt couche de surface=0.1*h mais on ne connait pas h
267 ! Dans la couche de surface
268 wm(i)= ustar(i)*phiminv(i)
269
270 ! forme Mathieu :
271 q_star = kqfs(i)/wm(i)
272 t_star = khfs(i)/wm(i)
273
274 therm(i) = sqrt( b1*(1.+2.*RETV*qT_th(i))*t_star**2 &
275 + (RETV*T2m(i))**2*b2*q_star**2 &
276 + max(0., 2.*RETV*T2m(i)*b212*q_star*t_star))
277
278 ! Theta et qT du thermique (forme H&B) avec exces
279 ! (attention, on ajoute therm(i) qui est virtuelle ...)
280 ! pourquoi pas sqrt(b1)*t_star ?
281 qT_th(i) = qT_th(i) + b2sr*q_star
282 ! new on diff\`ere le calcul de Theta_e
283 rhino(i, 1) = 0.
284 ENDIF
285 ENDDO
286
287 ! Improve pblh estimate for unstable conditions using the
288 ! convective temperature excess :
289 DO k = 2, isommet
290 DO i = 1, knon
291 IF (check(i)) THEN
292 zdu2 = u(i, k)**2 + v(i, k)**2
293 zdu2 = max(zdu2, 1e-20)
294 ! Theta_v environnement
295 zthvd=t(i, k)/s(i, k)*(1.+RETV*q(i, k))
296
297 ! et therm Theta_v (avec hypothese de constance de H&B,
298 zthvu = T2m(i)*(1.+RETV*qT_th(i)) + therm(i)
299
300 ! Le Ri par Theta_v
301 ! Niveau de ref 2m
302 rhino(i, k) = (z(i, k)-zref)*RG*(zthvd-zthvu) &
303 /(zdu2*0.5*(zthvd+zthvu))
304
305 IF (rhino(i, k).GE.ricr) THEN
306 pblh(i) = z(i, k-1) + (z(i, k-1)-z(i, k)) * &
307 (ricr-rhino(i, k-1))/(rhino(i, k-1)-rhino(i, k))
308 ! test04
309 pblh(i) = pblh(i) + 100.
310 pblT(i) = t(i, k-1) + (t(i, k)-t(i, k-1)) * &
311 (pblh(i)-z(i, k-1))/(z(i, k)-z(i, k-1))
312 check(i) = .FALSE.
313 ENDIF
314 ENDIF
315 ENDDO
316 ENDDO
317
318 ! Set pbl height to maximum value where computation exceeds number of
319 ! layers allowed
320 DO i = 1, knon
321 if (check(i)) pblh(i) = z(i, isommet)
322 ENDDO
323
324 ! PBL height must be greater than some minimum mechanical mixing depth
325 ! Several investigators have proposed minimum mechanical mixing depth
326 ! relationships as a function of the local friction velocity, u*. We
327 ! make use of a linear relationship of the form h = c u* where c=700.
328 ! The scaling arguments that give rise to this relationship most often
329 ! represent the coefficient c as some constant over the local coriolis
330 ! parameter. Here we make use of the experimental results of Koracin
331 ! and Berkowicz (1988) [BLM, Vol 43] for wich they recommend 0.07/f
332 ! where f was evaluated at 39.5 N and 52 N. Thus we use a typical mid
333 ! latitude value for f so that c = 0.07/f = 700.
334 DO i = 1, knon
335 pblmin = 700. * ustar(i)
336 pblh(i) = MAX(pblh(i), pblmin)
337 ! par exemple :
338 pblT(i) = t(i, 2) + (t(i, 3)-t(i, 2)) * &
339 (pblh(i)-z(i, 2))/(z(i, 3)-z(i, 2))
340 ENDDO
341
342 ! pblh is now available; do preparation for diffusivity calculation:
343 DO i = 1, knon
344 check(i) = .TRUE.
345 Zsat(i) = .FALSE.
346 ! omegafl utilise pour prolongement CAPE
347 omegafl(i) = .FALSE.
348 Cape(i) = 0.
349 EauLiq(i) = 0.
350 CTEI(i) = 0.
351
352 ! Do additional preparation for unstable cases only, set temperature
353 ! and moisture perturbations depending on stability.
354 ! Remarque : les formule sont prises dans leur forme CS
355 IF (unstbl(i)) THEN
356 ! Niveau de ref du thermique
357 zxt=(T2m(i)-zref*0.5*RG/RCPD/(1.+RVTMP2*qT_th(i))) &
358 *(1.+RETV*qT_th(i))
359 phiminv(i) = (1. - binm*pblh(i)/obklen(i))**onet
360 wm(i) = ustar(i)*phiminv(i)
361 ENDIF
362 ENDDO
363
364 ! Main level loop to compute the diffusivities and
365 ! counter-gradient terms:
366 loop_level: DO k = 2, isommet
367 ! Find levels within boundary layer:
368 DO i = 1, knon
369 zp(i) = z(i, k)
370 IF (zkmin == 0. .AND. zp(i) > pblh(i)) zp(i) = pblh(i)
371 ENDDO
372
373 ! For all layers, compute integral info and CTEI
374 DO i = 1, knon
375 if (check(i) .or. omegafl(i)) then
376 if (.not. Zsat(i)) then
377 T2 = T2m(i) * s(i, k)
378 ! thermodyn functions
379 qqsat= r2es * FOEEW(T2, RTT >= T2) / pplay(i, k)
380 qqsat=MIN(0.5, qqsat)
381 zcor=1./(1.-retv*qqsat)
382 qqsat=qqsat*zcor
383
384 if (qqsat < qT_th(i)) then
385 ! on calcule lcl
386 if (k == 2) then
387 plcl(i) = z(i, k)
388 else
389 plcl(i) = z(i, k-1) + (z(i, k-1)-z(i, k)) &
390 * (qT_th(i)-qsatbef(i)) / (qsatbef(i)-qqsat)
391 endif
392 Zsat(i) = .true.
393 endif
394 endif
395 qsatbef(i) = qqsat
396 ! cette ligne a deja ete faite normalement ?
397 endif
398 ENDDO
399 end DO loop_level
400
401 END SUBROUTINE HBTM
402
403 end module HBTM_m

Properties

Name Value
svn:executable

  ViewVC Help
Powered by ViewVC 1.1.21