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

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

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

revision 1.6 by heimbach, Thu Sep 27 20:12:11 2001 UTC revision 1.57 by jmc, Fri Feb 8 20:03:36 2008 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2  C $Name$  C $Name$
3    
 CBOI  
 C !TITLE: pkg/generic\_advdiff  
 C !AUTHORS: adcroft@mit.edu  
 C !INTRODUCTION:  
 C \section{Generica Advection Diffusion Package}  
 C  
 C Package "generic\_advdiff" provides a common set of routines for calculating  
 C advective/diffusive fluxes for tracers (cell centered quantities on a C-grid).  
 C  
 C Many different advection schemes are available: the standard centered  
 C second order, centered fourth order and upwind biased third order schemes  
 C are known as linear methods and require some stable time-stepping method  
 C such as Adams-Bashforth. Alternatives such as flux-limited schemes are  
 C stable in the forward sense and are best combined with the multi-dimensional  
 C method provided in gad\_advection.  
 C  
 C There are two high-level routines:  
 C  \begin{itemize}  
 C  \item{GAD\_CALC\_RHS} calculates all fluxes at time level "n" and is used  
 C  for the standard linear schemes. This must be used in conjuction with  
 C  Adams-Bashforth time-stepping. Diffusive and parameterized fluxes are  
 C  always calculated here.  
 C  \item{GAD\_ADVECTION} calculates just the advective fluxes using the  
 C  non-linear schemes and can not be used in conjuction with Adams-Bashforth  
 C  time-stepping.  
 C  \end{itemize}  
 CEOI  
   
4  #include "GAD_OPTIONS.h"  #include "GAD_OPTIONS.h"
5    #undef MULTIDIM_OLD_VERSION
6    
7    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
8  CBOP  CBOP
9  C !ROUTINE: GAD_ADVECTION  C !ROUTINE: GAD_ADVECTION
10    
11  C !INTERFACE: ==========================================================  C !INTERFACE: ==========================================================
12        SUBROUTINE GAD_ADVECTION(bi,bj,advectionScheme,tracerIdentity,        SUBROUTINE GAD_ADVECTION(
13       U                         Tracer,Gtracer,       I     implicitAdvection, advectionScheme, vertAdvecScheme,
14       I                         myTime,myIter,myThid)       I     tracerIdentity,
15         I     uVel, vVel, wVel, tracer,
16         O     gTracer,
17         I     bi,bj, myTime,myIter,myThid)
18    
19  C !DESCRIPTION:  C !DESCRIPTION:
20  C Calculates the tendancy of a tracer due to advection.  C Calculates the tendency of a tracer due to advection.
21  C It uses the multi-dimensional method given in \ref{sect:multiDimAdvection}  C It uses the multi-dimensional method given in \ref{sect:multiDimAdvection}
22  C and can only be used for the non-linear advection schemes such as the  C and can only be used for the non-linear advection schemes such as the
23  C direct-space-time method and flux-limiters.  C direct-space-time method and flux-limiters.
24  C  C
25  C The algorithm is as follows:  C The algorithm is as follows:
26  C \begin{itemize}  C \begin{itemize}
# Line 56  C      - \Delta t \partial_r (w\theta^{( Line 33  C      - \Delta t \partial_r (w\theta^{(
33  C \item{$G_\theta = ( \theta^{(n+3/3)} - \theta^{(n)} )/\Delta t$}  C \item{$G_\theta = ( \theta^{(n+3/3)} - \theta^{(n)} )/\Delta t$}
34  C \end{itemize}  C \end{itemize}
35  C  C
36  C The tendancy (output) is over-written by this routine.  C The tendency (output) is over-written by this routine.
37    
38  C !USES: ===============================================================  C !USES: ===============================================================
39        IMPLICIT NONE        IMPLICIT NONE
40  #include "SIZE.h"  #include "SIZE.h"
41  #include "EEPARAMS.h"  #include "EEPARAMS.h"
42  #include "PARAMS.h"  #include "PARAMS.h"
 #include "DYNVARS.h"  
43  #include "GRID.h"  #include "GRID.h"
44  #include "GAD.h"  #include "GAD.h"
45  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
46  # include "tamc.h"  # include "tamc.h"
47  # include "tamc_keys.h"  # include "tamc_keys.h"
48    # ifdef ALLOW_PTRACERS
49    #  include "PTRACERS_SIZE.h"
50    # endif
51  #endif  #endif
52    #ifdef ALLOW_EXCH2
53    #include "W2_EXCH2_TOPOLOGY.h"
54    #include "W2_EXCH2_PARAMS.h"
55    #endif /* ALLOW_EXCH2 */
56    
57  C !INPUT PARAMETERS: ===================================================  C !INPUT PARAMETERS: ===================================================
58  C  bi,bj                :: tile indices  C  implicitAdvection :: implicit vertical advection (later on)
59  C  advectionScheme      :: advection scheme to use  C  advectionScheme   :: advection scheme to use (Horizontal plane)
60  C  tracerIdentity       :: identifier for the tracer (required only for OBCS)  C  vertAdvecScheme   :: advection scheme to use (vertical direction)
61  C  Tracer               :: tracer field  C  tracerIdentity    :: tracer identifier (required only for OBCS)
62  C  myTime               :: current time  C  uVel              :: velocity, zonal component
63  C  myIter               :: iteration number  C  vVel              :: velocity, meridional component
64  C  myThid               :: thread number  C  wVel              :: velocity, vertical component
65        INTEGER bi,bj  C  tracer            :: tracer field
66        INTEGER advectionScheme  C  bi,bj             :: tile indices
67    C  myTime            :: current time
68    C  myIter            :: iteration number
69    C  myThid            :: thread number
70          LOGICAL implicitAdvection
71          INTEGER advectionScheme, vertAdvecScheme
72        INTEGER tracerIdentity        INTEGER tracerIdentity
73        _RL Gtracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)        _RL uVel  (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
74          _RL vVel  (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
75          _RL wVel  (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
76          _RL tracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
77          INTEGER bi,bj
78        _RL myTime        _RL myTime
79        INTEGER myIter        INTEGER myIter
80        INTEGER myThid        INTEGER myThid
81    
82  C !OUTPUT PARAMETERS: ==================================================  C !OUTPUT PARAMETERS: ==================================================
83  C  gTracer              :: tendancy array  C  gTracer           :: tendency array
84        _RL Tracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)        _RL gTracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
85    
86  C !LOCAL VARIABLES: ====================================================  C !LOCAL VARIABLES: ====================================================
87  C  maskUp               :: 2-D array for mask at W points  C  maskUp        :: 2-D array for mask at W points
88  C  iMin,iMax,jMin,jMax  :: loop range for called routines  C  maskLocW      :: 2-D array for mask at West points
89  C  i,j,k                :: loop indices  C  maskLocS      :: 2-D array for mask at South points
90  C  kup                  :: index into 2 1/2D array, toggles between 1 and 2  C [iMin,iMax]Upd :: loop range to update tracer field
91  C  kdown                :: index into 2 1/2D array, toggles between 2 and 1  C [jMin,jMax]Upd :: loop range to update tracer field
92  C  kp1                  :: =k+1 for k<Nr, =Nr for k=Nr  C  i,j,k         :: loop indices
93  C  xA,yA                :: areas of X and Y face of tracer cells  C  kUp           :: index into 2 1/2D array, toggles between 1 and 2
94  C  uTrans,vTrans,rTrans :: 2-D arrays of volume transports at U,V and W points  C  kDown         :: index into 2 1/2D array, toggles between 2 and 1
95  C  af                   :: 2-D array for horizontal advective flux  C  kp1           :: =k+1 for k<Nr, =Nr for k=Nr
96  C  fVerT                :: 2 1/2D arrays for vertical advective flux  C  xA,yA         :: areas of X and Y face of tracer cells
97  C  localTij             :: 2-D array used as temporary local copy of tracer fld  C  uFld,vFld     :: 2-D local copy of horizontal velocity, U,V components
98  C  localTijk            :: 3-D array used as temporary local copy of tracer fld  C  wFld          :: 2-D local copy of vertical velocity
99  C  kp1Msk               :: flag (0,1) to act as over-riding mask for W levels  C  uTrans,vTrans :: 2-D arrays of volume transports at U,V points
100  C  calc_fluxes_X        :: logical to indicate to calculate fluxes in X dir  C  rTrans        :: 2-D arrays of volume transports at W points
101  C  calc_fluxes_Y        :: logical to indicate to calculate fluxes in Y dir  C  rTransKp1     :: vertical volume transport at interface k+1
102  C  nipass               :: number of passes to make in multi-dimensional method  C  af            :: 2-D array for horizontal advective flux
103  C  ipass                :: number of the current pass being made  C  afx           :: 2-D array for horizontal advective flux, x direction
104        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  C  afy           :: 2-D array for horizontal advective flux, y direction
105        INTEGER iMin,iMax,jMin,jMax  C  fVerT         :: 2 1/2D arrays for vertical advective flux
106        INTEGER i,j,k,kup,kDown,kp1  C  localTij      :: 2-D array, temporary local copy of tracer fld
107    C  localTijk     :: 3-D array, temporary local copy of tracer fld
108    C  kp1Msk        :: flag (0,1) for over-riding mask for W levels
109    C  calc_fluxes_X :: logical to indicate to calculate fluxes in X dir
110    C  calc_fluxes_Y :: logical to indicate to calculate fluxes in Y dir
111    C  interiorOnly  :: only update the interior of myTile, but not the edges
112    C  overlapOnly   :: only update the edges of myTile, but not the interior
113    C  npass         :: number of passes in multi-dimensional method
114    C  ipass         :: number of the current pass being made
115    C  myTile        :: variables used to determine which cube face
116    C  nCFace        :: owns a tile for cube grid runs using
117    C                :: multi-dim advection.
118    C [N,S,E,W]_edge :: true if N,S,E,W edge of myTile is an Edge of the cube
119    c     _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
120          _RS maskLocW(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
121          _RS maskLocS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
122          INTEGER iMinUpd,iMaxUpd,jMinUpd,jMaxUpd
123          INTEGER i,j,k,kUp,kDown
124        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
125        _RS yA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS yA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
126          _RL uFld    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
127          _RL vFld    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
128          _RL wFld    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
129        _RL uTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
130        _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
131        _RL rTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
132          _RL rTransKp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
133        _RL af      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL af      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
134          _RL afx     (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
135          _RL afy     (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
136        _RL fVerT   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerT   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
137        _RL localTij(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL localTij(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
138        _RL localTijk(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL localTijk(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
139        _RL kp1Msk        _RL kp1Msk
140        LOGICAL calc_fluxes_X,calc_fluxes_Y        LOGICAL calc_fluxes_X, calc_fluxes_Y, withSigns
141        INTEGER nipass,ipass        LOGICAL interiorOnly, overlapOnly
142          INTEGER npass, ipass
143          INTEGER nCFace
144          LOGICAL N_edge, S_edge, E_edge, W_edge
145    #ifdef ALLOW_EXCH2
146          INTEGER myTile
147    #endif
148    #ifdef ALLOW_DIAGNOSTICS
149          CHARACTER*8 diagName
150          CHARACTER*4 diagSufx
151          LOGICAL     doDiagAdvX, doDiagAdvY, doDiagAdvR
152    C-    Functions:
153          CHARACTER*4 GAD_DIAG_SUFX
154          EXTERNAL    GAD_DIAG_SUFX
155          LOGICAL  DIAGNOSTICS_IS_ON
156          EXTERNAL DIAGNOSTICS_IS_ON
157    #endif
158  CEOP  CEOP
159    
160  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
161              act0 = tracerIdentity
162              max0 = maxpass
163            act1 = bi - myBxLo(myThid)            act1 = bi - myBxLo(myThid)
164            max1 = myBxHi(myThid) - myBxLo(myThid) + 1            max1 = myBxHi(myThid) - myBxLo(myThid) + 1
165            act2 = bj - myByLo(myThid)            act2 = bj - myByLo(myThid)
# Line 134  CEOP Line 167  CEOP
167            act3 = myThid - 1            act3 = myThid - 1
168            max3 = nTx*nTy            max3 = nTx*nTy
169            act4 = ikey_dynamics - 1            act4 = ikey_dynamics - 1
170            ikey = (act1 + 1) + act2*max1            igadkey = act0
171       &                      + act3*max1*max2       &                      + act1*max0
172       &                      + act4*max1*max2*max3       &                      + act2*max0*max1
173         &                      + act3*max0*max1*max2
174         &                      + act4*max0*max1*max2*max3
175              IF (tracerIdentity.GT.maxpass) THEN
176                 print *, 'ph-pass gad_advection ', maxpass, tracerIdentity
177                 STOP 'maxpass seems smaller than tracerIdentity'
178              ENDIF
179  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
180    
181    #ifdef ALLOW_DIAGNOSTICS
182    C--   Set diagnostics flags and suffix for the current tracer
183          doDiagAdvX = .FALSE.
184          doDiagAdvY = .FALSE.
185          doDiagAdvR = .FALSE.
186          IF ( useDiagnostics ) THEN
187            diagSufx = GAD_DIAG_SUFX( tracerIdentity, myThid )
188            diagName = 'ADVx'//diagSufx
189            doDiagAdvX = DIAGNOSTICS_IS_ON( diagName, myThid )
190            diagName = 'ADVy'//diagSufx
191            doDiagAdvY = DIAGNOSTICS_IS_ON( diagName, myThid )
192            diagName = 'ADVr'//diagSufx
193            doDiagAdvR = DIAGNOSTICS_IS_ON( diagName, myThid )
194          ENDIF
195    #endif
196    
197  C--   Set up work arrays with valid (i.e. not NaN) values  C--   Set up work arrays with valid (i.e. not NaN) values
198  C     These inital values do not alter the numerical results. They  C     These inital values do not alter the numerical results. They
199  C     just ensure that all memory references are to valid floating  C     just ensure that all memory references are to valid floating
# Line 153  C     uninitialised but inert locations. Line 208  C     uninitialised but inert locations.
208          rTrans(i,j)  = 0. _d 0          rTrans(i,j)  = 0. _d 0
209          fVerT(i,j,1) = 0. _d 0          fVerT(i,j,1) = 0. _d 0
210          fVerT(i,j,2) = 0. _d 0          fVerT(i,j,2) = 0. _d 0
211            rTransKp1(i,j)= 0. _d 0
212    #ifdef ALLOW_AUTODIFF_TAMC
213            localTij(i,j) = 0. _d 0
214            wfld(i,j)    = 0. _d 0
215    #endif
216         ENDDO         ENDDO
217        ENDDO        ENDDO
218    
219        iMin = 1-OLx  C--   Set tile-specific parameters for horizontal fluxes
220        iMax = sNx+OLx        IF (useCubedSphereExchange) THEN
221        jMin = 1-OLy         npass  = 3
222        jMax = sNy+OLy  #ifdef ALLOW_AUTODIFF_TAMC
223           IF ( npass.GT.maxcube ) STOP 'maxcube needs to be = 3'
224    #endif
225    #ifdef ALLOW_EXCH2
226           myTile = W2_myTileList(bi)
227           nCFace = exch2_myFace(myTile)
228           N_edge = exch2_isNedge(myTile).EQ.1
229           S_edge = exch2_isSedge(myTile).EQ.1
230           E_edge = exch2_isEedge(myTile).EQ.1
231           W_edge = exch2_isWedge(myTile).EQ.1
232    #else
233           nCFace = bi
234           N_edge = .TRUE.
235           S_edge = .TRUE.
236           E_edge = .TRUE.
237           W_edge = .TRUE.
238    #endif
239          ELSE
240           npass  = 2
241           nCFace = 0
242           N_edge = .FALSE.
243           S_edge = .FALSE.
244           E_edge = .FALSE.
245           W_edge = .FALSE.
246          ENDIF
247    
248  C--   Start of k loop for horizontal fluxes  C--   Start of k loop for horizontal fluxes
249        DO k=1,Nr        DO k=1,Nr
250  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
251           kkey = (ikey-1)*Nr + k           kkey = (igadkey-1)*Nr + k
252  CADJ STORE tracer(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte  CADJ STORE tracer(:,:,k,bi,bj) =
253    CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
254  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
255    
256  C--   Get temporary terms used by tendency routines  C--   Get temporary terms used by tendency routines
257        CALL CALC_COMMON_FACTORS (        CALL CALC_COMMON_FACTORS (
258       I         bi,bj,iMin,iMax,jMin,jMax,k,       I         uVel, vVel,
259       O         xA,yA,uTrans,vTrans,rTrans,maskUp,       O         uFld, vFld, uTrans, vTrans, xA, yA,
260       I         myThid)       I         k,bi,bj, myThid )
261    
262    #ifdef ALLOW_GMREDI
263    C--   Residual transp = Bolus transp + Eulerian transp
264          IF (useGMRedi)
265         &   CALL GMREDI_CALC_UVFLOW(
266         U                  uFld, vFld, uTrans, vTrans,
267         I                  k, bi, bj, myThid )
268    #endif /* ALLOW_GMREDI */
269    
270  C--   Make local copy of tracer array  C--   Make local copy of tracer array and mask West & South
271        DO j=1-OLy,sNy+OLy        DO j=1-OLy,sNy+OLy
272         DO i=1-OLx,sNx+OLx         DO i=1-OLx,sNx+OLx
273          localTij(i,j)=tracer(i,j,k,bi,bj)           localTij(i,j)=tracer(i,j,k,bi,bj)
274             maskLocW(i,j)=_maskW(i,j,k,bi,bj)
275             maskLocS(i,j)=_maskS(i,j,k,bi,bj)
276         ENDDO         ENDDO
277        ENDDO        ENDDO
278    
279    cph-exch2#ifndef ALLOW_AUTODIFF_TAMC
280        IF (useCubedSphereExchange) THEN        IF (useCubedSphereExchange) THEN
281         nipass=3          withSigns = .FALSE.
282        ELSE          CALL FILL_CS_CORNER_UV_RS(
283         nipass=1       &            withSigns, maskLocW,maskLocS, bi,bj, myThid )
284        ENDIF        ENDIF
285  cph       nipass=1  cph-exch2#endif
286    
287  C--   Multiple passes for different directions on different tiles  C--   Multiple passes for different directions on different tiles
288        DO ipass=1,nipass  C--   For cube need one pass for each of red, green and blue axes.
289          DO ipass=1,npass
290  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
291           passkey = ipass + (k-1)   *maxpass           passkey = ipass
292       &                   + (ikey-1)*maxpass*Nr       &                   + (k-1)      *maxpass
293           IF (nipass .GT. maxpass) THEN       &                   + (igadkey-1)*maxpass*Nr
294            STOP 'GAD_ADVECTION: nipass > maxpass. check tamc.h'           IF (npass .GT. maxpass) THEN
295              STOP 'GAD_ADVECTION: npass > maxcube. check tamc.h'
296           ENDIF           ENDIF
297  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
298    
299        IF (nipass.EQ.3) THEN        interiorOnly = .FALSE.
300         calc_fluxes_X=.FALSE.        overlapOnly  = .FALSE.
301         calc_fluxes_Y=.FALSE.        IF (useCubedSphereExchange) THEN
302         IF (ipass.EQ.1 .AND. (bi.EQ.1 .OR. bi.EQ.2) ) THEN  #ifdef MULTIDIM_OLD_VERSION
303          calc_fluxes_X=.TRUE.  C-    CubedSphere : pass 3 times, with full update of local tracer field
304         ELSEIF (ipass.EQ.1 .AND. (bi.EQ.4 .OR. bi.EQ.5) ) THEN         IF (ipass.EQ.1) THEN
305          calc_fluxes_Y=.TRUE.          calc_fluxes_X = nCFace.EQ.1 .OR. nCFace.EQ.2
306         ELSEIF (ipass.EQ.2 .AND. (bi.EQ.1 .OR. bi.EQ.6) ) THEN          calc_fluxes_Y = nCFace.EQ.4 .OR. nCFace.EQ.5
307          calc_fluxes_Y=.TRUE.         ELSEIF (ipass.EQ.2) THEN
308         ELSEIF (ipass.EQ.2 .AND. (bi.EQ.3 .OR. bi.EQ.4) ) THEN          calc_fluxes_X = nCFace.EQ.3 .OR. nCFace.EQ.4
309          calc_fluxes_X=.TRUE.          calc_fluxes_Y = nCFace.EQ.6 .OR. nCFace.EQ.1
310         ELSEIF (ipass.EQ.3 .AND. (bi.EQ.2 .OR. bi.EQ.3) ) THEN  #else /* MULTIDIM_OLD_VERSION */
311          calc_fluxes_Y=.TRUE.  C-    CubedSphere : pass 3 times, with partial update of local tracer field
312         ELSEIF (ipass.EQ.3 .AND. (bi.EQ.5 .OR. bi.EQ.6) ) THEN         IF (ipass.EQ.1) THEN
313          calc_fluxes_X=.TRUE.          overlapOnly  = MOD(nCFace,3).EQ.0
314            interiorOnly = MOD(nCFace,3).NE.0
315            calc_fluxes_X = nCFace.EQ.6 .OR. nCFace.EQ.1 .OR. nCFace.EQ.2
316            calc_fluxes_Y = nCFace.EQ.3 .OR. nCFace.EQ.4 .OR. nCFace.EQ.5
317           ELSEIF (ipass.EQ.2) THEN
318            overlapOnly  = MOD(nCFace,3).EQ.2
319            interiorOnly = MOD(nCFace,3).EQ.1
320            calc_fluxes_X = nCFace.EQ.2 .OR. nCFace.EQ.3 .OR. nCFace.EQ.4
321            calc_fluxes_Y = nCFace.EQ.5 .OR. nCFace.EQ.6 .OR. nCFace.EQ.1
322    #endif /* MULTIDIM_OLD_VERSION */
323           ELSE
324            interiorOnly = .TRUE.
325            calc_fluxes_X = nCFace.EQ.5 .OR. nCFace.EQ.6
326            calc_fluxes_Y = nCFace.EQ.2 .OR. nCFace.EQ.3
327         ENDIF         ENDIF
328        ELSE        ELSE
329         calc_fluxes_X=.TRUE.  C-    not CubedSphere
330         calc_fluxes_Y=.TRUE.          calc_fluxes_X = MOD(ipass,2).EQ.1
331            calc_fluxes_Y = .NOT.calc_fluxes_X
332        ENDIF        ENDIF
   
 C--   X direction  
       IF (calc_fluxes_X) THEN  
333    
334  C--   Internal exchange for calculations in X  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
335        IF (useCubedSphereExchange) THEN  C--   X direction
336         DO j=1,Oly  C-     Advective flux in X
337          DO i=1,Olx          DO j=1-Oly,sNy+Oly
338           localTij( 1-i , 1-j )=localTij( 1-j ,    i    )           DO i=1-Olx,sNx+Olx
339           localTij( 1-i ,sNy+j)=localTij( 1-j , sNy+1-i )            af(i,j) = 0.
340           localTij(sNx+i, 1-j )=localTij(sNx+j,    i    )           ENDDO
          localTij(sNx+i,sNy+j)=localTij(sNx+j, sNy+1-i )  
341          ENDDO          ENDDO
342         ENDDO  C
343        ENDIF  #ifdef ALLOW_AUTODIFF_TAMC
344    # ifndef DISABLE_MULTIDIM_ADVECTION
345    CADJ STORE localTij(:,:)  =
346    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
347    CADJ STORE af(:,:)  =
348    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
349    # endif
350    #endif /* ALLOW_AUTODIFF_TAMC */
351    C
352          IF (calc_fluxes_X) THEN
353    
354  C-    Advective flux in X  C-     Do not compute fluxes if
355        DO j=1-Oly,sNy+Oly  C       a) needed in overlap only
356         DO i=1-Olx,sNx+Olx  C   and b) the overlap of myTile are not cube-face Edges
357          af(i,j) = 0.         IF ( .NOT.overlapOnly .OR. N_edge .OR. S_edge ) THEN
358         ENDDO  
359        ENDDO  C-     Internal exchange for calculations in X
360    #ifdef MULTIDIM_OLD_VERSION
361            IF ( useCubedSphereExchange ) THEN
362    #else
363            IF ( overlapOnly ) THEN
364    #endif
365             CALL FILL_CS_CORNER_TR_RL( .TRUE., .FALSE.,
366         &                              localTij, bi,bj, myThid )
367            ENDIF
368    
369  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
370  #ifdef ALLOW_MULTIDIM_ADVECTION  # ifndef DISABLE_MULTIDIM_ADVECTION
371  CADJ STORE localTij(:,:)  = comlev1_bibj_pass, key=passkey, byte=isbyte  CADJ STORE localTij(:,:)  =
372  #endif  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
373    # endif
374  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
375    
376        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN          IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
377         CALL GAD_FLUXLIMIT_ADV_X(       &     .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
378       &      bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)            CALL GAD_DST2U1_ADV_X( bi,bj,k, advectionScheme, .TRUE.,
379        ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN       I                           dTtracerLev(k),uTrans,uFld,localTij,
380         CALL GAD_DST3_ADV_X(       O                           af, myThid )
381       &       bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)          ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
382        ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN            CALL GAD_FLUXLIMIT_ADV_X( bi,bj,k, .TRUE., dTtracerLev(k),
383         CALL GAD_DST3FL_ADV_X(       I                              uTrans, uFld, maskLocW, localTij,
384       &       bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)       O                              af, myThid )
385        ELSE          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
386         STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'            CALL GAD_DST3_ADV_X(      bi,bj,k, .TRUE., dTtracerLev(k),
387        ENDIF       I                              uTrans, uFld, maskLocW, localTij,
388         O                              af, myThid )
389            ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
390              CALL GAD_DST3FL_ADV_X(    bi,bj,k, .TRUE., dTtracerLev(k),
391         I                              uTrans, uFld, maskLocW, localTij,
392         O                              af, myThid )
393    #ifndef ALLOW_AUTODIFF_TAMC
394            ELSEIF (advectionScheme.EQ.ENUM_OS7MP ) THEN
395              CALL GAD_OS7MP_ADV_X(     bi,bj,k, .TRUE., dTtracerLev(k),
396         I                              uTrans, uFld, maskLocW, localTij,
397         O                              af, myThid )
398    #endif
399            ELSE
400             STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'
401            ENDIF
402    
403    C-     Internal exchange for next calculations in Y
404            IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
405             CALL FILL_CS_CORNER_TR_RL( .FALSE., .FALSE.,
406         &                              localTij, bi,bj, myThid )
407            ENDIF
408    
409        DO j=1-Oly,sNy+Oly  C-     Advective flux in X : done
410         DO i=1-Olx,sNx+Olx-1         ENDIF
411          localTij(i,j)=localTij(i,j)-deltaTtracer*  
412       &    _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)  C-     Update the local tracer field where needed:
413       &    *recip_rA(i,j,bi,bj)  
414       &    *( af(i+1,j)-af(i,j)  C      update in overlap-Only
415       &      -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))         IF ( overlapOnly ) THEN
416       &     )          iMinUpd = 1-Olx+1
417         ENDDO          iMaxUpd = sNx+Olx-1
418        ENDDO  C- notes: these 2 lines below have no real effect (because recip_hFac=0
419    C         in corner region) but safer to keep them.
420            IF ( W_edge ) iMinUpd = 1
421            IF ( E_edge ) iMaxUpd = sNx
422    
423            IF ( S_edge ) THEN
424             DO j=1-Oly,0
425              DO i=iMinUpd,iMaxUpd
426               localTij(i,j) = localTij(i,j)
427         &      -dTtracerLev(k)*recip_rhoFacC(k)
428         &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
429         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
430         &       *( af(i+1,j)-af(i,j)
431         &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
432         &        )
433              ENDDO
434             ENDDO
435            ENDIF
436            IF ( N_edge ) THEN
437             DO j=sNy+1,sNy+Oly
438              DO i=iMinUpd,iMaxUpd
439               localTij(i,j) = localTij(i,j)
440         &      -dTtracerLev(k)*recip_rhoFacC(k)
441         &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
442         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
443         &       *( af(i+1,j)-af(i,j)
444         &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
445         &        )
446              ENDDO
447             ENDDO
448            ENDIF
449    
450           ELSE
451    C      do not only update the overlap
452            jMinUpd = 1-Oly
453            jMaxUpd = sNy+Oly
454            IF ( interiorOnly .AND. S_edge ) jMinUpd = 1
455            IF ( interiorOnly .AND. N_edge ) jMaxUpd = sNy
456            DO j=jMinUpd,jMaxUpd
457             DO i=1-Olx+1,sNx+Olx-1
458               localTij(i,j) = localTij(i,j)
459         &      -dTtracerLev(k)*recip_rhoFacC(k)
460         &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
461         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
462         &       *( af(i+1,j)-af(i,j)
463         &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
464         &        )
465             ENDDO
466            ENDDO
467    C-      keep advective flux (for diagnostics)
468            DO j=1-Oly,sNy+Oly
469             DO i=1-Olx,sNx+Olx
470              afx(i,j) = af(i,j)
471             ENDDO
472            ENDDO
473    
474  #ifdef ALLOW_OBCS  #ifdef ALLOW_OBCS
475  C--   Apply open boundary conditions  C-     Apply open boundary conditions
476        IF (useOBCS) THEN          IF ( useOBCS ) THEN
477         IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN           IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
478          CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
479         ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
480          CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
481         END IF  #ifdef ALLOW_PTRACERS
482        END IF           ELSEIF (tracerIdentity.GE.GAD_TR1) THEN
483              CALL OBCS_APPLY_PTRACER( bi, bj, k,
484         &         tracerIdentity-GAD_TR1+1, localTij, myThid )
485    #endif /* ALLOW_PTRACERS */
486             ENDIF
487            ENDIF
488  #endif /* ALLOW_OBCS */  #endif /* ALLOW_OBCS */
489    
490    C-     end if/else update overlap-Only
491           ENDIF
492    
493  C--   End of X direction  C--   End of X direction
494        ENDIF        ENDIF
495    
496    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
497  C--   Y direction  C--   Y direction
498    cph-test
499    C-     Advective flux in Y
500            DO j=1-Oly,sNy+Oly
501             DO i=1-Olx,sNx+Olx
502              af(i,j) = 0.
503             ENDDO
504            ENDDO
505    C
506    #ifdef ALLOW_AUTODIFF_TAMC
507    # ifndef DISABLE_MULTIDIM_ADVECTION
508    CADJ STORE localTij(:,:)  =
509    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
510    CADJ STORE af(:,:)  =
511    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
512    # endif
513    #endif /* ALLOW_AUTODIFF_TAMC */
514    C
515        IF (calc_fluxes_Y) THEN        IF (calc_fluxes_Y) THEN
516    
517  C--   Internal exchange for calculations in Y  C-     Do not compute fluxes if
518        IF (useCubedSphereExchange) THEN  C       a) needed in overlap only
519         DO j=1,Oly  C   and b) the overlap of myTile are not cube-face edges
520          DO i=1,Olx         IF ( .NOT.overlapOnly .OR. E_edge .OR. W_edge ) THEN
521           localTij( 1-i , 1-j )=localTij(   j   , 1-i )  
522           localTij( 1-i ,sNy+j)=localTij(   j   ,sNy+i)  C-     Internal exchange for calculations in Y
523           localTij(sNx+i, 1-j )=localTij(sNx+1-j, 1-i )  #ifdef MULTIDIM_OLD_VERSION
524           localTij(sNx+i,sNy+j)=localTij(sNx+1-j,sNy+i)          IF ( useCubedSphereExchange ) THEN
525    #else
526            IF ( overlapOnly ) THEN
527    #endif
528             CALL FILL_CS_CORNER_TR_RL( .FALSE., .FALSE.,
529         &                              localTij, bi,bj, myThid )
530            ENDIF
531    
532    C-     Advective flux in Y
533            DO j=1-Oly,sNy+Oly
534             DO i=1-Olx,sNx+Olx
535              af(i,j) = 0.
536             ENDDO
537          ENDDO          ENDDO
        ENDDO  
       ENDIF  
   
 C-    Advective flux in Y  
       DO j=1-Oly,sNy+Oly  
        DO i=1-Olx,sNx+Olx  
         af(i,j) = 0.  
        ENDDO  
       ENDDO  
538    
539  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
540  #ifdef ALLOW_MULTIDIM_ADVECTION  #ifndef DISABLE_MULTIDIM_ADVECTION
541  CADJ STORE localTij(:,:)  = comlev1_bibj_pass, key=passkey, byte=isbyte  CADJ STORE localTij(:,:)  =
542    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
543  #endif  #endif
544  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
545    
546        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN          IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
547         CALL GAD_FLUXLIMIT_ADV_Y(       &     .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
548       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)            CALL GAD_DST2U1_ADV_Y( bi,bj,k, advectionScheme, .TRUE.,
549        ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN       I                           dTtracerLev(k),vTrans,vFld,localTij,
550         CALL GAD_DST3_ADV_Y(       O                           af, myThid )
551       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)          ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
552        ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN            CALL GAD_FLUXLIMIT_ADV_Y( bi,bj,k, .TRUE., dTtracerLev(k),
553         CALL GAD_DST3FL_ADV_Y(       I                              vTrans, vFld, maskLocS, localTij,
554       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)       O                              af, myThid )
555        ELSE          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
556         STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'            CALL GAD_DST3_ADV_Y(      bi,bj,k, .TRUE., dTtracerLev(k),
557        ENDIF       I                              vTrans, vFld, maskLocS, localTij,
558         O                              af, myThid )
559            ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
560              CALL GAD_DST3FL_ADV_Y(    bi,bj,k, .TRUE., dTtracerLev(k),
561         I                              vTrans, vFld, maskLocS, localTij,
562         O                              af, myThid )
563    #ifndef ALLOW_AUTODIFF_TAMC
564            ELSEIF (advectionScheme.EQ.ENUM_OS7MP ) THEN
565              CALL GAD_OS7MP_ADV_Y(     bi,bj,k, .TRUE., dTtracerLev(k),
566         I                              vTrans, vFld, maskLocS, localTij,
567         O                              af, myThid )
568    #endif
569            ELSE
570             STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
571            ENDIF
572    
573    C-     Internal exchange for next calculations in X
574            IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
575             CALL FILL_CS_CORNER_TR_RL( .TRUE., .FALSE.,
576         &                              localTij, bi,bj, myThid )
577            ENDIF
578    
579        DO j=1-Oly,sNy+Oly-1  C-     Advective flux in Y : done
580         DO i=1-Olx,sNx+Olx         ENDIF
581          localTij(i,j)=localTij(i,j)-deltaTtracer*  
582       &    _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)  C-     Update the local tracer field where needed:
583       &    *recip_rA(i,j,bi,bj)  
584       &    *( af(i,j+1)-af(i,j)  C      update in overlap-Only
585       &      -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))         IF ( overlapOnly ) THEN
586       &     )          jMinUpd = 1-Oly+1
587         ENDDO          jMaxUpd = sNy+Oly-1
588        ENDDO  C- notes: these 2 lines below have no real effect (because recip_hFac=0
589    C         in corner region) but safer to keep them.
590            IF ( S_edge ) jMinUpd = 1
591            IF ( N_edge ) jMaxUpd = sNy
592    
593            IF ( W_edge ) THEN
594             DO j=jMinUpd,jMaxUpd
595              DO i=1-Olx,0
596               localTij(i,j) = localTij(i,j)
597         &      -dTtracerLev(k)*recip_rhoFacC(k)
598         &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
599         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
600         &       *( af(i,j+1)-af(i,j)
601         &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
602         &        )
603              ENDDO
604             ENDDO
605            ENDIF
606            IF ( E_edge ) THEN
607             DO j=jMinUpd,jMaxUpd
608              DO i=sNx+1,sNx+Olx
609               localTij(i,j) = localTij(i,j)
610         &      -dTtracerLev(k)*recip_rhoFacC(k)
611         &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
612         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
613         &       *( af(i,j+1)-af(i,j)
614         &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
615         &        )
616              ENDDO
617             ENDDO
618            ENDIF
619    
620           ELSE
621    C      do not only update the overlap
622            iMinUpd = 1-Olx
623            iMaxUpd = sNx+Olx
624            IF ( interiorOnly .AND. W_edge ) iMinUpd = 1
625            IF ( interiorOnly .AND. E_edge ) iMaxUpd = sNx
626            DO j=1-Oly+1,sNy+Oly-1
627             DO i=iMinUpd,iMaxUpd
628               localTij(i,j) = localTij(i,j)
629         &      -dTtracerLev(k)*recip_rhoFacC(k)
630         &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
631         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
632         &       *( af(i,j+1)-af(i,j)
633         &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
634         &        )
635             ENDDO
636            ENDDO
637    C-      keep advective flux (for diagnostics)
638            DO j=1-Oly,sNy+Oly
639             DO i=1-Olx,sNx+Olx
640              afy(i,j) = af(i,j)
641             ENDDO
642            ENDDO
643    
644  #ifdef ALLOW_OBCS  #ifdef ALLOW_OBCS
645  C--   Apply open boundary conditions  C-     Apply open boundary conditions
646        IF (useOBCS) THEN          IF (useOBCS) THEN
647         IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN           IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
648          CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
649         ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
650          CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
651         END IF  #ifdef ALLOW_PTRACERS
652        END IF           ELSEIF (tracerIdentity.GE.GAD_TR1) THEN
653              CALL OBCS_APPLY_PTRACER( bi, bj, k,
654         &         tracerIdentity-GAD_TR1+1, localTij, myThid )
655    #endif /* ALLOW_PTRACERS */
656             ENDIF
657            ENDIF
658  #endif /* ALLOW_OBCS */  #endif /* ALLOW_OBCS */
659    
660    C      end if/else update overlap-Only
661           ENDIF
662    
663  C--   End of Y direction  C--   End of Y direction
664        ENDIF        ENDIF
665    
       DO j=1-Oly,sNy+Oly  
        DO i=1-Olx,sNx+Olx  
         localTijk(i,j,k)=localTij(i,j)  
        ENDDO  
       ENDDO  
   
666  C--   End of ipass loop  C--   End of ipass loop
667        ENDDO        ENDDO
668    
669          IF ( implicitAdvection ) THEN
670    C-    explicit advection is done ; store tendency in gTracer:
671            DO j=1-Oly,sNy+Oly
672             DO i=1-Olx,sNx+Olx
673              gTracer(i,j,k,bi,bj)=
674         &     (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)
675             ENDDO
676            ENDDO
677          ELSE
678    C-    horizontal advection done; store intermediate result in 3D array:
679            DO j=1-Oly,sNy+Oly
680             DO i=1-Olx,sNx+Olx
681              localTijk(i,j,k)=localTij(i,j)
682             ENDDO
683            ENDDO
684          ENDIF
685    
686    #ifdef ALLOW_DIAGNOSTICS
687            IF ( doDiagAdvX ) THEN
688              diagName = 'ADVx'//diagSufx
689              CALL DIAGNOSTICS_FILL(afx,diagName, k,1, 2,bi,bj, myThid)
690            ENDIF
691            IF ( doDiagAdvY ) THEN
692              diagName = 'ADVy'//diagSufx
693              CALL DIAGNOSTICS_FILL(afy,diagName, k,1, 2,bi,bj, myThid)
694            ENDIF
695    #endif
696    
697    #ifdef ALLOW_DEBUG
698          IF ( debugLevel .GE. debLevB
699         &   .AND. tracerIdentity.EQ.GAD_TEMPERATURE
700         &   .AND. k.LE.3 .AND. myIter.EQ.1+nIter0
701         &   .AND. nPx.EQ.1 .AND. nPy.EQ.1
702         &   .AND. useCubedSphereExchange ) THEN
703            CALL DEBUG_CS_CORNER_UV( ' afx,afy from GAD_ADVECTION',
704         &             afx,afy, k, standardMessageUnit,bi,bj,myThid )
705          ENDIF
706    #endif /* ALLOW_DEBUG */
707    
708  C--   End of K loop for horizontal fluxes  C--   End of K loop for horizontal fluxes
709        ENDDO        ENDDO
710    
711    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
712    
713          IF ( .NOT.implicitAdvection ) THEN
714  C--   Start of k loop for vertical flux  C--   Start of k loop for vertical flux
715        DO k=Nr,1,-1         DO k=Nr,1,-1
716  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
717           kkey = (ikey-1)*Nr + k           kkey = (igadkey-1)*Nr + (Nr-k+1)
718  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
719    C--   kUp    Cycles through 1,2 to point to w-layer above
 C--   kup    Cycles through 1,2 to point to w-layer above  
720  C--   kDown  Cycles through 2,1 to point to w-layer below  C--   kDown  Cycles through 2,1 to point to w-layer below
721        kup  = 1+MOD(k+1,2)          kUp  = 1+MOD(k+1,2)
722        kDown= 1+MOD(k,2)          kDown= 1+MOD(k,2)
723    c       kp1=min(Nr,k+1)
724            kp1Msk=1.
725            if (k.EQ.Nr) kp1Msk=0.
726    
727  C--   Get temporary terms used by tendency routines  #ifdef ALLOW_AUTODIFF_TAMC
728        CALL CALC_COMMON_FACTORS (  CADJ STORE rtrans(:,:)  =
729       I         bi,bj,iMin,iMax,jMin,jMax,k,  CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
730       O         xA,yA,uTrans,vTrans,rTrans,maskUp,  cphCADJ STORE wfld(:,:)  =
731       I         myThid)  cphCADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
732    #endif
 C-    Advective flux in R  
       DO j=1-Oly,sNy+Oly  
        DO i=1-Olx,sNx+Olx  
         af(i,j) = 0.  
        ENDDO  
       ENDDO  
733    
734  #ifdef ALLOW_AUTODIFF_TAMC  C-- Compute Vertical transport
735  CADJ STORE localTijk(:,:,k)    #ifdef ALLOW_AIM
736  CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte  C- a hack to prevent Water-Vapor vert.transport into the stratospheric level Nr
737            IF ( k.EQ.1 .OR.
738         &     (useAIM .AND. tracerIdentity.EQ.GAD_SALINITY .AND. k.EQ.Nr)
739         &              ) THEN
740    #else
741            IF ( k.EQ.1 ) THEN
742    #endif
743    
744    #ifdef ALLOW_AUTODIFF_TAMC
745    cphmultiCADJ STORE wfld(:,:)  =
746    cphmultiCADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
747    #endif /* ALLOW_AUTODIFF_TAMC */
748    
749    C- Surface interface :
750             DO j=1-Oly,sNy+Oly
751              DO i=1-Olx,sNx+Olx
752               rTransKp1(i,j) = kp1Msk*rTrans(i,j)
753               wFld(i,j)   = 0.
754               rTrans(i,j) = 0.
755               fVerT(i,j,kUp) = 0.
756              ENDDO
757             ENDDO
758    
759            ELSE
760    
761    #ifdef ALLOW_AUTODIFF_TAMC
762    cphmultiCADJ STORE wfld(:,:)  =
763    cphmultiCADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
764    #endif /* ALLOW_AUTODIFF_TAMC */
765    
766    C- Interior interface :
767             DO j=1-Oly,sNy+Oly
768              DO i=1-Olx,sNx+Olx
769               rTransKp1(i,j) = kp1Msk*rTrans(i,j)
770               wFld(i,j)   = wVel(i,j,k,bi,bj)
771               rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)
772         &                 *deepFac2F(k)*rhoFacF(k)
773         &                 *maskC(i,j,k-1,bi,bj)
774               fVerT(i,j,kUp) = 0.
775              ENDDO
776             ENDDO
777    
778    #ifdef ALLOW_GMREDI
779    C--   Residual transp = Bolus transp + Eulerian transp
780             IF (useGMRedi)
781         &     CALL GMREDI_CALC_WFLOW(
782         U                 wFld, rTrans,
783         I                 k, bi, bj, myThid )
784    #endif /* ALLOW_GMREDI */
785    
786    #ifdef ALLOW_AUTODIFF_TAMC
787    cphmultiCADJ STORE localTijk(:,:,k)
788    cphmultiCADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
789    cphmultiCADJ STORE rTrans(:,:)
790    cphmultiCADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
791  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
792    
 C     Note: wVel needs to be masked  
       IF (K.GE.2) THEN  
793  C-    Compute vertical advective flux in the interior:  C-    Compute vertical advective flux in the interior:
794         IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN           IF ( vertAdvecScheme.EQ.ENUM_UPWIND_1RST
795          CALL GAD_FLUXLIMIT_ADV_R(       &      .OR. vertAdvecScheme.EQ.ENUM_DST2 ) THEN
796       &       bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)             CALL GAD_DST2U1_ADV_R( bi,bj,k, advectionScheme,
797         ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN       I                            dTtracerLev(k),rTrans,wFld,localTijk,
798          CALL GAD_DST3_ADV_R(       O                            fVerT(1-Olx,1-Oly,kUp), myThid )
799       &       bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)           ELSEIF( vertAdvecScheme.EQ.ENUM_FLUX_LIMIT) THEN
800         ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN             CALL GAD_FLUXLIMIT_ADV_R( bi,bj,k, dTtracerLev(k),
801          CALL GAD_DST3FL_ADV_R(       I                               rTrans, wFld, localTijk,
802       &       bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)       O                               fVerT(1-Olx,1-Oly,kUp), myThid )
803         ELSE           ELSEIF( vertAdvecScheme.EQ.ENUM_DST3 ) THEN
804          STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'             CALL GAD_DST3_ADV_R(      bi,bj,k, dTtracerLev(k),
805         ENDIF       I                               rTrans, wFld, localTijk,
806  C-    Surface "correction" term at k>1 :       O                               fVerT(1-Olx,1-Oly,kUp), myThid )
807         DO j=1-Oly,sNy+Oly           ELSEIF( vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
808          DO i=1-Olx,sNx+Olx             CALL GAD_DST3FL_ADV_R(    bi,bj,k, dTtracerLev(k),
809           af(i,j) = af(i,j)       I                               rTrans, wFld, localTijk,
810       &           + (maskC(i,j,k,bi,bj)-maskC(i,j,k-1,bi,bj))*       O                               fVerT(1-Olx,1-Oly,kUp), myThid )
811       &             rTrans(i,j)*localTijk(i,j,k)  #ifndef ALLOW_AUTODIFF_TAMC
812          ENDDO           ELSEIF (vertAdvecScheme.EQ.ENUM_OS7MP ) THEN
813         ENDDO             CALL GAD_OS7MP_ADV_R(     bi,bj,k, dTtracerLev(k),
814        ELSE       I                               rTrans, wFld, localTijk,
815  C-    Surface "correction" term at k=1 :       O                               fVerT(1-Olx,1-Oly,kUp), myThid )
816         DO j=1-Oly,sNy+Oly  #endif
817          DO i=1-Olx,sNx+Olx           ELSE
818           af(i,j) = rTrans(i,j)*localTijk(i,j,k)            STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
819             ENDIF
820    
821    C- end Surface/Interior if bloc
822            ENDIF
823    
824    #ifdef ALLOW_AUTODIFF_TAMC
825    cphmultiCADJ STORE rTrans(:,:)
826    cphmultiCADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
827    cphmultiCADJ STORE rTranskp1(:,:)
828    cphmultiCADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
829    cph --- following storing of fVerT is critical for correct
830    cph --- gradient with multiDimAdvection
831    cph --- Without it, kDown component is not properly recomputed
832    cph --- This is a TAF bug (and no warning available)
833    CADJ STORE fVerT(:,:,:)
834    CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
835    #endif /* ALLOW_AUTODIFF_TAMC */
836    
837    C--   Divergence of vertical fluxes
838            DO j=1-Oly,sNy+Oly
839             DO i=1-Olx,sNx+Olx
840              localTij(i,j) = localTijk(i,j,k)
841         &      -dTtracerLev(k)*recip_rhoFacC(k)
842         &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
843         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
844         &       *( fVerT(i,j,kDown)-fVerT(i,j,kUp)
845         &         -tracer(i,j,k,bi,bj)*(rTransKp1(i,j)-rTrans(i,j))
846         &        )*rkSign
847              gTracer(i,j,k,bi,bj)=
848         &     (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)
849             ENDDO
850          ENDDO          ENDDO
        ENDDO  
       ENDIF  
 C-    add the advective flux to fVerT  
       DO j=1-Oly,sNy+Oly  
        DO i=1-Olx,sNx+Olx  
         fVerT(i,j,kUp) = af(i,j)  
        ENDDO  
       ENDDO  
851    
852  C--   Divergence of fluxes  #ifdef ALLOW_DIAGNOSTICS
853        kp1=min(Nr,k+1)          IF ( doDiagAdvR ) THEN
854        kp1Msk=1.            diagName = 'ADVr'//diagSufx
855        if (k.EQ.Nr) kp1Msk=0.            CALL DIAGNOSTICS_FILL( fVerT(1-Olx,1-Oly,kUp),
856        DO j=1-Oly,sNy+Oly       &                           diagName, k,1, 2,bi,bj, myThid)
857         DO i=1-Olx,sNx+Olx          ENDIF
858          localTij(i,j)=localTijk(i,j,k)-deltaTtracer*  #endif
859       &    _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)  
      &    *recip_rA(i,j,bi,bj)  
      &    *( fVerT(i,j,kUp)-fVerT(i,j,kDown)  
      &      -tracer(i,j,k,bi,bj)*rA(i,j,bi,bj)*  
      &        (wVel(i,j,k,bi,bj)-kp1Msk*wVel(i,j,kp1,bi,bj))  
      &     )*rkFac  
         gTracer(i,j,k,bi,bj)=  
      &   (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer  
        ENDDO  
       ENDDO  
   
860  C--   End of K loop for vertical flux  C--   End of K loop for vertical flux
861        ENDDO         ENDDO
862    C--   end of if not.implicitAdvection block
863          ENDIF
864    
865        RETURN        RETURN
866        END        END

Legend:
Removed from v.1.6  
changed lines
  Added in v.1.57

  ViewVC Help
Powered by ViewVC 1.1.22