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

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

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


Revision 1.23 - (hide annotations) (download)
Fri Jul 7 18:52:10 2006 UTC (18 years, 2 months ago) by baylor
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint58r_post, checkpoint58n_post, checkpoint58q_post, checkpoint58o_post, checkpoint58p_post, checkpoint58m_post
Changes since 1.22: +30 -2 lines
Check in of variable viscosity passing to nonhydro.

1 baylor 1.23 C $Header: /u/gcmpack/MITgcm/pkg/mom_common/mom_calc_visc.F,v 1.22 2006/05/31 19:53:15 heimbach Exp $
2 jmc 1.14 C $Name: $
3 baylor 1.1
4     #include "MOM_COMMON_OPTIONS.h"
5    
6 baylor 1.5
7 baylor 1.1 SUBROUTINE MOM_CALC_VISC(
8     I bi,bj,k,
9     O viscAh_Z,viscAh_D,viscA4_Z,viscA4_D,
10     O harmonic,biharmonic,useVariableViscosity,
11 jmc 1.12 I hDiv,vort3,tension,strain,KE,hFacZ,
12 baylor 1.1 I myThid)
13    
14     IMPLICIT NONE
15 baylor 1.5 C
16     C Calculate horizontal viscosities (L is typical grid width)
17     C harmonic viscosity=
18     C viscAh (or viscAhD on div pts and viscAhZ on zeta pts)
19     C +0.25*L**2*viscAhGrid/deltaT
20 baylor 1.17 C +sqrt((viscC2leith/pi)**6*grad(Vort3)**2
21     C +(viscC2leithD/pi)**6*grad(hDiv)**2)*L**3
22 baylor 1.5 C +(viscC2smag/pi)**2*L**2*sqrt(Tension**2+Strain**2)
23     C
24     C biharmonic viscosity=
25     C viscA4 (or viscA4D on div pts and viscA4Z on zeta pts)
26     C +0.25*0.125*L**4*viscA4Grid/deltaT (approx)
27 baylor 1.17 C +0.125*L**5*sqrt((viscC4leith/pi)**6*grad(Vort3)**2
28     C +(viscC4leithD/pi)**6*grad(hDiv)**2)
29 baylor 1.5 C +0.125*L**4*(viscC4smag/pi)**2*sqrt(Tension**2+Strain**2)
30     C
31     C Note that often 0.125*L**2 is the scale between harmonic and
32     C biharmonic (see Griffies and Hallberg (2000))
33     C This allows the same value of the coefficient to be used
34     C for roughly similar results with biharmonic and harmonic
35     C
36     C LIMITERS -- limit min and max values of viscosities
37     C viscAhRemax is min value for grid point harmonic Reynolds num
38 baylor 1.9 C harmonic viscosity>sqrt(2*KE)*L/viscAhRemax
39 baylor 1.5 C
40     C viscA4Remax is min value for grid point biharmonic Reynolds num
41 baylor 1.9 C biharmonic viscosity>sqrt(2*KE)*L**3/8/viscA4Remax
42 baylor 1.5 C
43     C viscAhgridmax is CFL stability limiter for harmonic viscosity
44     C harmonic viscosity<0.25*viscAhgridmax*L**2/deltaT
45     C
46     C viscA4gridmax is CFL stability limiter for biharmonic viscosity
47     C biharmonic viscosity<viscA4gridmax*L**4/32/deltaT (approx)
48     C
49     C viscAhgridmin and viscA4gridmin are lower limits for viscosity:
50     C harmonic viscosity>0.25*viscAhgridmax*L**2/deltaT
51     C biharmonic viscosity>viscA4gridmax*L**4/32/deltaT (approx)
52     C
53     C RECOMMENDED VALUES
54 baylor 1.18 C viscC2Leith=1-3
55     C viscC2LeithD=1-3
56     C viscC4Leith=1-3
57     C viscC4LeithD=1.5-3
58 baylor 1.5 C viscC2smag=2.2-4 (Griffies and Hallberg,2000)
59     C 0.2-0.9 (Smagorinsky,1993)
60     C viscC4smag=2.2-4 (Griffies and Hallberg,2000)
61 baylor 1.9 C viscAhRemax>=1, (<2 suppresses a computational mode)
62     C viscA4Remax>=1, (<2 suppresses a computational mode)
63 baylor 1.5 C viscAhgridmax=1
64     C viscA4gridmax=1
65     C viscAhgrid<1
66     C viscA4grid<1
67     C viscAhgridmin<<1
68     C viscA4gridmin<<1
69 baylor 1.1
70     C == Global variables ==
71     #include "SIZE.h"
72     #include "GRID.h"
73     #include "EEPARAMS.h"
74     #include "PARAMS.h"
75 baylor 1.23 #ifdef ALLOW_NONHYDROSTATIC
76     #include "NH_VARS.h"
77     #endif
78 baylor 1.1
79     C == Routine arguments ==
80     INTEGER bi,bj,k
81     _RL viscAh_Z(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
82     _RL viscAh_D(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
83     _RL viscA4_Z(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
84     _RL viscA4_D(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
85     _RL hDiv(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
86     _RL vort3(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
87     _RL tension(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
88     _RL strain(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
89     _RL KE(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
90     _RS hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
91     INTEGER myThid
92     LOGICAL harmonic,biharmonic,useVariableViscosity
93    
94     C == Local variables ==
95     INTEGER I,J
96 baylor 1.23 INTEGER kp1
97 baylor 1.5 _RL smag2fac, smag4fac
98 baylor 1.17 _RL leith2fac, leith4fac
99     _RL leithD2fac, leithD4fac
100 baylor 1.6 _RL viscAhRe_max, viscA4Re_max
101 jmc 1.15 _RL Alin,grdVrt,grdDiv, keZpt
102 baylor 1.1 _RL recip_dt,L2,L3,L4,L5,L2rdt,L4rdt
103 baylor 1.5 _RL Uscl,U4scl
104 jmc 1.16 _RL divDx(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
105     _RL divDy(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
106 jmc 1.20 _RL vrtDx(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
107     _RL vrtDy(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
108 baylor 1.5 _RL viscAh_ZMax(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
109     _RL viscAh_DMax(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
110     _RL viscA4_ZMax(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
111     _RL viscA4_DMax(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
112     _RL viscAh_ZMin(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
113     _RL viscAh_DMin(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
114     _RL viscA4_ZMin(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
115     _RL viscA4_DMin(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
116     _RL viscAh_ZLth(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
117     _RL viscAh_DLth(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
118     _RL viscA4_ZLth(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
119     _RL viscA4_DLth(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
120     _RL viscAh_ZLthD(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
121     _RL viscAh_DLthD(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
122     _RL viscA4_ZLthD(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
123     _RL viscA4_DLthD(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
124     _RL viscAh_ZSmg(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
125     _RL viscAh_DSmg(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
126     _RL viscA4_ZSmg(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
127     _RL viscA4_DSmg(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
128     LOGICAL calcLeith,calcSmag
129 baylor 1.1
130     useVariableViscosity=
131     & (viscAhGrid.NE.0.)
132     & .OR.(viscA4Grid.NE.0.)
133     & .OR.(viscC2leith.NE.0.)
134     & .OR.(viscC2leithD.NE.0.)
135     & .OR.(viscC4leith.NE.0.)
136     & .OR.(viscC4leithD.NE.0.)
137     & .OR.(viscC2smag.NE.0.)
138     & .OR.(viscC4smag.NE.0.)
139    
140     harmonic=
141     & (viscAh.NE.0.)
142     & .OR.(viscAhD.NE.0.)
143     & .OR.(viscAhZ.NE.0.)
144     & .OR.(viscAhGrid.NE.0.)
145     & .OR.(viscC2leith.NE.0.)
146     & .OR.(viscC2leithD.NE.0.)
147     & .OR.(viscC2smag.NE.0.)
148    
149 baylor 1.9 IF ((harmonic).and.(viscAhremax.ne.0.)) THEN
150 jmc 1.10 viscAhre_max=sqrt(2. _d 0)/viscAhRemax
151 baylor 1.9 ELSE
152 jmc 1.10 viscAhre_max=0. _d 0
153 baylor 1.9 ENDIF
154 baylor 1.5
155 baylor 1.1 biharmonic=
156     & (viscA4.NE.0.)
157     & .OR.(viscA4D.NE.0.)
158     & .OR.(viscA4Z.NE.0.)
159     & .OR.(viscA4Grid.NE.0.)
160     & .OR.(viscC4leith.NE.0.)
161     & .OR.(viscC4leithD.NE.0.)
162     & .OR.(viscC4smag.NE.0.)
163    
164 baylor 1.9 IF ((biharmonic).and.(viscA4remax.ne.0.)) THEN
165 jmc 1.10 viscA4re_max=0.125 _d 0*sqrt(2. _d 0)/viscA4Remax
166 baylor 1.9 ELSE
167 jmc 1.10 viscA4re_max=0. _d 0
168 baylor 1.9 ENDIF
169 baylor 1.5
170     calcleith=
171     & (viscC2leith.NE.0.)
172     & .OR.(viscC2leithD.NE.0.)
173     & .OR.(viscC4leith.NE.0.)
174     & .OR.(viscC4leithD.NE.0.)
175    
176     calcsmag=
177     & (viscC2smag.NE.0.)
178     & .OR.(viscC4smag.NE.0.)
179    
180 baylor 1.1 IF (deltaTmom.NE.0.) THEN
181 jmc 1.10 recip_dt=1. _d 0/deltaTmom
182 baylor 1.1 ELSE
183 jmc 1.10 recip_dt=0. _d 0
184 baylor 1.1 ENDIF
185    
186 baylor 1.5 IF (calcsmag) THEN
187     smag2fac=(viscC2smag/pi)**2
188 jmc 1.10 smag4fac=0.125 _d 0*(viscC4smag/pi)**2
189 baylor 1.9 ELSE
190 jmc 1.10 smag2fac=0. _d 0
191     smag4fac=0. _d 0
192 baylor 1.5 ENDIF
193 baylor 1.1
194 baylor 1.17 IF (calcleith) THEN
195     IF (useFullLeith) THEN
196 baylor 1.19 leith2fac =(viscC2leith /pi)**6
197 baylor 1.17 leithD2fac=(viscC2leithD/pi)**6
198 baylor 1.19 leith4fac =0.015625 _d 0*(viscC4leith /pi)**6
199 baylor 1.17 leithD4fac=0.015625 _d 0*(viscC4leithD/pi)**6
200     ELSE
201 baylor 1.19 leith2fac =(viscC2leith /pi)**3
202 baylor 1.17 leithD2fac=(viscC2leithD/pi)**3
203 baylor 1.19 leith4fac =0.125 _d 0*(viscC4leith /pi)**3
204     leithD4fac=0.125 _d 0*(viscC4leithD/pi)**3
205 baylor 1.17 ENDIF
206     ELSE
207     leith2fac=0. _d 0
208     leith4fac=0. _d 0
209     leithD2fac=0. _d 0
210     leithD4fac=0. _d 0
211     ENDIF
212    
213 heimbach 1.21 #ifdef ALLOW_AUTODIFF_TAMC
214 heimbach 1.22 IF ( calcLeith .OR. calcSmag ) THEN
215     STOP 'calcLeith or calcSmag not implemented for ADJOINT'
216     ENDIF
217     DO j=1-Oly,sNy+Oly
218 heimbach 1.21 DO i=1-Olx,sNx+Olx
219     viscAh_D(i,j)=viscAhD
220     viscAh_Z(i,j)=viscAhZ
221     viscA4_D(i,j)=viscA4D
222     viscA4_Z(i,j)=viscA4Z
223     c
224     visca4_zsmg(i,j) = 0. _d 0
225     viscah_zsmg(i,j) = 0. _d 0
226     c
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     c
232     viscAh_DSmg(i,j) = 0. _d 0
233     viscA4_DSmg(i,j) = 0. _d 0
234     c
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 heimbach 1.22 ENDDO
241 heimbach 1.21 #endif
242    
243    
244    
245 baylor 1.1 C - Viscosity
246     IF (useVariableViscosity) THEN
247 jmc 1.16
248 jmc 1.20 C- Initialise to zero gradient of vorticity & divergence:
249 jmc 1.16 DO j=1-Oly,sNy+Oly
250     DO i=1-Olx,sNx+Olx
251     divDx(i,j) = 0.
252     divDy(i,j) = 0.
253 jmc 1.20 vrtDx(i,j) = 0.
254     vrtDy(i,j) = 0.
255 jmc 1.16 ENDDO
256     ENDDO
257 jmc 1.20
258 jmc 1.16 IF (calcleith) THEN
259 jmc 1.20 C horizontal gradient of horizontal divergence:
260    
261 jmc 1.16 C- gradient in x direction:
262     #ifndef ALLOW_AUTODIFF_TAMC
263     IF (useCubedSphereExchange) THEN
264     C to compute d/dx(hDiv), fill corners with appropriate values:
265     CALL FILL_CS_CORNER_TR_RL( .TRUE., hDiv, bi,bj, myThid )
266     ENDIF
267     #endif
268     DO j=2-Oly,sNy+Oly-1
269     DO i=2-Olx,sNx+Olx-1
270     divDx(i,j) = (hDiv(i,j)-hDiv(i-1,j))*recip_DXC(i,j,bi,bj)
271     ENDDO
272     ENDDO
273    
274     C- gradient in y direction:
275     #ifndef ALLOW_AUTODIFF_TAMC
276     IF (useCubedSphereExchange) THEN
277     C to compute d/dy(hDiv), fill corners with appropriate values:
278     CALL FILL_CS_CORNER_TR_RL(.FALSE., hDiv, bi,bj, myThid )
279     ENDIF
280     #endif
281     DO j=2-Oly,sNy+Oly-1
282     DO i=2-Olx,sNx+Olx-1
283     divDy(i,j) = (hDiv(i,j)-hDiv(i,j-1))*recip_DYC(i,j,bi,bj)
284     ENDDO
285     ENDDO
286 jmc 1.20
287     C horizontal gradient of vertical vorticity:
288     C- gradient in x direction:
289     DO j=2-Oly,sNy+Oly
290     DO i=2-Olx,sNx+Olx-1
291     vrtDx(i,j) = (vort3(i+1,j)-vort3(i,j))
292     & *recip_DXG(i,j,bi,bj)
293     & *maskS(i,j,k,bi,bj)
294     ENDDO
295     ENDDO
296     C- gradient in y direction:
297     DO j=2-Oly,sNy+Oly-1
298     DO i=2-Olx,sNx+Olx
299     vrtDy(i,j) = (vort3(i,j+1)-vort3(i,j))
300     & *recip_DYG(i,j,bi,bj)
301     & *maskW(i,j,k,bi,bj)
302     ENDDO
303     ENDDO
304    
305 jmc 1.16 ENDIF
306    
307 baylor 1.1 DO j=2-Oly,sNy+Oly-1
308     DO i=2-Olx,sNx+Olx-1
309     CCCCCCCCCCCCCCC Divergence Point CalculationsCCCCCCCCCCCCCCCCCCCC
310 baylor 1.5
311 baylor 1.1 C These are (powers of) length scales
312 baylor 1.11 IF (useAreaViscLength) THEN
313 jmc 1.12 L2=rA(i,j,bi,bj)
314 baylor 1.11 ELSE
315     L2=2. _d 0/((recip_DXF(I,J,bi,bj)**2+recip_DYF(I,J,bi,bj)**2))
316     ENDIF
317 baylor 1.1 L3=(L2**1.5)
318     L4=(L2**2)
319 baylor 1.5 L5=(L2**2.5)
320    
321 jmc 1.10 L2rdt=0.25 _d 0*recip_dt*L2
322 baylor 1.5
323 baylor 1.11 IF (useAreaViscLength) THEN
324 jmc 1.12 L4rdt=0.125 _d 0*recip_dt*rA(i,j,bi,bj)**2
325 baylor 1.11 ELSE
326     L4rdt=recip_dt/( 6. _d 0*(recip_DXF(I,J,bi,bj)**4
327 jmc 1.10 & +recip_DYF(I,J,bi,bj)**4)
328     & +8. _d 0*((recip_DXF(I,J,bi,bj)
329     & *recip_DYF(I,J,bi,bj))**2) )
330 baylor 1.11 ENDIF
331 baylor 1.1
332 baylor 1.5 C Velocity Reynolds Scale
333 jmc 1.15 IF ( viscAhRe_max.GT.0. .AND. KE(i,j).GT.0. ) THEN
334     Uscl=sqrt(KE(i,j)*L2)*viscAhRe_max
335     ELSE
336     Uscl=0.
337     ENDIF
338     IF ( viscA4Re_max.GT.0. .AND. KE(i,j).GT.0. ) THEN
339     U4scl=sqrt(KE(i,j))*L3*viscA4Re_max
340     ELSE
341     U4scl=0.
342     ENDIF
343 baylor 1.5
344 heimbach 1.22 #ifndef ALLOW_AUTODIFF_TAMC
345 baylor 1.5 IF (useFullLeith.and.calcleith) THEN
346 baylor 1.1 C This is the vector magnitude of the vorticity gradient squared
347 jmc 1.20 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 baylor 1.1
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 jmc 1.16 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 baylor 1.5
359     viscAh_DLth(i,j)=
360 baylor 1.17 & sqrt(leith2fac*grdVrt+leithD2fac*grdDiv)*L3
361     viscA4_DLth(i,j)=
362     & sqrt(leith4fac*grdVrt+leithD4fac*grdDiv)*L5
363 baylor 1.5 viscAh_DLthd(i,j)=
364 baylor 1.17 & sqrt(leithD2fac*grdDiv)*L3
365     viscA4_DLthd(i,j)=
366     & sqrt(leithD4fac*grdDiv)*L5
367 baylor 1.5 ELSEIF (calcleith) THEN
368 baylor 1.1 C but this approximation will work on cube
369     c (and differs by as much as 4X)
370 jmc 1.20 grdVrt=max( abs(vrtDx(i,j+1)), abs(vrtDx(i,j)) )
371     grdVrt=max( grdVrt, abs(vrtDy(i+1,j)) )
372     grdVrt=max( grdVrt, abs(vrtDy(i,j)) )
373 baylor 1.5
374 jmc 1.20 c This approximation is good to the same order as above...
375 jmc 1.16 grdDiv=max( abs(divDx(i+1,j)), abs(divDx(i,j)) )
376     grdDiv=max( grdDiv, abs(divDy(i,j+1)) )
377     grdDiv=max( grdDiv, abs(divDy(i,j)) )
378 baylor 1.1
379 baylor 1.17 viscAh_Dlth(i,j)=(leith2fac*grdVrt+(leithD2fac*grdDiv))*L3
380     viscA4_Dlth(i,j)=(leith4fac*grdVrt+(leithD4fac*grdDiv))*L5
381     viscAh_DlthD(i,j)=((leithD2fac*grdDiv))*L3
382     viscA4_DlthD(i,j)=((leithD4fac*grdDiv))*L5
383 baylor 1.1 ELSE
384 jmc 1.10 viscAh_Dlth(i,j)=0. _d 0
385     viscA4_Dlth(i,j)=0. _d 0
386     viscAh_DlthD(i,j)=0. _d 0
387     viscA4_DlthD(i,j)=0. _d 0
388 baylor 1.1 ENDIF
389    
390 baylor 1.5 IF (calcsmag) THEN
391     viscAh_DSmg(i,j)=L2
392     & *sqrt(tension(i,j)**2
393 jmc 1.10 & +0.25 _d 0*(strain(i+1, j )**2+strain( i ,j+1)**2
394     & +strain(i , j )**2+strain(i+1,j+1)**2))
395 baylor 1.5 viscA4_DSmg(i,j)=smag4fac*L2*viscAh_DSmg(i,j)
396     viscAh_DSmg(i,j)=smag2fac*viscAh_DSmg(i,j)
397 baylor 1.1 ELSE
398 jmc 1.10 viscAh_DSmg(i,j)=0. _d 0
399     viscA4_DSmg(i,j)=0. _d 0
400 baylor 1.1 ENDIF
401 heimbach 1.22 #endif /* ALLOW_AUTODIFF_TAMC */
402 baylor 1.1
403     C Harmonic on Div.u points
404 baylor 1.5 Alin=viscAhD+viscAhGrid*L2rdt
405     & +viscAh_DLth(i,j)+viscAh_DSmg(i,j)
406     viscAh_DMin(i,j)=max(viscAhGridMin*L2rdt,Uscl)
407     viscAh_D(i,j)=max(viscAh_DMin(i,j),Alin)
408     viscAh_DMax(i,j)=min(viscAhGridMax*L2rdt,viscAhMax)
409     viscAh_D(i,j)=min(viscAh_DMax(i,j),viscAh_D(i,j))
410 baylor 1.1
411     C BiHarmonic on Div.u points
412 baylor 1.5 Alin=viscA4D+viscA4Grid*L4rdt
413     & +viscA4_DLth(i,j)+viscA4_DSmg(i,j)
414     viscA4_DMin(i,j)=max(viscA4GridMin*L4rdt,U4scl)
415     viscA4_D(i,j)=max(viscA4_DMin(i,j),Alin)
416     viscA4_DMax(i,j)=min(viscA4GridMax*L4rdt,viscA4Max)
417     viscA4_D(i,j)=min(viscA4_DMax(i,j),viscA4_D(i,j))
418 baylor 1.1
419 baylor 1.23 #ifdef ALLOW_NONHYDROSTATIC
420     C /* Pass Viscosities to calc_gw, if constant, not necessary */
421    
422     kp1 = MIN(k+1,Nr)
423    
424     if (k .eq. 1) then
425     viscAh_W(i,j,kp1,bi,bj)=0.5*viscAh_D(i,j)
426     viscA4_W(i,j,kp1,bi,bj)=0.5*viscA4_D(i,j)
427    
428     viscAh_W(i,j,k,bi,bj)=viscAh_D(i,j) /* These values dont get used */
429     viscA4_W(i,j,k,bi,bj)=viscA4_D(i,j)
430     else
431     C Note that previous call of this function has already added half.
432     viscAh_W(i,j,kp1,bi,bj)=0.5*viscAh_D(i,j)
433     viscA4_W(i,j,kp1,bi,bj)=0.5*viscA4_D(i,j)
434    
435     viscAh_W(i,j,k,bi,bj)=viscAh_W(i,j,k,bi,bj)+0.5*viscAh_D(i,j)
436     viscA4_W(i,j,k,bi,bj)=viscA4_W(i,j,k,bi,bj)+0.5*viscA4_D(i,j)
437     endif
438     #endif /* ALLOW_NONHYDROSTATIC */
439    
440 baylor 1.1 CCCCCCCCCCCCC Vorticity Point CalculationsCCCCCCCCCCCCCCCCCC
441     C These are (powers of) length scales
442 baylor 1.11 IF (useAreaViscLength) THEN
443 jmc 1.12 L2=rAz(i,j,bi,bj)
444 baylor 1.11 ELSE
445 jmc 1.12 L2=2. _d 0/((recip_DXV(I,J,bi,bj)**2+recip_DYU(I,J,bi,bj)**2))
446 baylor 1.11 ENDIF
447    
448 baylor 1.1 L3=(L2**1.5)
449     L4=(L2**2)
450 baylor 1.5 L5=(L2**2.5)
451    
452 jmc 1.10 L2rdt=0.25 _d 0*recip_dt*L2
453 baylor 1.11 IF (useAreaViscLength) THEN
454 jmc 1.14 L4rdt=0.125 _d 0*recip_dt*rAz(i,j,bi,bj)**2
455 baylor 1.11 ELSE
456     L4rdt=recip_dt/
457     & ( 6. _d 0*(recip_DXV(I,J,bi,bj)**4+recip_DYU(I,J,bi,bj)**4)
458     & +8. _d 0*((recip_DXV(I,J,bi,bj)*recip_DYU(I,J,bi,bj))**2))
459     ENDIF
460 baylor 1.5
461 jmc 1.15 C Velocity Reynolds Scale (Pb here at CS-grid corners !)
462     IF ( viscAhRe_max.GT.0. .OR. viscA4Re_max.GT.0. ) THEN
463     keZpt=0.25 _d 0*( (KE(i,j)+KE(i-1,j-1))
464     & +(KE(i-1,j)+KE(i,j-1)) )
465     IF ( keZpt.GT.0. ) THEN
466     Uscl = sqrt(keZpt*L2)*viscAhRe_max
467     U4scl= sqrt(keZpt)*L3*viscA4Re_max
468     ELSE
469     Uscl =0.
470     U4scl=0.
471     ENDIF
472     ELSE
473     Uscl =0.
474     U4scl=0.
475     ENDIF
476 baylor 1.1
477 heimbach 1.22 #ifndef ALLOW_AUTODIFF_TAMC
478 baylor 1.1 C This is the vector magnitude of the vorticity gradient squared
479 baylor 1.5 IF (useFullLeith.and.calcleith) THEN
480 jmc 1.20 grdVrt=0.25 _d 0*( (vrtDx(i-1,j)*vrtDx(i-1,j)
481     & + vrtDx(i,j)*vrtDx(i,j) )
482     & + (vrtDy(i,j-1)*vrtDy(i,j-1)
483     & + vrtDy(i,j)*vrtDy(i,j) ) )
484 baylor 1.1
485     C This is the vector magnitude of grad(div.v) squared
486 jmc 1.16 grdDiv=0.25 _d 0*( (divDx(i,j-1)*divDx(i,j-1)
487     & + divDx(i,j)*divDx(i,j) )
488     & + (divDy(i-1,j)*divDy(i-1,j)
489     & + divDy(i,j)*divDy(i,j) ) )
490 baylor 1.5
491     viscAh_ZLth(i,j)=
492 baylor 1.17 & sqrt(leith2fac*grdVrt+leithD2fac*grdDiv)*L3
493     viscA4_ZLth(i,j)=
494     & sqrt(leith4fac*grdVrt+leithD4fac*grdDiv)*L5
495 baylor 1.5 viscAh_ZLthD(i,j)=
496 baylor 1.17 & sqrt(leithD2fac*grdDiv)*L3
497     viscA4_ZLthD(i,j)=
498     & sqrt(leithD4fac*grdDiv)*L5
499 baylor 1.5
500     ELSEIF (calcleith) THEN
501 baylor 1.1 C but this approximation will work on cube (and differs by 4X)
502 jmc 1.20 grdVrt=max( abs(vrtDx(i-1,j)), abs(vrtDx(i,j)) )
503     grdVrt=max( grdVrt, abs(vrtDy(i,j-1)) )
504     grdVrt=max( grdVrt, abs(vrtDy(i,j)) )
505 baylor 1.5
506 jmc 1.16 grdDiv=max( abs(divDx(i,j)), abs(divDx(i,j-1)) )
507     grdDiv=max( grdDiv, abs(divDy(i,j)) )
508     grdDiv=max( grdDiv, abs(divDy(i-1,j)) )
509 baylor 1.5
510 baylor 1.17 viscAh_ZLth(i,j)=(leith2fac*grdVrt+(leithD2fac*grdDiv))*L3
511     viscA4_ZLth(i,j)=(leith4fac*grdVrt+(leithD4fac*grdDiv))*L5
512     viscAh_ZLthD(i,j)=(leithD2fac*grdDiv)*L3
513     viscA4_ZLthD(i,j)=(leithD4fac*grdDiv)*L5
514 baylor 1.1 ELSE
515 jmc 1.10 viscAh_ZLth(i,j)=0. _d 0
516     viscA4_ZLth(i,j)=0. _d 0
517     viscAh_ZLthD(i,j)=0. _d 0
518     viscA4_ZLthD(i,j)=0. _d 0
519 baylor 1.1 ENDIF
520    
521 baylor 1.5 IF (calcsmag) THEN
522     viscAh_ZSmg(i,j)=L2
523     & *sqrt(strain(i,j)**2
524 jmc 1.10 & +0.25 _d 0*(tension( i , j )**2+tension( i ,j-1)**2
525     & +tension(i-1, j )**2+tension(i-1,j-1)**2))
526 baylor 1.5 viscA4_ZSmg(i,j)=smag4fac*L2*viscAh_ZSmg(i,j)
527     viscAh_ZSmg(i,j)=smag2fac*viscAh_ZSmg(i,j)
528 baylor 1.1 ENDIF
529 heimbach 1.22 #endif /* ALLOW_AUTODIFF_TAMC */
530 baylor 1.1
531     C Harmonic on Zeta points
532 baylor 1.5 Alin=viscAhZ+viscAhGrid*L2rdt
533     & +viscAh_ZLth(i,j)+viscAh_ZSmg(i,j)
534     viscAh_ZMin(i,j)=max(viscAhGridMin*L2rdt,Uscl)
535     viscAh_Z(i,j)=max(viscAh_ZMin(i,j),Alin)
536     viscAh_ZMax(i,j)=min(viscAhGridMax*L2rdt,viscAhMax)
537     viscAh_Z(i,j)=min(viscAh_ZMax(i,j),viscAh_Z(i,j))
538    
539     C BiHarmonic on Zeta points
540     Alin=viscA4Z+viscA4Grid*L4rdt
541     & +viscA4_ZLth(i,j)+viscA4_ZSmg(i,j)
542     viscA4_ZMin(i,j)=max(viscA4GridMin*L4rdt,U4scl)
543     viscA4_Z(i,j)=max(viscA4_ZMin(i,j),Alin)
544     viscA4_ZMax(i,j)=min(viscA4GridMax*L4rdt,viscA4Max)
545     viscA4_Z(i,j)=min(viscA4_ZMax(i,j),viscA4_Z(i,j))
546 baylor 1.1 ENDDO
547     ENDDO
548     ELSE
549     DO j=1-Oly,sNy+Oly
550     DO i=1-Olx,sNx+Olx
551     viscAh_D(i,j)=viscAhD
552     viscAh_Z(i,j)=viscAhZ
553     viscA4_D(i,j)=viscA4D
554     viscA4_Z(i,j)=viscA4Z
555     ENDDO
556     ENDDO
557     ENDIF
558    
559     #ifdef ALLOW_DIAGNOSTICS
560     IF (useDiagnostics) THEN
561     CALL DIAGNOSTICS_FILL(viscAh_D,'VISCAHD ',k,1,2,bi,bj,myThid)
562     CALL DIAGNOSTICS_FILL(viscA4_D,'VISCA4D ',k,1,2,bi,bj,myThid)
563     CALL DIAGNOSTICS_FILL(viscAh_Z,'VISCAHZ ',k,1,2,bi,bj,myThid)
564     CALL DIAGNOSTICS_FILL(viscA4_Z,'VISCA4Z ',k,1,2,bi,bj,myThid)
565 baylor 1.23 #ifdef ALLOW_NONHYDROSTATIC
566     CALL DIAGNOSTICS_FILL(viscAh_W,'VISCAHW ',k,1,2,bi,bj,myThid)
567     CALL DIAGNOSTICS_FILL(viscA4_W,'VISCA4W ',k,1,2,bi,bj,myThid)
568     #endif
569 baylor 1.5
570     CALL DIAGNOSTICS_FILL(viscAh_DMax,'VAHDMAX ',k,1,2,bi,bj,myThid)
571     CALL DIAGNOSTICS_FILL(viscA4_DMax,'VA4DMAX ',k,1,2,bi,bj,myThid)
572     CALL DIAGNOSTICS_FILL(viscAh_ZMax,'VAHZMAX ',k,1,2,bi,bj,myThid)
573     CALL DIAGNOSTICS_FILL(viscA4_ZMax,'VA4ZMAX ',k,1,2,bi,bj,myThid)
574    
575     CALL DIAGNOSTICS_FILL(viscAh_DMin,'VAHDMIN ',k,1,2,bi,bj,myThid)
576     CALL DIAGNOSTICS_FILL(viscA4_DMin,'VA4DMIN ',k,1,2,bi,bj,myThid)
577     CALL DIAGNOSTICS_FILL(viscAh_ZMin,'VAHZMIN ',k,1,2,bi,bj,myThid)
578     CALL DIAGNOSTICS_FILL(viscA4_ZMin,'VA4ZMIN ',k,1,2,bi,bj,myThid)
579    
580     CALL DIAGNOSTICS_FILL(viscAh_DLth,'VAHDLTH ',k,1,2,bi,bj,myThid)
581     CALL DIAGNOSTICS_FILL(viscA4_DLth,'VA4DLTH ',k,1,2,bi,bj,myThid)
582     CALL DIAGNOSTICS_FILL(viscAh_ZLth,'VAHZLTH ',k,1,2,bi,bj,myThid)
583     CALL DIAGNOSTICS_FILL(viscA4_ZLth,'VA4ZLTH ',k,1,2,bi,bj,myThid)
584    
585 baylor 1.7 CALL DIAGNOSTICS_FILL(viscAh_DLthD,'VAHDLTHD'
586 baylor 1.8 & ,k,1,2,bi,bj,myThid)
587 baylor 1.7 CALL DIAGNOSTICS_FILL(viscA4_DLthD,'VA4DLTHD'
588 baylor 1.8 & ,k,1,2,bi,bj,myThid)
589 baylor 1.7 CALL DIAGNOSTICS_FILL(viscAh_ZLthD,'VAHZLTHD'
590 baylor 1.8 & ,k,1,2,bi,bj,myThid)
591 baylor 1.7 CALL DIAGNOSTICS_FILL(viscA4_ZLthD,'VA4ZLTHD'
592 baylor 1.8 & ,k,1,2,bi,bj,myThid)
593 baylor 1.5
594     CALL DIAGNOSTICS_FILL(viscAh_DSmg,'VAHDSMAG',k,1,2,bi,bj,myThid)
595     CALL DIAGNOSTICS_FILL(viscA4_DSmg,'VA4DSMAG',k,1,2,bi,bj,myThid)
596     CALL DIAGNOSTICS_FILL(viscAh_ZSmg,'VAHZSMAG',k,1,2,bi,bj,myThid)
597     CALL DIAGNOSTICS_FILL(viscA4_ZSmg,'VA4ZSMAG',k,1,2,bi,bj,myThid)
598 baylor 1.1 ENDIF
599     #endif
600    
601     RETURN
602     END
603 baylor 1.5

  ViewVC Help
Powered by ViewVC 1.1.22