/[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.50 - (show annotations) (download)
Sun Aug 11 02:38:18 2013 UTC (10 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64m, checkpoint64o, checkpoint64n
Changes since 1.49: +9 -10 lines
should never call any of the DIAGNOSTICS_[]FILL routine if useDiagnostics=F

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

  ViewVC Help
Powered by ViewVC 1.1.22