/[MITgcm]/MITgcm/pkg/generic_advdiff/gad_advection.F
ViewVC logotype

Contents of /MITgcm/pkg/generic_advdiff/gad_advection.F

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


Revision 1.3 - (show annotations) (download)
Mon Sep 17 19:48:04 2001 UTC (22 years, 8 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint40
Changes since 1.2: +75 -2 lines
Added three pass method for deal with multi-dimensional scheme
with cubic topology.

1 C $Header: /u/gcmpack/models/MITgcmUV/pkg/generic_advdiff/gad_advection.F,v 1.2 2001/09/10 13:09:04 adcroft Exp $
2 C $Name: $
3
4 #include "GAD_OPTIONS.h"
5
6 SUBROUTINE GAD_ADVECTION(bi,bj,advectionScheme,tracerIdentity,
7 U Tracer,Gtracer,
8 I myTime,myIter,myThid)
9 C /==========================================================\
10 C | SUBROUTINE GAD_ADVECTION |
11 C | o Solves the pure advection tracer equation. |
12 C |==========================================================|
13 C \==========================================================/
14 IMPLICIT NONE
15
16 C == Global variables ===
17 #include "SIZE.h"
18 #include "EEPARAMS.h"
19 #include "PARAMS.h"
20 #include "DYNVARS.h"
21 #include "GRID.h"
22 #include "GAD.h"
23
24 C == Routine arguments ==
25 INTEGER bi,bj
26 INTEGER advectionScheme
27 INTEGER tracerIdentity
28 _RL Tracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
29 _RL Gtracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
30 _RL myTime
31 INTEGER myIter
32 INTEGER myThid
33
34 C == Local variables
35 _RS maskUp (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
36 INTEGER iMin,iMax,jMin,jMax
37 INTEGER i,j,k,kup,kDown,kp1
38 _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
39 _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
40 _RL uTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
41 _RL vTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
42 _RL rTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
43 _RL af (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
44 _RL fVerT (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
45 _RL localTij(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
46 _RL localTijk(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
47 _RL kp1Msk
48 LOGICAL calc_fluxes_X,calc_fluxes_Y
49 INTEGER nipass,ipass
50
51 C-- Set up work arrays with valid (i.e. not NaN) values
52 C These inital values do not alter the numerical results. They
53 C just ensure that all memory references are to valid floating
54 C point numbers. This prevents spurious hardware signals due to
55 C uninitialised but inert locations.
56 DO j=1-OLy,sNy+OLy
57 DO i=1-OLx,sNx+OLx
58 xA(i,j) = 0. _d 0
59 yA(i,j) = 0. _d 0
60 uTrans(i,j) = 0. _d 0
61 vTrans(i,j) = 0. _d 0
62 rTrans(i,j) = 0. _d 0
63 fVerT(i,j,1) = 0. _d 0
64 fVerT(i,j,2) = 0. _d 0
65 ENDDO
66 ENDDO
67
68 iMin = 1-OLx
69 iMax = sNx+OLx
70 jMin = 1-OLy
71 jMax = sNy+OLy
72
73 C-- Start of k loop for horizontal fluxes
74 DO k=1,Nr
75
76 C-- Get temporary terms used by tendency routines
77 CALL CALC_COMMON_FACTORS (
78 I bi,bj,iMin,iMax,jMin,jMax,k,
79 O xA,yA,uTrans,vTrans,rTrans,maskUp,
80 I myThid)
81
82 C-- Make local copy of tracer array
83 DO j=1-OLy,sNy+OLy
84 DO i=1-OLx,sNx+OLx
85 localTij(i,j)=tracer(i,j,k,bi,bj)
86 ENDDO
87 ENDDO
88
89 IF (useCubedSphereExchange) THEN
90 nipass=3
91 ELSE
92 nipass=1
93 ENDIF
94 nipass=1
95
96 C-- Multiple passes for different directions on different tiles
97 DO ipass=1,nipass
98
99 IF (nipass.EQ.3) THEN
100 calc_fluxes_X=.FALSE.
101 calc_fluxes_Y=.FALSE.
102 IF (ipass.EQ.1 .AND. (bi.EQ.1 .OR. bi.EQ.2) ) THEN
103 calc_fluxes_X=.TRUE.
104 ELSEIF (ipass.EQ.1 .AND. (bi.EQ.4 .OR. bi.EQ.5) ) THEN
105 calc_fluxes_Y=.TRUE.
106 ELSEIF (ipass.EQ.2 .AND. (bi.EQ.1 .OR. bi.EQ.6) ) THEN
107 calc_fluxes_Y=.TRUE.
108 ELSEIF (ipass.EQ.2 .AND. (bi.EQ.3 .OR. bi.EQ.4) ) THEN
109 calc_fluxes_X=.TRUE.
110 ELSEIF (ipass.EQ.3 .AND. (bi.EQ.2 .OR. bi.EQ.3) ) THEN
111 calc_fluxes_Y=.TRUE.
112 ELSEIF (ipass.EQ.3 .AND. (bi.EQ.5 .OR. bi.EQ.6) ) THEN
113 calc_fluxes_X=.TRUE.
114 ENDIF
115 ELSE
116 calc_fluxes_X=.TRUE.
117 calc_fluxes_Y=.TRUE.
118 ENDIF
119
120 C-- X direction
121 IF (calc_fluxes_X) THEN
122
123 C-- Internal exchange for calculations in X
124 IF (useCubedSphereExchange) THEN
125 DO j=1,Oly
126 DO i=1,Olx
127 localTij( 1-i , 1-j )=localTij( 1-j , i )
128 localTij( 1-i ,sNy+j)=localTij( 1-j , sNy+1-i )
129 localTij(sNx+i, 1-j )=localTij(sNx+j, i )
130 localTij(sNx+i,sNy+j)=localTij(sNx+j, sNy+1-i )
131 ENDDO
132 ENDDO
133 ENDIF
134
135 C- Advective flux in X
136 DO j=1-Oly,sNy+Oly
137 DO i=1-Olx,sNx+Olx
138 af(i,j) = 0.
139 ENDDO
140 ENDDO
141 IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
142 CALL GAD_FLUXLIMIT_ADV_X(
143 & bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
144 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
145 CALL GAD_DST3_ADV_X(
146 & bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
147 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
148 CALL GAD_DST3FL_ADV_X(
149 & bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
150 ELSE
151 STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
152 ENDIF
153 DO j=1-Oly,sNy+Oly
154 DO i=1-Olx,sNx+Olx-1
155 localTij(i,j)=localTij(i,j)-deltaTtracer*
156 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
157 & *recip_rA(i,j,bi,bj)
158 & *( af(i+1,j)-af(i,j)
159 & -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
160 & )
161 ENDDO
162 ENDDO
163
164 #ifdef ALLOW_OBCS
165 C-- Apply open boundary conditions
166 IF (useOBCS) THEN
167 IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
168 CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
169 ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
170 CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
171 END IF
172 END IF
173 #endif /* ALLOW_OBCS */
174
175 C-- End of X direction
176 ENDIF
177
178 C-- Y direction
179 IF (calc_fluxes_Y) THEN
180
181 C-- Internal exchange for calculations in Y
182 IF (useCubedSphereExchange) THEN
183 DO j=1,Oly
184 DO i=1,Olx
185 localTij( 1-i , 1-j )=localTij( j , 1-i )
186 localTij( 1-i ,sNy+j)=localTij( j ,sNy+i)
187 localTij(sNx+i, 1-j )=localTij(sNx+1-j, 1-i )
188 localTij(sNx+i,sNy+j)=localTij(sNx+1-j,sNy+i)
189 ENDDO
190 ENDDO
191 ENDIF
192
193 C- Advective flux in Y
194 DO j=1-Oly,sNy+Oly
195 DO i=1-Olx,sNx+Olx
196 af(i,j) = 0.
197 ENDDO
198 ENDDO
199 IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
200 CALL GAD_FLUXLIMIT_ADV_Y(
201 & bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)
202 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
203 CALL GAD_DST3_ADV_Y(
204 & bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)
205 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
206 CALL GAD_DST3FL_ADV_Y(
207 & bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)
208 ELSE
209 STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
210 ENDIF
211 DO j=1-Oly,sNy+Oly-1
212 DO i=1-Olx,sNx+Olx
213 localTij(i,j)=localTij(i,j)-deltaTtracer*
214 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
215 & *recip_rA(i,j,bi,bj)
216 & *( af(i,j+1)-af(i,j)
217 & -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
218 & )
219 ENDDO
220 ENDDO
221
222 #ifdef ALLOW_OBCS
223 C-- Apply open boundary conditions
224 IF (useOBCS) THEN
225 IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
226 CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
227 ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
228 CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
229 END IF
230 END IF
231 #endif /* ALLOW_OBCS */
232
233 C-- End of Y direction
234 ENDIF
235
236 DO j=1-Oly,sNy+Oly
237 DO i=1-Olx,sNx+Olx
238 localTijk(i,j,k)=localTij(i,j)
239 ENDDO
240 ENDDO
241
242 C-- End of ipass loop
243 ENDDO
244
245 C-- End of K loop for horizontal fluxes
246 ENDDO
247
248 C-- Start of k loop for vertical flux
249 DO k=Nr,1,-1
250
251 C-- kup Cycles through 1,2 to point to w-layer above
252 C-- kDown Cycles through 2,1 to point to w-layer below
253 kup = 1+MOD(k+1,2)
254 kDown= 1+MOD(k,2)
255
256 C-- Get temporary terms used by tendency routines
257 CALL CALC_COMMON_FACTORS (
258 I bi,bj,iMin,iMax,jMin,jMax,k,
259 O xA,yA,uTrans,vTrans,rTrans,maskUp,
260 I myThid)
261
262 C- Advective flux in R
263 DO j=1-Oly,sNy+Oly
264 DO i=1-Olx,sNx+Olx
265 af(i,j) = 0.
266 ENDDO
267 ENDDO
268
269 C Note: wVel needs to be masked
270 IF (K.GE.2) THEN
271 C- Compute vertical advective flux in the interior:
272 IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
273 CALL GAD_FLUXLIMIT_ADV_R(
274 & bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
275 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
276 CALL GAD_DST3_ADV_R(
277 & bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
278 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
279 CALL GAD_DST3FL_ADV_R(
280 & bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
281 ELSE
282 STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
283 ENDIF
284 C- Surface "correction" term at k>1 :
285 DO j=1-Oly,sNy+Oly
286 DO i=1-Olx,sNx+Olx
287 af(i,j) = af(i,j)
288 & + (maskC(i,j,k,bi,bj)-maskC(i,j,k-1,bi,bj))*
289 & rTrans(i,j)*localTijk(i,j,k)
290 ENDDO
291 ENDDO
292 ELSE
293 C- Surface "correction" term at k=1 :
294 DO j=1-Oly,sNy+Oly
295 DO i=1-Olx,sNx+Olx
296 af(i,j) = rTrans(i,j)*localTijk(i,j,k)
297 ENDDO
298 ENDDO
299 ENDIF
300 C- add the advective flux to fVerT
301 DO j=1-Oly,sNy+Oly
302 DO i=1-Olx,sNx+Olx
303 fVerT(i,j,kUp) = af(i,j)
304 ENDDO
305 ENDDO
306
307 C-- Divergence of fluxes
308 kp1=min(Nr,k+1)
309 kp1Msk=1.
310 if (k.EQ.Nr) kp1Msk=0.
311 DO j=1-Oly,sNy+Oly
312 DO i=1-Olx,sNx+Olx
313 localTij(i,j)=localTijk(i,j,k)-deltaTtracer*
314 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
315 & *recip_rA(i,j,bi,bj)
316 & *( fVerT(i,j,kUp)-fVerT(i,j,kDown)
317 & -tracer(i,j,k,bi,bj)*rA(i,j,bi,bj)*
318 & (wVel(i,j,k,bi,bj)-kp1Msk*wVel(i,j,kp1,bi,bj))
319 & )*rkFac
320 gTracer(i,j,k,bi,bj)=
321 & (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer
322 ENDDO
323 ENDDO
324
325 C-- End of K loop for vertical flux
326 ENDDO
327
328 RETURN
329 END

  ViewVC Help
Powered by ViewVC 1.1.22