GCC Code Coverage Report
Directory: ./ Exec Total Coverage
File: phylmd/nonlocal.F90 Lines: 0 172 0.0 %
Date: 2023-06-30 12:56:34 Branches: 0 92 0.0 %

Line Branch Exec Source
1
2
! $Header$
3
4
! ======================================================================
5
SUBROUTINE nonlocal(knon, paprs, pplay, tsol, beta, u, v, t, q, cd_h, cd_m, &
6
    pcfh, pcfm, cgh, cgq)
7
  USE dimphy
8
  IMPLICIT NONE
9
  ! ======================================================================
10
  ! Laurent Li (LMD/CNRS), le 30 septembre 1998
11
  ! Couche limite non-locale. Adaptation du code du CCM3.
12
  ! Code non teste, donc a ne pas utiliser.
13
  ! ======================================================================
14
  ! Nonlocal scheme that determines eddy diffusivities based on a
15
  ! diagnosed boundary layer height and a turbulent velocity scale.
16
  ! Also countergradient effects for heat and moisture are included.
17
18
  ! For more information, see Holtslag, A.A.M., and B.A. Boville, 1993:
19
  ! Local versus nonlocal boundary-layer diffusion in a global climate
20
  ! model. J. of Climate, vol. 6, 1825-1842.
21
  ! ======================================================================
22
  include "YOMCST.h"
23
24
  ! Arguments:
25
26
  INTEGER knon ! nombre de points a calculer
27
  REAL tsol(klon) ! temperature du sol (K)
28
  REAL beta(klon) ! efficacite d'evaporation (entre 0 et 1)
29
  REAL paprs(klon, klev+1) ! pression a inter-couche (Pa)
30
  REAL pplay(klon, klev) ! pression au milieu de couche (Pa)
31
  REAL u(klon, klev) ! vitesse U (m/s)
32
  REAL v(klon, klev) ! vitesse V (m/s)
33
  REAL t(klon, klev) ! temperature (K)
34
  REAL q(klon, klev) ! vapeur d'eau (kg/kg)
35
  REAL cd_h(klon) ! coefficient de friction au sol pour chaleur
36
  REAL cd_m(klon) ! coefficient de friction au sol pour vitesse
37
38
  INTEGER isommet
39
  REAL vk
40
  PARAMETER (vk=0.40)
41
  REAL ricr
42
  PARAMETER (ricr=0.4)
43
  REAL fak
44
  PARAMETER (fak=8.5)
45
  REAL fakn
46
  PARAMETER (fakn=7.2)
47
  REAL onet
48
  PARAMETER (onet=1.0/3.0)
49
  REAL t_coup
50
  PARAMETER (t_coup=273.15)
51
  REAL zkmin
52
  PARAMETER (zkmin=0.01)
53
  REAL betam
54
  PARAMETER (betam=15.0)
55
  REAL betah
56
  PARAMETER (betah=15.0)
57
  REAL betas
58
  PARAMETER (betas=5.0)
59
  REAL sffrac
60
  PARAMETER (sffrac=0.1)
61
  REAL binm
62
  PARAMETER (binm=betam*sffrac)
63
  REAL binh
64
  PARAMETER (binh=betah*sffrac)
65
  REAL ccon
66
  PARAMETER (ccon=fak*sffrac*vk)
67
68
  REAL z(klon, klev)
69
  REAL pcfm(klon, klev), pcfh(klon, klev)
70
71
  INTEGER i, k
72
  REAL zxt, zxq, zxu, zxv, zxmod, taux, tauy
73
  REAL zx_alf1, zx_alf2 ! parametres pour extrapolation
74
  REAL khfs(klon) ! surface kinematic heat flux [mK/s]
75
  REAL kqfs(klon) ! sfc kinematic constituent flux [m/s]
76
  REAL heatv(klon) ! surface virtual heat flux
77
  REAL ustar(klon)
78
  REAL rino(klon, klev) ! bulk Richardon no. from level to ref lev
79
  LOGICAL unstbl(klon) ! pts w/unstbl pbl (positive virtual ht flx)
80
  LOGICAL stblev(klon) ! stable pbl with levels within pbl
81
  LOGICAL unslev(klon) ! unstbl pbl with levels within pbl
82
  LOGICAL unssrf(klon) ! unstb pbl w/lvls within srf pbl lyr
83
  LOGICAL unsout(klon) ! unstb pbl w/lvls in outer pbl lyr
84
  LOGICAL check(klon) ! True=>chk if Richardson no.>critcal
85
  REAL pblh(klon)
86
  REAL cgh(klon, 2:klev) ! counter-gradient term for heat [K/m]
87
  REAL cgq(klon, 2:klev) ! counter-gradient term for constituents
88
  REAL cgs(klon, 2:klev) ! counter-gradient star (cg/flux)
89
  REAL obklen(klon)
90
  REAL ztvd, ztvu, zdu2
91
  REAL therm(klon) ! thermal virtual temperature excess
92
  REAL phiminv(klon) ! inverse phi function for momentum
93
  REAL phihinv(klon) ! inverse phi function for heat
94
  REAL wm(klon) ! turbulent velocity scale for momentum
95
  REAL fak1(klon) ! k*ustar*pblh
96
  REAL fak2(klon) ! k*wm*pblh
97
  REAL fak3(klon) ! fakn*wstr/wm
98
  REAL pblk(klon) ! level eddy diffusivity for momentum
99
  REAL pr(klon) ! Prandtl number for eddy diffusivities
100
  REAL zl(klon) ! zmzp / Obukhov length
101
  REAL zh(klon) ! zmzp / pblh
102
  REAL zzh(klon) ! (1-(zmzp/pblh))**2
103
  REAL wstr(klon) ! w*, convective velocity scale
104
  REAL zm(klon) ! current level height
105
  REAL zp(klon) ! current level height + one level up
106
  REAL zcor, zdelta, zcvm5, zxqs
107
  REAL fac, pblmin, zmzp, term
108
109
  include "YOETHF.h"
110
  include "FCTTRE.h"
111
112
  ! Initialisation
113
114
  isommet = klev
115
116
  DO i = 1, klon
117
    pcfh(i, 1) = cd_h(i)
118
    pcfm(i, 1) = cd_m(i)
119
  END DO
120
  DO k = 2, klev
121
    DO i = 1, klon
122
      pcfh(i, k) = zkmin
123
      pcfm(i, k) = zkmin
124
      cgs(i, k) = 0.0
125
      cgh(i, k) = 0.0
126
      cgq(i, k) = 0.0
127
    END DO
128
  END DO
129
130
  ! Calculer les hauteurs de chaque couche
131
132
  DO i = 1, knon
133
    z(i, 1) = rd*t(i, 1)/(0.5*(paprs(i,1)+pplay(i,1)))*(paprs(i,1)-pplay(i,1) &
134
      )/rg
135
  END DO
136
  DO k = 2, klev
137
    DO i = 1, knon
138
      z(i, k) = z(i, k-1) + rd*0.5*(t(i,k-1)+t(i,k))/paprs(i, k)*(pplay(i,k-1 &
139
        )-pplay(i,k))/rg
140
    END DO
141
  END DO
142
143
  DO i = 1, knon
144
    IF (thermcep) THEN
145
      zdelta = max(0., sign(1.,rtt-tsol(i)))
146
      zcvm5 = r5les*rlvtt*(1.-zdelta) + r5ies*rlstt*zdelta
147
      zcvm5 = zcvm5/rcpd/(1.0+rvtmp2*q(i,1))
148
      zxqs = r2es*foeew(tsol(i), zdelta)/paprs(i, 1)
149
      zxqs = min(0.5, zxqs)
150
      zcor = 1./(1.-retv*zxqs)
151
      zxqs = zxqs*zcor
152
    ELSE
153
      IF (tsol(i)<t_coup) THEN
154
        zxqs = qsats(tsol(i))/paprs(i, 1)
155
      ELSE
156
        zxqs = qsatl(tsol(i))/paprs(i, 1)
157
      END IF
158
    END IF
159
    zx_alf1 = 1.0
160
    zx_alf2 = 1.0 - zx_alf1
161
    zxt = (t(i,1)+z(i,1)*rg/rcpd/(1.+rvtmp2*q(i,1)))*(1.+retv*q(i,1))*zx_alf1 &
162
      + (t(i,2)+z(i,2)*rg/rcpd/(1.+rvtmp2*q(i,2)))*(1.+retv*q(i,2))*zx_alf2
163
    zxu = u(i, 1)*zx_alf1 + u(i, 2)*zx_alf2
164
    zxv = v(i, 1)*zx_alf1 + v(i, 2)*zx_alf2
165
    zxq = q(i, 1)*zx_alf1 + q(i, 2)*zx_alf2
166
    zxmod = 1.0 + sqrt(zxu**2+zxv**2)
167
    khfs(i) = (tsol(i)*(1.+retv*q(i,1))-zxt)*zxmod*cd_h(i)
168
    kqfs(i) = (zxqs-zxq)*zxmod*cd_h(i)*beta(i)
169
    heatv(i) = khfs(i) + 0.61*zxt*kqfs(i)
170
    taux = zxu*zxmod*cd_m(i)
171
    tauy = zxv*zxmod*cd_m(i)
172
    ustar(i) = sqrt(taux**2+tauy**2)
173
    ustar(i) = max(sqrt(ustar(i)), 0.01)
174
  END DO
175
176
  DO i = 1, knon
177
    rino(i, 1) = 0.0
178
    check(i) = .TRUE.
179
    pblh(i) = z(i, 1)
180
    obklen(i) = -t(i, 1)*ustar(i)**3/(rg*vk*heatv(i))
181
  END DO
182
183
184
  ! PBL height calculation:
185
  ! Search for level of pbl. Scan upward until the Richardson number between
186
  ! the first level and the current level exceeds the "critical" value.
187
188
  fac = 100.0
189
  DO k = 1, isommet
190
    DO i = 1, knon
191
      IF (check(i)) THEN
192
        zdu2 = (u(i,k)-u(i,1))**2 + (v(i,k)-v(i,1))**2 + fac*ustar(i)**2
193
        zdu2 = max(zdu2, 1.0E-20)
194
        ztvd = (t(i,k)+z(i,k)*0.5*rg/rcpd/(1.+rvtmp2*q(i, &
195
          k)))*(1.+retv*q(i,k))
196
        ztvu = (t(i,1)-z(i,k)*0.5*rg/rcpd/(1.+rvtmp2*q(i, &
197
          1)))*(1.+retv*q(i,1))
198
        rino(i, k) = (z(i,k)-z(i,1))*rg*(ztvd-ztvu)/(zdu2*0.5*(ztvd+ztvu))
199
        IF (rino(i,k)>=ricr) THEN
200
          pblh(i) = z(i, k-1) + (z(i,k-1)-z(i,k))*(ricr-rino(i,k-1))/(rino(i, &
201
            k-1)-rino(i,k))
202
          check(i) = .FALSE.
203
        END IF
204
      END IF
205
    END DO
206
  END DO
207
208
209
  ! Set pbl height to maximum value where computation exceeds number of
210
  ! layers allowed
211
212
  DO i = 1, knon
213
    IF (check(i)) pblh(i) = z(i, isommet)
214
  END DO
215
216
  ! Improve estimate of pbl height for the unstable points.
217
  ! Find unstable points (sensible heat flux is upward):
218
219
  DO i = 1, knon
220
    IF (heatv(i)>0.) THEN
221
      unstbl(i) = .TRUE.
222
      check(i) = .TRUE.
223
    ELSE
224
      unstbl(i) = .FALSE.
225
      check(i) = .FALSE.
226
    END IF
227
  END DO
228
229
  ! For the unstable case, compute velocity scale and the
230
  ! convective temperature excess:
231
232
  DO i = 1, knon
233
    IF (check(i)) THEN
234
      phiminv(i) = (1.-binm*pblh(i)/obklen(i))**onet
235
      wm(i) = ustar(i)*phiminv(i)
236
      therm(i) = heatv(i)*fak/wm(i)
237
      rino(i, 1) = 0.0
238
    END IF
239
  END DO
240
241
  ! Improve pblh estimate for unstable conditions using the
242
  ! convective temperature excess:
243
244
  DO k = 1, isommet
245
    DO i = 1, knon
246
      IF (check(i)) THEN
247
        zdu2 = (u(i,k)-u(i,1))**2 + (v(i,k)-v(i,1))**2 + fac*ustar(i)**2
248
        zdu2 = max(zdu2, 1.0E-20)
249
        ztvd = (t(i,k)+z(i,k)*0.5*rg/rcpd/(1.+rvtmp2*q(i, &
250
          k)))*(1.+retv*q(i,k))
251
        ztvu = (t(i,1)+therm(i)-z(i,k)*0.5*rg/rcpd/(1.+rvtmp2*q(i, &
252
          1)))*(1.+retv*q(i,1))
253
        rino(i, k) = (z(i,k)-z(i,1))*rg*(ztvd-ztvu)/(zdu2*0.5*(ztvd+ztvu))
254
        IF (rino(i,k)>=ricr) THEN
255
          pblh(i) = z(i, k-1) + (z(i,k-1)-z(i,k))*(ricr-rino(i,k-1))/(rino(i, &
256
            k-1)-rino(i,k))
257
          check(i) = .FALSE.
258
        END IF
259
      END IF
260
    END DO
261
  END DO
262
263
  ! Set pbl height to maximum value where computation exceeds number of
264
  ! layers allowed
265
266
  DO i = 1, knon
267
    IF (check(i)) pblh(i) = z(i, isommet)
268
  END DO
269
270
  ! Points for which pblh exceeds number of pbl layers allowed;
271
  ! set to maximum
272
273
  DO i = 1, knon
274
    IF (check(i)) pblh(i) = z(i, isommet)
275
  END DO
276
277
  ! PBL height must be greater than some minimum mechanical mixing depth
278
  ! Several investigators have proposed minimum mechanical mixing depth
279
  ! relationships as a function of the local friction velocity, u*.  We
280
  ! make use of a linear relationship of the form h = c u* where c=700.
281
  ! The scaling arguments that give rise to this relationship most often
282
  ! represent the coefficient c as some constant over the local coriolis
283
  ! parameter.  Here we make use of the experimental results of Koracin
284
  ! and Berkowicz (1988) [BLM, Vol 43] for wich they recommend 0.07/f
285
  ! where f was evaluated at 39.5 N and 52 N.  Thus we use a typical mid
286
  ! latitude value for f so that c = 0.07/f = 700.
287
288
  DO i = 1, knon
289
    pblmin = 700.0*ustar(i)
290
    pblh(i) = max(pblh(i), pblmin)
291
  END DO
292
293
  ! pblh is now available; do preparation for diffusivity calculation:
294
295
  DO i = 1, knon
296
    pblk(i) = 0.0
297
    fak1(i) = ustar(i)*pblh(i)*vk
298
299
    ! Do additional preparation for unstable cases only, set temperature
300
    ! and moisture perturbations depending on stability.
301
302
    IF (unstbl(i)) THEN
303
      zxt = (t(i,1)-z(i,1)*0.5*rg/rcpd/(1.+rvtmp2*q(i,1)))*(1.+retv*q(i,1))
304
      phiminv(i) = (1.-binm*pblh(i)/obklen(i))**onet
305
      phihinv(i) = sqrt(1.-binh*pblh(i)/obklen(i))
306
      wm(i) = ustar(i)*phiminv(i)
307
      fak2(i) = wm(i)*pblh(i)*vk
308
      wstr(i) = (heatv(i)*rg*pblh(i)/zxt)**onet
309
      fak3(i) = fakn*wstr(i)/wm(i)
310
    END IF
311
  END DO
312
313
  ! Main level loop to compute the diffusivities and
314
  ! counter-gradient terms:
315
316
  DO k = 2, isommet
317
318
    ! Find levels within boundary layer:
319
320
    DO i = 1, knon
321
      unslev(i) = .FALSE.
322
      stblev(i) = .FALSE.
323
      zm(i) = z(i, k-1)
324
      zp(i) = z(i, k)
325
      IF (zkmin==0.0 .AND. zp(i)>pblh(i)) zp(i) = pblh(i)
326
      IF (zm(i)<pblh(i)) THEN
327
        zmzp = 0.5*(zm(i)+zp(i))
328
        zh(i) = zmzp/pblh(i)
329
        zl(i) = zmzp/obklen(i)
330
        zzh(i) = 0.
331
        IF (zh(i)<=1.0) zzh(i) = (1.-zh(i))**2
332
333
        ! stblev for points zm < plbh and stable and neutral
334
        ! unslev for points zm < plbh and unstable
335
336
        IF (unstbl(i)) THEN
337
          unslev(i) = .TRUE.
338
        ELSE
339
          stblev(i) = .TRUE.
340
        END IF
341
      END IF
342
    END DO
343
344
    ! Stable and neutral points; set diffusivities; counter-gradient
345
    ! terms zero for stable case:
346
347
    DO i = 1, knon
348
      IF (stblev(i)) THEN
349
        IF (zl(i)<=1.) THEN
350
          pblk(i) = fak1(i)*zh(i)*zzh(i)/(1.+betas*zl(i))
351
        ELSE
352
          pblk(i) = fak1(i)*zh(i)*zzh(i)/(betas+zl(i))
353
        END IF
354
        pcfm(i, k) = pblk(i)
355
        pcfh(i, k) = pcfm(i, k)
356
      END IF
357
    END DO
358
359
    ! unssrf, unstable within surface layer of pbl
360
    ! unsout, unstable within outer   layer of pbl
361
362
    DO i = 1, knon
363
      unssrf(i) = .FALSE.
364
      unsout(i) = .FALSE.
365
      IF (unslev(i)) THEN
366
        IF (zh(i)<sffrac) THEN
367
          unssrf(i) = .TRUE.
368
        ELSE
369
          unsout(i) = .TRUE.
370
        END IF
371
      END IF
372
    END DO
373
374
    ! Unstable for surface layer; counter-gradient terms zero
375
376
    DO i = 1, knon
377
      IF (unssrf(i)) THEN
378
        term = (1.-betam*zl(i))**onet
379
        pblk(i) = fak1(i)*zh(i)*zzh(i)*term
380
        pr(i) = term/sqrt(1.-betah*zl(i))
381
      END IF
382
    END DO
383
384
    ! Unstable for outer layer; counter-gradient terms non-zero:
385
386
    DO i = 1, knon
387
      IF (unsout(i)) THEN
388
        pblk(i) = fak2(i)*zh(i)*zzh(i)
389
        cgs(i, k) = fak3(i)/(pblh(i)*wm(i))
390
        cgh(i, k) = khfs(i)*cgs(i, k)
391
        pr(i) = phiminv(i)/phihinv(i) + ccon*fak3(i)/fak
392
        cgq(i, k) = kqfs(i)*cgs(i, k)
393
      END IF
394
    END DO
395
396
    ! For all unstable layers, set diffusivities
397
398
    DO i = 1, knon
399
      IF (unslev(i)) THEN
400
        pcfm(i, k) = pblk(i)
401
        pcfh(i, k) = pblk(i)/pr(i)
402
      END IF
403
    END DO
404
  END DO ! end of level loop
405
406
  RETURN
407
END SUBROUTINE nonlocal