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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 38 - (show annotations)
Thu Jan 6 17:52:19 2011 UTC (13 years, 4 months ago) by guez
File size: 17501 byte(s)
Extracted ASCII art from "inigeom" into a separate text file in the
documentation.

"test_disvert" now creates a separate file for layer thicknesses.

Moved variables from module "yomcst" to module "suphec_m" because this
is where those variables are defined. Kept in "yomcst" only parameters
of Earth orbit. Gave the attribute "parameter" to some variables of
module "suphec_m".

Variables of module "yoethf" were defined in procedure "suphec". Moved
these definitions to a new procedure "yoethf" in module "yoethf_m".

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

Properties

Name Value
svn:executable

  ViewVC Help
Powered by ViewVC 1.1.21