/[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.29 - (show annotations) (download)
Mon Apr 30 13:49:40 2007 UTC (17 years, 2 months ago) by jmc
Branch: MAIN
Changes since 1.28: +6 -3 lines
undo previous modifs which were producing a TAF seg-fault.

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

  ViewVC Help
Powered by ViewVC 1.1.22