/[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.23 - (show annotations) (download)
Sat Jun 26 02:38:54 2004 UTC (20 years ago) by jmc
Branch: MAIN
Changes since 1.22: +9 -7 lines
T & S: separate Vert.Advec.Scheme from horizontal Advec.Scheme

1 C $Header: /u/gcmpack/MITgcm/pkg/generic_advdiff/gad_advection.F,v 1.22 2004/06/25 18:19:20 jmc Exp $
2 C $Name: $
3
4 #include "GAD_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7 CBOP
8 C !ROUTINE: GAD_ADVECTION
9
10 C !INTERFACE: ==========================================================
11 SUBROUTINE GAD_ADVECTION(
12 I implicitAdvection, advectionScheme, vertAdvecScheme,
13 I tracerIdentity,
14 I uVel, vVel, wVel, tracer,
15 O gTracer,
16 I bi,bj, myTime,myIter,myThid)
17
18 C !DESCRIPTION:
19 C Calculates the tendancy of a tracer due to advection.
20 C It uses the multi-dimensional method given in \ref{sect:multiDimAdvection}
21 C and can only be used for the non-linear advection schemes such as the
22 C direct-space-time method and flux-limiters.
23 C
24 C The algorithm is as follows:
25 C \begin{itemize}
26 C \item{$\theta^{(n+1/3)} = \theta^{(n)}
27 C - \Delta t \partial_x (u\theta^{(n)}) + \theta^{(n)} \partial_x u$}
28 C \item{$\theta^{(n+2/3)} = \theta^{(n+1/3)}
29 C - \Delta t \partial_y (v\theta^{(n+1/3)}) + \theta^{(n)} \partial_y v$}
30 C \item{$\theta^{(n+3/3)} = \theta^{(n+2/3)}
31 C - \Delta t \partial_r (w\theta^{(n+2/3)}) + \theta^{(n)} \partial_r w$}
32 C \item{$G_\theta = ( \theta^{(n+3/3)} - \theta^{(n)} )/\Delta t$}
33 C \end{itemize}
34 C
35 C The tendancy (output) is over-written by this routine.
36
37 C !USES: ===============================================================
38 IMPLICIT NONE
39 #include "SIZE.h"
40 #include "EEPARAMS.h"
41 #include "PARAMS.h"
42 #include "GRID.h"
43 #include "GAD.h"
44 #ifdef ALLOW_AUTODIFF_TAMC
45 # include "tamc.h"
46 # include "tamc_keys.h"
47 #endif
48
49 C !INPUT PARAMETERS: ===================================================
50 C implicitAdvection :: implicit vertical advection (later on)
51 C advectionScheme :: advection scheme to use (Horizontal plane)
52 C vertAdvecScheme :: advection scheme to use (vertical direction)
53 C tracerIdentity :: tracer identifier (required only for OBCS)
54 C uVel :: velocity, zonal component
55 C vVel :: velocity, meridional component
56 C wVel :: velocity, vertical component
57 C tracer :: tracer field
58 C bi,bj :: tile indices
59 C myTime :: current time
60 C myIter :: iteration number
61 C myThid :: thread number
62 LOGICAL implicitAdvection
63 INTEGER advectionScheme, vertAdvecScheme
64 INTEGER tracerIdentity
65 _RL uVel (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
66 _RL vVel (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
67 _RL wVel (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
68 _RL tracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
69 INTEGER bi,bj
70 _RL myTime
71 INTEGER myIter
72 INTEGER myThid
73
74 C !OUTPUT PARAMETERS: ==================================================
75 C gTracer :: tendancy array
76 _RL gTracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
77
78 C !LOCAL VARIABLES: ====================================================
79 C maskUp :: 2-D array for mask at W points
80 C iMin,iMax, :: loop range for called routines
81 C jMin,jMax :: loop range for called routines
82 C i,j,k :: loop indices
83 C kup :: index into 2 1/2D array, toggles between 1 and 2
84 C kdown :: index into 2 1/2D array, toggles between 2 and 1
85 C kp1 :: =k+1 for k<Nr, =Nr for k=Nr
86 C xA,yA :: areas of X and Y face of tracer cells
87 C uTrans,vTrans :: 2-D arrays of volume transports at U,V points
88 C rTrans :: 2-D arrays of volume transports at W points
89 C rTransKp1 :: vertical volume transport at interface k+1
90 C af :: 2-D array for horizontal advective flux
91 C fVerT :: 2 1/2D arrays for vertical advective flux
92 C localTij :: 2-D array, temporary local copy of tracer fld
93 C localTijk :: 3-D array, temporary local copy of tracer fld
94 C kp1Msk :: flag (0,1) for over-riding mask for W levels
95 C calc_fluxes_X :: logical to indicate to calculate fluxes in X dir
96 C calc_fluxes_Y :: logical to indicate to calculate fluxes in Y dir
97 C nipass :: number of passes in multi-dimensional method
98 C ipass :: number of the current pass being made
99 _RS maskUp (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
100 INTEGER iMin,iMax,jMin,jMax
101 INTEGER i,j,k,kup,kDown
102 _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
103 _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
104 _RL uTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
105 _RL vTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
106 _RL rTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
107 _RL rTransKp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
108 _RL af (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
109 _RL fVerT (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
110 _RL localTij(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
111 _RL localTijk(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
112 _RL kp1Msk
113 LOGICAL calc_fluxes_X,calc_fluxes_Y
114 INTEGER nipass,ipass
115 CEOP
116
117 #ifdef ALLOW_AUTODIFF_TAMC
118 act0 = tracerIdentity - 1
119 max0 = maxpass
120 act1 = bi - myBxLo(myThid)
121 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
122 act2 = bj - myByLo(myThid)
123 max2 = myByHi(myThid) - myByLo(myThid) + 1
124 act3 = myThid - 1
125 max3 = nTx*nTy
126 act4 = ikey_dynamics - 1
127 igadkey = (act0 + 1)
128 & + act1*max0
129 & + act2*max0*max1
130 & + act3*max0*max1*max2
131 & + act4*max0*max1*max2*max3
132 if (tracerIdentity.GT.maxpass) then
133 print *, 'ph-pass gad_advection ', maxpass, tracerIdentity
134 STOP 'maxpass seems smaller than tracerIdentity'
135 endif
136 #endif /* ALLOW_AUTODIFF_TAMC */
137
138 C-- Set up work arrays with valid (i.e. not NaN) values
139 C These inital values do not alter the numerical results. They
140 C just ensure that all memory references are to valid floating
141 C point numbers. This prevents spurious hardware signals due to
142 C uninitialised but inert locations.
143 DO j=1-OLy,sNy+OLy
144 DO i=1-OLx,sNx+OLx
145 xA(i,j) = 0. _d 0
146 yA(i,j) = 0. _d 0
147 uTrans(i,j) = 0. _d 0
148 vTrans(i,j) = 0. _d 0
149 rTrans(i,j) = 0. _d 0
150 fVerT(i,j,1) = 0. _d 0
151 fVerT(i,j,2) = 0. _d 0
152 rTransKp1(i,j)= 0. _d 0
153 ENDDO
154 ENDDO
155
156 iMin = 1-OLx
157 iMax = sNx+OLx
158 jMin = 1-OLy
159 jMax = sNy+OLy
160
161 C-- Start of k loop for horizontal fluxes
162 DO k=1,Nr
163 #ifdef ALLOW_AUTODIFF_TAMC
164 kkey = (igadkey-1)*Nr + k
165 CADJ STORE tracer(:,:,k,bi,bj) =
166 CADJ & comlev1_bibj_k_gad, key=kkey, byte=isbyte
167 #endif /* ALLOW_AUTODIFF_TAMC */
168
169 C-- Get temporary terms used by tendency routines
170 CALL CALC_COMMON_FACTORS (
171 I bi,bj,iMin,iMax,jMin,jMax,k,
172 O xA,yA,uTrans,vTrans,rTrans,maskUp,
173 I myThid)
174
175 #ifdef ALLOW_GMREDI
176 C-- Residual transp = Bolus transp + Eulerian transp
177 IF (useGMRedi)
178 & CALL GMREDI_CALC_UVFLOW(
179 & uTrans, vTrans, bi, bj, k, myThid)
180 #endif /* ALLOW_GMREDI */
181
182 C-- Make local copy of tracer array
183 DO j=1-OLy,sNy+OLy
184 DO i=1-OLx,sNx+OLx
185 localTij(i,j)=tracer(i,j,k,bi,bj)
186 ENDDO
187 ENDDO
188
189 IF (useCubedSphereExchange) THEN
190 nipass=3
191 #ifdef ALLOW_AUTODIFF_TAMC
192 if ( nipass.GT.maxcube )
193 & STOP 'maxcube needs to be = 3'
194 #endif
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) *maxcube
204 & + (igadkey-1)*maxcube*Nr
205 IF (nipass .GT. maxpass) THEN
206 STOP 'GAD_ADVECTION: nipass > maxcube. 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(:,:) =
256 CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
257 #endif
258 #endif /* ALLOW_AUTODIFF_TAMC */
259
260 IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
261 CALL GAD_FLUXLIMIT_ADV_X(
262 & bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
263 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
264 CALL GAD_DST3_ADV_X(
265 & bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
266 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
267 CALL GAD_DST3FL_ADV_X(
268 & bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
269 ELSE
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(:,:) =
323 CADJ & comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
324 #endif
325 #endif /* ALLOW_AUTODIFF_TAMC */
326
327 IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
328 CALL GAD_FLUXLIMIT_ADV_Y(
329 & bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)
330 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
331 CALL GAD_DST3_ADV_Y(
332 & bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)
333 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
334 CALL GAD_DST3FL_ADV_Y(
335 & bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)
336 ELSE
337 STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
338 ENDIF
339
340 DO j=1-Oly,sNy+Oly-1
341 DO i=1-Olx,sNx+Olx
342 localTij(i,j)=localTij(i,j)-deltaTtracer*
343 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
344 & *recip_rA(i,j,bi,bj)
345 & *( af(i,j+1)-af(i,j)
346 & -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
347 & )
348 ENDDO
349 ENDDO
350
351 #ifdef ALLOW_OBCS
352 C-- Apply open boundary conditions
353 IF (useOBCS) THEN
354 IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
355 CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
356 ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
357 CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
358 END IF
359 END IF
360 #endif /* ALLOW_OBCS */
361
362 C-- End of Y direction
363 ENDIF
364
365 C-- End of ipass loop
366 ENDDO
367
368 IF ( implicitAdvection ) THEN
369 C- explicit advection is done ; store tendency in gTracer:
370 DO j=1-Oly,sNy+Oly
371 DO i=1-Olx,sNx+Olx
372 gTracer(i,j,k,bi,bj)=
373 & (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer
374 ENDDO
375 ENDDO
376 ELSE
377 C- horizontal advection done; store intermediate result in 3D array:
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 ENDIF
384
385 C-- End of K loop for horizontal fluxes
386 ENDDO
387
388 IF ( .NOT.implicitAdvection ) THEN
389 C-- Start of k loop for vertical flux
390 DO k=Nr,1,-1
391 #ifdef ALLOW_AUTODIFF_TAMC
392 kkey = (igadkey-1)*Nr + k
393 #endif /* ALLOW_AUTODIFF_TAMC */
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 C-- Compute Vertical transport
403 #ifdef ALLOW_AIM
404 C- a hack to prevent Water-Vapor vert.transport into the stratospheric level Nr
405 IF ( k.EQ.1 .OR.
406 & (useAIM .AND. tracerIdentity.EQ.GAD_SALINITY .AND. k.EQ.Nr)
407 & ) THEN
408 #else
409 IF ( k.EQ.1 ) THEN
410 #endif
411
412 C- Surface interface :
413 DO j=1-Oly,sNy+Oly
414 DO i=1-Olx,sNx+Olx
415 rTransKp1(i,j) = kp1Msk*rTrans(i,j)
416 rTrans(i,j) = 0.
417 fVerT(i,j,kUp) = 0.
418 af(i,j) = 0.
419 ENDDO
420 ENDDO
421
422 ELSE
423 C- Interior interface :
424
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 #ifdef ALLOW_AUTODIFF_TAMC
442 CADJ STORE localTijk(:,:,k)
443 CADJ & = comlev1_bibj_k_gad, key=kkey, byte=isbyte
444 CADJ STORE rTrans(:,:)
445 CADJ & = comlev1_bibj_k_gad, key=kkey, byte=isbyte
446 #endif /* ALLOW_AUTODIFF_TAMC */
447
448 C- Compute vertical advective flux in the interior:
449 IF (vertAdvecScheme.EQ.ENUM_FLUX_LIMIT) THEN
450 CALL GAD_FLUXLIMIT_ADV_R(
451 & bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
452 ELSEIF (vertAdvecScheme.EQ.ENUM_DST3 ) THEN
453 CALL GAD_DST3_ADV_R(
454 & bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
455 ELSEIF (vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
456 CALL GAD_DST3FL_ADV_R(
457 & bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
458 ELSE
459 STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
460 ENDIF
461 C- add the advective flux to fVerT
462 DO j=1-Oly,sNy+Oly
463 DO i=1-Olx,sNx+Olx
464 fVerT(i,j,kUp) = af(i,j)
465 ENDDO
466 ENDDO
467
468 C- end Surface/Interior if bloc
469 ENDIF
470
471 #ifdef ALLOW_AUTODIFF_TAMC
472 CADJ STORE rTrans(:,:)
473 CADJ & = comlev1_bibj_k_gad, key=kkey, byte=isbyte
474 CADJ STORE rTranskp1(:,:)
475 CADJ & = comlev1_bibj_k_gad, key=kkey, byte=isbyte
476 #endif /* ALLOW_AUTODIFF_TAMC */
477
478 C-- Divergence of vertical fluxes
479 DO j=1-Oly,sNy+Oly
480 DO i=1-Olx,sNx+Olx
481 localTij(i,j)=localTijk(i,j,k)-deltaTtracer*
482 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
483 & *recip_rA(i,j,bi,bj)
484 & *( fVerT(i,j,kUp)-fVerT(i,j,kDown)
485 & -tracer(i,j,k,bi,bj)*(rTrans(i,j)-rTransKp1(i,j))
486 & )*rkFac
487 gTracer(i,j,k,bi,bj)=
488 & (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer
489 ENDDO
490 ENDDO
491
492 C-- End of K loop for vertical flux
493 ENDDO
494 C-- end of if not.implicitAdvection block
495 ENDIF
496
497 RETURN
498 END

  ViewVC Help
Powered by ViewVC 1.1.22