/[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.20 - (hide annotations) (download)
Sun Mar 28 19:28:34 2004 UTC (20 years, 3 months ago) by edhill
Branch: MAIN
Changes since 1.19: +1 -28 lines
 o add '*.tex' files to the list used to generate the API documentation
   - add examples of the above to generic_advdiff and mnc
 o temporarily remove eesupp from dir_list since the formatting of
    the comments in those files needs much work

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

  ViewVC Help
Powered by ViewVC 1.1.22