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

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

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


Revision 1.15 - (show annotations) (download)
Fri Apr 28 17:17:14 2017 UTC (7 years, 5 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, HEAD
Changes since 1.14: +4 -2 lines
 pass these runtime flags as formal parameters to
  s/r mom_vi_u/v_coriolis, mom_vi_u/v_coriolis_c4, so that these routines
  can also be used in pkg/seaice:
  selectVortScheme, highOrderVorticity, upwindVorticity, useJamartMomAdv

1 C $Header: /u/gcmpack/MITgcm/pkg/mom_vecinv/mom_vi_u_coriolis_c4.F,v 1.14 2017/03/23 01:47:50 jmc Exp $
2 C $Name: $
3
4 #include "MOM_VECINV_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: MOM_VI_U_CORIOLIS_C4
8 C !INTERFACE:
9 SUBROUTINE MOM_VI_U_CORIOLIS_C4(
10 I bi,bj,k,
11 I selectVortScheme,highOrderVorticity,upwindVorticity,
12 I vFld,omega3,r_hFacZ,
13 O uCoriolisTerm,
14 I myThid)
15 C !DESCRIPTION: \bv
16 C *==========================================================*
17 C | S/R MOM_VI_U_CORIOLIS_C4
18 C |==========================================================*
19 C | o Calculate flux (in Y-dir.) of vorticity at U point
20 C | using 4th order (or 1rst order) interpolation
21 C *==========================================================*
22 C \ev
23
24 C !USES:
25 IMPLICIT NONE
26
27 C == Global variables ==
28 #include "SIZE.h"
29 #include "EEPARAMS.h"
30 #include "GRID.h"
31 #ifdef ALLOW_EXCH2
32 #include "W2_EXCH2_SIZE.h"
33 #include "W2_EXCH2_TOPOLOGY.h"
34 #endif /* ALLOW_EXCH2 */
35
36 C !INPUT/OUTPUT PARAMETERS:
37 C == Routine arguments ==
38 INTEGER bi,bj,k
39 _RL vFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
40 _RL omega3(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
41 _RS r_hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
42 _RL uCoriolisTerm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
43 INTEGER selectVortScheme
44 LOGICAL highOrderVorticity,upwindVorticity
45 INTEGER myThid
46 CEOP
47
48 C == Local variables ==
49 C msgBuf :: Informational/error meesage buffer
50 CHARACTER*(MAX_LEN_MBUF) msgBuf
51 INTEGER i,j
52 _RL vort3r(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
53 _RL vBarXY,vort3u,Rjp,Rjm,Rj
54 _RL vBarXm,vBarXp
55
56 LOGICAL northWestCorner, northEastCorner,
57 & southWestCorner, southEastCorner
58 INTEGER myFace
59 #ifdef ALLOW_EXCH2
60 INTEGER myTile
61 #endif /* ALLOW_EXCH2 */
62 _RL oneSixth, oneTwelve
63 LOGICAL fourthVort3
64 C jmc: not sure about these 1/6 & 1/12 factors (should use the same)
65 PARAMETER(oneSixth=1.D0/6.D0 , oneTwelve=1.D0/12.D0)
66 PARAMETER(fourthVort3=.TRUE. )
67
68 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
69
70 DO j=1-Oly,sNy+Oly
71 DO i=1-Olx,sNx+Olx
72 vort3r(i,j) = r_hFacZ(i,j)*omega3(i,j)
73 ENDDO
74 ENDDO
75
76 C-- Special stuff for Cubed Sphere
77 IF ( useCubedSphereExchange.AND.highOrderVorticity ) THEN
78
79 #ifdef ALLOW_EXCH2
80 myTile = W2_myTileList(bi,bj)
81 myFace = exch2_myFace(myTile)
82 southWestCorner = exch2_isWedge(myTile).EQ.1
83 & .AND. exch2_isSedge(myTile).EQ.1
84 southEastCorner = exch2_isEedge(myTile).EQ.1
85 & .AND. exch2_isSedge(myTile).EQ.1
86 northEastCorner = exch2_isEedge(myTile).EQ.1
87 & .AND. exch2_isNedge(myTile).EQ.1
88 northWestCorner = exch2_isWedge(myTile).EQ.1
89 & .AND. exch2_isNedge(myTile).EQ.1
90 #else
91 myFace = bi
92 southWestCorner = .TRUE.
93 southEastCorner = .TRUE.
94 northWestCorner = .TRUE.
95 northEastCorner = .TRUE.
96 #endif /* ALLOW_EXCH2 */
97 IF ( southWestCorner ) THEN
98 i = 1
99 j = 1
100 vort3r(i,j-1) = ( vort3r(i,j-1) + vort3r(i+1,j) )*0.5 _d 0
101 ENDIF
102 IF ( southEastCorner ) THEN
103 i = sNx+1
104 j = 1
105 vort3r(i,j-1) = ( vort3r(i,j-1) + vort3r(i-1,j) )*0.5 _d 0
106 ENDIF
107 IF ( northWestCorner ) THEN
108 i = 1
109 j = sNy+1
110 vort3r(i,j+1) = ( vort3r(i,j+1) + vort3r(i+1,j) )*0.5 _d 0
111 ENDIF
112 IF ( northEastCorner ) THEN
113 i = sNx+1
114 j = sNy+1
115 vort3r(i,j+1) = ( vort3r(i,j+1) + vort3r(i-1,j) )*0.5 _d 0
116 ENDIF
117
118 C-- End of special stuff for Cubed Sphere.
119 ENDIF
120
121 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
122
123 IF ( selectVortScheme.EQ.0 ) THEN
124 C-- using Sadourny Enstrophy conserving discretization:
125
126 c DO j=2-Oly,sNy+Oly-2
127 c DO i=2-Olx,sNx+Olx
128 DO j=1,sNy
129 DO i=1,sNx+1
130
131 vBarXY=0.25*(
132 & (vFld( i , j )*dxG( i , j ,bi,bj)*_hFacS( i , j ,k,bi,bj)
133 & +vFld(i-1, j )*dxG(i-1, j ,bi,bj)*_hFacS(i-1, j ,k,bi,bj))
134 & +(vFld( i ,j+1)*dxG( i ,j+1,bi,bj)*_hFacS( i ,j+1,k,bi,bj)
135 & +vFld(i-1,j+1)*dxG(i-1,j+1,bi,bj)*_hFacS(i-1,j+1,k,bi,bj))
136 & )
137 IF (upwindVorticity) THEN
138 IF (vBarXY.GT.0.) THEN
139 vort3u=vort3r(i,j)
140 ELSE
141 vort3u=vort3r(i,j+1)
142 ENDIF
143 ELSEIF (fourthVort3) THEN
144 #ifdef ALLOW_OBCS
145 Rjp = ( vort3r(i,j+2) - vort3r(i,j+1) )*maskInW(i,j+1,bi,bj)
146 Rjm = ( vort3r(i, j ) - vort3r(i,j-1) )*maskInW(i,j-1,bi,bj)
147 #else
148 Rjp = vort3r(i,j+2) - vort3r(i,j+1)
149 Rjm = vort3r(i, j ) - vort3r(i,j-1)
150 #endif
151 vort3u=0.5*( (vort3r(i,j) + vort3r(i,j+1))
152 & -oneTwelve*(Rjp-Rjm)
153 & )
154 ELSE
155 vort3u=0.5*( vort3r(i,j) + vort3r(i,j+1) )
156 ENDIF
157
158 uCoriolisTerm(i,j) = vort3u*vBarXY*recip_dxC(i,j,bi,bj)
159 & * _maskW(i,j,k,bi,bj)
160
161 ENDDO
162 ENDDO
163
164 ELSEIF ( selectVortScheme.EQ.2 ) THEN
165 C-- using Energy conserving discretization:
166
167 c DO j=2-Oly,sNy+Oly-2
168 c DO i=2-Olx,sNx+Olx
169 DO j=1,sNy
170 DO i=1,sNx+1
171
172 vBarXm=0.5*(
173 & vFld( i , j )*dxG( i , j ,bi,bj)*_hFacS( i , j ,k,bi,bj)
174 & +vFld(i-1, j )*dxG(i-1, j ,bi,bj)*_hFacS(i-1, j ,k,bi,bj) )
175 vBarXp=0.5*(
176 & vFld( i ,j+1)*dxG( i ,j+1,bi,bj)*_hFacS( i ,j+1,k,bi,bj)
177 & +vFld(i-1,j+1)*dxG(i-1,j+1,bi,bj)*_hFacS(i-1,j+1,k,bi,bj) )
178 IF (upwindVorticity) THEN
179 IF ( (vBarXm+vBarXp) .GT.0.) THEN
180 vort3u=vBarXm*vort3r(i, j )
181 ELSE
182 vort3u=vBarXp*vort3r(i,j+1)
183 ENDIF
184 ELSEIF (fourthVort3) THEN
185 #ifdef ALLOW_OBCS
186 Rjp = ( vort3r(i,j+2) - vort3r(i,j+1) )*maskInW(i,j+1,bi,bj)
187 Rjm = ( vort3r(i, j ) - vort3r(i,j-1) )*maskInW(i,j-1,bi,bj)
188 #else
189 Rjp = vort3r(i,j+2) - vort3r(i,j+1)
190 Rjm = vort3r(i, j ) - vort3r(i,j-1)
191 #endif
192 Rj = vort3r(i,j+1) - vort3r(i, j )
193 Rjp = vort3r(i,j+1) -oneSixth*( Rjp-Rj )
194 Rjm = vort3r(i, j ) -oneSixth*( Rj-Rjm )
195 c Rjp = vort3r(i,j+1) -oneSixth*( vort3r(i,j+2)-vort3r(i, j ) )
196 c Rjm = vort3r(i, j ) +oneSixth*( vort3r(i,j+1)-vort3r(i,j-1) )
197 vort3u=0.5*( vBarXm*Rjm + vBarXp*Rjp )
198 ELSE
199 vort3u=0.5*( vBarXm*vort3r(i, j ) + vBarXp*vort3r(i,j+1) )
200 ENDIF
201
202 uCoriolisTerm(i,j) = vort3u*recip_dxC(i,j,bi,bj)
203 & * _maskW(i,j,k,bi,bj)
204
205 ENDDO
206 ENDDO
207
208 ELSE
209 WRITE(msgBuf,'(A,I5,A)')
210 & 'MOM_VI_U_CORIOLIS_C4: selectVortScheme=', selectVortScheme,
211 & ' not implemented'
212 CALL PRINT_ERROR( msgBuf, myThid )
213 STOP 'ABNORMAL END: S/R MOM_VI_U_CORIOLIS_C4'
214
215 ENDIF
216
217 RETURN
218 END

  ViewVC Help
Powered by ViewVC 1.1.22