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

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

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


Revision 1.47 - (hide annotations) (download)
Sat Nov 21 01:27:07 2009 UTC (14 years, 7 months ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint62a, checkpoint62, checkpoint61z
Changes since 1.46: +12 -9 lines
fixing diagnostics_fill calls

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

  ViewVC Help
Powered by ViewVC 1.1.22