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

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

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


Revision 1.18 - (hide annotations) (download)
Wed Jan 7 21:35:00 2004 UTC (20 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint52l_pre, hrcube4, hrcube5, checkpoint52j_pre, checkpoint52l_post, checkpoint52k_post, checkpoint52f_post, checkpoint52i_pre, hrcube_1, hrcube_2, hrcube_3, checkpoint52e_post, checkpoint52f_pre, checkpoint52i_post, checkpoint52h_pre, checkpoint52j_post
Changes since 1.17: +76 -66 lines
rewrite (as in MultiDimAdvec) explicit tracer stepping (gad_calc_rhs.F)
 to work with implicit vertical advection and AB.

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

  ViewVC Help
Powered by ViewVC 1.1.22