/[MITgcm]/MITgcm_contrib/ifenty/ECCO_v4/code_ad/mom_calc_visc.F
ViewVC logotype

Annotation of /MITgcm_contrib/ifenty/ECCO_v4/code_ad/mom_calc_visc.F

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


Revision 1.1 - (hide annotations) (download)
Tue Apr 29 21:56:12 2014 UTC (11 years, 3 months ago) by ifenty
Branch: MAIN
CVS Tags: HEAD
ECCO v4 code and input directories

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

  ViewVC Help
Powered by ViewVC 1.1.22