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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 71 - (show annotations)
Mon Jul 8 18:12:18 2013 UTC (10 years, 9 months ago) by guez
File size: 17613 byte(s)
No reason to call inidissip in ce0l.

In inidissip, set random seed to 1 beacuse PGI compiler does not
accept all zeros.

dq was computed needlessly in caladvtrac. Arguments masse and dq of
calfis not used.

Replaced real*8 by double precision.

Pass arrays with inverted order of vertical levels to conflx instead
of creating local variables for this inside conflx.

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

Properties

Name Value
svn:executable

  ViewVC Help
Powered by ViewVC 1.1.21