/[MITgcm]/MITgcm/pkg/mom_common/mom_calc_visc.F
ViewVC logotype

Diff of /MITgcm/pkg/mom_common/mom_calc_visc.F

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

revision 1.6 by baylor, Tue Sep 20 21:01:30 2005 UTC revision 1.15 by jmc, Mon Oct 3 21:43:03 2005 UTC
# Line 8  C $Name$ Line 8  C $Name$
8       I        bi,bj,k,       I        bi,bj,k,
9       O        viscAh_Z,viscAh_D,viscA4_Z,viscA4_D,       O        viscAh_Z,viscAh_D,viscA4_Z,viscA4_D,
10       O        harmonic,biharmonic,useVariableViscosity,       O        harmonic,biharmonic,useVariableViscosity,
11       I        hDiv,vort3,tension,strain,KE,hfacZ,       I        hDiv,vort3,tension,strain,KE,hFacZ,
12       I        myThid)       I        myThid)
13    
14        IMPLICIT NONE        IMPLICIT NONE
# Line 35  C     for roughly similar results with b Line 35  C     for roughly similar results with b
35  C  C
36  C     LIMITERS -- limit min and max values of viscosities  C     LIMITERS -- limit min and max values of viscosities
37  C     viscAhRemax is min value for grid point harmonic Reynolds num  C     viscAhRemax is min value for grid point harmonic Reynolds num
38  C      harmonic viscosity>sqrt(2*KE)*L/2/viscAhRemax  C      harmonic viscosity>sqrt(2*KE)*L/viscAhRemax
39  C  C
40  C     viscA4Remax is min value for grid point biharmonic Reynolds num  C     viscA4Remax is min value for grid point biharmonic Reynolds num
41  C      biharmonic viscosity>sqrt(2*KE)*L**3/16/viscA4Remax  C      biharmonic viscosity>sqrt(2*KE)*L**3/8/viscA4Remax
42  C  C
43  C     viscAhgridmax is CFL stability limiter for harmonic viscosity  C     viscAhgridmax is CFL stability limiter for harmonic viscosity
44  C      harmonic viscosity<0.25*viscAhgridmax*L**2/deltaT  C      harmonic viscosity<0.25*viscAhgridmax*L**2/deltaT
# Line 58  C     viscC4LeithD=? Line 58  C     viscC4LeithD=?
58  C     viscC2smag=2.2-4 (Griffies and Hallberg,2000)  C     viscC2smag=2.2-4 (Griffies and Hallberg,2000)
59  C               0.2-0.9 (Smagorinsky,1993)  C               0.2-0.9 (Smagorinsky,1993)
60  C     viscC4smag=2.2-4 (Griffies and Hallberg,2000)  C     viscC4smag=2.2-4 (Griffies and Hallberg,2000)
61  C     viscAhRemax>=1  C     viscAhRemax>=1, (<2 suppresses a computational mode)
62  C     viscA4Remax>=1  C     viscA4Remax>=1, (<2 suppresses a computational mode)
63  C     viscAhgridmax=1  C     viscAhgridmax=1
64  C     viscA4gridmax=1  C     viscA4gridmax=1
65  C     viscAhgrid<1  C     viscAhgrid<1
# Line 92  C     == Local variables == Line 92  C     == Local variables ==
92        INTEGER I,J        INTEGER I,J
93        _RL smag2fac, smag4fac        _RL smag2fac, smag4fac
94        _RL viscAhRe_max, viscA4Re_max        _RL viscAhRe_max, viscA4Re_max
95        _RL Alin,Alinmin,grdVrt,grdDiv        _RL Alin,grdVrt,grdDiv, keZpt
96        _RL recip_dt,L2,L3,L4,L5,L2rdt,L4rdt        _RL recip_dt,L2,L3,L4,L5,L2rdt,L4rdt
97        _RL Uscl,U4scl        _RL Uscl,U4scl
98        _RL viscAh_ZMax(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL viscAh_ZMax(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 136  C     == Local variables == Line 136  C     == Local variables ==
136       &  .OR.(viscC2leithD.NE.0.)       &  .OR.(viscC2leithD.NE.0.)
137       &  .OR.(viscC2smag.NE.0.)       &  .OR.(viscC2smag.NE.0.)
138    
139        IF (harmonic) viscAhre_max=viscAhremax        IF ((harmonic).and.(viscAhremax.ne.0.)) THEN
140            viscAhre_max=sqrt(2. _d 0)/viscAhRemax
141          ELSE
142            viscAhre_max=0. _d 0
143          ENDIF
144    
145        biharmonic=        biharmonic=
146       &      (viscA4.NE.0.)       &      (viscA4.NE.0.)
# Line 147  C     == Local variables == Line 151  C     == Local variables ==
151       &  .OR.(viscC4leithD.NE.0.)       &  .OR.(viscC4leithD.NE.0.)
152       &  .OR.(viscC4smag.NE.0.)       &  .OR.(viscC4smag.NE.0.)
153    
154        IF (biharmonic) viscA4re_max=viscA4remax        IF ((biharmonic).and.(viscA4remax.ne.0.)) THEN
155            viscA4re_max=0.125 _d 0*sqrt(2. _d 0)/viscA4Remax
156          ELSE
157            viscA4re_max=0. _d 0
158          ENDIF
159    
160        calcleith=        calcleith=
161       &      (viscC2leith.NE.0.)       &      (viscC2leith.NE.0.)
# Line 160  C     == Local variables == Line 168  C     == Local variables ==
168       &  .OR.(viscC4smag.NE.0.)       &  .OR.(viscC4smag.NE.0.)
169    
170        IF (deltaTmom.NE.0.) THEN        IF (deltaTmom.NE.0.) THEN
171         recip_dt=1./deltaTmom         recip_dt=1. _d 0/deltaTmom
172        ELSE        ELSE
173         recip_dt=0.         recip_dt=0. _d 0
174        ENDIF        ENDIF
175    
176        IF (calcsmag) THEN        IF (calcsmag) THEN
177          smag2fac=(viscC2smag/pi)**2          smag2fac=(viscC2smag/pi)**2
178          smag4fac=0.125*(viscC4smag/pi)**2          smag4fac=0.125 _d 0*(viscC4smag/pi)**2
179          ELSE
180            smag2fac=0. _d 0
181            smag4fac=0. _d 0
182        ENDIF        ENDIF
183    
184  C     - Viscosity  C     - Viscosity
# Line 177  C     - Viscosity Line 188  C     - Viscosity
188  CCCCCCCCCCCCCCC Divergence Point CalculationsCCCCCCCCCCCCCCCCCCCC  CCCCCCCCCCCCCCC Divergence Point CalculationsCCCCCCCCCCCCCCCCCCCC
189    
190  C These are (powers of) length scales  C These are (powers of) length scales
191           L2=2./((recip_DXF(I,J,bi,bj)**2+recip_DYF(I,J,bi,bj)**2))           IF (useAreaViscLength) THEN
192              L2=rA(i,j,bi,bj)
193             ELSE
194              L2=2. _d 0/((recip_DXF(I,J,bi,bj)**2+recip_DYF(I,J,bi,bj)**2))
195             ENDIF
196           L3=(L2**1.5)           L3=(L2**1.5)
197           L4=(L2**2)           L4=(L2**2)
198           L5=(L2**2.5)           L5=(L2**2.5)
199    
200           L2rdt=0.25*recip_dt*L2           L2rdt=0.25 _d 0*recip_dt*L2
201    
202           L4rdt=recip_dt/( 6.*(recip_DXF(I,J,bi,bj)**4           IF (useAreaViscLength) THEN
203       &                       +recip_DYF(I,J,bi,bj)**4)            L4rdt=0.125 _d 0*recip_dt*rA(i,j,bi,bj)**2
204       &                   +8.*((recip_DXF(I,J,bi,bj)           ELSE
205       &                        *recip_DYF(I,J,bi,bj))**2) )            L4rdt=recip_dt/( 6. _d 0*(recip_DXF(I,J,bi,bj)**4
206         &                            +recip_DYF(I,J,bi,bj)**4)
207         &                   +8. _d 0*((recip_DXF(I,J,bi,bj)
208         &                             *recip_DYF(I,J,bi,bj))**2) )
209             ENDIF
210    
211  C Velocity Reynolds Scale  C Velocity Reynolds Scale
212           Uscl=sqrt(KE(i,j)*L2*0.5)/viscAhRe_max           IF ( viscAhRe_max.GT.0. .AND. KE(i,j).GT.0. ) THEN
213           U4scl=0.125*L2*Uscl/viscA4Re_max             Uscl=sqrt(KE(i,j)*L2)*viscAhRe_max
214             ELSE
215               Uscl=0.
216             ENDIF
217             IF ( viscA4Re_max.GT.0. .AND. KE(i,j).GT.0. ) THEN
218               U4scl=sqrt(KE(i,j))*L3*viscA4Re_max
219             ELSE
220               U4scl=0.
221             ENDIF
222    
223           IF (useFullLeith.and.calcleith) THEN           IF (useFullLeith.and.calcleith) THEN
224  C This is the vector magnitude of the vorticity gradient squared  C This is the vector magnitude of the vorticity gradient squared
225            grdVrt=0.25*(            grdVrt=0.25 _d 0*(
226       &     ((vort3(i+1,j)-vort3(i,j))*recip_DXG(i,j,bi,bj))**2       &     ((vort3(i+1,j)-vort3(i,j))*recip_DXG(i,j,bi,bj))**2
227       &     +((vort3(i,j+1)-vort3(i,j))*recip_DYG(i,j,bi,bj))**2       &     +((vort3(i,j+1)-vort3(i,j))*recip_DYG(i,j,bi,bj))**2
228       &     +((vort3(i+1,j+1)-vort3(i,j+1))*recip_DXG(i,j+1,bi,bj))**2       &     +((vort3(i+1,j+1)-vort3(i,j+1))
229       &     +((vort3(i+1,j+1)-vort3(i+1,j))*recip_DYG(i+1,j,bi,bj))**2)       &               *recip_DXG(i,j+1,bi,bj))**2
230         &     +((vort3(i+1,j+1)-vort3(i+1,j))
231         &               *recip_DYG(i+1,j,bi,bj))**2)
232    
233  C This is the vector magnitude of grad (div.v) squared  C This is the vector magnitude of grad (div.v) squared
234  C Using it in Leith serves to damp instabilities in w.  C Using it in Leith serves to damp instabilities in w.
235            grdDiv=0.25*(            grdDiv=0.25 _d 0*(
236       &     ((hDiv(i+1,j)-hDiv(i,j))*recip_DXC(i+1,j,bi,bj))**2       &     ((hDiv(i+1,j)-hDiv(i,j))*recip_DXC(i+1,j,bi,bj))**2
237       &     +((hDiv(i,j+1)-hDiv(i,j))*recip_DYC(i,j+1,bi,bj))**2       &     +((hDiv(i,j+1)-hDiv(i,j))*recip_DYC(i,j+1,bi,bj))**2
238       &     +((hDiv(i,j)-hDiv(i-1,j))*recip_DXC(i,j,bi,bj))**2       &     +((hDiv(i,j)-hDiv(i-1,j))*recip_DXC(i,j,bi,bj))**2
# Line 211  C Using it in Leith serves to damp insta Line 240  C Using it in Leith serves to damp insta
240    
241            viscAh_DLth(i,j)=            viscAh_DLth(i,j)=
242       &     sqrt(viscC2leith**2*grdVrt+viscC2leithD**2*grdDiv)*L3       &     sqrt(viscC2leith**2*grdVrt+viscC2leithD**2*grdDiv)*L3
243            viscA4_DLth(i,j)=            viscA4_DLth(i,j)=0.125 _d 0*
244       &     sqrt(viscC4leith**2*grdVrt+viscC4leithD**2*grdDiv)*L5       &     sqrt(viscC4leith**2*grdVrt+viscC4leithD**2*grdDiv)*L5
245            viscAh_DLthd(i,j)=            viscAh_DLthd(i,j)=
246       &     sqrt(viscC2leithD**2*grdDiv)*L3       &     sqrt(viscC2leithD**2*grdDiv)*L3
247            viscA4_DLthd(i,j)=            viscA4_DLthd(i,j)=0.125 _d 0*
248       &     sqrt(viscC4leithD**2*grdDiv)*L5       &     sqrt(viscC4leithD**2*grdDiv)*L5
249           ELSEIF (calcleith) THEN           ELSEIF (calcleith) THEN
250  C but this approximation will work on cube  C but this approximation will work on cube
# Line 239  c (and differs by as much as 4X) Line 268  c (and differs by as much as 4X)
268  c This approximation is good to the same order as above...  c This approximation is good to the same order as above...
269            viscAh_Dlth(i,j)=            viscAh_Dlth(i,j)=
270       &      (viscC2leith*grdVrt+(viscC2leithD*grdDiv))*L3       &      (viscC2leith*grdVrt+(viscC2leithD*grdDiv))*L3
271            viscA4_Dlth(i,j)=0.125*            viscA4_Dlth(i,j)=0.125 _d 0*
272       &      (viscC4leith*grdVrt+(viscC4leithD*grdDiv))*L5       &      (viscC4leith*grdVrt+(viscC4leithD*grdDiv))*L5
273            viscAh_DlthD(i,j)=            viscAh_DlthD(i,j)=
274       &      ((viscC2leithD*grdDiv))*L3       &      ((viscC2leithD*grdDiv))*L3
275            viscA4_DlthD(i,j)=0.125*            viscA4_DlthD(i,j)=0.125 _d 0*
276       &      ((viscC4leithD*grdDiv))*L5       &      ((viscC4leithD*grdDiv))*L5
277           ELSE           ELSE
278            viscAh_Dlth(i,j)=0d0            viscAh_Dlth(i,j)=0. _d 0
279            viscA4_Dlth(i,j)=0d0            viscA4_Dlth(i,j)=0. _d 0
280            viscAh_DlthD(i,j)=0d0            viscAh_DlthD(i,j)=0. _d 0
281            viscA4_DlthD(i,j)=0d0            viscA4_DlthD(i,j)=0. _d 0
282           ENDIF           ENDIF
283    
284           IF (calcsmag) THEN           IF (calcsmag) THEN
285            viscAh_DSmg(i,j)=L2            viscAh_DSmg(i,j)=L2
286       &       *sqrt(tension(i,j)**2       &       *sqrt(tension(i,j)**2
287       &       +0.25*(strain(i+1, j )**2+strain( i ,j+1)**2       &       +0.25 _d 0*(strain(i+1, j )**2+strain( i ,j+1)**2
288       &              +strain(i  , j )**2+strain(i+1,j+1)**2))       &                  +strain(i  , j )**2+strain(i+1,j+1)**2))
289            viscA4_DSmg(i,j)=smag4fac*L2*viscAh_DSmg(i,j)            viscA4_DSmg(i,j)=smag4fac*L2*viscAh_DSmg(i,j)
290            viscAh_DSmg(i,j)=smag2fac*viscAh_DSmg(i,j)            viscAh_DSmg(i,j)=smag2fac*viscAh_DSmg(i,j)
291           ELSE           ELSE
292            viscAh_DSmg(i,j)=0d0            viscAh_DSmg(i,j)=0. _d 0
293            viscA4_DSmg(i,j)=0d0            viscA4_DSmg(i,j)=0. _d 0
294           ENDIF           ENDIF
295    
296  C  Harmonic on Div.u points  C  Harmonic on Div.u points
# Line 282  C  BiHarmonic on Div.u points Line 311  C  BiHarmonic on Div.u points
311    
312  CCCCCCCCCCCCC Vorticity Point CalculationsCCCCCCCCCCCCCCCCCC  CCCCCCCCCCCCC Vorticity Point CalculationsCCCCCCCCCCCCCCCCCC
313  C These are (powers of) length scales  C These are (powers of) length scales
314           L2=2./((recip_DXV(I,J,bi,bj)**2+recip_DYU(I,J,bi,bj)**2))           IF (useAreaViscLength) THEN
315              L2=rAz(i,j,bi,bj)
316             ELSE
317              L2=2. _d 0/((recip_DXV(I,J,bi,bj)**2+recip_DYU(I,J,bi,bj)**2))
318             ENDIF
319    
320           L3=(L2**1.5)           L3=(L2**1.5)
321           L4=(L2**2)           L4=(L2**2)
322           L5=(L2**2.5)           L5=(L2**2.5)
323    
324           L2rdt=0.25*recip_dt*L2           L2rdt=0.25 _d 0*recip_dt*L2
325           L4rdt=recip_dt/           IF (useAreaViscLength) THEN
326       &     ( 6.*(recip_DXF(I,J,bi,bj)**4+recip_DYF(I,J,bi,bj)**4)            L4rdt=0.125 _d 0*recip_dt*rAz(i,j,bi,bj)**2
327       &      +8.*((recip_DXF(I,J,bi,bj)*recip_DYF(I,J,bi,bj))**2))           ELSE
328              L4rdt=recip_dt/
329         &     ( 6. _d 0*(recip_DXV(I,J,bi,bj)**4+recip_DYU(I,J,bi,bj)**4)
330         &      +8. _d 0*((recip_DXV(I,J,bi,bj)*recip_DYU(I,J,bi,bj))**2))
331             ENDIF
332    
333  C Velocity Reynolds Scale  C Velocity Reynolds Scale (Pb here at CS-grid corners !)
334           Uscl=sqrt((KE(i,j)+KE(i,j+1)+KE(i+1,j)+KE(i+1,j+1))*L2*0.125)/           IF ( viscAhRe_max.GT.0. .OR. viscA4Re_max.GT.0. ) THEN
335       &         viscAhRe_max             keZpt=0.25 _d 0*( (KE(i,j)+KE(i-1,j-1))
336           U4scl=0.125*L2*Uscl/viscA4Re_max       &                      +(KE(i-1,j)+KE(i,j-1)) )
337               IF ( keZpt.GT.0. ) THEN
338                 Uscl = sqrt(keZpt*L2)*viscAhRe_max
339                 U4scl= sqrt(keZpt)*L3*viscA4Re_max
340               ELSE
341                 Uscl =0.
342                 U4scl=0.
343               ENDIF
344             ELSE
345               Uscl =0.
346               U4scl=0.
347             ENDIF
348    
349  C This is the vector magnitude of the vorticity gradient squared  C This is the vector magnitude of the vorticity gradient squared
350           IF (useFullLeith.and.calcleith) THEN           IF (useFullLeith.and.calcleith) THEN
351            grdVrt=0.25*(            grdVrt=0.25 _d 0*(
352       &     ((vort3(i+1,j)-vort3(i,j))*recip_DXG(i,j,bi,bj))**2       &     ((vort3(i+1,j)-vort3(i,j))*recip_DXG(i,j,bi,bj))**2
353       &     +((vort3(i,j+1)-vort3(i,j))*recip_DYG(i,j,bi,bj))**2       &     +((vort3(i,j+1)-vort3(i,j))*recip_DYG(i,j,bi,bj))**2
354       &     +((vort3(i-1,j)-vort3(i,j))*recip_DXG(i-1,j,bi,bj))**2       &     +((vort3(i-1,j)-vort3(i,j))*recip_DXG(i-1,j,bi,bj))**2
355       &     +((vort3(i,j-1)-vort3(i,j))*recip_DYG(i,j-1,bi,bj))**2)       &     +((vort3(i,j-1)-vort3(i,j))*recip_DYG(i,j-1,bi,bj))**2)
356    
357  C This is the vector magnitude of grad(div.v) squared  C This is the vector magnitude of grad(div.v) squared
358            grdDiv=0.25*(            grdDiv=0.25 _d 0*(
359       &     ((hDiv(i,j)-hDiv(i-1,j))*recip_DXC(i,j,bi,bj))**2       &     ((hDiv(i,j)-hDiv(i-1,j))*recip_DXC(i,j,bi,bj))**2
360       &     +((hDiv(i,j)-hDiv(i,j-1))*recip_DYC(i,j,bi,bj))**2       &     +((hDiv(i,j)-hDiv(i,j-1))*recip_DYC(i,j,bi,bj))**2
361       &     +((hDiv(i,j-1)-hDiv(i-1,j-1))*recip_DXC(i,j-1,bi,bj))**2       &     +((hDiv(i,j-1)-hDiv(i-1,j-1))*recip_DXC(i,j-1,bi,bj))**2
# Line 314  C This is the vector magnitude of grad(d Line 363  C This is the vector magnitude of grad(d
363    
364            viscAh_ZLth(i,j)=            viscAh_ZLth(i,j)=
365       &     sqrt(viscC2leith**2*grdVrt+viscC2leithD**2*grdDiv)*L3       &     sqrt(viscC2leith**2*grdVrt+viscC2leithD**2*grdDiv)*L3
366            viscA4_ZLth(i,j)=            viscA4_ZLth(i,j)=0.125 _d 0*
367       &     sqrt(viscC4leith**2*grdVrt+viscC4leithD**2*grdDiv)*L5       &     sqrt(viscC4leith**2*grdVrt+viscC4leithD**2*grdDiv)*L5
368            viscAh_ZLthD(i,j)=            viscAh_ZLthD(i,j)=
369       &     sqrt(viscC2leithD**2*grdDiv)*L3       &     sqrt(viscC2leithD**2*grdDiv)*L3
370            viscA4_ZLthD(i,j)=            viscA4_ZLthD(i,j)=0.125 _d 0*
371       &     sqrt(viscC4leithD**2*grdDiv)*L5       &     sqrt(viscC4leithD**2*grdDiv)*L5
372    
373           ELSEIF (calcleith) THEN           ELSEIF (calcleith) THEN
# Line 335  C but this approximation will work on cu Line 384  C but this approximation will work on cu
384            grdDiv=max(grdDiv,            grdDiv=max(grdDiv,
385       &     abs((hDiv(i,j)-hDiv(i,j-1))*recip_DYC(i,j,bi,bj)))       &     abs((hDiv(i,j)-hDiv(i,j-1))*recip_DYC(i,j,bi,bj)))
386            grdDiv=max(grdDiv,            grdDiv=max(grdDiv,
387       &     abs((hDiv(i,j-1)-hDiv(i-1,j-1))*recip_DXG(i,j-1,bi,bj)))       &     abs((hDiv(i,j-1)-hDiv(i-1,j-1))*recip_DXC(i,j-1,bi,bj)))
388            grdDiv=max(grdDiv,            grdDiv=max(grdDiv,
389       &     abs((hDiv(i-1,j)-hDiv(i-1,j-1))*recip_DYG(i-1,j,bi,bj)))       &     abs((hDiv(i-1,j)-hDiv(i-1,j-1))*recip_DYC(i-1,j,bi,bj)))
390    
391            viscAh_ZLth(i,j)=(viscC2leith*grdVrt            viscAh_ZLth(i,j)=(viscC2leith*grdVrt
392       &                     +(viscC2leithD*grdDiv))*L3       &                     +(viscC2leithD*grdDiv))*L3
393            viscA4_ZLth(i,j)=(viscC4leith*grdVrt            viscA4_ZLth(i,j)=0.125 _d 0*(viscC4leith*grdVrt
394       &                     +(viscC4leithD*grdDiv))*L5       &                     +(viscC4leithD*grdDiv))*L5
395            viscAh_ZLthD(i,j)=((viscC2leithD*grdDiv))*L3            viscAh_ZLthD(i,j)=((viscC2leithD*grdDiv))*L3
396            viscA4_ZLthD(i,j)=((viscC4leithD*grdDiv))*L5            viscA4_ZLthD(i,j)=0.125 _d 0*((viscC4leithD*grdDiv))*L5
397           ELSE           ELSE
398            viscAh_ZLth(i,j)=0d0            viscAh_ZLth(i,j)=0. _d 0
399            viscA4_ZLth(i,j)=0d0            viscA4_ZLth(i,j)=0. _d 0
400            viscAh_ZLthD(i,j)=0d0            viscAh_ZLthD(i,j)=0. _d 0
401            viscA4_ZLthD(i,j)=0d0            viscA4_ZLthD(i,j)=0. _d 0
402           ENDIF           ENDIF
403    
404           IF (calcsmag) THEN           IF (calcsmag) THEN
405            viscAh_ZSmg(i,j)=L2            viscAh_ZSmg(i,j)=L2
406       &      *sqrt(strain(i,j)**2       &      *sqrt(strain(i,j)**2
407       &        +0.25*(tension( i , j )**2+tension( i ,j-1)**2       &        +0.25 _d 0*(tension( i , j )**2+tension( i ,j-1)**2
408       &              +tension(i-1, j )**2+tension(i-1,j-1)**2))       &                   +tension(i-1, j )**2+tension(i-1,j-1)**2))
409            viscA4_ZSmg(i,j)=smag4fac*L2*viscAh_ZSmg(i,j)            viscA4_ZSmg(i,j)=smag4fac*L2*viscAh_ZSmg(i,j)
410            viscAh_ZSmg(i,j)=smag2fac*viscAh_ZSmg(i,j)            viscAh_ZSmg(i,j)=smag2fac*viscAh_ZSmg(i,j)
411           ENDIF           ENDIF
# Line 411  C  BiHarmonic on Zeta points Line 460  C  BiHarmonic on Zeta points
460         CALL DIAGNOSTICS_FILL(viscAh_ZLth,'VAHZLTH ',k,1,2,bi,bj,myThid)         CALL DIAGNOSTICS_FILL(viscAh_ZLth,'VAHZLTH ',k,1,2,bi,bj,myThid)
461         CALL DIAGNOSTICS_FILL(viscA4_ZLth,'VA4ZLTH ',k,1,2,bi,bj,myThid)         CALL DIAGNOSTICS_FILL(viscA4_ZLth,'VA4ZLTH ',k,1,2,bi,bj,myThid)
462    
463         CALL DIAGNOSTICS_FILL(viscAh_DLthD,'VAHDLTHD',k,1,2,bi,bj,myThid)         CALL DIAGNOSTICS_FILL(viscAh_DLthD,'VAHDLTHD'
464         CALL DIAGNOSTICS_FILL(viscA4_DLthD,'VA4DLTHD',k,1,2,bi,bj,myThid)       &   ,k,1,2,bi,bj,myThid)
465         CALL DIAGNOSTICS_FILL(viscAh_ZLthD,'VAHZLTHD',k,1,2,bi,bj,myThid)         CALL DIAGNOSTICS_FILL(viscA4_DLthD,'VA4DLTHD'
466         CALL DIAGNOSTICS_FILL(viscA4_ZLthD,'VA4ZLTHD',k,1,2,bi,bj,myThid)       &   ,k,1,2,bi,bj,myThid)
467           CALL DIAGNOSTICS_FILL(viscAh_ZLthD,'VAHZLTHD'
468         &   ,k,1,2,bi,bj,myThid)
469           CALL DIAGNOSTICS_FILL(viscA4_ZLthD,'VA4ZLTHD'
470         &   ,k,1,2,bi,bj,myThid)
471    
472         CALL DIAGNOSTICS_FILL(viscAh_DSmg,'VAHDSMAG',k,1,2,bi,bj,myThid)         CALL DIAGNOSTICS_FILL(viscAh_DSmg,'VAHDSMAG',k,1,2,bi,bj,myThid)
473         CALL DIAGNOSTICS_FILL(viscA4_DSmg,'VA4DSMAG',k,1,2,bi,bj,myThid)         CALL DIAGNOSTICS_FILL(viscA4_DSmg,'VA4DSMAG',k,1,2,bi,bj,myThid)

Legend:
Removed from v.1.6  
changed lines
  Added in v.1.15

  ViewVC Help
Powered by ViewVC 1.1.22