/[MITgcm]/MITgcm/pkg/mom_vecinv/mom_vi_hdissip.F
ViewVC logotype

Contents of /MITgcm/pkg/mom_vecinv/mom_vi_hdissip.F

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


Revision 1.6 - (show annotations) (download)
Wed May 26 14:50:10 2004 UTC (20 years ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint54, checkpoint53d_post, checkpoint54b_post, checkpoint54a_pre, checkpoint54a_post, checkpoint53g_post, checkpoint53f_post, checkpoint54c_post
Changes since 1.5: +105 -74 lines
Added variable viscosity for the vector invariant equations
based on Leith, 1968, Phys. Fluids (10) 1409-1416
 - the use of the variable viscosty in the no-slip boundary conditions
   has not been implemented (but should be)
 - new parameters viscC2leith and viscC4leith are non-dimensional
 - I decided to modulate the variable viscosuty with the same viscAhMax
   and viscA4max; ideally we should have another maximum based on dx^2/dt etc.

1 C $Header: /u/gcmpack/MITgcm/pkg/mom_vecinv/mom_vi_hdissip.F,v 1.5 2004/02/07 23:15:47 dimitri Exp $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5
6 SUBROUTINE MOM_VI_HDISSIP(
7 I bi,bj,k,
8 I hDiv,vort3,hFacZ,dStar,zStar,
9 c I viscAh_Z,viscAh_D,viscA4_Z,viscA4_D,
10 O uDissip,vDissip,
11 I myThid)
12 IMPLICIT NONE
13 C
14 C Calculate horizontal dissipation terms
15 C [del^2 - del^4] (u,v)
16 C
17
18 C == Global variables ==
19 #include "SIZE.h"
20 #include "GRID.h"
21 #include "EEPARAMS.h"
22 #include "PARAMS.h"
23
24 C == Routine arguments ==
25 INTEGER bi,bj,k
26 _RL hDiv(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
27 _RL vort3(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
28 _RS hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
29 _RL dStar(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
30 _RL zStar(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
31 _RL viscAh_Z(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
32 _RL viscAh_D(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
33 _RL viscA4_Z(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
34 _RL viscA4_D(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
35 _RL uDissip(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
36 _RL vDissip(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
37 INTEGER myThid
38
39 C == Local variables ==
40 INTEGER I,J
41 _RL Zip,Zij,Zpj,Dim,Dij,Dmj,uD2,vD2,uD4,vD4
42 _RL Alin,Alth,grdVrt,vg2,vg4
43 LOGICAL useVariableViscosity
44
45 useVariableViscosity=
46 & (viscAhGrid*deltaTmom.NE.0.)
47 & .OR.(viscA4Grid*deltaTmom.NE.0.)
48 & .OR.(viscC2leith.NE.0.)
49 & .OR.(viscC4leith.NE.0.)
50
51 IF (deltaTmom.NE.0.) THEN
52 vg2=viscAhGrid/deltaTmom
53 vg4=viscA4Grid/deltaTmom
54 ELSE
55 vg2=0.
56 vg4=0.
57 ENDIF
58
59 C - Viscosity
60 IF (useVariableViscosity) THEN
61 DO j=2-Oly,sNy+Oly-1
62 DO i=2-Olx,sNx+Olx-1
63 C This is the vector magnitude of the vorticity gradient
64 c grdVrt=sqrt(0.25*(
65 c & ((vort3(i+1,j)-vort3(i,j))*recip_DXG(i,j,bi,bj))**2
66 c & +((vort3(i,j+1)-vort3(i,j))*recip_DYG(i,j,bi,bj))**2
67 c & +((vort3(i+1,j+1)-vort3(i,j+1))*recip_DXG(i,j+1,bi,bj))**2
68 c & +((vort3(i+1,j+1)-vort3(i+1,j))*recip_DYG(i+1,j,bi,bj))**2 ))
69 C but this approximation will work on cube (and differs by as much as 4X)
70 grdVrt=abs((vort3(i+1,j)-vort3(i,j))*recip_DXG(i,j,bi,bj))
71 grdVrt=max(grdVrt,
72 & abs((vort3(i,j+1)-vort3(i,j))*recip_DYG(i,j,bi,bj)))
73 grdVrt=max(grdVrt,
74 & abs((vort3(i+1,j+1)-vort3(i,j+1))*recip_DXG(i,j+1,bi,bj)))
75 grdVrt=max(grdVrt,
76 & abs((vort3(i+1,j+1)-vort3(i+1,j))*recip_DYG(i+1,j,bi,bj)))
77 Alth=viscC2leith*grdVrt*(rA(i,j,bi,bj)**1.5)
78 Alin=viscAh+vg2*rA ( i , j ,bi,bj)
79 viscAh_D(i,j)=min(viscAhMax,Alin+Alth)
80
81 Alth=viscC4leith*grdVrt*0.125*(rA(i,j,bi,bj)**2.5)
82 Alin=viscA4+vg4*(rA ( i , j ,bi,bj)**2)
83 viscA4_D(i,j)=min(viscA4Max,Alin+Alth)
84
85 C This is the vector magnitude of the vorticity gradient
86 c grdVrt=sqrt(0.25*(
87 c & ((vort3(i+1,j)-vort3(i,j))*recip_DXG(i,j,bi,bj))**2
88 c & +((vort3(i,j+1)-vort3(i,j))*recip_DYG(i,j,bi,bj))**2
89 c & +((vort3(i-1,j)-vort3(i,j))*recip_DXG(i-1,j,bi,bj))**2
90 c & +((vort3(i,j-1)-vort3(i,j))*recip_DYG(i,j-1,bi,bj))**2 ))
91 C but this approximation will work on cube (and differs by as much as 4X)
92 grdVrt=abs((vort3(i+1,j)-vort3(i,j))*recip_DXG(i,j,bi,bj))
93 grdVrt=max(grdVrt,
94 & abs((vort3(i,j+1)-vort3(i,j))*recip_DYG(i,j,bi,bj)))
95 grdVrt=max(grdVrt,
96 & abs((vort3(i-1,j)-vort3(i,j))*recip_DXG(i-1,j,bi,bj)))
97 grdVrt=max(grdVrt,
98 & abs((vort3(i,j-1)-vort3(i,j))*recip_DYG(i,j-1,bi,bj)))
99 Alth=viscC2leith*grdVrt*(rAz(i,j,bi,bj)**1.5)
100 Alin=viscAh+vg2*rAz( i , j ,bi,bj)
101 viscAh_Z(i,j)=min(viscAhMax,Alin+Alth)
102
103 Alth=viscC4leith*grdVrt*0.125*(rAz(i,j,bi,bj)**2.5)
104 Alin=viscA4+vg4*(rAz( i , j ,bi,bj)**2)
105 viscA4_Z(i,j)=min(viscA4Max,Alin+Alth)
106 ENDDO
107 ENDDO
108 ELSE
109 DO j=1-Oly,sNy+Oly
110 DO i=1-Olx,sNx+Olx
111 viscAh_D(i,j)=viscAh
112 viscAh_Z(i,j)=viscAh
113 viscA4_D(i,j)=viscA4
114 viscA4_Z(i,j)=viscA4
115 ENDDO
116 ENDDO
117 ENDIF
118
119 C - Laplacian and bi-harmonic terms
120 DO j=2-Oly,sNy+Oly-1
121 DO i=2-Olx,sNx+Olx-1
122
123 Dim=hDiv( i ,j-1)
124 Dij=hDiv( i , j )
125 Dmj=hDiv(i-1, j )
126 Zip=hFacZ( i ,j+1)*vort3( i ,j+1)
127 Zij=hFacZ( i , j )*vort3( i , j )
128 Zpj=hFacZ(i+1, j )*vort3(i+1, j )
129
130 C This bit scales the harmonic dissipation operator to be proportional
131 C to the grid-cell area over the time-step. viscAh is then non-dimensional
132 C and should be less than 1/8, for example viscAh=0.01
133 if (useVariableViscosity) then
134 Dij=Dij*viscAh_D(i,j)
135 Dim=Dim*viscAh_D(i,j-1)
136 Dmj=Dmj*viscAh_D(i-1,j)
137 Zij=Zij*viscAh_Z(i,j)
138 Zip=Zip*viscAh_Z(i,j+1)
139 Zpj=Zpj*viscAh_Z(i+1,j)
140 uD2 = (
141 & cosFacU(j,bi,bj)*( Dij-Dmj )*recip_DXC(i,j,bi,bj)
142 & -recip_hFacW(i,j,k,bi,bj)*( Zip-Zij )*recip_DYG(i,j,bi,bj) )
143 vD2 = (
144 & recip_hFacS(i,j,k,bi,bj)*( Zpj-Zij )*recip_DXG(i,j,bi,bj)
145 & *cosFacV(j,bi,bj)
146 & +( Dij-Dim )*recip_DYC(i,j,bi,bj) )
147 else
148 uD2 = viscAh*(
149 & cosFacU(j,bi,bj)*( Dij-Dmj )*recip_DXC(i,j,bi,bj)
150 & -recip_hFacW(i,j,k,bi,bj)*( Zip-Zij )*recip_DYG(i,j,bi,bj) )
151 vD2 = viscAh*(
152 & recip_hFacS(i,j,k,bi,bj)*( Zpj-Zij )*recip_DXG(i,j,bi,bj)
153 & *cosFacV(j,bi,bj)
154 & +( Dij-Dim )*recip_DYC(i,j,bi,bj) )
155 endif
156
157 Dim=dyF( i ,j-1,bi,bj)*dStar( i ,j-1)
158 Dij=dyF( i , j ,bi,bj)*dStar( i , j )
159 Dmj=dyF(i-1, j ,bi,bj)*dStar(i-1, j )
160
161 Zip=dxV( i ,j+1,bi,bj)*hFacZ( i ,j+1)*zStar( i ,j+1)
162 Zij=dxV( i , j ,bi,bj)*hFacZ( i , j )*zStar( i , j )
163 Zpj=dxV(i+1, j ,bi,bj)*hFacZ(i+1, j )*zStar(i+1, j )
164
165 C This bit scales the harmonic dissipation operator to be proportional
166 C to the grid-cell area over the time-step. viscAh is then non-dimensional
167 C and should be less than 1/8, for example viscAh=0.01
168 if (useVariableViscosity) then
169 Dij=Dij*viscA4_D(i,j)
170 Dim=Dim*viscA4_D(i,j-1)
171 Dmj=Dmj*viscA4_D(i-1,j)
172 Zij=Zij*viscA4_Z(i,j)
173 Zip=Zip*viscA4_Z(i,j+1)
174 Zpj=Zpj*viscA4_Z(i+1,j)
175 uD4 = recip_rAw(i,j,bi,bj)*(
176 & ( (Dij-Dmj)*cosFacU(j,bi,bj) )
177 & -recip_hFacW(i,j,k,bi,bj)*( Zip-Zij ) )
178 vD4 = recip_rAs(i,j,bi,bj)*(
179 & recip_hFacS(i,j,k,bi,bj)*( (Zpj-Zij)*cosFacV(j,bi,bj) )
180 & + ( Dij-Dim ) )
181 else
182 uD4 = recip_rAw(i,j,bi,bj)*(
183 & viscA4*( (Dij-Dmj)*cosFacU(j,bi,bj) )
184 & -recip_hFacW(i,j,k,bi,bj)*viscA4*( Zip-Zij ) )
185 vD4 = recip_rAs(i,j,bi,bj)*(
186 & recip_hFacS(i,j,k,bi,bj)*viscA4*( (Zpj-Zij)*cosFacV(j,bi,bj) )
187 & + viscA4*( Dij-Dim ) )
188 endif
189
190 uDissip(i,j) = uD2 - uD4
191 vDissip(i,j) = vD2 - vD4
192
193 ENDDO
194 ENDDO
195
196 RETURN
197 END

  ViewVC Help
Powered by ViewVC 1.1.22