/[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.16 - (hide annotations) (download)
Tue Nov 25 23:31:44 2003 UTC (20 years, 6 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint52d_pre, checkpoint52e_pre, checkpoint52c_post, checkpoint52d_post, branch-netcdf
Branch point for: netcdf-sm0
Changes since 1.15: +21 -9 lines
o modified STOREs in GAD_ADVECTION
o corrected key comp. for passkey

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

  ViewVC Help
Powered by ViewVC 1.1.22