/[MITgcm]/MITgcm_contrib/ecco_darwin/v4_llc270/code/mom_calc_visc.F
ViewVC logotype

Annotation of /MITgcm_contrib/ecco_darwin/v4_llc270/code/mom_calc_visc.F

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


Revision 1.1 - (hide annotations) (download)
Tue Nov 28 22:09:00 2017 UTC (7 years, 8 months ago) by dimitri
Branch: MAIN
CVS Tags: HEAD
Hong Zhang's forward-only optimized llc270 (2001-2015)

1 dimitri 1.1 C $Header: /u/gcmpack/MITgcm_contrib/gael/verification/global_oce_llc90/code/mom_calc_visc.F,v 1.3 2014/10/20 03:23:48 gforget Exp $
2     C $Name: $
3    
4     #include "MOM_COMMON_OPTIONS.h"
5     #ifdef ALLOW_AUTODIFF
6     # include "AUTODIFF_OPTIONS.h"
7     #endif
8    
9     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
10     CBOP
11     C !ROUTINE: MOM_CALC_VISC
12    
13     C !INTERFACE:
14     SUBROUTINE MOM_CALC_VISC(
15     I bi,bj,k,
16     O viscAh_Z,viscAh_D,viscA4_Z,viscA4_D,
17     I hDiv,vort3,tension,strain,KE,hFacZ,
18     I myThid)
19    
20     C !DESCRIPTION:
21     C Calculate horizontal viscosities (L is typical grid width)
22     C harmonic viscosity=
23     C viscAh (or viscAhD on div pts and viscAhZ on zeta pts)
24     C +0.25*L**2*viscAhGrid/deltaT
25     C +sqrt((viscC2leith/pi)**6*grad(Vort3)**2
26     C +(viscC2leithD/pi)**6*grad(hDiv)**2)*L**3
27     C +(viscC2smag/pi)**2*L**2*sqrt(Tension**2+Strain**2)
28     C
29     C biharmonic viscosity=
30     C viscA4 (or viscA4D on div pts and viscA4Z on zeta pts)
31     C +0.25*0.125*L**4*viscA4Grid/deltaT (approx)
32     C +0.125*L**5*sqrt((viscC4leith/pi)**6*grad(Vort3)**2
33     C +(viscC4leithD/pi)**6*grad(hDiv)**2)
34     C +0.125*L**4*(viscC4smag/pi)**2*sqrt(Tension**2+Strain**2)
35     C
36     C Note that often 0.125*L**2 is the scale between harmonic and
37     C biharmonic (see Griffies and Hallberg (2000))
38     C This allows the same value of the coefficient to be used
39     C for roughly similar results with biharmonic and harmonic
40     C
41     C LIMITERS -- limit min and max values of viscosities
42     C viscAhReMax is min value for grid point harmonic Reynolds num
43     C harmonic viscosity>sqrt(2*KE)*L/viscAhReMax
44     C
45     C viscA4ReMax is min value for grid point biharmonic Reynolds num
46     C biharmonic viscosity>sqrt(2*KE)*L**3/8/viscA4ReMax
47     C
48     C viscAhgridmax is CFL stability limiter for harmonic viscosity
49     C harmonic viscosity<0.25*viscAhgridmax*L**2/deltaT
50     C
51     C viscA4gridmax is CFL stability limiter for biharmonic viscosity
52     C biharmonic viscosity<viscA4gridmax*L**4/32/deltaT (approx)
53     C
54     C viscAhgridmin and viscA4gridmin are lower limits for viscosity:
55     C harmonic viscosity>0.25*viscAhgridmin*L**2/deltaT
56     C biharmonic viscosity>viscA4gridmin*L**4/32/deltaT (approx)
57    
58     C RECOMMENDED VALUES
59     C viscC2Leith=1-3
60     C viscC2LeithD=1-3
61     C viscC4Leith=1-3
62     C viscC4LeithD=1.5-3
63     C viscC2smag=2.2-4 (Griffies and Hallberg,2000)
64     C 0.2-0.9 (Smagorinsky,1993)
65     C viscC4smag=2.2-4 (Griffies and Hallberg,2000)
66     C viscAhReMax>=1, (<2 suppresses a computational mode)
67     C viscA4ReMax>=1, (<2 suppresses a computational mode)
68     C viscAhgridmax=1
69     C viscA4gridmax=1
70     C viscAhgrid<1
71     C viscA4grid<1
72     C viscAhgridmin<<1
73     C viscA4gridmin<<1
74    
75     C !USES:
76     IMPLICIT NONE
77    
78     C == Global variables ==
79     #include "SIZE.h"
80     #include "GRID.h"
81     #include "EEPARAMS.h"
82     #include "PARAMS.h"
83     #include "MOM_VISC.h"
84     #ifdef ALLOW_AUTODIFF_TAMC
85     #include "tamc.h"
86     #include "tamc_keys.h"
87     #endif /* ALLOW_AUTODIFF_TAMC */
88    
89     C !INPUT/OUTPUT PARAMETERS:
90     C myThid :: my thread Id number
91     INTEGER bi,bj,k
92     _RL viscAh_Z(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
93     _RL viscAh_D(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
94     _RL viscA4_Z(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
95     _RL viscA4_D(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
96     _RL hDiv(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
97     _RL vort3(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
98     _RL tension(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
99     _RL strain(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
100     _RL KE(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
101     _RS hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
102     INTEGER myThid
103     CEOP
104    
105     C !LOCAL VARIABLES:
106     INTEGER i,j
107     #ifdef ALLOW_NONHYDROSTATIC
108     _RL shiftAh, shiftA4
109     #endif
110     #ifdef ALLOW_AUTODIFF_TAMC
111     INTEGER lockey_1, lockey_2
112     #endif
113     _RL smag2fac, smag4fac
114     _RL leith2fac, leith4fac
115     _RL leithD2fac, leithD4fac
116     _RL viscAhRe_max, viscA4Re_max
117     _RL Alin,grdVrt,grdDiv, keZpt
118     _RL L2, L3, L5, L2rdt, L4rdt, recip_dt
119     _RL Uscl,U4scl
120     _RL divDx(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
121     _RL divDy(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
122     _RL vrtDx(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
123     _RL vrtDy(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
124     _RL viscAh_ZMax(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
125     _RL viscAh_DMax(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
126     _RL viscA4_ZMax(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
127     _RL viscA4_DMax(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
128     _RL viscAh_ZMin(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
129     _RL viscAh_DMin(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
130     _RL viscA4_ZMin(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
131     _RL viscA4_DMin(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
132     _RL viscAh_ZLth(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
133     _RL viscAh_DLth(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
134     _RL viscA4_ZLth(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
135     _RL viscA4_DLth(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
136     _RL viscAh_ZLthD(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
137     _RL viscAh_DLthD(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
138     _RL viscA4_ZLthD(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
139     _RL viscA4_DLthD(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
140     _RL viscAh_ZSmg(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
141     _RL viscAh_DSmg(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
142     _RL viscA4_ZSmg(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
143     _RL viscA4_DSmg(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
144     LOGICAL calcLeith, calcSmag
145    
146     #ifdef ALLOW_AUTODIFF_TAMC
147     act1 = bi - myBxLo(myThid)
148     max1 = myBxHi(myThid) - myBxLo(myThid) + 1
149     act2 = bj - myByLo(myThid)
150     max2 = myByHi(myThid) - myByLo(myThid) + 1
151     act3 = myThid - 1
152     max3 = nTx*nTy
153     act4 = ikey_dynamics - 1
154     ikey = (act1 + 1) + act2*max1
155     & + act3*max1*max2
156     & + act4*max1*max2*max3
157     lockey_1 = (ikey-1)*Nr + k
158     #endif /* ALLOW_AUTODIFF_TAMC */
159    
160     C-- Set flags which are used in this S/R and elsewhere :
161     C useVariableVisc, useHarmonicVisc and useBiharmonicVisc
162     C are now set early on (in S/R SET_PARAMS)
163    
164     c IF ( useVariableVisc ) THEN
165     C---- variable viscosity :
166    
167     recip_dt = 1. _d 0
168     IF ( deltaTmom.NE.0. ) recip_dt = 1. _d 0/deltaTmom
169    
170     IF ( useHarmonicVisc .AND. viscAhReMax.NE.0. ) THEN
171     viscAhRe_max=SQRT(2. _d 0)/viscAhReMax
172     ELSE
173     viscAhRe_max=0. _d 0
174     ENDIF
175    
176     IF ( useBiharmonicVisc .AND. viscA4ReMax.NE.0. ) THEN
177     viscA4Re_max=0.125 _d 0*SQRT(2. _d 0)/viscA4ReMax
178     ELSE
179     viscA4Re_max=0. _d 0
180     ENDIF
181    
182     calcLeith=
183     & (viscC2leith.NE.0.)
184     & .OR.(viscC2leithD.NE.0.)
185     & .OR.(viscC4leith.NE.0.)
186     & .OR.(viscC4leithD.NE.0.)
187    
188     calcSmag=
189     & (viscC2smag.NE.0.)
190     & .OR.(viscC4smag.NE.0.)
191    
192     IF (calcSmag) THEN
193     smag2fac=(viscC2smag/pi)**2
194     smag4fac=0.125 _d 0*(viscC4smag/pi)**2
195     ELSE
196     smag2fac=0. _d 0
197     smag4fac=0. _d 0
198     ENDIF
199    
200     IF (calcLeith) THEN
201     IF (useFullLeith) THEN
202     leith2fac =(viscC2leith /pi)**6
203     leithD2fac=(viscC2leithD/pi)**6
204     leith4fac =0.015625 _d 0*(viscC4leith /pi)**6
205     leithD4fac=0.015625 _d 0*(viscC4leithD/pi)**6
206     ELSE
207     leith2fac =(viscC2leith /pi)**3
208     leithD2fac=(viscC2leithD/pi)**3
209     leith4fac =0.125 _d 0*(viscC4leith /pi)**3
210     leithD4fac=0.125 _d 0*(viscC4leithD/pi)**3
211     ENDIF
212     ELSE
213     leith2fac=0. _d 0
214     leith4fac=0. _d 0
215     leithD2fac=0. _d 0
216     leithD4fac=0. _d 0
217     ENDIF
218    
219     DO j=1-OLy,sNy+OLy
220     DO i=1-OLx,sNx+OLx
221     C- viscosity arrays have been initialised everywhere before calling this S/R
222     c viscAh_D(i,j) = viscAhD
223     c viscAh_Z(i,j) = viscAhZ
224     c viscA4_D(i,j) = viscA4D
225     c viscA4_Z(i,j) = viscA4Z
226    
227     visca4_zsmg(i,j) = 0. _d 0
228     viscah_zsmg(i,j) = 0. _d 0
229    
230     viscAh_Dlth(i,j) = 0. _d 0
231     viscA4_Dlth(i,j) = 0. _d 0
232     viscAh_DlthD(i,j)= 0. _d 0
233     viscA4_DlthD(i,j)= 0. _d 0
234    
235     viscAh_DSmg(i,j) = 0. _d 0
236     viscA4_DSmg(i,j) = 0. _d 0
237    
238     viscAh_ZLth(i,j) = 0. _d 0
239     viscA4_ZLth(i,j) = 0. _d 0
240     viscAh_ZLthD(i,j)= 0. _d 0
241     viscA4_ZLthD(i,j)= 0. _d 0
242     ENDDO
243     ENDDO
244    
245     C- Initialise to zero gradient of vorticity & divergence:
246     DO j=1-OLy,sNy+OLy
247     DO i=1-OLx,sNx+OLx
248     divDx(i,j) = 0.
249     divDy(i,j) = 0.
250     vrtDx(i,j) = 0.
251     vrtDy(i,j) = 0.
252     ENDDO
253     ENDDO
254    
255     IF ( calcLeith ) THEN
256     C-- horizontal gradient of horizontal divergence:
257     C- gradient in x direction:
258     IF (useCubedSphereExchange) THEN
259     C to compute d/dx(hDiv), fill corners with appropriate values:
260     CALL FILL_CS_CORNER_TR_RL( 1, .FALSE.,
261     & hDiv, bi,bj, myThid )
262     ENDIF
263     DO j=2-OLy,sNy+OLy-1
264     DO i=2-OLx,sNx+OLx-1
265     divDx(i,j) = (hDiv(i,j)-hDiv(i-1,j))*recip_dxC(i,j,bi,bj)
266     ENDDO
267     ENDDO
268    
269     C- gradient in y direction:
270     IF (useCubedSphereExchange) THEN
271     C to compute d/dy(hDiv), fill corners with appropriate values:
272     CALL FILL_CS_CORNER_TR_RL( 2, .FALSE.,
273     & hDiv, bi,bj, myThid )
274     ENDIF
275     DO j=2-OLy,sNy+OLy-1
276     DO i=2-OLx,sNx+OLx-1
277     divDy(i,j) = (hDiv(i,j)-hDiv(i,j-1))*recip_dyC(i,j,bi,bj)
278     ENDDO
279     ENDDO
280    
281     C-- horizontal gradient of vertical vorticity:
282     C- gradient in x direction:
283     DO j=2-OLy,sNy+OLy
284     DO i=2-OLx,sNx+OLx-1
285     vrtDx(i,j) = (vort3(i+1,j)-vort3(i,j))
286     & *recip_dxG(i,j,bi,bj)
287     & *maskS(i,j,k,bi,bj)
288     #ifdef ALLOW_OBCS
289     & *maskInS(i,j,bi,bj)
290     #endif
291     ENDDO
292     ENDDO
293     C- gradient in y direction:
294     DO j=2-OLy,sNy+OLy-1
295     DO i=2-OLx,sNx+OLx
296     vrtDy(i,j) = (vort3(i,j+1)-vort3(i,j))
297     & *recip_dyG(i,j,bi,bj)
298     & *maskW(i,j,k,bi,bj)
299     #ifdef ALLOW_OBCS
300     & *maskInW(i,j,bi,bj)
301     #endif
302     ENDDO
303     ENDDO
304    
305     C-- end if calcLeith
306     ENDIF
307    
308     DO j=2-OLy,sNy+OLy-1
309     DO i=2-OLx,sNx+OLx-1
310     CCCCCCCCCCCCCCC Divergence Point CalculationsCCCCCCCCCCCCCCCCCCCC
311    
312     #ifdef ALLOW_AUTODIFF_TAMC
313     # ifndef AUTODIFF_DISABLE_LEITH
314     lockey_2 = i+olx + (sNx+2*olx)*(j+oly-1)
315     & + (sNx+2*olx)*(sNy+2*oly)*(lockey_1-1)
316     CADJ STORE viscA4_ZSmg(i,j)
317     CADJ & = comlev1_mom_ijk_loop , key=lockey_2, byte=isbyte
318     CADJ STORE viscAh_ZSmg(i,j)
319     CADJ & = comlev1_mom_ijk_loop , key=lockey_2, byte=isbyte
320     # endif
321     #endif /* ALLOW_AUTODIFF_TAMC */
322    
323     C These are (powers of) length scales
324     L2 = L2_D(i,j,bi,bj)
325     L2rdt = 0.25 _d 0*recip_dt*L2
326     L3 = L3_D(i,j,bi,bj)
327     L4rdt = L4rdt_D(i,j,bi,bj)
328     L5 = (L2*L3)
329    
330     #ifndef AUTODIFF_DISABLE_REYNOLDS_SCALE
331     C Velocity Reynolds Scale
332     IF ( viscAhRe_max.GT.0. .AND. KE(i,j).GT.0. ) THEN
333     Uscl=SQRT(KE(i,j)*L2)*viscAhRe_max
334     ELSE
335     Uscl=0.
336     ENDIF
337     IF ( viscA4Re_max.GT.0. .AND. KE(i,j).GT.0. ) THEN
338     U4scl=SQRT(KE(i,j))*L3*viscA4Re_max
339     ELSE
340     U4scl=0.
341     ENDIF
342     #endif /* ndef AUTODIFF_DISABLE_REYNOLDS_SCALE */
343    
344     #ifndef AUTODIFF_DISABLE_LEITH
345     IF (useFullLeith.AND.calcLeith) THEN
346     C This is the vector magnitude of the vorticity gradient squared
347     grdVrt=0.25 _d 0*( (vrtDx(i,j+1)*vrtDx(i,j+1)
348     & + vrtDx(i,j)*vrtDx(i,j) )
349     & + (vrtDy(i+1,j)*vrtDy(i+1,j)
350     & + vrtDy(i,j)*vrtDy(i,j) ) )
351    
352     C This is the vector magnitude of grad (div.v) squared
353     C Using it in Leith serves to damp instabilities in w.
354     grdDiv=0.25 _d 0*( (divDx(i+1,j)*divDx(i+1,j)
355     & + divDx(i,j)*divDx(i,j) )
356     & + (divDy(i,j+1)*divDy(i,j+1)
357     & + divDy(i,j)*divDy(i,j) ) )
358    
359     viscAh_DLth(i,j)=
360     & SQRT(leith2fac*grdVrt+leithD2fac*grdDiv)*L3
361     viscA4_DLth(i,j)=
362     & SQRT(leith4fac*grdVrt+leithD4fac*grdDiv)*L5
363     viscAh_DLthd(i,j)=
364     & SQRT(leithD2fac*grdDiv)*L3
365     viscA4_DLthd(i,j)=
366     & SQRT(leithD4fac*grdDiv)*L5
367     ELSEIF (calcLeith) THEN
368     C but this approximation will work on cube (and differs by as much as 4X)
369     grdVrt=MAX( ABS(vrtDx(i,j+1)), ABS(vrtDx(i,j)) )
370     grdVrt=MAX( grdVrt, ABS(vrtDy(i+1,j)) )
371     grdVrt=MAX( grdVrt, ABS(vrtDy(i,j)) )
372    
373     C This approximation is good to the same order as above...
374     grdDiv=MAX( ABS(divDx(i+1,j)), ABS(divDx(i,j)) )
375     grdDiv=MAX( grdDiv, ABS(divDy(i,j+1)) )
376     grdDiv=MAX( grdDiv, ABS(divDy(i,j)) )
377    
378     viscAh_Dlth(i,j)=(leith2fac*grdVrt+(leithD2fac*grdDiv))*L3
379     viscA4_Dlth(i,j)=(leith4fac*grdVrt+(leithD4fac*grdDiv))*L5
380     viscAh_DlthD(i,j)=((leithD2fac*grdDiv))*L3
381     viscA4_DlthD(i,j)=((leithD4fac*grdDiv))*L5
382     ELSE
383     viscAh_Dlth(i,j)=0. _d 0
384     viscA4_Dlth(i,j)=0. _d 0
385     viscAh_DlthD(i,j)=0. _d 0
386     viscA4_DlthD(i,j)=0. _d 0
387     ENDIF
388    
389     IF (calcSmag) THEN
390     viscAh_DSmg(i,j)=L2
391     & *SQRT(tension(i,j)**2
392     & +0.25 _d 0*(strain(i+1, j )**2+strain( i ,j+1)**2
393     & +strain(i , j )**2+strain(i+1,j+1)**2))
394     viscA4_DSmg(i,j)=smag4fac*L2*viscAh_DSmg(i,j)
395     viscAh_DSmg(i,j)=smag2fac*viscAh_DSmg(i,j)
396     ELSE
397     viscAh_DSmg(i,j)=0. _d 0
398     viscA4_DSmg(i,j)=0. _d 0
399     ENDIF
400     #endif /* AUTODIFF_DISABLE_LEITH */
401    
402     C Harmonic on Div.u points
403     Alin=viscAhD+viscAhGrid*L2rdt
404     & +viscAh_DLth(i,j)+viscAh_DSmg(i,j)
405     #ifdef ALLOW_3D_VISCAH
406     & +viscFacAdj*viscAhDfld(i,j,k,bi,bj)
407     #endif
408     viscAh_DMin(i,j)=MAX(viscAhGridMin*L2rdt,Uscl)
409     viscAh_D(i,j)=MAX(viscAh_DMin(i,j),Alin)
410     viscAh_DMax(i,j)=MIN(viscAhGridMax*L2rdt,viscAhMax)
411     viscAh_D(i,j)=MIN(viscAh_DMax(i,j),viscAh_D(i,j))
412    
413     if ( (yC(i,j,bi,bj).GE.33.) .AND.
414     & (yC(i,j,bi,bj).LE.39.) .AND.
415     & (xC(i,j,bi,bj).GE.-7.) .AND.
416     & (xC(i,j,bi,bj).LE.-2.)
417     & ) then
418     viscAh_D(i,j)=10. _d 0 * viscAh_D(i,j)
419     endif
420    
421     C BiHarmonic on Div.u points
422     Alin=viscA4D+viscA4Grid*L4rdt
423     & +viscA4_DLth(i,j)+viscA4_DSmg(i,j)
424     #ifdef ALLOW_3D_VISCA4
425     & +viscFacAdj*viscA4Dfld(i,j,k,bi,bj)
426     #endif
427     viscA4_DMin(i,j)=MAX(viscA4GridMin*L4rdt,U4scl)
428     viscA4_D(i,j)=MAX(viscA4_DMin(i,j),Alin)
429     viscA4_DMax(i,j)=MIN(viscA4GridMax*L4rdt,viscA4Max)
430     viscA4_D(i,j)=MIN(viscA4_DMax(i,j),viscA4_D(i,j))
431    
432     CCCCCCCCCCCCC Vorticity Point CalculationsCCCCCCCCCCCCCCCCCC
433     C These are (powers of) length scales
434     L2 = L2_Z(i,j,bi,bj)
435     L2rdt = 0.25 _d 0*recip_dt*L2
436     L3 = L3_Z(i,j,bi,bj)
437     L4rdt = L4rdt_Z(i,j,bi,bj)
438     L5 = (L2*L3)
439    
440     #ifndef AUTODIFF_DISABLE_REYNOLDS_SCALE
441     C Velocity Reynolds Scale (Pb here at CS-grid corners !)
442     IF ( viscAhRe_max.GT.0. .OR. viscA4Re_max.GT.0. ) THEN
443     keZpt=0.25 _d 0*( (KE(i,j)+KE(i-1,j-1))
444     & +(KE(i-1,j)+KE(i,j-1)) )
445     IF ( keZpt.GT.0. ) THEN
446     Uscl = SQRT(keZpt*L2)*viscAhRe_max
447     U4scl= SQRT(keZpt)*L3*viscA4Re_max
448     ELSE
449     Uscl =0.
450     U4scl=0.
451     ENDIF
452     ELSE
453     Uscl =0.
454     U4scl=0.
455     ENDIF
456     #endif /* ndef AUTODIFF_DISABLE_REYNOLDS_SCALE */
457    
458     #ifndef AUTODIFF_DISABLE_LEITH
459     C This is the vector magnitude of the vorticity gradient squared
460     IF (useFullLeith.AND.calcLeith) THEN
461     grdVrt=0.25 _d 0*( (vrtDx(i-1,j)*vrtDx(i-1,j)
462     & + vrtDx(i,j)*vrtDx(i,j) )
463     & + (vrtDy(i,j-1)*vrtDy(i,j-1)
464     & + vrtDy(i,j)*vrtDy(i,j) ) )
465    
466     C This is the vector magnitude of grad(div.v) squared
467     grdDiv=0.25 _d 0*( (divDx(i,j-1)*divDx(i,j-1)
468     & + divDx(i,j)*divDx(i,j) )
469     & + (divDy(i-1,j)*divDy(i-1,j)
470     & + divDy(i,j)*divDy(i,j) ) )
471    
472     viscAh_ZLth(i,j)=
473     & SQRT(leith2fac*grdVrt+leithD2fac*grdDiv)*L3
474     viscA4_ZLth(i,j)=
475     & SQRT(leith4fac*grdVrt+leithD4fac*grdDiv)*L5
476     viscAh_ZLthD(i,j)=
477     & SQRT(leithD2fac*grdDiv)*L3
478     viscA4_ZLthD(i,j)=
479     & SQRT(leithD4fac*grdDiv)*L5
480    
481     ELSEIF (calcLeith) THEN
482     C but this approximation will work on cube (and differs by 4X)
483     grdVrt=MAX( ABS(vrtDx(i-1,j)), ABS(vrtDx(i,j)) )
484     grdVrt=MAX( grdVrt, ABS(vrtDy(i,j-1)) )
485     grdVrt=MAX( grdVrt, ABS(vrtDy(i,j)) )
486    
487     grdDiv=MAX( ABS(divDx(i,j)), ABS(divDx(i,j-1)) )
488     grdDiv=MAX( grdDiv, ABS(divDy(i,j)) )
489     grdDiv=MAX( grdDiv, ABS(divDy(i-1,j)) )
490    
491     viscAh_ZLth(i,j)=(leith2fac*grdVrt+(leithD2fac*grdDiv))*L3
492     viscA4_ZLth(i,j)=(leith4fac*grdVrt+(leithD4fac*grdDiv))*L5
493     viscAh_ZLthD(i,j)=(leithD2fac*grdDiv)*L3
494     viscA4_ZLthD(i,j)=(leithD4fac*grdDiv)*L5
495     ELSE
496     viscAh_ZLth(i,j)=0. _d 0
497     viscA4_ZLth(i,j)=0. _d 0
498     viscAh_ZLthD(i,j)=0. _d 0
499     viscA4_ZLthD(i,j)=0. _d 0
500     ENDIF
501    
502     IF (calcSmag) THEN
503     viscAh_ZSmg(i,j)=L2
504     & *SQRT(strain(i,j)**2
505     & +0.25 _d 0*(tension( i , j )**2+tension( i ,j-1)**2
506     & +tension(i-1, j )**2+tension(i-1,j-1)**2))
507     viscA4_ZSmg(i,j)=smag4fac*L2*viscAh_ZSmg(i,j)
508     viscAh_ZSmg(i,j)=smag2fac*viscAh_ZSmg(i,j)
509     ENDIF
510     #endif /* AUTODIFF_DISABLE_LEITH */
511    
512     C Harmonic on Zeta points
513     Alin=viscAhZ+viscAhGrid*L2rdt
514     & +viscAh_ZLth(i,j)+viscAh_ZSmg(i,j)
515     #ifdef ALLOW_3D_VISCAH
516     & +viscFacAdj*viscAhZfld(i,j,k,bi,bj)
517     #endif
518     viscAh_ZMin(i,j)=MAX(viscAhGridMin*L2rdt,Uscl)
519     viscAh_Z(i,j)=MAX(viscAh_ZMin(i,j),Alin)
520     viscAh_ZMax(i,j)=MIN(viscAhGridMax*L2rdt,viscAhMax)
521     viscAh_Z(i,j)=MIN(viscAh_ZMax(i,j),viscAh_Z(i,j))
522    
523     if ( (yG(i,j,bi,bj).GE.33.) .AND.
524     & (yG(i,j,bi,bj).LE.39.) .AND.
525     & (xG(i,j,bi,bj).GE.-7.) .AND.
526     & (xG(i,j,bi,bj).LE.-2.)
527     & ) then
528     viscAh_Z(i,j)=10. _d 0 * viscAh_Z(i,j)
529     endif
530    
531     C BiHarmonic on Zeta points
532     Alin=viscA4Z+viscA4Grid*L4rdt
533     & +viscA4_ZLth(i,j)+viscA4_ZSmg(i,j)
534     #ifdef ALLOW_3D_VISCA4
535     & +viscFacAdj*viscA4Zfld(i,j,k,bi,bj)
536     #endif
537     viscA4_ZMin(i,j)=MAX(viscA4GridMin*L4rdt,U4scl)
538     viscA4_Z(i,j)=MAX(viscA4_ZMin(i,j),Alin)
539     viscA4_ZMax(i,j)=MIN(viscA4GridMax*L4rdt,viscA4Max)
540     viscA4_Z(i,j)=MIN(viscA4_ZMax(i,j),viscA4_Z(i,j))
541     ENDDO
542     ENDDO
543    
544     #ifdef ALLOW_NONHYDROSTATIC
545     IF ( nonHydrostatic ) THEN
546     C-- Pass Viscosities to calc_gw (if constant, not necessary)
547    
548     IF ( k.LT.Nr ) THEN
549     C Prepare for next level (next call)
550     DO j=1-OLy,sNy+OLy
551     DO i=1-OLx,sNx+OLx
552     viscAh_W(i,j,k+1,bi,bj) = halfRL*viscAh_D(i,j)
553     viscA4_W(i,j,k+1,bi,bj) = halfRL*viscA4_D(i,j)
554     ENDDO
555     ENDDO
556     ENDIF
557    
558     shiftAh = viscAhW - viscAhD
559     shiftA4 = viscA4W - viscA4D
560     IF ( k.EQ.1 ) THEN
561     C These values dont get used
562     DO j=1-OLy,sNy+OLy
563     DO i=1-OLx,sNx+OLx
564     viscAh_W(i,j,k,bi,bj) = shiftAh + viscAh_D(i,j)
565     viscA4_W(i,j,k,bi,bj) = shiftA4 + viscA4_D(i,j)
566     ENDDO
567     ENDDO
568     ELSE
569     C Note that previous call of this function has already added half.
570     DO j=1-OLy,sNy+OLy
571     DO i=1-OLx,sNx+OLx
572     viscAh_W(i,j,k,bi,bj) = shiftAh + viscAh_W(i,j,k,bi,bj)
573     & + halfRL*viscAh_D(i,j)
574     viscA4_W(i,j,k,bi,bj) = shiftA4 + viscA4_W(i,j,k,bi,bj)
575     & + halfRL*viscA4_D(i,j)
576     ENDDO
577     ENDDO
578     ENDIF
579    
580     ENDIF
581     #endif /* ALLOW_NONHYDROSTATIC */
582    
583     c ELSE
584     C---- use constant viscosity (useVariableVisc=F):
585     c DO j=1-OLy,sNy+OLy
586     c DO i=1-OLx,sNx+OLx
587     c viscAh_D(i,j) = viscAhD
588     c viscAh_Z(i,j) = viscAhZ
589     c viscA4_D(i,j) = viscA4D
590     c viscA4_Z(i,j) = viscA4Z
591     c ENDDO
592     c ENDDO
593     C---- variable/constant viscosity : end if/else block
594     c ENDIF
595    
596     #ifdef ALLOW_DIAGNOSTICS
597     IF (useDiagnostics) THEN
598     CALL DIAGNOSTICS_FILL(viscAh_D,'VISCAHD ',k,1,2,bi,bj,myThid)
599     CALL DIAGNOSTICS_FILL(viscA4_D,'VISCA4D ',k,1,2,bi,bj,myThid)
600     CALL DIAGNOSTICS_FILL(viscAh_Z,'VISCAHZ ',k,1,2,bi,bj,myThid)
601     CALL DIAGNOSTICS_FILL(viscA4_Z,'VISCA4Z ',k,1,2,bi,bj,myThid)
602    
603     CALL DIAGNOSTICS_FILL(viscAh_DMax,'VAHDMAX ',k,1,2,bi,bj,myThid)
604     CALL DIAGNOSTICS_FILL(viscA4_DMax,'VA4DMAX ',k,1,2,bi,bj,myThid)
605     CALL DIAGNOSTICS_FILL(viscAh_ZMax,'VAHZMAX ',k,1,2,bi,bj,myThid)
606     CALL DIAGNOSTICS_FILL(viscA4_ZMax,'VA4ZMAX ',k,1,2,bi,bj,myThid)
607    
608     CALL DIAGNOSTICS_FILL(viscAh_DMin,'VAHDMIN ',k,1,2,bi,bj,myThid)
609     CALL DIAGNOSTICS_FILL(viscA4_DMin,'VA4DMIN ',k,1,2,bi,bj,myThid)
610     CALL DIAGNOSTICS_FILL(viscAh_ZMin,'VAHZMIN ',k,1,2,bi,bj,myThid)
611     CALL DIAGNOSTICS_FILL(viscA4_ZMin,'VA4ZMIN ',k,1,2,bi,bj,myThid)
612    
613     CALL DIAGNOSTICS_FILL(viscAh_DLth,'VAHDLTH ',k,1,2,bi,bj,myThid)
614     CALL DIAGNOSTICS_FILL(viscA4_DLth,'VA4DLTH ',k,1,2,bi,bj,myThid)
615     CALL DIAGNOSTICS_FILL(viscAh_ZLth,'VAHZLTH ',k,1,2,bi,bj,myThid)
616     CALL DIAGNOSTICS_FILL(viscA4_ZLth,'VA4ZLTH ',k,1,2,bi,bj,myThid)
617    
618     CALL DIAGNOSTICS_FILL(viscAh_DLthD,'VAHDLTHD',
619     & k,1,2,bi,bj,myThid)
620     CALL DIAGNOSTICS_FILL(viscA4_DLthD,'VA4DLTHD',
621     & k,1,2,bi,bj,myThid)
622     CALL DIAGNOSTICS_FILL(viscAh_ZLthD,'VAHZLTHD',
623     & k,1,2,bi,bj,myThid)
624     CALL DIAGNOSTICS_FILL(viscA4_ZLthD,'VA4ZLTHD',
625     & k,1,2,bi,bj,myThid)
626    
627     CALL DIAGNOSTICS_FILL(viscAh_DSmg,'VAHDSMAG',k,1,2,bi,bj,myThid)
628     CALL DIAGNOSTICS_FILL(viscA4_DSmg,'VA4DSMAG',k,1,2,bi,bj,myThid)
629     CALL DIAGNOSTICS_FILL(viscAh_ZSmg,'VAHZSMAG',k,1,2,bi,bj,myThid)
630     CALL DIAGNOSTICS_FILL(viscA4_ZSmg,'VA4ZSMAG',k,1,2,bi,bj,myThid)
631     ENDIF
632     #endif
633    
634     RETURN
635     END

  ViewVC Help
Powered by ViewVC 1.1.22