/[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.15 - (show annotations) (download)
Fri Jun 27 01:57:28 2003 UTC (21 years ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint51k_post, checkpoint51o_pre, checkpoint51l_post, checkpoint52, checkpoint51f_post, checkpoint51d_post, checkpoint51t_post, checkpoint51n_post, checkpoint51s_post, checkpoint51j_post, checkpoint51n_pre, checkpoint52b_pre, checkpoint51l_pre, checkpoint51q_post, checkpoint52b_post, checkpoint51h_pre, branchpoint-genmake2, checkpoint51r_post, checkpoint51i_post, checkpoint51b_post, checkpoint51c_post, checkpoint52a_pre, checkpoint51i_pre, checkpoint51e_post, checkpoint51o_post, checkpoint51f_pre, checkpoint52a_post, checkpoint51g_post, ecco_c52_e35, checkpoint51m_post, checkpoint51p_post, checkpoint51u_post
Branch point for: branch-genmake2, branch-nonh, tg2-branch, checkpoint51n_branch
Changes since 1.14: +5 -3 lines
updated wraning

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

  ViewVC Help
Powered by ViewVC 1.1.22