/[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.11 - (show annotations) (download)
Wed Mar 6 02:01:54 2002 UTC (22 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint44h_pre
Changes since 1.10: +52 -41 lines
add GM-bolus transport to Eulerian transport to advect Tracers (T,S, ...)

1 C $Header: /u/gcmpack/MITgcm/pkg/generic_advdiff/gad_advection.F,v 1.8 2001/09/28 16:49:54 adcroft Exp $
2 C $Name: $
3
4 CBOI
5 C !TITLE: pkg/generic\_advdiff
6 C !AUTHORS: adcroft@mit.edu
7 C !INTRODUCTION: Generic Advection Diffusion Package
8 C
9 C Package "generic\_advdiff" provides a common set of routines for calculating
10 C advective/diffusive fluxes for tracers (cell centered quantities on a C-grid).
11 C
12 C Many different advection schemes are available: the standard centered
13 C second order, centered fourth order and upwind biased third order schemes
14 C are known as linear methods and require some stable time-stepping method
15 C such as Adams-Bashforth. Alternatives such as flux-limited schemes are
16 C stable in the forward sense and are best combined with the multi-dimensional
17 C method provided in gad\_advection.
18 C
19 C There are two high-level routines:
20 C \begin{itemize}
21 C \item{GAD\_CALC\_RHS} calculates all fluxes at time level "n" and is used
22 C for the standard linear schemes. This must be used in conjuction with
23 C Adams-Bashforth time-stepping. Diffusive and parameterized fluxes are
24 C always calculated here.
25 C \item{GAD\_ADVECTION} calculates just the advective fluxes using the
26 C non-linear schemes and can not be used in conjuction with Adams-Bashforth
27 C time-stepping.
28 C \end{itemize}
29 CEOI
30
31 #include "GAD_OPTIONS.h"
32
33 CBOP
34 C !ROUTINE: GAD_ADVECTION
35
36 C !INTERFACE: ==========================================================
37 SUBROUTINE GAD_ADVECTION(bi,bj,advectionScheme,tracerIdentity,
38 U Tracer,Gtracer,
39 I myTime,myIter,myThid)
40
41 C !DESCRIPTION:
42 C Calculates the tendancy of a tracer due to advection.
43 C It uses the multi-dimensional method given in \ref{sect:multiDimAdvection}
44 C and can only be used for the non-linear advection schemes such as the
45 C direct-space-time method and flux-limiters.
46 C
47 C The algorithm is as follows:
48 C \begin{itemize}
49 C \item{$\theta^{(n+1/3)} = \theta^{(n)}
50 C - \Delta t \partial_x (u\theta^{(n)}) + \theta^{(n)} \partial_x u$}
51 C \item{$\theta^{(n+2/3)} = \theta^{(n+1/3)}
52 C - \Delta t \partial_y (v\theta^{(n+1/3)}) + \theta^{(n)} \partial_y v$}
53 C \item{$\theta^{(n+3/3)} = \theta^{(n+2/3)}
54 C - \Delta t \partial_r (w\theta^{(n+2/3)}) + \theta^{(n)} \partial_r w$}
55 C \item{$G_\theta = ( \theta^{(n+3/3)} - \theta^{(n)} )/\Delta t$}
56 C \end{itemize}
57 C
58 C The tendancy (output) is over-written by this routine.
59
60 C !USES: ===============================================================
61 IMPLICIT NONE
62 #include "SIZE.h"
63 #include "EEPARAMS.h"
64 #include "PARAMS.h"
65 #include "DYNVARS.h"
66 #include "GRID.h"
67 #include "GAD.h"
68 #ifdef ALLOW_AUTODIFF_TAMC
69 # include "tamc.h"
70 # include "tamc_keys.h"
71 #endif
72
73 C !INPUT PARAMETERS: ===================================================
74 C bi,bj :: tile indices
75 C advectionScheme :: advection scheme to use
76 C tracerIdentity :: identifier for the tracer (required only for OBCS)
77 C Tracer :: tracer field
78 C myTime :: current time
79 C myIter :: iteration number
80 C myThid :: thread number
81 INTEGER bi,bj
82 INTEGER advectionScheme
83 INTEGER tracerIdentity
84 _RL Tracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
85 _RL myTime
86 INTEGER myIter
87 INTEGER myThid
88
89 C !OUTPUT PARAMETERS: ==================================================
90 C gTracer :: tendancy array
91 _RL gTracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
92
93 C !LOCAL VARIABLES: ====================================================
94 C maskUp :: 2-D array for mask at W points
95 C iMin,iMax,jMin,jMax :: loop range for called routines
96 C i,j,k :: loop indices
97 C kup :: index into 2 1/2D array, toggles between 1 and 2
98 C kdown :: index into 2 1/2D array, toggles between 2 and 1
99 C kp1 :: =k+1 for k<Nr, =Nr for k=Nr
100 C xA,yA :: areas of X and Y face of tracer cells
101 C uTrans,vTrans,rTrans :: 2-D arrays of volume transports at U,V and W points
102 C rTransKp1 :: vertical volume transport at interface k+1
103 C af :: 2-D array for horizontal advective flux
104 C fVerT :: 2 1/2D arrays for vertical advective flux
105 C localTij :: 2-D array used as temporary local copy of tracer fld
106 C localTijk :: 3-D array used as temporary local copy of tracer fld
107 C kp1Msk :: flag (0,1) to act as over-riding mask for W levels
108 C calc_fluxes_X :: logical to indicate to calculate fluxes in X dir
109 C calc_fluxes_Y :: logical to indicate to calculate fluxes in Y dir
110 C nipass :: number of passes to make in multi-dimensional method
111 C ipass :: number of the current pass being made
112 _RS maskUp (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
113 INTEGER iMin,iMax,jMin,jMax
114 INTEGER i,j,k,kup,kDown
115 _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
116 _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
117 _RL uTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
118 _RL vTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
119 _RL rTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
120 _RL rTransKp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
121 _RL af (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
122 _RL fVerT (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
123 _RL localTij(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
124 _RL localTijk(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
125 _RL kp1Msk
126 LOGICAL calc_fluxes_X,calc_fluxes_Y
127 INTEGER nipass,ipass
128 CEOP
129
130 #ifdef ALLOW_AUTODIFF_TAMC
131 act1 = bi - myBxLo(myThid)
132 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
133 act2 = bj - myByLo(myThid)
134 max2 = myByHi(myThid) - myByLo(myThid) + 1
135 act3 = myThid - 1
136 max3 = nTx*nTy
137 act4 = ikey_dynamics - 1
138 ikey = (act1 + 1) + act2*max1
139 & + act3*max1*max2
140 & + act4*max1*max2*max3
141 #endif /* ALLOW_AUTODIFF_TAMC */
142
143 C-- Set up work arrays with valid (i.e. not NaN) values
144 C These inital values do not alter the numerical results. They
145 C just ensure that all memory references are to valid floating
146 C point numbers. This prevents spurious hardware signals due to
147 C uninitialised but inert locations.
148 DO j=1-OLy,sNy+OLy
149 DO i=1-OLx,sNx+OLx
150 xA(i,j) = 0. _d 0
151 yA(i,j) = 0. _d 0
152 uTrans(i,j) = 0. _d 0
153 vTrans(i,j) = 0. _d 0
154 rTrans(i,j) = 0. _d 0
155 fVerT(i,j,1) = 0. _d 0
156 fVerT(i,j,2) = 0. _d 0
157 rTransKp1(i,j)= 0. _d 0
158 ENDDO
159 ENDDO
160
161 iMin = 1-OLx
162 iMax = sNx+OLx
163 jMin = 1-OLy
164 jMax = sNy+OLy
165
166 C-- Start of k loop for horizontal fluxes
167 DO k=1,Nr
168 #ifdef ALLOW_AUTODIFF_TAMC
169 kkey = (ikey-1)*Nr + k
170 CADJ STORE tracer(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
171 #endif /* ALLOW_AUTODIFF_TAMC */
172
173 C-- Get temporary terms used by tendency routines
174 CALL CALC_COMMON_FACTORS (
175 I bi,bj,iMin,iMax,jMin,jMax,k,
176 O xA,yA,uTrans,vTrans,rTrans,maskUp,
177 I myThid)
178
179 #ifdef ALLOW_GMREDI
180 C-- Residual transp = Bolus transp + Eulerian transp
181 IF (useGMRedi)
182 & CALL GMREDI_CALC_UVFLOW(
183 & uTrans, vTrans, bi, bj, k, myThid)
184 #endif /* ALLOW_GMREDI */
185
186 C-- Make local copy of tracer array
187 DO j=1-OLy,sNy+OLy
188 DO i=1-OLx,sNx+OLx
189 localTij(i,j)=tracer(i,j,k,bi,bj)
190 ENDDO
191 ENDDO
192
193 IF (useCubedSphereExchange) THEN
194 nipass=3
195 ELSE
196 nipass=1
197 ENDIF
198 cph nipass=1
199
200 C-- Multiple passes for different directions on different tiles
201 DO ipass=1,nipass
202 #ifdef ALLOW_AUTODIFF_TAMC
203 passkey = ipass + (k-1) *maxpass
204 & + (ikey-1)*maxpass*Nr
205 IF (nipass .GT. maxpass) THEN
206 STOP 'GAD_ADVECTION: nipass > maxpass. check tamc.h'
207 ENDIF
208 #endif /* ALLOW_AUTODIFF_TAMC */
209
210 IF (nipass.EQ.3) THEN
211 calc_fluxes_X=.FALSE.
212 calc_fluxes_Y=.FALSE.
213 IF (ipass.EQ.1 .AND. (bi.EQ.1 .OR. bi.EQ.2) ) THEN
214 calc_fluxes_X=.TRUE.
215 ELSEIF (ipass.EQ.1 .AND. (bi.EQ.4 .OR. bi.EQ.5) ) THEN
216 calc_fluxes_Y=.TRUE.
217 ELSEIF (ipass.EQ.2 .AND. (bi.EQ.1 .OR. bi.EQ.6) ) THEN
218 calc_fluxes_Y=.TRUE.
219 ELSEIF (ipass.EQ.2 .AND. (bi.EQ.3 .OR. bi.EQ.4) ) THEN
220 calc_fluxes_X=.TRUE.
221 ELSEIF (ipass.EQ.3 .AND. (bi.EQ.2 .OR. bi.EQ.3) ) THEN
222 calc_fluxes_Y=.TRUE.
223 ELSEIF (ipass.EQ.3 .AND. (bi.EQ.5 .OR. bi.EQ.6) ) THEN
224 calc_fluxes_X=.TRUE.
225 ENDIF
226 ELSE
227 calc_fluxes_X=.TRUE.
228 calc_fluxes_Y=.TRUE.
229 ENDIF
230
231 C-- X direction
232 IF (calc_fluxes_X) THEN
233
234 C-- Internal exchange for calculations in X
235 IF (useCubedSphereExchange) THEN
236 DO j=1,Oly
237 DO i=1,Olx
238 localTij( 1-i , 1-j )=localTij( 1-j , i )
239 localTij( 1-i ,sNy+j)=localTij( 1-j , sNy+1-i )
240 localTij(sNx+i, 1-j )=localTij(sNx+j, i )
241 localTij(sNx+i,sNy+j)=localTij(sNx+j, sNy+1-i )
242 ENDDO
243 ENDDO
244 ENDIF
245
246 C- Advective flux in X
247 DO j=1-Oly,sNy+Oly
248 DO i=1-Olx,sNx+Olx
249 af(i,j) = 0.
250 ENDDO
251 ENDDO
252
253 #ifdef ALLOW_AUTODIFF_TAMC
254 #ifndef DISABLE_MULTIDIM_ADVECTION
255 CADJ STORE localTij(:,:) = comlev1_bibj_pass, key=passkey, byte=isbyte
256 #endif
257 #endif /* ALLOW_AUTODIFF_TAMC */
258
259 IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
260 CALL GAD_FLUXLIMIT_ADV_X(
261 & bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
262 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
263 CALL GAD_DST3_ADV_X(
264 & bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
265 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
266 CALL GAD_DST3FL_ADV_X(
267 & bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
268 ELSE
269 write(0,*) advectionScheme
270 STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'
271 ENDIF
272
273 DO j=1-Oly,sNy+Oly
274 DO i=1-Olx,sNx+Olx-1
275 localTij(i,j)=localTij(i,j)-deltaTtracer*
276 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
277 & *recip_rA(i,j,bi,bj)
278 & *( af(i+1,j)-af(i,j)
279 & -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
280 & )
281 ENDDO
282 ENDDO
283
284 #ifdef ALLOW_OBCS
285 C-- Apply open boundary conditions
286 IF (useOBCS) THEN
287 IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
288 CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
289 ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
290 CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
291 END IF
292 END IF
293 #endif /* ALLOW_OBCS */
294
295 C-- End of X direction
296 ENDIF
297
298 C-- Y direction
299 IF (calc_fluxes_Y) THEN
300
301 C-- Internal exchange for calculations in Y
302 IF (useCubedSphereExchange) THEN
303 DO j=1,Oly
304 DO i=1,Olx
305 localTij( 1-i , 1-j )=localTij( j , 1-i )
306 localTij( 1-i ,sNy+j)=localTij( j ,sNy+i)
307 localTij(sNx+i, 1-j )=localTij(sNx+1-j, 1-i )
308 localTij(sNx+i,sNy+j)=localTij(sNx+1-j,sNy+i)
309 ENDDO
310 ENDDO
311 ENDIF
312
313 C- Advective flux in Y
314 DO j=1-Oly,sNy+Oly
315 DO i=1-Olx,sNx+Olx
316 af(i,j) = 0.
317 ENDDO
318 ENDDO
319
320 #ifdef ALLOW_AUTODIFF_TAMC
321 #ifndef DISABLE_MULTIDIM_ADVECTION
322 CADJ STORE localTij(:,:) = comlev1_bibj_pass, key=passkey, byte=isbyte
323 #endif
324 #endif /* ALLOW_AUTODIFF_TAMC */
325
326 IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
327 CALL GAD_FLUXLIMIT_ADV_Y(
328 & bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)
329 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
330 CALL GAD_DST3_ADV_Y(
331 & bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)
332 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
333 CALL GAD_DST3FL_ADV_Y(
334 & bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)
335 ELSE
336 STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
337 ENDIF
338
339 DO j=1-Oly,sNy+Oly-1
340 DO i=1-Olx,sNx+Olx
341 localTij(i,j)=localTij(i,j)-deltaTtracer*
342 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
343 & *recip_rA(i,j,bi,bj)
344 & *( af(i,j+1)-af(i,j)
345 & -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
346 & )
347 ENDDO
348 ENDDO
349
350 #ifdef ALLOW_OBCS
351 C-- Apply open boundary conditions
352 IF (useOBCS) THEN
353 IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
354 CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
355 ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
356 CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
357 END IF
358 END IF
359 #endif /* ALLOW_OBCS */
360
361 C-- End of Y direction
362 ENDIF
363
364 DO j=1-Oly,sNy+Oly
365 DO i=1-Olx,sNx+Olx
366 localTijk(i,j,k)=localTij(i,j)
367 ENDDO
368 ENDDO
369
370 C-- End of ipass loop
371 ENDDO
372
373 C-- End of K loop for horizontal fluxes
374 ENDDO
375
376 C-- Start of k loop for vertical flux
377 DO k=Nr,1,-1
378 #ifdef ALLOW_AUTODIFF_TAMC
379 kkey = (ikey-1)*Nr + k
380 #endif /* ALLOW_AUTODIFF_TAMC */
381
382 C-- kup Cycles through 1,2 to point to w-layer above
383 C-- kDown Cycles through 2,1 to point to w-layer below
384 kup = 1+MOD(k+1,2)
385 kDown= 1+MOD(k,2)
386 c kp1=min(Nr,k+1)
387 kp1Msk=1.
388 if (k.EQ.Nr) kp1Msk=0.
389
390 #ifdef ALLOW_AUTODIFF_TAMC
391 CADJ STORE localTijk(:,:,k)
392 CADJ & = comlev1_bibj_k, key=kkey, byte=isbyte
393 #endif /* ALLOW_AUTODIFF_TAMC */
394
395 C-- Compute Vertical transport
396 C Note: wVel needs to be masked
397
398 IF (k.EQ.1) THEN
399 C- Surface interface :
400
401 DO j=1-Oly,sNy+Oly
402 DO i=1-Olx,sNx+Olx
403 rTransKp1(i,j) = rTrans(i,j)
404 rTrans(i,j) = 0.
405 fVerT(i,j,kUp) = 0.
406 ENDDO
407 ENDDO
408
409 ELSE
410 C- Interior interface :
411 DO j=1-Oly,sNy+Oly
412 DO i=1-Olx,sNx+Olx
413 rTransKp1(i,j) = kp1Msk*rTrans(i,j)
414 rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)
415 & *maskC(i,j,k-1,bi,bj)
416 af(i,j) = 0.
417 ENDDO
418 ENDDO
419
420 #ifdef ALLOW_GMREDI
421 C-- Residual transp = Bolus transp + Eulerian transp
422 IF (useGMRedi)
423 & CALL GMREDI_CALC_WFLOW(
424 & rTrans, bi, bj, k, myThid)
425 #endif /* ALLOW_GMREDI */
426
427 C- Compute vertical advective flux in the interior:
428 IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
429 CALL GAD_FLUXLIMIT_ADV_R(
430 & bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
431 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
432 CALL GAD_DST3_ADV_R(
433 & bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
434 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
435 CALL GAD_DST3FL_ADV_R(
436 & bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
437 ELSE
438 STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
439 ENDIF
440 C- add the advective flux to fVerT
441 DO j=1-Oly,sNy+Oly
442 DO i=1-Olx,sNx+Olx
443 fVerT(i,j,kUp) = af(i,j)
444 ENDDO
445 ENDDO
446
447 C- end Surface/Interior if bloc
448 ENDIF
449
450 C-- Divergence of fluxes
451 DO j=1-Oly,sNy+Oly
452 DO i=1-Olx,sNx+Olx
453 localTij(i,j)=localTijk(i,j,k)-deltaTtracer*
454 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
455 & *recip_rA(i,j,bi,bj)
456 & *( fVerT(i,j,kUp)-fVerT(i,j,kDown)
457 & -tracer(i,j,k,bi,bj)*(rTrans(i,j)-rTransKp1(i,j))
458 & )*rkFac
459 gTracer(i,j,k,bi,bj)=
460 & (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer
461 ENDDO
462 ENDDO
463
464 C-- End of K loop for vertical flux
465 ENDDO
466
467 RETURN
468 END

  ViewVC Help
Powered by ViewVC 1.1.22