/[MITgcm]/MITgcm/pkg/kpp/kpp_routines.F
ViewVC logotype

Contents of /MITgcm/pkg/kpp/kpp_routines.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.30 - (show annotations) (download)
Tue May 1 04:09:25 2007 UTC (17 years, 2 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint59a
Changes since 1.29: +53 -28 lines
 add more code to have only Ri-number based mixing in shelf ice caverns
 add myThid to all kpp routines (long overdue)

1 C $Header: /u/gcmpack/MITgcm/pkg/kpp/kpp_routines.F,v 1.29 2007/04/30 13:49:40 jmc Exp $
2 C $Name: $
3
4 #include "KPP_OPTIONS.h"
5
6 C-- File kpp_routines.F: subroutines needed to implement
7 C-- KPP vertical mixing scheme
8 C-- Contents
9 C-- o KPPMIX - Main driver and interface routine.
10 C-- o BLDEPTH - Determine oceanic planetary boundary layer depth.
11 C-- o WSCALE - Compute turbulent velocity scales.
12 C-- o RI_IWMIX - Compute interior viscosity diffusivity coefficients.
13 C-- o Z121 - Apply 121 vertical smoothing.
14 C-- o SMOOTH_HORIZ- Apply horizontal smoothing to global array.
15 C-- o BLMIX - Boundary layer mixing coefficients.
16 C-- o ENHANCE - Enhance diffusivity at boundary layer interface.
17 C-- o STATEKPP - Compute buoyancy-related input arrays.
18
19 c***********************************************************************
20
21 SUBROUTINE KPPMIX (
22 I kmtj, shsq, dvsq, ustar, msk
23 I , bo, bosol, dbloc, Ritop, coriol
24 I , diffusKzS, diffusKzT
25 I , ikppkey
26 O , diffus
27 U , ghat
28 O , hbl
29 I , mytime, mythid )
30
31 c-----------------------------------------------------------------------
32 c
33 c Main driver subroutine for kpp vertical mixing scheme and
34 c interface to greater ocean model
35 c
36 c written by: bill large, june 6, 1994
37 c modified by: jan morzel, june 30, 1994
38 c bill large, august 11, 1994
39 c bill large, january 25, 1995 : "dVsq" and 1d code
40 c detlef stammer, august 1997 : for use with MIT GCM Classic
41 c d. menemenlis, june 1998 : for use with MIT GCM UV
42 c
43 c-----------------------------------------------------------------------
44
45 IMPLICIT NONE
46
47 #include "SIZE.h"
48 #include "EEPARAMS.h"
49 #include "PARAMS.h"
50 #include "KPP_PARAMS.h"
51
52 c input
53 c myTime - current time in simulation
54 c myThid - thread number for this instance of the routine
55 c kmtj (imt) - number of vertical layers on this row
56 c msk (imt) - surface mask (=1 if water, =0 otherwise)
57 c shsq (imt,Nr) - (local velocity shear)^2 ((m/s)^2)
58 c dvsq (imt,Nr) - (velocity shear re sfc)^2 ((m/s)^2)
59 c ustar (imt) - surface friction velocity (m/s)
60 c bo (imt) - surface turbulent buoy. forcing (m^2/s^3)
61 c bosol (imt) - radiative buoyancy forcing (m^2/s^3)
62 c dbloc (imt,Nr) - local delta buoyancy across interfaces (m/s^2)
63 c dblocSm(imt,Nr) - horizontally smoothed dbloc (m/s^2)
64 c stored in ghat to save space
65 c Ritop (imt,Nr) - numerator of bulk Richardson Number
66 c (zref-z) * delta buoyancy w.r.t. surface ((m/s)^2)
67 c coriol (imt) - Coriolis parameter (1/s)
68 c diffusKzS(imt,Nr)- background vertical diffusivity for scalars (m^2/s)
69 c diffusKzT(imt,Nr)- background vertical diffusivity for theta (m^2/s)
70 c note: there is a conversion from 2-D to 1-D for input output variables,
71 c e.g., hbl(sNx,sNy) -> hbl(imt),
72 c where hbl(i,j) -> hbl((j-1)*sNx+i)
73
74 _RL mytime
75 integer mythid
76 integer kmtj (imt )
77 _RL shsq (imt,Nr)
78 _RL dvsq (imt,Nr)
79 _RL ustar (imt )
80 _RL bo (imt )
81 _RL bosol (imt )
82 _RL dbloc (imt,Nr)
83 _RL Ritop (imt,Nr)
84 _RL coriol (imt )
85 _RS msk (imt )
86 _RL diffusKzS(imt,Nr)
87 _RL diffusKzT(imt,Nr)
88
89 integer ikppkey
90
91 c output
92 c diffus (imt,1) - vertical viscosity coefficient (m^2/s)
93 c diffus (imt,2) - vertical scalar diffusivity (m^2/s)
94 c diffus (imt,3) - vertical temperature diffusivity (m^2/s)
95 c ghat (imt) - nonlocal transport coefficient (s/m^2)
96 c hbl (imt) - mixing layer depth (m)
97
98 _RL diffus(imt,0:Nrp1,mdiff)
99 _RL ghat (imt,Nr)
100 _RL hbl (imt)
101
102 #ifdef ALLOW_KPP
103
104 c local
105 c kbl (imt ) - index of first grid level below hbl
106 c bfsfc (imt ) - surface buoyancy forcing (m^2/s^3)
107 c casea (imt ) - 1 in case A; 0 in case B
108 c stable (imt ) - 1 in stable forcing; 0 if unstable
109 c dkm1 (imt, mdiff) - boundary layer diffusivity at kbl-1 level
110 c blmc (imt,Nr,mdiff) - boundary layer mixing coefficients
111 c sigma (imt ) - normalized depth (d / hbl)
112 c Rib (imt,Nr ) - bulk Richardson number
113
114 integer kbl(imt )
115 _RL bfsfc (imt )
116 _RL casea (imt )
117 _RL stable (imt )
118 _RL dkm1 (imt, mdiff)
119 _RL blmc (imt,Nr,mdiff)
120 _RL sigma (imt )
121 _RL Rib (imt,Nr )
122
123 integer i, k, md
124
125 c-----------------------------------------------------------------------
126 c compute interior mixing coefficients everywhere, due to constant
127 c internal wave activity, static instability, and local shear
128 c instability.
129 c (ghat is temporary storage for horizontally smoothed dbloc)
130 c-----------------------------------------------------------------------
131
132 cph(
133 cph these storings avoid recomp. of Ri_iwmix
134 CADJ STORE ghat = comlev1_kpp, key = ikppkey
135 CADJ STORE dbloc = comlev1_kpp, key = ikppkey
136 cph)
137 call Ri_iwmix (
138 I kmtj, shsq, dbloc, ghat
139 I , diffusKzS, diffusKzT
140 I , ikppkey
141 O , diffus )
142
143 cph(
144 cph these storings avoid recomp. of Ri_iwmix
145 cph DESPITE TAFs 'not necessary' warning!
146 CADJ STORE dbloc = comlev1_kpp, key = ikppkey
147 CADJ STORE shsq = comlev1_kpp, key = ikppkey
148 CADJ STORE ghat = comlev1_kpp, key = ikppkey
149 CADJ STORE diffus = comlev1_kpp, key = ikppkey
150 cph)
151
152 c-----------------------------------------------------------------------
153 c set seafloor values to zero and fill extra "Nrp1" coefficients
154 c for blmix
155 c-----------------------------------------------------------------------
156
157 do md = 1, mdiff
158 do i = 1,imt
159 do k=kmtj(i),Nrp1
160 diffus(i,k,md) = 0.0
161 end do
162 end do
163 end do
164
165 c-----------------------------------------------------------------------
166 c compute boundary layer mixing coefficients:
167 c
168 c diagnose the new boundary layer depth
169 c-----------------------------------------------------------------------
170
171 call bldepth (
172 I kmtj
173 I , dvsq, dbloc, Ritop, ustar, bo, bosol, coriol
174 I , ikppkey
175 O , hbl, bfsfc, stable, casea, kbl, Rib, sigma
176 I , mytime, mythid )
177
178 CADJ STORE hbl,bfsfc,stable,casea,kbl = comlev1_kpp, key = ikppkey
179
180 c-----------------------------------------------------------------------
181 c compute boundary layer diffusivities
182 c-----------------------------------------------------------------------
183
184 call blmix (
185 I ustar, bfsfc, hbl, stable, casea, diffus, kbl
186 O , dkm1, blmc, ghat, sigma, ikppkey
187 I , mythid )
188 cph(
189 CADJ STORE dkm1,blmc,ghat = comlev1_kpp, key = ikppkey
190 CADJ STORE hbl, kbl, diffus, casea = comlev1_kpp, key = ikppkey
191 cph)
192
193 c-----------------------------------------------------------------------
194 c enhance diffusivity at interface kbl - 1
195 c-----------------------------------------------------------------------
196
197 call enhance (
198 I dkm1, hbl, kbl, diffus, casea
199 U , ghat
200 O , blmc
201 I , mythid )
202
203 cph(
204 cph avoids recomp. of enhance
205 CADJ STORE blmc = comlev1_kpp, key = ikppkey
206 cph)
207
208 c-----------------------------------------------------------------------
209 c combine interior and boundary layer coefficients and nonlocal term
210 c !!!NOTE!!! In shallow (2-level) regions and for shallow mixed layers
211 c (< 1 level), diffusivity blmc can become negative. The max-s below
212 c are a hack until this problem is properly diagnosed and fixed.
213 c-----------------------------------------------------------------------
214 do k = 1, Nr
215 do i = 1, imt
216 if (k .lt. kbl(i)) then
217 #ifdef ALLOW_SHELFICE
218 C when there is shelfice on top (msk(i)=0), reset the boundary layer
219 C mixing coefficients blmc to pure Ri-number based mixing
220 blmc(i,k,1) = max ( blmc(i,k,1)*msk(i),
221 & diffus(i,k,1) )
222 blmc(i,k,2) = max ( blmc(i,k,2)*msk(i),
223 & diffus(i,k,2) )
224 blmc(i,k,3) = max ( blmc(i,k,3)*msk(i),
225 & diffus(i,k,3) )
226 #endif /* not ALLOW_SHELFICE */
227 diffus(i,k,1) = max ( blmc(i,k,1), viscAr )
228 diffus(i,k,2) = max ( blmc(i,k,2), diffusKzS(i,Nr) )
229 diffus(i,k,3) = max ( blmc(i,k,3), diffusKzT(i,Nr) )
230 else
231 ghat(i,k) = 0.
232 endif
233 end do
234 end do
235
236 #endif /* ALLOW_KPP */
237
238 return
239 end
240
241 c*************************************************************************
242
243 subroutine bldepth (
244 I kmtj
245 I , dvsq, dbloc, Ritop, ustar, bo, bosol, coriol
246 I , ikppkey
247 O , hbl, bfsfc, stable, casea, kbl, Rib, sigma
248 I , mytime, mythid )
249
250 c the oceanic planetary boundary layer depth, hbl, is determined as
251 c the shallowest depth where the bulk Richardson number is
252 c equal to the critical value, Ricr.
253 c
254 c bulk Richardson numbers are evaluated by computing velocity and
255 c buoyancy differences between values at zgrid(kl) < 0 and surface
256 c reference values.
257 c in this configuration, the reference values are equal to the
258 c values in the surface layer.
259 c when using a very fine vertical grid, these values should be
260 c computed as the vertical average of velocity and buoyancy from
261 c the surface down to epsilon*zgrid(kl).
262 c
263 c when the bulk Richardson number at k exceeds Ricr, hbl is
264 c linearly interpolated between grid levels zgrid(k) and zgrid(k-1).
265 c
266 c The water column and the surface forcing are diagnosed for
267 c stable/ustable forcing conditions, and where hbl is relative
268 c to grid points (caseA), so that conditional branches can be
269 c avoided in later subroutines.
270 c
271 IMPLICIT NONE
272
273 #include "SIZE.h"
274 #include "KPP_PARAMS.h"
275
276 c input
277 c------
278 c myTime : current time in simulation
279 c myThid : thread number for this instance of the routine
280 c kmtj : number of vertical layers
281 c dvsq : (velocity shear re sfc)^2 ((m/s)^2)
282 c dbloc : local delta buoyancy across interfaces (m/s^2)
283 c Ritop : numerator of bulk Richardson Number
284 c =(z-zref)*dbsfc, where dbsfc=delta
285 c buoyancy with respect to surface ((m/s)^2)
286 c ustar : surface friction velocity (m/s)
287 c bo : surface turbulent buoyancy forcing (m^2/s^3)
288 c bosol : radiative buoyancy forcing (m^2/s^3)
289 c coriol : Coriolis parameter (1/s)
290 _RL mytime
291 integer mythid
292 integer kmtj(imt)
293 _RL dvsq (imt,Nr)
294 _RL dbloc (imt,Nr)
295 _RL Ritop (imt,Nr)
296 _RL ustar (imt)
297 _RL bo (imt)
298 _RL bosol (imt)
299 _RL coriol (imt)
300 integer ikppkey, kkppkey
301
302 c output
303 c--------
304 c hbl : boundary layer depth (m)
305 c bfsfc : Bo+radiation absorbed to d=hbf*hbl (m^2/s^3)
306 c stable : =1 in stable forcing; =0 unstable
307 c casea : =1 in case A, =0 in case B
308 c kbl : -1 of first grid level below hbl
309 c Rib : Bulk Richardson number
310 c sigma : normalized depth (d/hbl)
311 _RL hbl (imt)
312 _RL bfsfc (imt)
313 _RL stable (imt)
314 _RL casea (imt)
315 integer kbl(imt)
316 _RL Rib (imt,Nr)
317 _RL sigma (imt)
318
319 #ifdef ALLOW_KPP
320
321 c local
322 c-------
323 c wm, ws : turbulent velocity scales (m/s)
324 _RL wm(imt), ws(imt)
325 _RL worka(imt)
326
327 _RL bvsq, vtsq, hekman, hmonob, hlimit, tempVar1, tempVar2
328 integer i, kl
329
330 _RL p5 , eins
331 parameter ( p5=0.5, eins=1.0 )
332 _RL minusone
333 parameter ( minusone=-1.0 )
334
335 c find bulk Richardson number at every grid level until > Ricr
336 c
337 c note: the reference depth is -epsilon/2.*zgrid(k), but the reference
338 c u,v,t,s values are simply the surface layer values,
339 c and not the averaged values from 0 to 2*ref.depth,
340 c which is necessary for very fine grids(top layer < 2m thickness)
341 c note: max values when Ricr never satisfied are
342 c kbl(i)=kmtj(i) and hbl(i)=-zgrid(kmtj(i))
343
344 c initialize hbl and kbl to bottomed out values
345
346 do i = 1, imt
347 Rib(i,1) = 0.0
348 kbl(i) = max(kmtj(i),1)
349 hbl(i) = -zgrid(kbl(i))
350 end do
351
352 do kl = 2, Nr
353
354 #ifdef ALLOW_AUTODIFF_TAMC
355 kkppkey = (ikppkey-1)*Nr + kl
356 #endif
357
358 c compute bfsfc = sw fraction at hbf * zgrid
359
360 do i = 1, imt
361 worka(i) = zgrid(kl)
362 end do
363 CADJ store worka = comlev1_kpp_k, key = kkppkey
364 call SWFRAC(
365 I imt, hbf,
366 I mytime, mythid,
367 U worka )
368 CADJ store worka = comlev1_kpp_k, key = kkppkey
369
370
371 do i = 1, imt
372
373 c use caseA as temporary array
374
375 casea(i) = -zgrid(kl)
376
377 c compute bfsfc= Bo + radiative contribution down to hbf * hbl
378
379 bfsfc(i) = bo(i) + bosol(i)*(1. - worka(i))
380 stable(i) = p5 + sign(p5,bfsfc(i))
381 sigma(i) = stable(i) + (1. - stable(i)) * epsilon
382
383 end do
384
385 c-----------------------------------------------------------------------
386 c compute velocity scales at sigma, for hbl= caseA = -zgrid(kl)
387 c-----------------------------------------------------------------------
388
389 call wscale (
390 I sigma, casea, ustar, bfsfc,
391 O wm, ws, myThid )
392 CADJ store ws = comlev1_kpp_k, key = kkppkey
393
394 do i = 1, imt
395
396 c-----------------------------------------------------------------------
397 c compute the turbulent shear contribution to Rib
398 c-----------------------------------------------------------------------
399
400 bvsq = p5 *
401 1 ( dbloc(i,kl-1) / (zgrid(kl-1)-zgrid(kl ))+
402 2 dbloc(i,kl ) / (zgrid(kl )-zgrid(kl+1)))
403
404 if (bvsq .eq. 0.) then
405 vtsq = 0.0
406 else
407 vtsq = -zgrid(kl) * ws(i) * sqrt(abs(bvsq)) * Vtc
408 endif
409
410 c compute bulk Richardson number at new level
411 c note: Ritop needs to be zero on land and ocean bottom
412 c points so that the following if statement gets triggered
413 c correctly; otherwise, hbl might get set to (big) negative
414 c values, that might exceed the limit for the "exp" function
415 c in "SWFRAC"
416
417 c
418 c rg: assignment to double precision variable to avoid overflow
419 c ph: test for zero nominator
420 c
421
422 tempVar1 = dvsq(i,kl) + vtsq
423 tempVar2 = max(tempVar1, phepsi)
424 Rib(i,kl) = Ritop(i,kl) / tempVar2
425
426 end do
427 end do
428
429 cph(
430 cph without this store, there is a recomputation error for
431 cph rib in adbldepth (probably partial recomputation problem)
432 CADJ store Rib = comlev1_kpp
433 CADJ & , key = ikppkey, shape = (/ (sNx+2*OLx)*(sNy+2*OLy),Nr /)
434 cph)
435
436 do kl = 2, Nr
437 do i = 1, imt
438 if (kbl(i).eq.kmtj(i) .and. Rib(i,kl).gt.Ricr) kbl(i) = kl
439 end do
440 end do
441
442 CADJ store kbl = comlev1_kpp
443 CADJ & , key = ikppkey, shape = (/ (sNx+2*OLx)*(sNy+2*OLy) /)
444
445 do i = 1, imt
446 kl = kbl(i)
447 c linearly interpolate to find hbl where Rib = Ricr
448 if (kl.gt.1 .and. kl.lt.kmtj(i)) then
449 tempVar1 = (Rib(i,kl)-Rib(i,kl-1))
450 hbl(i) = -zgrid(kl-1) + (zgrid(kl-1)-zgrid(kl)) *
451 1 (Ricr - Rib(i,kl-1)) / tempVar1
452 endif
453 end do
454
455 CADJ store hbl = comlev1_kpp
456 CADJ & , key = ikppkey, shape = (/ (sNx+2*OLx)*(sNy+2*OLy) /)
457
458 c-----------------------------------------------------------------------
459 c find stability and buoyancy forcing for boundary layer
460 c-----------------------------------------------------------------------
461
462 do i = 1, imt
463 worka(i) = hbl(i)
464 end do
465 CADJ store worka = comlev1_kpp
466 CADJ & , key = ikppkey, shape = (/ (sNx+2*OLx)*(sNy+2*OLy) /)
467 call SWFRAC(
468 I imt, minusone,
469 I mytime, mythid,
470 U worka )
471 CADJ store worka = comlev1_kpp
472 CADJ & , key = ikppkey, shape = (/ (sNx+2*OLx)*(sNy+2*OLy) /)
473
474 do i = 1, imt
475 bfsfc(i) = bo(i) + bosol(i) * (1. - worka(i))
476 end do
477 CADJ store bfsfc = comlev1_kpp
478 CADJ & , key = ikppkey, shape = (/ (sNx+2*OLx)*(sNy+2*OLy) /)
479
480 c-- ensure bfsfc is never 0
481 do i = 1, imt
482 stable(i) = p5 + sign( p5, bfsfc(i) )
483 bfsfc(i) = sign(eins,bfsfc(i))*max(phepsi,abs(bfsfc(i)))
484 end do
485
486 cph(
487 cph added stable to store list to avoid extensive recomp.
488 CADJ store bfsfc, stable = comlev1_kpp
489 CADJ & , key = ikppkey, shape = (/ (sNx+2*OLx)*(sNy+2*OLy) /)
490 cph)
491
492 c-----------------------------------------------------------------------
493 c check hbl limits for hekman or hmonob
494 c ph: test for zero nominator
495 c-----------------------------------------------------------------------
496
497 do i = 1, imt
498 if (bfsfc(i) .gt. 0.0) then
499 hekman = cekman * ustar(i) / max(abs(Coriol(i)),phepsi)
500 hmonob = cmonob * ustar(i)*ustar(i)*ustar(i)
501 & / vonk / bfsfc(i)
502 hlimit = stable(i) * min(hekman,hmonob)
503 & + (stable(i)-1.) * zgrid(Nr)
504 hbl(i) = min(hbl(i),hlimit)
505 end if
506 end do
507 CADJ store hbl = comlev1_kpp
508 CADJ & , key = ikppkey, shape = (/ (sNx+2*OLx)*(sNy+2*OLy) /)
509
510 do i = 1, imt
511 hbl(i) = max(hbl(i),minKPPhbl)
512 kbl(i) = kmtj(i)
513 end do
514
515 CADJ store hbl = comlev1_kpp
516 CADJ & , key = ikppkey, shape = (/ (sNx+2*OLx)*(sNy+2*OLy) /)
517
518 c-----------------------------------------------------------------------
519 c find new kbl
520 c-----------------------------------------------------------------------
521
522 do kl = 2, Nr
523 do i = 1, imt
524 if ( kbl(i).eq.kmtj(i) .and. (-zgrid(kl)).gt.hbl(i) ) then
525 kbl(i) = kl
526 endif
527 end do
528 end do
529
530 c-----------------------------------------------------------------------
531 c find stability and buoyancy forcing for final hbl values
532 c-----------------------------------------------------------------------
533
534 do i = 1, imt
535 worka(i) = hbl(i)
536 end do
537 CADJ store worka = comlev1_kpp
538 CADJ & , key = ikppkey, shape = (/ (sNx+2*OLx)*(sNy+2*OLy) /)
539 call SWFRAC(
540 I imt, minusone,
541 I mytime, mythid,
542 U worka )
543 CADJ store worka = comlev1_kpp
544 CADJ & , key = ikppkey, shape = (/ (sNx+2*OLx)*(sNy+2*OLy) /)
545
546 do i = 1, imt
547 bfsfc(i) = bo(i) + bosol(i) * (1. - worka(i))
548 end do
549 CADJ store bfsfc = comlev1_kpp
550 CADJ & , key = ikppkey, shape = (/ (sNx+2*OLx)*(sNy+2*OLy) /)
551
552 c-- ensures bfsfc is never 0
553 do i = 1, imt
554 stable(i) = p5 + sign( p5, bfsfc(i) )
555 bfsfc(i) = sign(eins,bfsfc(i))*max(phepsi,abs(bfsfc(i)))
556 end do
557
558 c-----------------------------------------------------------------------
559 c determine caseA and caseB
560 c-----------------------------------------------------------------------
561
562 do i = 1, imt
563 casea(i) = p5 +
564 1 sign(p5, -zgrid(kbl(i)) - p5*hwide(kbl(i)) - hbl(i))
565 end do
566
567 #endif /* ALLOW_KPP */
568
569 return
570 end
571
572 c*************************************************************************
573
574 subroutine wscale (
575 I sigma, hbl, ustar, bfsfc,
576 O wm, ws,
577 I myThid )
578
579 c compute turbulent velocity scales.
580 c use a 2D-lookup table for wm and ws as functions of ustar and
581 c zetahat (=vonk*sigma*hbl*bfsfc).
582 c
583 c note: the lookup table is only used for unstable conditions
584 c (zehat.le.0), in the stable domain wm (=ws) gets computed
585 c directly.
586 c
587 IMPLICIT NONE
588
589 #include "SIZE.h"
590 #include "KPP_PARAMS.h"
591
592 c input
593 c------
594 c sigma : normalized depth (d/hbl)
595 c hbl : boundary layer depth (m)
596 c ustar : surface friction velocity (m/s)
597 c bfsfc : total surface buoyancy flux (m^2/s^3)
598 c myThid : thread number for this instance of the routine
599 integer myThid
600 _RL sigma(imt)
601 _RL hbl (imt)
602 _RL ustar(imt)
603 _RL bfsfc(imt)
604
605 c output
606 c--------
607 c wm, ws : turbulent velocity scales at sigma
608 _RL wm(imt), ws(imt)
609
610 #ifdef ALLOW_KPP
611
612 c local
613 c------
614 c zehat : = zeta * ustar**3
615 _RL zehat
616
617 integer iz, izp1, ju, i, jup1
618 _RL udiff, zdiff, zfrac, ufrac, fzfrac, wam
619 _RL wbm, was, wbs, u3, tempVar
620
621 c-----------------------------------------------------------------------
622 c use lookup table for zehat < zmax only; otherwise use
623 c stable formulae
624 c-----------------------------------------------------------------------
625
626 do i = 1, imt
627 zehat = vonk*sigma(i)*hbl(i)*bfsfc(i)
628
629 if (zehat .le. zmax) then
630
631 zdiff = zehat - zmin
632 iz = int( zdiff / deltaz )
633 iz = min( iz, nni )
634 iz = max( iz, 0 )
635 izp1 = iz + 1
636
637 udiff = ustar(i) - umin
638 ju = int( udiff / deltau )
639 ju = min( ju, nnj )
640 ju = max( ju, 0 )
641 jup1 = ju + 1
642
643 zfrac = zdiff / deltaz - float(iz)
644 ufrac = udiff / deltau - float(ju)
645
646 fzfrac= 1. - zfrac
647 wam = fzfrac * wmt(iz,jup1) + zfrac * wmt(izp1,jup1)
648 wbm = fzfrac * wmt(iz,ju ) + zfrac * wmt(izp1,ju )
649 wm(i) = (1.-ufrac) * wbm + ufrac * wam
650
651 was = fzfrac * wst(iz,jup1) + zfrac * wst(izp1,jup1)
652 wbs = fzfrac * wst(iz,ju ) + zfrac * wst(izp1,ju )
653 ws(i) = (1.-ufrac) * wbs + ufrac * was
654
655 else
656
657 u3 = ustar(i) * ustar(i) * ustar(i)
658 tempVar = u3 + conc1 * zehat
659 wm(i) = vonk * ustar(i) * u3 / tempVar
660 ws(i) = wm(i)
661
662 endif
663
664 end do
665
666 #endif /* ALLOW_KPP */
667
668 return
669 end
670
671 c*************************************************************************
672
673 subroutine Ri_iwmix (
674 I kmtj, shsq, dbloc, dblocSm
675 I , diffusKzS, diffusKzT
676 I , ikppkey
677 O , diffus )
678
679 c compute interior viscosity diffusivity coefficients due
680 c to shear instability (dependent on a local Richardson number),
681 c to background internal wave activity, and
682 c to static instability (local Richardson number < 0).
683
684 IMPLICIT NONE
685
686 #include "SIZE.h"
687 #include "EEPARAMS.h"
688 #include "PARAMS.h"
689 #include "KPP_PARAMS.h"
690
691 c input
692 c kmtj (imt) number of vertical layers on this row
693 c shsq (imt,Nr) (local velocity shear)^2 ((m/s)^2)
694 c dbloc (imt,Nr) local delta buoyancy (m/s^2)
695 c dblocSm(imt,Nr) horizontally smoothed dbloc (m/s^2)
696 c diffusKzS(imt,Nr)- background vertical diffusivity for scalars (m^2/s)
697 c diffusKzT(imt,Nr)- background vertical diffusivity for theta (m^2/s)
698 integer kmtj (imt)
699 _RL shsq (imt,Nr)
700 _RL dbloc (imt,Nr)
701 _RL dblocSm (imt,Nr)
702 _RL diffusKzS(imt,Nr)
703 _RL diffusKzT(imt,Nr)
704 integer ikppkey
705
706 c output
707 c diffus(imt,0:Nrp1,1) vertical viscosivity coefficient (m^2/s)
708 c diffus(imt,0:Nrp1,2) vertical scalar diffusivity (m^2/s)
709 c diffus(imt,0:Nrp1,3) vertical temperature diffusivity (m^2/s)
710 _RL diffus(imt,0:Nrp1,3)
711
712 #ifdef ALLOW_KPP
713
714 c local variables
715 c Rig local Richardson number
716 c fRi, fcon function of Rig
717 _RL Rig
718 _RL fRi, fcon
719 _RL ratio
720 integer i, ki
721 _RL c1, c0
722
723 #ifdef ALLOW_KPP_VERTICALLY_SMOOTH
724 integer mr
725 CADJ INIT kpp_ri_tape_mr = common, 1
726 #endif
727
728 c constants
729 c1 = 1.0
730 c0 = 0.0
731
732 c-----------------------------------------------------------------------
733 c compute interior gradient Ri at all interfaces ki=1,Nr, (not surface)
734 c use diffus(*,*,1) as temporary storage of Ri to be smoothed
735 c use diffus(*,*,2) as temporary storage for Brunt-Vaisala squared
736 c set values at bottom and below to nearest value above bottom
737 #ifdef ALLOW_AUTODIFF_TAMC
738 C break data flow dependence on diffus
739 diffus(1,1,1) = 0.0
740
741 do ki = 1, Nr
742 do i = 1, imt
743 diffus(i,ki,1) = 0.
744 diffus(i,ki,2) = 0.
745 diffus(i,ki,3) = 0.
746 enddo
747 enddo
748 #endif
749
750
751 do ki = 1, Nr
752 do i = 1, imt
753 if (kmtj(i) .LE. 1 ) then
754 diffus(i,ki,1) = 0.
755 diffus(i,ki,2) = 0.
756 elseif (ki .GE. kmtj(i)) then
757 diffus(i,ki,1) = diffus(i,ki-1,1)
758 diffus(i,ki,2) = diffus(i,ki-1,2)
759 else
760 diffus(i,ki,1) = dblocSm(i,ki) * (zgrid(ki)-zgrid(ki+1))
761 & / max( Shsq(i,ki), phepsi )
762 diffus(i,ki,2) = dbloc(i,ki) / (zgrid(ki)-zgrid(ki+1))
763 endif
764 end do
765 end do
766 CADJ store diffus = comlev1_kpp, key = ikppkey
767
768 c-----------------------------------------------------------------------
769 c vertically smooth Ri
770 #ifdef ALLOW_KPP_VERTICALLY_SMOOTH
771 do mr = 1, num_v_smooth_Ri
772
773 CADJ store diffus(:,:,1) = kpp_ri_tape_mr
774 CADJ & , key=mr, shape=(/ (sNx+2*OLx)*(sNy+2*OLy),Nr+2 /)
775
776 call z121 (
777 U diffus(1,0,1)
778 I myThid )
779 end do
780 #endif
781
782 c-----------------------------------------------------------------------
783 c after smoothing loop
784
785 do ki = 1, Nr
786 do i = 1, imt
787
788 c evaluate f of Brunt-Vaisala squared for convection, store in fcon
789
790 Rig = max ( diffus(i,ki,2) , BVSQcon )
791 ratio = min ( (BVSQcon - Rig) / BVSQcon, c1 )
792 fcon = c1 - ratio * ratio
793 fcon = fcon * fcon * fcon
794
795 c evaluate f of smooth Ri for shear instability, store in fRi
796
797 Rig = max ( diffus(i,ki,1), c0 )
798 ratio = min ( Rig / Riinfty , c1 )
799 fRi = c1 - ratio * ratio
800 fRi = fRi * fRi * fRi
801
802 c ----------------------------------------------------------------------
803 c evaluate diffusivities and viscosity
804 c mixing due to internal waves, and shear and static instability
805
806 #ifndef EXCLUDE_KPP_SHEAR_MIX
807 if ( .NOT. inAdMode ) then
808 diffus(i,ki,1) = viscAr + fcon * difmcon + fRi * difm0
809 diffus(i,ki,2) = diffusKzS(i,ki)+fcon*difscon+fRi*difs0
810 diffus(i,ki,3) = diffusKzT(i,ki)+fcon*diftcon+fRi*dift0
811 else
812 diffus(i,ki,1) = viscAr
813 diffus(i,ki,2) = diffusKzS(i,ki)
814 diffus(i,ki,3) = diffusKzT(i,ki)
815 endif
816 #else
817 diffus(i,ki,1) = viscAr
818 diffus(i,ki,2) = diffusKzS(i,ki)
819 diffus(i,ki,3) = diffusKzT(i,ki)
820 #endif
821
822 end do
823 end do
824
825 c ------------------------------------------------------------------------
826 c set surface values to 0.0
827
828 do i = 1, imt
829 diffus(i,0,1) = c0
830 diffus(i,0,2) = c0
831 diffus(i,0,3) = c0
832 end do
833
834 #endif /* ALLOW_KPP */
835
836 return
837 end
838
839 c*************************************************************************
840
841 subroutine z121 (
842 U v,
843 I myThid )
844
845 c Apply 121 smoothing in k to 2-d array V(i,k=1,Nr)
846 c top (0) value is used as a dummy
847 c bottom (Nrp1) value is set to input value from above.
848
849 c Note that it is important to exclude from the smoothing any points
850 c that are outside the range of the K(Ri) scheme, ie. >0.8, or <0.0.
851 c Otherwise, there is interference with other physics, especially
852 c penetrative convection.
853
854 IMPLICIT NONE
855 #include "SIZE.h"
856 #include "KPP_PARAMS.h"
857
858 c input/output
859 c-------------
860 c v : 2-D array to be smoothed in Nrp1 direction
861 c myThid: thread number for this instance of the routine
862 integer myThid
863 _RL v(imt,0:Nrp1)
864
865 #ifdef ALLOW_KPP
866
867 c local
868 _RL zwork, zflag
869 _RL KRi_range(1:Nrp1)
870 integer i, k, km1, kp1
871
872 _RL p0 , p25 , p5 , p2
873 parameter ( p0 = 0.0, p25 = 0.25, p5 = 0.5, p2 = 2.0 )
874
875 KRi_range(Nrp1) = p0
876
877 #ifdef ALLOW_AUTODIFF_TAMC
878 C-- dummy assignment to end declaration part for TAMC
879 i = 0
880
881 C-- HPF directive to help TAMC
882 CHPF$ INDEPENDENT
883 CADJ INIT z121tape = common, Nr
884 #endif /* ALLOW_AUTODIFF_TAMC */
885
886 do i = 1, imt
887
888 k = 1
889 CADJ STORE v(i,k) = z121tape
890 v(i,Nrp1) = v(i,Nr)
891
892 do k = 1, Nr
893 KRi_range(k) = p5 + SIGN(p5,v(i,k))
894 KRi_range(k) = KRi_range(k) *
895 & ( p5 + SIGN(p5,(Riinfty-v(i,k))) )
896 end do
897
898 zwork = KRi_range(1) * v(i,1)
899 v(i,1) = p2 * v(i,1) +
900 & KRi_range(1) * KRi_range(2) * v(i,2)
901 zflag = p2 + KRi_range(1) * KRi_range(2)
902 v(i,1) = v(i,1) / zflag
903
904 do k = 2, Nr
905 CADJ STORE v(i,k), zwork = z121tape
906 km1 = k - 1
907 kp1 = k + 1
908 zflag = v(i,k)
909 v(i,k) = p2 * v(i,k) +
910 & KRi_range(k) * KRi_range(kp1) * v(i,kp1) +
911 & KRi_range(k) * zwork
912 zwork = KRi_range(k) * zflag
913 zflag = p2 + KRi_range(k)*(KRi_range(kp1)+KRi_range(km1))
914 v(i,k) = v(i,k) / zflag
915 end do
916
917 end do
918
919 #endif /* ALLOW_KPP */
920
921 return
922 end
923
924 c*************************************************************************
925
926 subroutine smooth_horiz (
927 I k, bi, bj,
928 U fld,
929 I myThid )
930
931 c Apply horizontal smoothing to global _RL 2-D array
932
933 IMPLICIT NONE
934 #include "SIZE.h"
935 #include "GRID.h"
936 #include "KPP_PARAMS.h"
937
938 c input
939 c bi, bj : array indices
940 c k : vertical index used for masking
941 c myThid : thread number for this instance of the routine
942 INTEGER myThid
943 integer k, bi, bj
944
945 c input/output
946 c fld : 2-D array to be smoothed
947 _RL fld( 1-OLx:sNx+OLx, 1-OLy:sNy+OLy )
948
949 #ifdef ALLOW_KPP
950
951 c local
952 integer i, j, im1, ip1, jm1, jp1
953 _RL tempVar
954 _RL fld_tmp( 1-OLx:sNx+OLx, 1-OLy:sNy+OLy )
955
956 integer imin , imax , jmin , jmax
957 parameter(imin=2-OLx, imax=sNx+OLx-1, jmin=2-OLy, jmax=sNy+OLy-1)
958
959 _RL p0 , p5 , p25 , p125 , p0625
960 parameter( p0=0.0, p5=0.5, p25=0.25, p125=0.125, p0625=0.0625 )
961
962 DO j = jmin, jmax
963 jm1 = j-1
964 jp1 = j+1
965 DO i = imin, imax
966 im1 = i-1
967 ip1 = i+1
968 tempVar =
969 & p25 * maskC(i ,j ,k,bi,bj) +
970 & p125 * ( maskC(im1,j ,k,bi,bj) +
971 & maskC(ip1,j ,k,bi,bj) +
972 & maskC(i ,jm1,k,bi,bj) +
973 & maskC(i ,jp1,k,bi,bj) ) +
974 & p0625 * ( maskC(im1,jm1,k,bi,bj) +
975 & maskC(im1,jp1,k,bi,bj) +
976 & maskC(ip1,jm1,k,bi,bj) +
977 & maskC(ip1,jp1,k,bi,bj) )
978 IF ( tempVar .GE. p25 ) THEN
979 fld_tmp(i,j) = (
980 & p25 * fld(i ,j )*maskC(i ,j ,k,bi,bj) +
981 & p125 *(fld(im1,j )*maskC(im1,j ,k,bi,bj) +
982 & fld(ip1,j )*maskC(ip1,j ,k,bi,bj) +
983 & fld(i ,jm1)*maskC(i ,jm1,k,bi,bj) +
984 & fld(i ,jp1)*maskC(i ,jp1,k,bi,bj))+
985 & p0625*(fld(im1,jm1)*maskC(im1,jm1,k,bi,bj) +
986 & fld(im1,jp1)*maskC(im1,jp1,k,bi,bj) +
987 & fld(ip1,jm1)*maskC(ip1,jm1,k,bi,bj) +
988 & fld(ip1,jp1)*maskC(ip1,jp1,k,bi,bj)))
989 & / tempVar
990 ELSE
991 fld_tmp(i,j) = fld(i,j)
992 ENDIF
993 ENDDO
994 ENDDO
995
996 c transfer smoothed field to output array
997 DO j = jmin, jmax
998 DO i = imin, imax
999 fld(i,j) = fld_tmp(i,j)
1000 ENDDO
1001 ENDDO
1002
1003 #endif /* ALLOW_KPP */
1004
1005 return
1006 end
1007
1008 c*************************************************************************
1009
1010 subroutine blmix (
1011 I ustar, bfsfc, hbl, stable, casea, diffus, kbl
1012 O , dkm1, blmc, ghat, sigma, ikppkey
1013 I , mythid )
1014
1015 c mixing coefficients within boundary layer depend on surface
1016 c forcing and the magnitude and gradient of interior mixing below
1017 c the boundary layer ("matching").
1018 c
1019 c caution: if mixing bottoms out at hbl = -zgrid(Nr) then
1020 c fictitious layer at Nrp1 is needed with small but finite width
1021 c hwide(Nrp1) (eg. epsln = 1.e-20).
1022 c
1023 IMPLICIT NONE
1024
1025 #include "SIZE.h"
1026 #include "KPP_PARAMS.h"
1027
1028 c input
1029 c ustar (imt) surface friction velocity (m/s)
1030 c bfsfc (imt) surface buoyancy forcing (m^2/s^3)
1031 c hbl (imt) boundary layer depth (m)
1032 c stable(imt) = 1 in stable forcing
1033 c casea (imt) = 1 in case A
1034 c diffus(imt,0:Nrp1,mdiff) vertical diffusivities (m^2/s)
1035 c kbl (imt) -1 of first grid level below hbl
1036 c myThid thread number for this instance of the routine
1037 integer myThid
1038 _RL ustar (imt)
1039 _RL bfsfc (imt)
1040 _RL hbl (imt)
1041 _RL stable(imt)
1042 _RL casea (imt)
1043 _RL diffus(imt,0:Nrp1,mdiff)
1044 integer kbl(imt)
1045
1046 c output
1047 c dkm1 (imt,mdiff) boundary layer difs at kbl-1 level
1048 c blmc (imt,Nr,mdiff) boundary layer mixing coefficients (m^2/s)
1049 c ghat (imt,Nr) nonlocal scalar transport
1050 c sigma(imt) normalized depth (d / hbl)
1051 _RL dkm1 (imt,mdiff)
1052 _RL blmc (imt,Nr,mdiff)
1053 _RL ghat (imt,Nr)
1054 _RL sigma(imt)
1055 integer ikppkey, kkppkey
1056
1057 #ifdef ALLOW_KPP
1058
1059 c local
1060 c gat1*(imt) shape function at sigma = 1
1061 c dat1*(imt) derivative of shape function at sigma = 1
1062 c ws(imt), wm(imt) turbulent velocity scales (m/s)
1063 _RL gat1m(imt), gat1s(imt), gat1t(imt)
1064 _RL dat1m(imt), dat1s(imt), dat1t(imt)
1065 _RL ws(imt), wm(imt)
1066 integer i, kn, ki
1067 _RL R, dvdzup, dvdzdn, viscp
1068 _RL difsp, diftp, visch, difsh, difth
1069 _RL f1, sig, a1, a2, a3, delhat
1070 _RL Gm, Gs, Gt
1071 _RL tempVar
1072
1073 _RL p0 , eins
1074 parameter (p0=0.0, eins=1.0)
1075
1076 c-----------------------------------------------------------------------
1077 c compute velocity scales at hbl
1078 c-----------------------------------------------------------------------
1079
1080 do i = 1, imt
1081 sigma(i) = stable(i) * 1.0 + (1. - stable(i)) * epsilon
1082 end do
1083
1084 CADJ STORE sigma = comlev1_kpp, key = ikppkey
1085 call wscale (
1086 I sigma, hbl, ustar, bfsfc,
1087 O wm, ws, myThid )
1088 CADJ STORE wm = comlev1_kpp, key = ikppkey
1089 CADJ STORE ws = comlev1_kpp, key = ikppkey
1090
1091 do i = 1, imt
1092 wm(i) = sign(eins,wm(i))*max(phepsi,abs(wm(i)))
1093 ws(i) = sign(eins,ws(i))*max(phepsi,abs(ws(i)))
1094 end do
1095 CADJ STORE wm = comlev1_kpp, key = ikppkey
1096 CADJ STORE ws = comlev1_kpp, key = ikppkey
1097
1098 do i = 1, imt
1099
1100 kn = int(caseA(i)+phepsi) *(kbl(i) -1) +
1101 $ (1 - int(caseA(i)+phepsi)) * kbl(i)
1102
1103 c-----------------------------------------------------------------------
1104 c find the interior viscosities and derivatives at hbl(i)
1105 c-----------------------------------------------------------------------
1106
1107 delhat = 0.5*hwide(kn) - zgrid(kn) - hbl(i)
1108 R = 1.0 - delhat / hwide(kn)
1109 dvdzup = (diffus(i,kn-1,1) - diffus(i,kn ,1)) / hwide(kn)
1110 dvdzdn = (diffus(i,kn ,1) - diffus(i,kn+1,1)) / hwide(kn+1)
1111 viscp = 0.5 * ( (1.-R) * (dvdzup + abs(dvdzup)) +
1112 1 R * (dvdzdn + abs(dvdzdn)) )
1113
1114 dvdzup = (diffus(i,kn-1,2) - diffus(i,kn ,2)) / hwide(kn)
1115 dvdzdn = (diffus(i,kn ,2) - diffus(i,kn+1,2)) / hwide(kn+1)
1116 difsp = 0.5 * ( (1.-R) * (dvdzup + abs(dvdzup)) +
1117 1 R * (dvdzdn + abs(dvdzdn)) )
1118
1119 dvdzup = (diffus(i,kn-1,3) - diffus(i,kn ,3)) / hwide(kn)
1120 dvdzdn = (diffus(i,kn ,3) - diffus(i,kn+1,3)) / hwide(kn+1)
1121 diftp = 0.5 * ( (1.-R) * (dvdzup + abs(dvdzup)) +
1122 1 R * (dvdzdn + abs(dvdzdn)) )
1123
1124 visch = diffus(i,kn,1) + viscp * delhat
1125 difsh = diffus(i,kn,2) + difsp * delhat
1126 difth = diffus(i,kn,3) + diftp * delhat
1127
1128 f1 = stable(i) * conc1 * bfsfc(i) /
1129 & max(ustar(i)**4,phepsi)
1130 gat1m(i) = visch / hbl(i) / wm(i)
1131 dat1m(i) = -viscp / wm(i) + f1 * visch
1132
1133 gat1s(i) = difsh / hbl(i) / ws(i)
1134 dat1s(i) = -difsp / ws(i) + f1 * difsh
1135
1136 gat1t(i) = difth / hbl(i) / ws(i)
1137 dat1t(i) = -diftp / ws(i) + f1 * difth
1138
1139 end do
1140 #ifdef KPP_AUTODIFF_EXCESSIVE_STORE
1141 CADJ STORE gat1m = comlev1_kpp, key = ikppkey
1142 CADJ STORE gat1s = comlev1_kpp, key = ikppkey
1143 CADJ STORE gat1t = comlev1_kpp, key = ikppkey
1144 CADJ STORE dat1m = comlev1_kpp, key = ikppkey
1145 CADJ STORE dat1s = comlev1_kpp, key = ikppkey
1146 CADJ STORE dat1t = comlev1_kpp, key = ikppkey
1147 #endif
1148 do i = 1, imt
1149 dat1m(i) = min(dat1m(i),p0)
1150 dat1s(i) = min(dat1s(i),p0)
1151 dat1t(i) = min(dat1t(i),p0)
1152 end do
1153 #ifdef KPP_AUTODIFF_EXCESSIVE_STORE
1154 CADJ STORE dat1m = comlev1_kpp, key = ikppkey
1155 CADJ STORE dat1s = comlev1_kpp, key = ikppkey
1156 CADJ STORE dat1t = comlev1_kpp, key = ikppkey
1157 #endif
1158
1159 do ki = 1, Nr
1160
1161 #ifdef ALLOW_AUTODIFF_TAMC
1162 kkppkey = (ikppkey-1)*Nr + ki
1163 #endif
1164
1165 c-----------------------------------------------------------------------
1166 c compute turbulent velocity scales on the interfaces
1167 c-----------------------------------------------------------------------
1168
1169 do i = 1, imt
1170 sig = (-zgrid(ki) + 0.5 * hwide(ki)) / hbl(i)
1171 sigma(i) = stable(i)*sig + (1.-stable(i))*min(sig,epsilon)
1172 end do
1173 #ifdef KPP_AUTODIFF_EXCESSIVE_STORE
1174 CADJ STORE wm = comlev1_kpp_k, key = kkppkey
1175 CADJ STORE ws = comlev1_kpp_k, key = kkppkey
1176 #endif
1177 CADJ STORE sigma = comlev1_kpp_k, key = kkppkey
1178 call wscale (
1179 I sigma, hbl, ustar, bfsfc,
1180 O wm, ws, myThid )
1181 CADJ STORE wm = comlev1_kpp_k, key = kkppkey
1182 CADJ STORE ws = comlev1_kpp_k, key = kkppkey
1183
1184 c-----------------------------------------------------------------------
1185 c compute the dimensionless shape functions at the interfaces
1186 c-----------------------------------------------------------------------
1187
1188 do i = 1, imt
1189 sig = (-zgrid(ki) + 0.5 * hwide(ki)) / hbl(i)
1190 a1 = sig - 2.
1191 a2 = 3. - 2. * sig
1192 a3 = sig - 1.
1193
1194 Gm = a1 + a2 * gat1m(i) + a3 * dat1m(i)
1195 Gs = a1 + a2 * gat1s(i) + a3 * dat1s(i)
1196 Gt = a1 + a2 * gat1t(i) + a3 * dat1t(i)
1197
1198 c-----------------------------------------------------------------------
1199 c compute boundary layer diffusivities at the interfaces
1200 c-----------------------------------------------------------------------
1201
1202 blmc(i,ki,1) = hbl(i) * wm(i) * sig * (1. + sig * Gm)
1203 blmc(i,ki,2) = hbl(i) * ws(i) * sig * (1. + sig * Gs)
1204 blmc(i,ki,3) = hbl(i) * ws(i) * sig * (1. + sig * Gt)
1205
1206 c-----------------------------------------------------------------------
1207 c nonlocal transport term = ghat * <ws>o
1208 c-----------------------------------------------------------------------
1209
1210 tempVar = ws(i) * hbl(i)
1211 ghat(i,ki) = (1.-stable(i)) * cg / max(phepsi,tempVar)
1212
1213 end do
1214 end do
1215
1216 c-----------------------------------------------------------------------
1217 c find diffusivities at kbl-1 grid level
1218 c-----------------------------------------------------------------------
1219
1220 do i = 1, imt
1221 sig = -zgrid(kbl(i)-1) / hbl(i)
1222 sigma(i) = stable(i) * sig
1223 & + (1. - stable(i)) * min(sig,epsilon)
1224 end do
1225
1226 #ifdef KPP_AUTODIFF_EXCESSIVE_STORE
1227 CADJ STORE wm = comlev1_kpp, key = ikppkey
1228 CADJ STORE ws = comlev1_kpp, key = ikppkey
1229 #endif
1230 CADJ STORE sigma = comlev1_kpp, key = ikppkey
1231 call wscale (
1232 I sigma, hbl, ustar, bfsfc,
1233 O wm, ws, myThid )
1234 CADJ STORE wm = comlev1_kpp, key = ikppkey
1235 CADJ STORE ws = comlev1_kpp, key = ikppkey
1236
1237 do i = 1, imt
1238 sig = -zgrid(kbl(i)-1) / hbl(i)
1239 a1 = sig - 2.
1240 a2 = 3. - 2. * sig
1241 a3 = sig - 1.
1242 Gm = a1 + a2 * gat1m(i) + a3 * dat1m(i)
1243 Gs = a1 + a2 * gat1s(i) + a3 * dat1s(i)
1244 Gt = a1 + a2 * gat1t(i) + a3 * dat1t(i)
1245 dkm1(i,1) = hbl(i) * wm(i) * sig * (1. + sig * Gm)
1246 dkm1(i,2) = hbl(i) * ws(i) * sig * (1. + sig * Gs)
1247 dkm1(i,3) = hbl(i) * ws(i) * sig * (1. + sig * Gt)
1248 end do
1249
1250 #endif /* ALLOW_KPP */
1251
1252 return
1253 end
1254
1255 c*************************************************************************
1256
1257 subroutine enhance (
1258 I dkm1, hbl, kbl, diffus, casea
1259 U , ghat
1260 O , blmc
1261 & , myThid )
1262
1263 c enhance the diffusivity at the kbl-.5 interface
1264
1265 IMPLICIT NONE
1266
1267 #include "SIZE.h"
1268 #include "KPP_PARAMS.h"
1269
1270 c input
1271 c dkm1(imt,mdiff) bl diffusivity at kbl-1 grid level
1272 c hbl(imt) boundary layer depth (m)
1273 c kbl(imt) grid above hbl
1274 c diffus(imt,0:Nrp1,mdiff) vertical diffusivities (m^2/s)
1275 c casea(imt) = 1 in caseA, = 0 in case B
1276 c myThid thread number for this instance of the routine
1277 integer myThid
1278 _RL dkm1 (imt,mdiff)
1279 _RL hbl (imt)
1280 integer kbl (imt)
1281 _RL diffus(imt,0:Nrp1,mdiff)
1282 _RL casea (imt)
1283
1284 c input/output
1285 c nonlocal transport, modified ghat at kbl(i)-1 interface (s/m**2)
1286 _RL ghat (imt,Nr)
1287
1288 c output
1289 c enhanced bound. layer mixing coeff.
1290 _RL blmc (imt,Nr,mdiff)
1291
1292 #ifdef ALLOW_KPP
1293
1294 c local
1295 c fraction hbl lies beteen zgrid neighbors
1296 _RL delta
1297 integer ki, i, md
1298 _RL dkmp5, dstar
1299
1300 do i = 1, imt
1301 ki = kbl(i)-1
1302 if ((ki .ge. 1) .and. (ki .lt. Nr)) then
1303 delta = (hbl(i) + zgrid(ki)) / (zgrid(ki) - zgrid(ki+1))
1304 do md = 1, mdiff
1305 dkmp5 = casea(i) * diffus(i,ki,md) +
1306 1 (1.- casea(i)) * blmc (i,ki,md)
1307 dstar = (1.- delta)**2 * dkm1(i,md)
1308 & + delta**2 * dkmp5
1309 blmc(i,ki,md) = (1.- delta)*diffus(i,ki,md)
1310 & + delta*dstar
1311 end do
1312 ghat(i,ki) = (1.- casea(i)) * ghat(i,ki)
1313 endif
1314 end do
1315
1316 #endif /* ALLOW_KPP */
1317
1318 return
1319 end
1320
1321 c*************************************************************************
1322
1323 SUBROUTINE STATEKPP (
1324 O RHO1, DBLOC, DBSFC, TTALPHA, SSBETA,
1325 I ikppkey, bi, bj, myThid )
1326 c
1327 c-----------------------------------------------------------------------
1328 c "statekpp" computes all necessary input arrays
1329 c for the kpp mixing scheme
1330 c
1331 c input:
1332 c bi, bj = array indices on which to apply calculations
1333 c
1334 c output:
1335 c rho1 = potential density of surface layer (kg/m^3)
1336 c dbloc = local buoyancy gradient at Nr interfaces
1337 c g/rho{k+1,k+1} * [ drho{k,k+1}-drho{k+1,k+1} ] (m/s^2)
1338 c dbsfc = buoyancy difference with respect to the surface
1339 c g * [ drho{1,k}/rho{1,k} - drho{k,k}/rho{k,k} ] (m/s^2)
1340 c ttalpha= thermal expansion coefficient without 1/rho factor
1341 c d(rho) / d(potential temperature) (kg/m^3/C)
1342 c ssbeta = salt expansion coefficient without 1/rho factor
1343 c d(rho) / d(salinity) (kg/m^3/PSU)
1344 c
1345 c see also subroutines find_rho.F find_alpha.F find_beta.F
1346 c
1347 c written by: jan morzel, feb. 10, 1995 (converted from "sigma" version)
1348 c modified by: d. menemenlis, june 1998 : for use with MIT GCM UV
1349 c
1350 c 28 april 05: added computation of mixed layer depth KPPmld
1351 c for a deltaRho equivalent to a deltaTheta of 0.8 deg C
1352
1353 c-----------------------------------------------------------------------
1354
1355 IMPLICIT NONE
1356
1357 #include "SIZE.h"
1358 #include "EEPARAMS.h"
1359 #include "PARAMS.h"
1360 #include "KPP_PARAMS.h"
1361 #include "DYNVARS.h"
1362 #include "GRID.h"
1363
1364 c-------------- Routine arguments -----------------------------------------
1365 INTEGER bi, bj, myThid
1366 _RL RHO1 ( 1-OLx:sNx+OLx, 1-OLy:sNy+OLy )
1367 _RL DBLOC ( 1-OLx:sNx+OLx, 1-OLy:sNy+OLy, Nr )
1368 _RL DBSFC ( 1-OLx:sNx+OLx, 1-OLy:sNy+OLy, Nr )
1369 _RL TTALPHA( 1-OLx:sNx+OLx, 1-OLy:sNy+OLy, Nrp1 )
1370 _RL SSBETA ( 1-OLx:sNx+OLx, 1-OLy:sNy+OLy, Nrp1 )
1371
1372 #ifdef ALLOW_KPP
1373
1374 c--------------------------------------------------------------------------
1375 c
1376 c local arrays:
1377 c
1378 c rhok - density of t(k ) & s(k ) at depth k
1379 c rhokm1 - density of t(k-1) & s(k-1) at depth k
1380 c rho1k - density of t(1 ) & s(1 ) at depth k
1381 c work1,2,3 - work arrays for holding horizontal slabs
1382
1383 _RL RHOK (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
1384 _RL RHOKM1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
1385 _RL RHO1K (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
1386 _RL WORK1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
1387 _RL WORK2 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
1388 _RL WORK3 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
1389 #ifdef ALLOW_DIAGNOSTICS
1390 c KPPMLD - mixed layer depth based on density criterion
1391 _RL KPPMLD(1 :sNx ,1 :sNy )
1392 #endif /* ALLOW_DIAGNOSTICS */
1393
1394 INTEGER I, J, K
1395 INTEGER ikppkey, kkppkey
1396
1397 c calculate density, alpha, beta in surface layer, and set dbsfc to zero
1398
1399 kkppkey = (ikppkey-1)*Nr + 1
1400
1401 #ifdef KPP_AUTODIFF_EXCESSIVE_STORE
1402 CADJ STORE theta(:,:,1,bi,bj) = comlev1_kpp_k, key=kkppkey
1403 CADJ STORE salt (:,:,1,bi,bj) = comlev1_kpp_k, key=kkppkey
1404 #endif /* KPP_AUTODIFF_EXCESSIVE_STORE */
1405 call FIND_RHO(
1406 I bi, bj, 1-OLx, sNx+OLx, 1-OLy, sNy+OLy, 1, 1,
1407 I theta, salt,
1408 O WORK1,
1409 I myThid )
1410 #ifdef KPP_AUTODIFF_EXCESSIVE_STORE
1411 CADJ STORE theta(:,:,1,bi,bj) = comlev1_kpp_k, key=kkppkey
1412 CADJ STORE salt (:,:,1,bi,bj) = comlev1_kpp_k, key=kkppkey
1413 #endif /* KPP_AUTODIFF_EXCESSIVE_STORE */
1414
1415 call FIND_ALPHA(
1416 I bi, bj, 1-OLx, sNx+OLx, 1-OLy, sNy+OLy, 1, 1,
1417 O WORK2, myThid )
1418
1419 call FIND_BETA(
1420 I bi, bj, 1-OLx, sNx+OLx, 1-OLy, sNy+OLy, 1, 1,
1421 O WORK3, myThid )
1422
1423 DO J = 1-OLy, sNy+OLy
1424 DO I = 1-OLx, sNx+OLx
1425 RHO1(I,J) = WORK1(I,J) + rhoConst
1426 TTALPHA(I,J,1) = WORK2(I,J)
1427 SSBETA(I,J,1) = WORK3(I,J)
1428 DBSFC(I,J,1) = 0.
1429 END DO
1430 END DO
1431
1432 #ifdef ALLOW_DIAGNOSTICS
1433 c work3 - density of t(1)-.8 & s(1 ) at depth 1
1434 IF ( useDiagnostics ) THEN
1435 DO J = 1, sNy
1436 DO I = 1, sNx
1437 KPPMLD(I,J) = ABS(R_low(I,J,bi,bj))
1438 WORK3 (I,J) = WORK1(I,J) - 0.8 * WORK2(I,J)
1439 END DO
1440 END DO
1441 ENDIF
1442 #endif /* ALLOW_DIAGNOSTICS */
1443
1444 c calculate alpha, beta, and gradients in interior layers
1445
1446 CHPF$ INDEPENDENT, NEW (RHOK,RHOKM1,RHO1K,WORK1,WORK2)
1447 DO K = 2, Nr
1448
1449 kkppkey = (ikppkey-1)*Nr + k
1450
1451 #ifdef KPP_AUTODIFF_EXCESSIVE_STORE
1452 CADJ STORE theta(:,:,k,bi,bj) = comlev1_kpp_k, key=kkppkey
1453 CADJ STORE salt (:,:,k,bi,bj) = comlev1_kpp_k, key=kkppkey
1454 #endif /* KPP_AUTODIFF_EXCESSIVE_STORE */
1455 call FIND_RHO(
1456 I bi, bj, 1-OLx, sNx+OLx, 1-OLy, sNy+OLy, K, K,
1457 I theta, salt,
1458 O RHOK,
1459 I myThid )
1460
1461 #ifdef KPP_AUTODIFF_EXCESSIVE_STORE
1462 CADJ STORE theta(:,:,k-1,bi,bj) = comlev1_kpp_k, key=kkppkey
1463 CADJ STORE salt (:,:,k-1,bi,bj) = comlev1_kpp_k, key=kkppkey
1464 #endif /* KPP_AUTODIFF_EXCESSIVE_STORE */
1465 call FIND_RHO(
1466 I bi, bj, 1-OLx, sNx+OLx, 1-OLy, sNy+OLy, K-1, K,
1467 I theta, salt,
1468 O RHOKM1,
1469 I myThid )
1470
1471 #ifdef KPP_AUTODIFF_EXCESSIVE_STORE
1472 CADJ STORE theta(:,:,1,bi,bj) = comlev1_kpp_k, key=kkppkey
1473 CADJ STORE salt (:,:,1,bi,bj) = comlev1_kpp_k, key=kkppkey
1474 #endif /* KPP_AUTODIFF_EXCESSIVE_STORE */
1475 call FIND_RHO(
1476 I bi, bj, 1-OLx, sNx+OLx, 1-OLy, sNy+OLy, 1, K,
1477 I theta, salt,
1478 O RHO1K,
1479 I myThid )
1480
1481 #ifdef KPP_AUTODIFF_EXCESSIVE_STORE
1482 CADJ STORE rhok (:,:) = comlev1_kpp_k, key=kkppkey
1483 CADJ STORE rhokm1(:,:) = comlev1_kpp_k, key=kkppkey
1484 CADJ STORE rho1k (:,:) = comlev1_kpp_k, key=kkppkey
1485 #endif /* KPP_AUTODIFF_EXCESSIVE_STORE */
1486
1487 call FIND_ALPHA(
1488 I bi, bj, 1-OLx, sNx+OLx, 1-OLy, sNy+OLy, K, K,
1489 O WORK1, myThid )
1490
1491 call FIND_BETA(
1492 I bi, bj, 1-OLx, sNx+OLx, 1-OLy, sNy+OLy, K, K,
1493 O WORK2, myThid )
1494
1495 DO J = 1-OLy, sNy+OLy
1496 DO I = 1-OLx, sNx+OLx
1497 TTALPHA(I,J,K) = WORK1 (I,J)
1498 SSBETA(I,J,K) = WORK2 (I,J)
1499 DBLOC(I,J,K-1) = gravity * (RHOK(I,J) - RHOKM1(I,J)) /
1500 & (RHOK(I,J) + rhoConst)
1501 DBSFC(I,J,K) = gravity * (RHOK(I,J) - RHO1K (I,J)) /
1502 & (RHOK(I,J) + rhoConst)
1503 END DO
1504 END DO
1505
1506 #ifdef ALLOW_DIAGNOSTICS
1507 IF ( useDiagnostics ) THEN
1508 c work1 - density of t(k-1) & s(k-1) at depth 1
1509 c work2 - density of t(k ) & s(k ) at depth 1
1510 c work3 - density of t(1)-.8 & s(1 ) at depth 1
1511 call FIND_RHO(
1512 I bi, bj, 1, sNx, 1, sNy, K-1, 1, theta, salt,
1513 O WORK1,
1514 I myThid )
1515 call FIND_RHO(
1516 I bi, bj, 1, sNx, 1, sNy, K , 1, theta, salt,
1517 O WORK2,
1518 I myThid )
1519 DO J = 1, sNy
1520 DO I = 1, sNx
1521 IF ( k .LE. klowC(I,J,bi,bj) .AND.
1522 & WORK1(I,J) .LT. WORK3(I,J) .AND.
1523 & WORK2(I,J) .GE. WORK3(I,J) ) THEN
1524 KPPMLD(I,J) = MIN ( KPPMLD(I,J),
1525 & ABS(((WORK3(I,J)-WORK1(I,J))*rC(k)+
1526 & (WORK2(I,J)-WORK3(I,J))*rC(k-1))/
1527 & (WORK2(I,J)-WORK1(I,J))))
1528 ENDIF
1529 END DO
1530 END DO
1531 ENDIF
1532 #endif /* ALLOW_DIAGNOSTICS */
1533
1534 END DO
1535
1536 c compute arrays for K = Nrp1
1537 DO J = 1-OLy, sNy+OLy
1538 DO I = 1-OLx, sNx+OLx
1539 TTALPHA(I,J,Nrp1) = TTALPHA(I,J,Nr)
1540 SSBETA(I,J,Nrp1) = SSBETA(I,J,Nr)
1541 DBLOC(I,J,Nr) = 0.
1542 END DO
1543 END DO
1544
1545 #ifdef ALLOW_DIAGNOSTICS
1546 IF ( useDiagnostics ) THEN
1547 CALL DIAGNOSTICS_FILL(KPPmld,'KPPmld ',0,1,3,bi,bj,myThid)
1548 ENDIF
1549 #endif /* ALLOW_DIAGNOSTICS */
1550
1551 #endif /* ALLOW_KPP */
1552
1553 RETURN
1554 END

  ViewVC Help
Powered by ViewVC 1.1.22