/[lmdze]/trunk/Sources/phylmd/hbtm.f
ViewVC logotype

Contents of /trunk/Sources/phylmd/hbtm.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 149 - (show annotations)
Thu Jun 18 12:23:44 2015 UTC (8 years, 10 months ago) by guez
File size: 17370 byte(s)
In invert_zoom_x, call rtsafe instead of the equivalent coding that
was there. funcd needs to access a[0-4] and abs_y so we upgrade a[0-4]
from arguments of coefpoly to variables of module coefpoly_m and abs_y
from local variable of invert_zoom_x to private variable of module
invert_zoom_x_m.

Removed unused arguments t10m and q10m of hbtm.

1 module HBTM_m
2
3 IMPLICIT none
4
5 contains
6
7 SUBROUTINE HBTM(knon, paprs, pplay, t2m, q2m, ustar, flux_t, &
8 flux_q, u, v, t, q, pblh, cape, EauLiq, ctei, pblT, therm, trmb1, &
9 trmb2, trmb3, plcl)
10
11 ! D'apr\'es Holstag et Boville et Troen et Mahrt
12 ! JAS 47 BLM
13 ! Algorithme th\'ese Anne Mathieu
14 ! Crit\'ere d'entra\^inement Peter Duynkerke (JAS 50)
15 ! written by: Anne MATHIEU and Alain LAHELLEC, 22nd November 1999
16 ! features : implem. exces Mathieu
17
18 ! modifications : decembre 99 passage th a niveau plus bas. voir fixer
19 ! la prise du th a z/Lambda = -.2 (max Ray)
20 ! Autre algo : entrainement ~ Theta+v =cste mais comment=>The?
21 ! on peut fixer q a .7 qsat (cf. non adiabatique) => T2 et The2
22 ! voir aussi //KE pblh = niveau The_e ou l = env.
23
24 ! fin therm a la HBTM passage a forme Mathieu 12/09/2001
25
26 ! Adaptation a LMDZ version couplee Pour le moment on fait passer
27 ! en argument les grandeurs de surface : flux, t, q2m, t, on va
28 ! utiliser systematiquement les grandeurs a 2m mais on garde la
29 ! possibilit\'e de changer si besoin est (jusqu'à pr\'esent la
30 ! forme de HB avec le 1er niveau modele etait conservee)
31
32 USE dimphy, ONLY: klev, klon
33 USE suphec_m, ONLY: rcpd, rd, retv, rg, rkappa, rlvtt, rtt, rv
34 USE yoethf_m, ONLY: r2es, rvtmp2
35 USE fcttre, ONLY: foeew
36
37 REAL RLvCp, REPS
38 ! Arguments:
39
40 ! nombre de points a calculer
41 INTEGER, intent(in):: knon
42
43 REAL, intent(in):: t2m(klon) ! temperature a 2 m
44 ! q a 2 et 10m
45 REAL q2m(klon)
46 REAL ustar(klon)
47 ! pression a inter-couche (Pa)
48 REAL paprs(klon, klev+1)
49 ! pression au milieu de couche (Pa)
50 REAL pplay(klon, klev)
51 ! Flux
52 REAL flux_t(klon, klev), flux_q(klon, klev)
53 ! vitesse U (m/s)
54 REAL u(klon, klev)
55 ! vitesse V (m/s)
56 REAL v(klon, klev)
57 ! temperature (K)
58 REAL t(klon, klev)
59 ! vapeur d'eau (kg/kg)
60 REAL q(klon, klev)
61
62 INTEGER isommet
63 ! limite max sommet pbl
64 PARAMETER (isommet=klev)
65 REAL vk
66 ! Von Karman => passer a .41 ! cf U.Olgstrom
67 PARAMETER (vk=0.35)
68 REAL ricr
69 PARAMETER (ricr=0.4)
70 REAL fak
71 ! b calcul du Prandtl et de dTetas
72 PARAMETER (fak=8.5)
73 REAL fakn
74 ! a
75 PARAMETER (fakn=7.2)
76 REAL onet
77 PARAMETER (onet=1.0/3.0)
78 REAL t_coup
79 PARAMETER(t_coup=273.15)
80 REAL zkmin
81 PARAMETER (zkmin=0.01)
82 REAL betam
83 ! pour Phim / h dans la S.L stable
84 PARAMETER (betam=15.0)
85 REAL betah
86 PARAMETER (betah=15.0)
87 REAL betas
88 ! Phit dans la S.L. stable (mais 2 formes /
89 PARAMETER (betas=5.0)
90 ! z/OBL<>1
91 REAL sffrac
92 ! S.L. = z/h < .1
93 PARAMETER (sffrac=0.1)
94 REAL binm
95 PARAMETER (binm=betam*sffrac)
96 REAL binh
97 PARAMETER (binh=betah*sffrac)
98 REAL ccon
99 PARAMETER (ccon=fak*sffrac*vk)
100
101 REAL q_star, t_star
102 ! Lambert correlations T' q' avec T* q*
103 REAL b1, b2, b212, b2sr
104 PARAMETER (b1=70., b2=20.)
105
106 REAL z(klon, klev)
107
108 REAL zref
109 ! Niveau de ref a 2m peut eventuellement
110 PARAMETER (zref=2.)
111 ! etre choisi a 10m
112
113 INTEGER i, k
114 REAL zxt
115 ! surface kinematic heat flux [mK/s]
116 REAL khfs(klon)
117 ! sfc kinematic constituent flux [m/s]
118 REAL kqfs(klon)
119 ! surface virtual heat flux
120 REAL heatv(klon)
121 ! bulk Richardon no. mais en Theta_v
122 REAL rhino(klon, klev)
123 ! pts w/unstbl pbl (positive virtual ht flx)
124 LOGICAL unstbl(klon)
125 ! stable pbl with levels within pbl
126 LOGICAL stblev(klon)
127 ! unstbl pbl with levels within pbl
128 LOGICAL unslev(klon)
129 ! unstb pbl w/lvls within srf pbl lyr
130 LOGICAL unssrf(klon)
131 ! unstb pbl w/lvls in outer pbl lyr
132 LOGICAL unsout(klon)
133 LOGICAL check(klon) ! Richardson number > critical
134 ! flag de prolongerment cape pour pt Omega
135 LOGICAL omegafl(klon)
136 REAL pblh(klon)
137 REAL pblT(klon)
138 REAL plcl(klon)
139
140 ! Monin-Obukhov lengh
141 REAL obklen(klon)
142
143 REAL zdu2
144 ! thermal virtual temperature excess
145 REAL therm(klon)
146 REAL trmb1(klon), trmb2(klon), trmb3(klon)
147 ! Algorithme thermique
148 REAL s(klon, klev) ! [P/Po]^Kappa milieux couches
149 ! equivalent potential temperature of therma
150 REAL The_th(klon)
151 ! total water of thermal
152 REAL qT_th(klon)
153 ! T thermique niveau precedent
154 REAL Tbef(klon)
155 REAL qsatbef(klon)
156 ! le thermique est sature
157 LOGICAL Zsat(klon)
158 ! Cape du thermique
159 REAL Cape(klon)
160 ! Cape locale
161 REAL Kape(klon)
162 ! Eau liqu integr du thermique
163 REAL EauLiq(klon)
164 ! Critere d'instab d'entrainmt des nuages de
165 REAL ctei(klon)
166 REAL aa, zthvd, zthvu, qqsat
167 REAL a1, a2, a3
168 REAL t2
169
170 ! inverse phi function for momentum
171 REAL phiminv(klon)
172 ! inverse phi function for heat
173 REAL phihinv(klon)
174 ! turbulent velocity scale for momentum
175 REAL wm(klon)
176 ! k*ustar*pblh
177 REAL fak1(klon)
178 ! k*wm*pblh
179 REAL fak2(klon)
180 ! fakn*wstr/wm
181 REAL fak3(klon)
182 ! level eddy diffusivity for momentum
183 REAL pblk(klon)
184 ! Prandtl number for eddy diffusivities
185 REAL pr(klon)
186 ! zmzp / Obukhov length
187 REAL zl(klon)
188 ! zmzp / pblh
189 REAL zh(klon)
190 ! (1-(zmzp/pblh))**2
191 REAL zzh(klon)
192 ! w*, convective velocity scale
193 REAL wstr(klon)
194 ! current level height
195 REAL zm(klon)
196 ! current level height + one level up
197 REAL zp(klon)
198 REAL zcor
199
200 REAL fac, pblmin, zmzp, term
201
202 !-----------------------------------------------------------------
203
204 ! initialisations
205 q_star = 0
206 t_star = 0
207
208 b212=sqrt(b1*b2)
209 b2sr=sqrt(b2)
210
211 ! Initialisation
212 RLvCp = RLVTT/RCPD
213 REPS = RD/RV
214
215 ! Calculer les hauteurs de chaque couche
216 ! (geopotentielle Int_dp/ro = Int_[Rd.T.dp/p] z = geop/g)
217 ! pourquoi ne pas utiliser Phi/RG ?
218 DO i = 1, knon
219 z(i, 1) = RD * t(i, 1) / (0.5*(paprs(i, 1)+pplay(i, 1))) &
220 * (paprs(i, 1)-pplay(i, 1)) / RG
221 s(i, 1) = (pplay(i, 1)/paprs(i, 1))**RKappa
222 ENDDO
223 ! s(k) = [pplay(k)/ps]^kappa
224 ! + + + + + + + + + pplay <-> s(k) t dp=pplay(k-1)-pplay(k)
225 ! ----------------- paprs <-> sig(k)
226 ! + + + + + + + + + pplay <-> s(k-1)
227 ! + + + + + + + + + pplay <-> s(1) t dp=paprs-pplay z(1)
228 ! ----------------- paprs <-> sig(1)
229
230 DO k = 2, klev
231 DO i = 1, knon
232 z(i, k) = z(i, k-1) &
233 + RD * 0.5*(t(i, k-1)+t(i, k)) / paprs(i, k) &
234 * (pplay(i, k-1)-pplay(i, k)) / RG
235 s(i, k) = (pplay(i, k) / paprs(i, 1))**RKappa
236 ENDDO
237 ENDDO
238
239 ! Determination des grandeurs de surface
240 DO i = 1, knon
241 ! Niveau de ref choisi a 2m
242 zxt = t2m(i)
243
244 ! convention >0 vers le bas ds lmdz
245 khfs(i) = - flux_t(i, 1)*zxt*Rd / (RCPD*paprs(i, 1))
246 kqfs(i) = - flux_q(i, 1)*zxt*Rd / (paprs(i, 1))
247 ! verifier que khfs et kqfs sont bien de la forme w'l'
248 heatv(i) = khfs(i) + 0.608*zxt*kqfs(i)
249 ! a comparer aussi aux sorties de clqh : flux_T/RoCp et flux_q/RoLv
250 ! Theta et qT du thermique sans exces (interpolin vers surf)
251 ! chgt de niveau du thermique (jeudi 30/12/1999)
252 ! (interpolation lineaire avant integration phi_h)
253 qT_th(i) = q2m(i)
254 ENDDO
255
256 DO i = 1, knon
257 ! Global Richardson
258 rhino(i, 1) = 0.0
259 check(i) = .TRUE.
260 ! on initialise pblh a l'altitude du 1er niv
261 pblh(i) = z(i, 1)
262 plcl(i) = 6000.
263 ! Lambda = -u*^3 / (alpha.g.kvon.<w'Theta'v>
264 obklen(i) = -t(i, 1)*ustar(i)**3/(RG*vk*heatv(i))
265 trmb1(i) = 0.
266 trmb2(i) = 0.
267 trmb3(i) = 0.
268 ENDDO
269
270 ! PBL height calculation: Search for level of pbl. Scan upward
271 ! until the Richardson number between the first level and the
272 ! current level exceeds the "critical" value. (bonne idee Nu de
273 ! separer le Ric et l'exces de temp du thermique)
274 fac = 100.
275 DO k = 2, isommet
276 DO i = 1, knon
277 IF (check(i)) THEN
278 ! pourquoi / niveau 1 (au lieu du sol) et le terme en u*^2 ?
279 zdu2 = u(i, k)**2+v(i, k)**2
280 zdu2 = max(zdu2, 1.0e-20)
281 ! Theta_v environnement
282 zthvd=t(i, k)/s(i, k)*(1.+RETV*q(i, k))
283
284 ! therm Theta_v sans exces (avec hypothese fausse de H&B, sinon,
285 ! passer par Theta_e et virpot)
286 zthvu = T2m(i)*(1.+RETV*qT_th(i))
287 ! Le Ri par Theta_v
288 ! On a nveau de ref a 2m ???
289 rhino(i, k) = (z(i, k)-zref)*RG*(zthvd-zthvu) &
290 /(zdu2*0.5*(zthvd+zthvu))
291
292 IF (rhino(i, k).GE.ricr) THEN
293 pblh(i) = z(i, k-1) + (z(i, k-1)-z(i, k)) * &
294 (ricr-rhino(i, k-1))/(rhino(i, k-1)-rhino(i, k))
295 ! test04
296 pblh(i) = pblh(i) + 100.
297 pblT(i) = t(i, k-1) + (t(i, k)-t(i, k-1)) * &
298 (pblh(i)-z(i, k-1))/(z(i, k)-z(i, k-1))
299 check(i) = .FALSE.
300 ENDIF
301 ENDIF
302 ENDDO
303 ENDDO
304
305 ! Set pbl height to maximum value where computation exceeds number of
306 ! layers allowed
307 DO i = 1, knon
308 if (check(i)) pblh(i) = z(i, isommet)
309 ENDDO
310
311 ! Improve estimate of pbl height for the unstable points.
312 ! Find unstable points (sensible heat flux is upward):
313 DO i = 1, knon
314 IF (heatv(i) > 0.) THEN
315 unstbl(i) = .TRUE.
316 check(i) = .TRUE.
317 ELSE
318 unstbl(i) = .FALSE.
319 check(i) = .FALSE.
320 ENDIF
321 ENDDO
322
323 ! For the unstable case, compute velocity scale and the
324 ! convective temperature excess:
325 DO i = 1, knon
326 IF (check(i)) THEN
327 phiminv(i) = (1.-binm*pblh(i)/obklen(i))**onet
328
329 ! CALCUL DE wm
330 ! Ici on considerera que l'on est dans la couche de surf jusqu'a 100
331 ! On prend svt couche de surface=0.1*h mais on ne connait pas h
332 ! Dans la couche de surface
333 wm(i)= ustar(i)*phiminv(i)
334
335 ! forme Mathieu :
336 q_star = kqfs(i)/wm(i)
337 t_star = khfs(i)/wm(i)
338
339 a1=b1*(1.+2.*RETV*qT_th(i))*t_star**2
340 a2=(RETV*T2m(i))**2*b2*q_star**2
341 a3=2.*RETV*T2m(i)*b212*q_star*t_star
342 aa=a1+a2+a3
343
344 therm(i) = sqrt( b1*(1.+2.*RETV*qT_th(i))*t_star**2 &
345 + (RETV*T2m(i))**2*b2*q_star**2 &
346 + max(0., 2.*RETV*T2m(i)*b212*q_star*t_star))
347
348 ! Theta et qT du thermique (forme H&B) avec exces
349 ! (attention, on ajoute therm(i) qui est virtuelle ...)
350 ! pourquoi pas sqrt(b1)*t_star ?
351 qT_th(i) = qT_th(i) + b2sr*q_star
352 ! new on differre le calcul de Theta_e
353 rhino(i, 1) = 0.
354 ENDIF
355 ENDDO
356
357 ! Improve pblh estimate for unstable conditions using the
358 ! convective temperature excess :
359 DO k = 2, isommet
360 DO i = 1, knon
361 IF (check(i)) THEN
362 zdu2 = u(i, k)**2 + v(i, k)**2
363 zdu2 = max(zdu2, 1e-20)
364 ! Theta_v environnement
365 zthvd=t(i, k)/s(i, k)*(1.+RETV*q(i, k))
366
367 ! et therm Theta_v (avec hypothese de constance de H&B,
368 zthvu = T2m(i)*(1.+RETV*qT_th(i)) + therm(i)
369
370 ! Le Ri par Theta_v
371 ! Niveau de ref 2m
372 rhino(i, k) = (z(i, k)-zref)*RG*(zthvd-zthvu) &
373 /(zdu2*0.5*(zthvd+zthvu))
374
375 IF (rhino(i, k).GE.ricr) THEN
376 pblh(i) = z(i, k-1) + (z(i, k-1)-z(i, k)) * &
377 (ricr-rhino(i, k-1))/(rhino(i, k-1)-rhino(i, k))
378 ! test04
379 pblh(i) = pblh(i) + 100.
380 pblT(i) = t(i, k-1) + (t(i, k)-t(i, k-1)) * &
381 (pblh(i)-z(i, k-1))/(z(i, k)-z(i, k-1))
382 check(i) = .FALSE.
383 ENDIF
384 ENDIF
385 ENDDO
386 ENDDO
387
388 ! Set pbl height to maximum value where computation exceeds number of
389 ! layers allowed
390 DO i = 1, knon
391 if (check(i)) pblh(i) = z(i, isommet)
392 ENDDO
393
394 ! PBL height must be greater than some minimum mechanical mixing depth
395 ! Several investigators have proposed minimum mechanical mixing depth
396 ! relationships as a function of the local friction velocity, u*. We
397 ! make use of a linear relationship of the form h = c u* where c=700.
398 ! The scaling arguments that give rise to this relationship most often
399 ! represent the coefficient c as some constant over the local coriolis
400 ! parameter. Here we make use of the experimental results of Koracin
401 ! and Berkowicz (1988) [BLM, Vol 43] for wich they recommend 0.07/f
402 ! where f was evaluated at 39.5 N and 52 N. Thus we use a typical mid
403 ! latitude value for f so that c = 0.07/f = 700.
404 DO i = 1, knon
405 pblmin = 700. * ustar(i)
406 pblh(i) = MAX(pblh(i), pblmin)
407 ! par exemple :
408 pblT(i) = t(i, 2) + (t(i, 3)-t(i, 2)) * &
409 (pblh(i)-z(i, 2))/(z(i, 3)-z(i, 2))
410 ENDDO
411
412 ! pblh is now available; do preparation for diffusivity calculation:
413 DO i = 1, knon
414 check(i) = .TRUE.
415 Zsat(i) = .FALSE.
416 ! omegafl utilise pour prolongement CAPE
417 omegafl(i) = .FALSE.
418 Cape(i) = 0.
419 Kape(i) = 0.
420 EauLiq(i) = 0.
421 CTEI(i) = 0.
422 pblk(i) = 0.0
423 fak1(i) = ustar(i)*pblh(i)*vk
424
425 ! Do additional preparation for unstable cases only, set temperature
426 ! and moisture perturbations depending on stability.
427 ! Remarque : les formule sont prises dans leur forme CS
428 IF (unstbl(i)) THEN
429 ! Niveau de ref du thermique
430 zxt=(T2m(i)-zref*0.5*RG/RCPD/(1.+RVTMP2*qT_th(i))) &
431 *(1.+RETV*qT_th(i))
432 phiminv(i) = (1. - binm*pblh(i)/obklen(i))**onet
433 phihinv(i) = sqrt(1. - binh*pblh(i)/obklen(i))
434 wm(i) = ustar(i)*phiminv(i)
435 fak2(i) = wm(i)*pblh(i)*vk
436 wstr(i) = (heatv(i)*RG*pblh(i)/zxt)**onet
437 fak3(i) = fakn*wstr(i)/wm(i)
438 ENDIF
439 ! Computes Theta_e for thermal (all cases : to be modified)
440 ! attention ajout therm(i) = virtuelle
441 The_th(i) = T2m(i) + therm(i) + RLvCp*qT_th(i)
442 ENDDO
443
444 ! Main level loop to compute the diffusivities and
445 ! counter-gradient terms:
446 loop_level: DO k = 2, isommet
447 ! Find levels within boundary layer:
448 DO i = 1, knon
449 unslev(i) = .FALSE.
450 stblev(i) = .FALSE.
451 zm(i) = z(i, k-1)
452 zp(i) = z(i, k)
453 IF (zkmin == 0. .AND. zp(i) > pblh(i)) zp(i) = pblh(i)
454 IF (zm(i) < pblh(i)) THEN
455 zmzp = 0.5*(zm(i) + zp(i))
456 zh(i) = zmzp/pblh(i)
457 zl(i) = zmzp/obklen(i)
458 zzh(i) = 0.
459 IF (zh(i) <= 1.) zzh(i) = (1. - zh(i))**2
460
461 ! stblev for points zm < plbh and stable and neutral
462 ! unslev for points zm < plbh and unstable
463 IF (unstbl(i)) THEN
464 unslev(i) = .TRUE.
465 ELSE
466 stblev(i) = .TRUE.
467 ENDIF
468 ENDIF
469 ENDDO
470
471 ! Stable and neutral points; set diffusivities; counter-gradient
472 ! terms zero for stable case:
473 DO i = 1, knon
474 IF (stblev(i)) THEN
475 IF (zl(i) <= 1.) THEN
476 pblk(i) = fak1(i)*zh(i)*zzh(i)/(1. + betas*zl(i))
477 ELSE
478 pblk(i) = fak1(i)*zh(i)*zzh(i)/(betas + zl(i))
479 ENDIF
480 ENDIF
481 ENDDO
482
483 ! unssrf, unstable within surface layer of pbl
484 ! unsout, unstable within outer layer of pbl
485 DO i = 1, knon
486 unssrf(i) = .FALSE.
487 unsout(i) = .FALSE.
488 IF (unslev(i)) THEN
489 IF (zh(i) < sffrac) THEN
490 unssrf(i) = .TRUE.
491 ELSE
492 unsout(i) = .TRUE.
493 ENDIF
494 ENDIF
495 ENDDO
496
497 ! Unstable for surface layer; counter-gradient terms zero
498 DO i = 1, knon
499 IF (unssrf(i)) THEN
500 term = (1. - betam*zl(i))**onet
501 pblk(i) = fak1(i)*zh(i)*zzh(i)*term
502 pr(i) = term/sqrt(1. - betah*zl(i))
503 ENDIF
504 ENDDO
505
506 ! Unstable for outer layer; counter-gradient terms non-zero:
507 DO i = 1, knon
508 IF (unsout(i)) THEN
509 pblk(i) = fak2(i)*zh(i)*zzh(i)
510 pr(i) = phiminv(i)/phihinv(i) + ccon*fak3(i)/fak
511 ENDIF
512 ENDDO
513
514 ! For all layers, compute integral info and CTEI
515 DO i = 1, knon
516 if (check(i) .or. omegafl(i)) then
517 if (.not. Zsat(i)) then
518 T2 = T2m(i) * s(i, k)
519 ! thermodyn functions
520 qqsat= r2es * FOEEW(T2, RTT >= T2) / pplay(i, k)
521 qqsat=MIN(0.5, qqsat)
522 zcor=1./(1.-retv*qqsat)
523 qqsat=qqsat*zcor
524
525 if (qqsat < qT_th(i)) then
526 ! on calcule lcl
527 if (k == 2) then
528 plcl(i) = z(i, k)
529 else
530 plcl(i) = z(i, k-1) + (z(i, k-1)-z(i, k)) &
531 * (qT_th(i)-qsatbef(i)) / (qsatbef(i)-qqsat)
532 endif
533 Zsat(i) = .true.
534 Tbef(i) = T2
535 endif
536 endif
537 qsatbef(i) = qqsat
538 ! cette ligne a deja ete faite normalement ?
539 endif
540 ENDDO
541 end DO loop_level
542
543 END SUBROUTINE HBTM
544
545 end module HBTM_m

Properties

Name Value
svn:executable

  ViewVC Help
Powered by ViewVC 1.1.21