/[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.8.6.2 - (show annotations) (download)
Fri Mar 7 03:55:23 2003 UTC (21 years, 3 months ago) by heimbach
Branch: ecco-branch
CVS Tags: ecco_c50_e32, ecco_c50_e33, ecco_c50_e30, ecco_c50_e31, ecco_c51_e34d, ecco_c51_e34e, ecco_c51_e34f, ecco_c51_e34g, ecco_c51_e34a, ecco_c51_e34b, ecco_c51_e34c, ecco_c50_e29, ecco_c50_e28, ecco_c50_e33a, ecco_c51_e34
Changes since 1.8.6.1: +80 -52 lines
merging c49 and e27.

1 C $Header: /u/gcmpack/MITgcm/pkg/generic_advdiff/gad_advection.F,v 1.14 2002/11/12 20:42:24 heimbach 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 act0 = tracerIdentity - 1
132 max0 = maxpass
133 act1 = bi - myBxLo(myThid)
134 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
135 act2 = bj - myByLo(myThid)
136 max2 = myByHi(myThid) - myByLo(myThid) + 1
137 act3 = myThid - 1
138 max3 = nTx*nTy
139 act4 = ikey_dynamics - 1
140 igadkey = (act0 + 1)
141 & + act1*max0
142 & + act2*max0*max1
143 & + act3*max0*max1*max2
144 & + act4*max0*max1*max2*max3
145 if (tracerIdentity.GT.maxpass)
146 & STOP 'maxpass seems smaller than tracerIdentity'
147 #endif /* ALLOW_AUTODIFF_TAMC */
148
149 C-- Set up work arrays with valid (i.e. not NaN) values
150 C These inital values do not alter the numerical results. They
151 C just ensure that all memory references are to valid floating
152 C point numbers. This prevents spurious hardware signals due to
153 C uninitialised but inert locations.
154 DO j=1-OLy,sNy+OLy
155 DO i=1-OLx,sNx+OLx
156 xA(i,j) = 0. _d 0
157 yA(i,j) = 0. _d 0
158 uTrans(i,j) = 0. _d 0
159 vTrans(i,j) = 0. _d 0
160 rTrans(i,j) = 0. _d 0
161 fVerT(i,j,1) = 0. _d 0
162 fVerT(i,j,2) = 0. _d 0
163 rTransKp1(i,j)= 0. _d 0
164 ENDDO
165 ENDDO
166
167 iMin = 1-OLx
168 iMax = sNx+OLx
169 jMin = 1-OLy
170 jMax = sNy+OLy
171
172 C-- Start of k loop for horizontal fluxes
173 DO k=1,Nr
174 #ifdef ALLOW_AUTODIFF_TAMC
175 kkey = (igadkey-1)*Nr + k
176 CADJ STORE tracer(:,:,k,bi,bj) =
177 CADJ & comlev1_bibj_k_gad, key=kkey, byte=isbyte
178 #endif /* ALLOW_AUTODIFF_TAMC */
179
180 C-- Get temporary terms used by tendency routines
181 CALL CALC_COMMON_FACTORS (
182 I bi,bj,iMin,iMax,jMin,jMax,k,
183 O xA,yA,uTrans,vTrans,rTrans,maskUp,
184 I myThid)
185
186 #ifdef ALLOW_GMREDI
187 C-- Residual transp = Bolus transp + Eulerian transp
188 IF (useGMRedi)
189 & CALL GMREDI_CALC_UVFLOW(
190 & uTrans, vTrans, bi, bj, k, myThid)
191 #endif /* ALLOW_GMREDI */
192
193 C-- Make local copy of tracer array
194 DO j=1-OLy,sNy+OLy
195 DO i=1-OLx,sNx+OLx
196 localTij(i,j)=tracer(i,j,k,bi,bj)
197 ENDDO
198 ENDDO
199
200 IF (useCubedSphereExchange) THEN
201 nipass=3
202 #ifdef ALLOW_AUTODIFF_TAMC
203 if ( nipass.GT.maxcube )
204 & STOP 'maxcube needs to be = 3'
205 #endif
206 ELSE
207 nipass=1
208 ENDIF
209 cph nipass=1
210
211 C-- Multiple passes for different directions on different tiles
212 DO ipass=1,nipass
213 #ifdef ALLOW_AUTODIFF_TAMC
214 passkey = ipass + (k-1) *maxcube
215 & + (igadkey-1)*maxcube*Nr
216 IF (nipass .GT. maxpass) THEN
217 STOP 'GAD_ADVECTION: nipass > maxcube. check tamc.h'
218 ENDIF
219 #endif /* ALLOW_AUTODIFF_TAMC */
220
221 IF (nipass.EQ.3) THEN
222 calc_fluxes_X=.FALSE.
223 calc_fluxes_Y=.FALSE.
224 IF (ipass.EQ.1 .AND. (bi.EQ.1 .OR. bi.EQ.2) ) THEN
225 calc_fluxes_X=.TRUE.
226 ELSEIF (ipass.EQ.1 .AND. (bi.EQ.4 .OR. bi.EQ.5) ) THEN
227 calc_fluxes_Y=.TRUE.
228 ELSEIF (ipass.EQ.2 .AND. (bi.EQ.1 .OR. bi.EQ.6) ) THEN
229 calc_fluxes_Y=.TRUE.
230 ELSEIF (ipass.EQ.2 .AND. (bi.EQ.3 .OR. bi.EQ.4) ) THEN
231 calc_fluxes_X=.TRUE.
232 ELSEIF (ipass.EQ.3 .AND. (bi.EQ.2 .OR. bi.EQ.3) ) THEN
233 calc_fluxes_Y=.TRUE.
234 ELSEIF (ipass.EQ.3 .AND. (bi.EQ.5 .OR. bi.EQ.6) ) THEN
235 calc_fluxes_X=.TRUE.
236 ENDIF
237 ELSE
238 calc_fluxes_X=.TRUE.
239 calc_fluxes_Y=.TRUE.
240 ENDIF
241
242 C-- X direction
243 IF (calc_fluxes_X) THEN
244
245 C-- Internal exchange for calculations in X
246 IF (useCubedSphereExchange) THEN
247 DO j=1,Oly
248 DO i=1,Olx
249 localTij( 1-i , 1-j )=localTij( 1-j , i )
250 localTij( 1-i ,sNy+j)=localTij( 1-j , sNy+1-i )
251 localTij(sNx+i, 1-j )=localTij(sNx+j, i )
252 localTij(sNx+i,sNy+j)=localTij(sNx+j, sNy+1-i )
253 ENDDO
254 ENDDO
255 ENDIF
256
257 C- Advective flux in X
258 DO j=1-Oly,sNy+Oly
259 DO i=1-Olx,sNx+Olx
260 af(i,j) = 0.
261 ENDDO
262 ENDDO
263
264 #ifdef ALLOW_AUTODIFF_TAMC
265 #ifndef DISABLE_MULTIDIM_ADVECTION
266 CADJ STORE localTij(:,:) =
267 CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
268 #endif
269 #endif /* ALLOW_AUTODIFF_TAMC */
270
271 IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
272 CALL GAD_FLUXLIMIT_ADV_X(
273 & bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
274 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
275 CALL GAD_DST3_ADV_X(
276 & bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
277 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
278 CALL GAD_DST3FL_ADV_X(
279 & bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
280 ELSE
281 STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'
282 ENDIF
283
284 DO j=1-Oly,sNy+Oly
285 DO i=1-Olx,sNx+Olx-1
286 localTij(i,j)=localTij(i,j)-deltaTtracer*
287 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
288 & *recip_rA(i,j,bi,bj)
289 & *( af(i+1,j)-af(i,j)
290 & -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
291 & )
292 ENDDO
293 ENDDO
294
295 #ifdef ALLOW_OBCS
296 C-- Apply open boundary conditions
297 IF (useOBCS) THEN
298 IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
299 CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
300 ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
301 CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
302 END IF
303 END IF
304 #endif /* ALLOW_OBCS */
305
306 C-- End of X direction
307 ENDIF
308
309 C-- Y direction
310 IF (calc_fluxes_Y) THEN
311
312 C-- Internal exchange for calculations in Y
313 IF (useCubedSphereExchange) THEN
314 DO j=1,Oly
315 DO i=1,Olx
316 localTij( 1-i , 1-j )=localTij( j , 1-i )
317 localTij( 1-i ,sNy+j)=localTij( j ,sNy+i)
318 localTij(sNx+i, 1-j )=localTij(sNx+1-j, 1-i )
319 localTij(sNx+i,sNy+j)=localTij(sNx+1-j,sNy+i)
320 ENDDO
321 ENDDO
322 ENDIF
323
324 C- Advective flux in Y
325 DO j=1-Oly,sNy+Oly
326 DO i=1-Olx,sNx+Olx
327 af(i,j) = 0.
328 ENDDO
329 ENDDO
330
331 #ifdef ALLOW_AUTODIFF_TAMC
332 #ifndef DISABLE_MULTIDIM_ADVECTION
333 CADJ STORE localTij(:,:) =
334 CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
335 #endif
336 #endif /* ALLOW_AUTODIFF_TAMC */
337
338 IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
339 CALL GAD_FLUXLIMIT_ADV_Y(
340 & bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)
341 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
342 CALL GAD_DST3_ADV_Y(
343 & bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)
344 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
345 CALL GAD_DST3FL_ADV_Y(
346 & bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)
347 ELSE
348 STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
349 ENDIF
350
351 DO j=1-Oly,sNy+Oly-1
352 DO i=1-Olx,sNx+Olx
353 localTij(i,j)=localTij(i,j)-deltaTtracer*
354 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
355 & *recip_rA(i,j,bi,bj)
356 & *( af(i,j+1)-af(i,j)
357 & -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
358 & )
359 ENDDO
360 ENDDO
361
362 #ifdef ALLOW_OBCS
363 C-- Apply open boundary conditions
364 IF (useOBCS) THEN
365 IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
366 CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
367 ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
368 CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
369 END IF
370 END IF
371 #endif /* ALLOW_OBCS */
372
373 C-- End of Y direction
374 ENDIF
375
376 DO j=1-Oly,sNy+Oly
377 DO i=1-Olx,sNx+Olx
378 localTijk(i,j,k)=localTij(i,j)
379 ENDDO
380 ENDDO
381
382 C-- End of ipass loop
383 ENDDO
384
385 C-- End of K loop for horizontal fluxes
386 ENDDO
387
388 C-- Start of k loop for vertical flux
389 DO k=Nr,1,-1
390 #ifdef ALLOW_AUTODIFF_TAMC
391 kkey = (ikey-1)*Nr + k
392 #endif /* ALLOW_AUTODIFF_TAMC */
393
394 C-- kup Cycles through 1,2 to point to w-layer above
395 C-- kDown Cycles through 2,1 to point to w-layer below
396 kup = 1+MOD(k+1,2)
397 kDown= 1+MOD(k,2)
398 c kp1=min(Nr,k+1)
399 kp1Msk=1.
400 if (k.EQ.Nr) kp1Msk=0.
401
402 #ifdef ALLOW_AUTODIFF_TAMC
403 CADJ STORE localTijk(:,:,k)
404 CADJ & = comlev1_bibj_k_gad, key=kkey, byte=isbyte
405 CADJ STORE rTrans(:,:)
406 CADJ & = comlev1_bibj_k_gad, key=kkey, byte=isbyte
407 #endif /* ALLOW_AUTODIFF_TAMC */
408
409 C-- Compute Vertical transport
410 C Note: wVel needs to be masked
411
412 IF (k.EQ.1) THEN
413 C- Surface interface :
414
415 DO j=1-Oly,sNy+Oly
416 DO i=1-Olx,sNx+Olx
417 rTransKp1(i,j) = rTrans(i,j)
418 rTrans(i,j) = 0.
419 fVerT(i,j,kUp) = 0.
420 ENDDO
421 ENDDO
422
423 ELSE
424 C- Interior interface :
425 DO j=1-Oly,sNy+Oly
426 DO i=1-Olx,sNx+Olx
427 rTransKp1(i,j) = kp1Msk*rTrans(i,j)
428 rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)
429 & *maskC(i,j,k-1,bi,bj)
430 af(i,j) = 0.
431 ENDDO
432 ENDDO
433
434 #ifdef ALLOW_GMREDI
435 C-- Residual transp = Bolus transp + Eulerian transp
436 IF (useGMRedi)
437 & CALL GMREDI_CALC_WFLOW(
438 & rTrans, bi, bj, k, myThid)
439 #endif /* ALLOW_GMREDI */
440
441 C- Compute vertical advective flux in the interior:
442 IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
443 CALL GAD_FLUXLIMIT_ADV_R(
444 & bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
445 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
446 CALL GAD_DST3_ADV_R(
447 & bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
448 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
449 CALL GAD_DST3FL_ADV_R(
450 & bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
451 ELSE
452 STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
453 ENDIF
454 C- add the advective flux to fVerT
455 DO j=1-Oly,sNy+Oly
456 DO i=1-Olx,sNx+Olx
457 fVerT(i,j,kUp) = af(i,j)
458 ENDDO
459 ENDDO
460
461 C- end Surface/Interior if bloc
462 ENDIF
463
464 C-- Divergence of fluxes
465 DO j=1-Oly,sNy+Oly
466 DO i=1-Olx,sNx+Olx
467 localTij(i,j)=localTijk(i,j,k)-deltaTtracer*
468 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
469 & *recip_rA(i,j,bi,bj)
470 & *( fVerT(i,j,kUp)-fVerT(i,j,kDown)
471 & -tracer(i,j,k,bi,bj)*(rTrans(i,j)-rTransKp1(i,j))
472 & )*rkFac
473 gTracer(i,j,k,bi,bj)=
474 & (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer
475 ENDDO
476 ENDDO
477
478 C-- End of K loop for vertical flux
479 ENDDO
480
481 RETURN
482 END

  ViewVC Help
Powered by ViewVC 1.1.22