/[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.9 by adcroft, Mon Mar 4 17:26:41 2002 UTC revision 1.55 by jmc, Thu Feb 7 23:59:02 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: Generic 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 55  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 Tracer(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 gTracer(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 GAD_DIAG_SUFX, diagSufx
151          EXTERNAL    GAD_DIAG_SUFX
152    #endif
153  CEOP  CEOP
154    
155  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
156              act0 = tracerIdentity
157              max0 = maxpass
158            act1 = bi - myBxLo(myThid)            act1 = bi - myBxLo(myThid)
159            max1 = myBxHi(myThid) - myBxLo(myThid) + 1            max1 = myBxHi(myThid) - myBxLo(myThid) + 1
160            act2 = bj - myByLo(myThid)            act2 = bj - myByLo(myThid)
# Line 133  CEOP Line 162  CEOP
162            act3 = myThid - 1            act3 = myThid - 1
163            max3 = nTx*nTy            max3 = nTx*nTy
164            act4 = ikey_dynamics - 1            act4 = ikey_dynamics - 1
165            ikey = (act1 + 1) + act2*max1            igadkey = act0
166       &                      + act3*max1*max2       &                      + act1*max0
167       &                      + act4*max1*max2*max3       &                      + act2*max0*max1
168         &                      + act3*max0*max1*max2
169         &                      + act4*max0*max1*max2*max3
170              if (tracerIdentity.GT.maxpass) then
171                 print *, 'ph-pass gad_advection ', maxpass, tracerIdentity
172                 STOP 'maxpass seems smaller than tracerIdentity'
173              endif
174  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
175    
176    #ifdef ALLOW_DIAGNOSTICS
177    C--   Set diagnostic suffix for the current tracer
178          IF ( useDiagnostics ) THEN
179            diagSufx = GAD_DIAG_SUFX( tracerIdentity, myThid )
180          ENDIF
181    #endif
182    
183  C--   Set up work arrays with valid (i.e. not NaN) values  C--   Set up work arrays with valid (i.e. not NaN) values
184  C     These inital values do not alter the numerical results. They  C     These inital values do not alter the numerical results. They
185  C     just ensure that all memory references are to valid floating  C     just ensure that all memory references are to valid floating
# Line 152  C     uninitialised but inert locations. Line 194  C     uninitialised but inert locations.
194          rTrans(i,j)  = 0. _d 0          rTrans(i,j)  = 0. _d 0
195          fVerT(i,j,1) = 0. _d 0          fVerT(i,j,1) = 0. _d 0
196          fVerT(i,j,2) = 0. _d 0          fVerT(i,j,2) = 0. _d 0
197            rTransKp1(i,j)= 0. _d 0
198    #ifdef ALLOW_AUTODIFF_TAMC
199            localTij(i,j) = 0. _d 0
200            wfld(i,j)    = 0. _d 0
201    #endif
202         ENDDO         ENDDO
203        ENDDO        ENDDO
204    
205        iMin = 1-OLx  C--   Set tile-specific parameters for horizontal fluxes
206        iMax = sNx+OLx        IF (useCubedSphereExchange) THEN
207        jMin = 1-OLy         npass  = 3
208        jMax = sNy+OLy  #ifdef ALLOW_AUTODIFF_TAMC
209           IF ( npass.GT.maxcube ) STOP 'maxcube needs to be = 3'
210    #endif
211    #ifdef ALLOW_EXCH2
212           myTile = W2_myTileList(bi)
213           nCFace = exch2_myFace(myTile)
214           N_edge = exch2_isNedge(myTile).EQ.1
215           S_edge = exch2_isSedge(myTile).EQ.1
216           E_edge = exch2_isEedge(myTile).EQ.1
217           W_edge = exch2_isWedge(myTile).EQ.1
218    #else
219           nCFace = bi
220           N_edge = .TRUE.
221           S_edge = .TRUE.
222           E_edge = .TRUE.
223           W_edge = .TRUE.
224    #endif
225          ELSE
226           npass  = 2
227           nCFace = 0
228           N_edge = .FALSE.
229           S_edge = .FALSE.
230           E_edge = .FALSE.
231           W_edge = .FALSE.
232          ENDIF
233    
234  C--   Start of k loop for horizontal fluxes  C--   Start of k loop for horizontal fluxes
235        DO k=1,Nr        DO k=1,Nr
236  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
237           kkey = (ikey-1)*Nr + k           kkey = (igadkey-1)*Nr + k
238  CADJ STORE tracer(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte  CADJ STORE tracer(:,:,k,bi,bj) =
239    CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
240  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
241    
242  C--   Get temporary terms used by tendency routines  C--   Get temporary terms used by tendency routines
243        CALL CALC_COMMON_FACTORS (        CALL CALC_COMMON_FACTORS (
244       I         bi,bj,iMin,iMax,jMin,jMax,k,       I         uVel, vVel,
245       O         xA,yA,uTrans,vTrans,rTrans,maskUp,       O         uFld, vFld, uTrans, vTrans, xA, yA,
246       I         myThid)       I         k,bi,bj, myThid )
247    
248    #ifdef ALLOW_GMREDI
249    C--   Residual transp = Bolus transp + Eulerian transp
250          IF (useGMRedi)
251         &   CALL GMREDI_CALC_UVFLOW(
252         U                  uFld, vFld, uTrans, vTrans,
253         I                  k, bi, bj, myThid )
254    #endif /* ALLOW_GMREDI */
255    
256  C--   Make local copy of tracer array  C--   Make local copy of tracer array and mask West & South
257        DO j=1-OLy,sNy+OLy        DO j=1-OLy,sNy+OLy
258         DO i=1-OLx,sNx+OLx         DO i=1-OLx,sNx+OLx
259          localTij(i,j)=tracer(i,j,k,bi,bj)           localTij(i,j)=tracer(i,j,k,bi,bj)
260             maskLocW(i,j)=_maskW(i,j,k,bi,bj)
261             maskLocS(i,j)=_maskS(i,j,k,bi,bj)
262         ENDDO         ENDDO
263        ENDDO        ENDDO
264    
265    cph-exch2#ifndef ALLOW_AUTODIFF_TAMC
266        IF (useCubedSphereExchange) THEN        IF (useCubedSphereExchange) THEN
267         nipass=3          withSigns = .FALSE.
268        ELSE          CALL FILL_CS_CORNER_UV_RS(
269         nipass=1       &            withSigns, maskLocW,maskLocS, bi,bj, myThid )
270        ENDIF        ENDIF
271  cph       nipass=1  cph-exch2#endif
272    
273  C--   Multiple passes for different directions on different tiles  C--   Multiple passes for different directions on different tiles
274        DO ipass=1,nipass  C--   For cube need one pass for each of red, green and blue axes.
275          DO ipass=1,npass
276  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
277           passkey = ipass + (k-1)   *maxpass           passkey = ipass
278       &                   + (ikey-1)*maxpass*Nr       &                   + (k-1)      *maxpass
279           IF (nipass .GT. maxpass) THEN       &                   + (igadkey-1)*maxpass*Nr
280            STOP 'GAD_ADVECTION: nipass > maxpass. check tamc.h'           IF (npass .GT. maxpass) THEN
281              STOP 'GAD_ADVECTION: npass > maxcube. check tamc.h'
282           ENDIF           ENDIF
283  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
284    
285        IF (nipass.EQ.3) THEN        interiorOnly = .FALSE.
286         calc_fluxes_X=.FALSE.        overlapOnly  = .FALSE.
287         calc_fluxes_Y=.FALSE.        IF (useCubedSphereExchange) THEN
288         IF (ipass.EQ.1 .AND. (bi.EQ.1 .OR. bi.EQ.2) ) THEN  #ifdef MULTIDIM_OLD_VERSION
289          calc_fluxes_X=.TRUE.  C-    CubedSphere : pass 3 times, with full update of local tracer field
290         ELSEIF (ipass.EQ.1 .AND. (bi.EQ.4 .OR. bi.EQ.5) ) THEN         IF (ipass.EQ.1) THEN
291          calc_fluxes_Y=.TRUE.          calc_fluxes_X = nCFace.EQ.1 .OR. nCFace.EQ.2
292         ELSEIF (ipass.EQ.2 .AND. (bi.EQ.1 .OR. bi.EQ.6) ) THEN          calc_fluxes_Y = nCFace.EQ.4 .OR. nCFace.EQ.5
293          calc_fluxes_Y=.TRUE.         ELSEIF (ipass.EQ.2) THEN
294         ELSEIF (ipass.EQ.2 .AND. (bi.EQ.3 .OR. bi.EQ.4) ) THEN          calc_fluxes_X = nCFace.EQ.3 .OR. nCFace.EQ.4
295          calc_fluxes_X=.TRUE.          calc_fluxes_Y = nCFace.EQ.6 .OR. nCFace.EQ.1
296         ELSEIF (ipass.EQ.3 .AND. (bi.EQ.2 .OR. bi.EQ.3) ) THEN  #else /* MULTIDIM_OLD_VERSION */
297          calc_fluxes_Y=.TRUE.  C-    CubedSphere : pass 3 times, with partial update of local tracer field
298         ELSEIF (ipass.EQ.3 .AND. (bi.EQ.5 .OR. bi.EQ.6) ) THEN         IF (ipass.EQ.1) THEN
299          calc_fluxes_X=.TRUE.          overlapOnly  = MOD(nCFace,3).EQ.0
300            interiorOnly = MOD(nCFace,3).NE.0
301            calc_fluxes_X = nCFace.EQ.6 .OR. nCFace.EQ.1 .OR. nCFace.EQ.2
302            calc_fluxes_Y = nCFace.EQ.3 .OR. nCFace.EQ.4 .OR. nCFace.EQ.5
303           ELSEIF (ipass.EQ.2) THEN
304            overlapOnly  = MOD(nCFace,3).EQ.2
305            interiorOnly = MOD(nCFace,3).EQ.1
306            calc_fluxes_X = nCFace.EQ.2 .OR. nCFace.EQ.3 .OR. nCFace.EQ.4
307            calc_fluxes_Y = nCFace.EQ.5 .OR. nCFace.EQ.6 .OR. nCFace.EQ.1
308    #endif /* MULTIDIM_OLD_VERSION */
309           ELSE
310            interiorOnly = .TRUE.
311            calc_fluxes_X = nCFace.EQ.5 .OR. nCFace.EQ.6
312            calc_fluxes_Y = nCFace.EQ.2 .OR. nCFace.EQ.3
313         ENDIF         ENDIF
314        ELSE        ELSE
315         calc_fluxes_X=.TRUE.  C-    not CubedSphere
316         calc_fluxes_Y=.TRUE.          calc_fluxes_X = MOD(ipass,2).EQ.1
317            calc_fluxes_Y = .NOT.calc_fluxes_X
318        ENDIF        ENDIF
   
 C--   X direction  
       IF (calc_fluxes_X) THEN  
319    
320  C--   Internal exchange for calculations in X  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
321        IF (useCubedSphereExchange) THEN  C--   X direction
322         DO j=1,Oly  C-     Advective flux in X
323          DO i=1,Olx          DO j=1-Oly,sNy+Oly
324           localTij( 1-i , 1-j )=localTij( 1-j ,    i    )           DO i=1-Olx,sNx+Olx
325           localTij( 1-i ,sNy+j)=localTij( 1-j , sNy+1-i )            af(i,j) = 0.
326           localTij(sNx+i, 1-j )=localTij(sNx+j,    i    )           ENDDO
          localTij(sNx+i,sNy+j)=localTij(sNx+j, sNy+1-i )  
327          ENDDO          ENDDO
328         ENDDO  C
329        ENDIF  #ifdef ALLOW_AUTODIFF_TAMC
330    # ifndef DISABLE_MULTIDIM_ADVECTION
331    CADJ STORE localTij(:,:)  =
332    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
333    CADJ STORE af(:,:)  =
334    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
335    # endif
336    #endif /* ALLOW_AUTODIFF_TAMC */
337    C
338          IF (calc_fluxes_X) THEN
339    
340  C-    Advective flux in X  C-     Do not compute fluxes if
341        DO j=1-Oly,sNy+Oly  C       a) needed in overlap only
342         DO i=1-Olx,sNx+Olx  C   and b) the overlap of myTile are not cube-face Edges
343          af(i,j) = 0.         IF ( .NOT.overlapOnly .OR. N_edge .OR. S_edge ) THEN
344         ENDDO  
345        ENDDO  C-     Internal exchange for calculations in X
346    #ifdef MULTIDIM_OLD_VERSION
347            IF ( useCubedSphereExchange ) THEN
348    #else
349            IF ( overlapOnly ) THEN
350    #endif
351             CALL FILL_CS_CORNER_TR_RL( .TRUE., .FALSE.,
352         &                              localTij, bi,bj, myThid )
353            ENDIF
354    
355  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
356  #ifndef DISABLE_MULTIDIM_ADVECTION  # ifndef DISABLE_MULTIDIM_ADVECTION
357  CADJ STORE localTij(:,:)  = comlev1_bibj_pass, key=passkey, byte=isbyte  CADJ STORE localTij(:,:)  =
358  #endif  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
359    # endif
360  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
361    
362        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN          IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
363         CALL GAD_FLUXLIMIT_ADV_X(       &     .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
364       &      bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)            CALL GAD_DST2U1_ADV_X( bi,bj,k, advectionScheme, .TRUE.,
365        ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN       I                           dTtracerLev(k),uTrans,uFld,localTij,
366         CALL GAD_DST3_ADV_X(       O                           af, myThid )
367       &       bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)          ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
368        ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN            CALL GAD_FLUXLIMIT_ADV_X( bi,bj,k, .TRUE., dTtracerLev(k),
369         CALL GAD_DST3FL_ADV_X(       I                              uTrans, uFld, maskLocW, localTij,
370       &       bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)       O                              af, myThid )
371        ELSE          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
372         write(0,*) advectionScheme            CALL GAD_DST3_ADV_X(      bi,bj,k, .TRUE., dTtracerLev(k),
373         STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'       I                              uTrans, uFld, maskLocW, localTij,
374        ENDIF       O                              af, myThid )
375            ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
376              CALL GAD_DST3FL_ADV_X(    bi,bj,k, .TRUE., dTtracerLev(k),
377         I                              uTrans, uFld, maskLocW, localTij,
378         O                              af, myThid )
379    #ifndef ALLOW_AUTODIFF_TAMC
380            ELSEIF (advectionScheme.EQ.ENUM_OS7MP ) THEN
381              CALL GAD_OS7MP_ADV_X(     bi,bj,k, .TRUE., dTtracerLev(k),
382         I                              uTrans, uFld, maskLocW, localTij,
383         O                              af, myThid )
384    #endif
385            ELSE
386             STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'
387            ENDIF
388    
389    C-     Internal exchange for next calculations in Y
390            IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
391             CALL FILL_CS_CORNER_TR_RL( .FALSE., .FALSE.,
392         &                              localTij, bi,bj, myThid )
393            ENDIF
394    
395        DO j=1-Oly,sNy+Oly  C-     Advective flux in X : done
396         DO i=1-Olx,sNx+Olx-1         ENDIF
397          localTij(i,j)=localTij(i,j)-deltaTtracer*  
398       &    _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)  C-     Update the local tracer field where needed:
399       &    *recip_rA(i,j,bi,bj)  
400       &    *( af(i+1,j)-af(i,j)  C      update in overlap-Only
401       &      -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))         IF ( overlapOnly ) THEN
402       &     )          iMinUpd = 1-Olx+1
403         ENDDO          iMaxUpd = sNx+Olx-1
404        ENDDO  C- notes: these 2 lines below have no real effect (because recip_hFac=0
405    C         in corner region) but safer to keep them.
406            IF ( W_edge ) iMinUpd = 1
407            IF ( E_edge ) iMaxUpd = sNx
408    
409            IF ( S_edge ) THEN
410             DO j=1-Oly,0
411              DO i=iMinUpd,iMaxUpd
412               localTij(i,j) = localTij(i,j)
413         &      -dTtracerLev(k)*recip_rhoFacC(k)
414         &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
415         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
416         &       *( af(i+1,j)-af(i,j)
417         &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
418         &        )
419              ENDDO
420             ENDDO
421            ENDIF
422            IF ( N_edge ) THEN
423             DO j=sNy+1,sNy+Oly
424              DO i=iMinUpd,iMaxUpd
425               localTij(i,j) = localTij(i,j)
426         &      -dTtracerLev(k)*recip_rhoFacC(k)
427         &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
428         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
429         &       *( af(i+1,j)-af(i,j)
430         &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
431         &        )
432              ENDDO
433             ENDDO
434            ENDIF
435    
436           ELSE
437    C      do not only update the overlap
438            jMinUpd = 1-Oly
439            jMaxUpd = sNy+Oly
440            IF ( interiorOnly .AND. S_edge ) jMinUpd = 1
441            IF ( interiorOnly .AND. N_edge ) jMaxUpd = sNy
442            DO j=jMinUpd,jMaxUpd
443             DO i=1-Olx+1,sNx+Olx-1
444               localTij(i,j) = localTij(i,j)
445         &      -dTtracerLev(k)*recip_rhoFacC(k)
446         &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
447         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
448         &       *( af(i+1,j)-af(i,j)
449         &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
450         &        )
451             ENDDO
452            ENDDO
453    C-      keep advective flux (for diagnostics)
454            DO j=1-Oly,sNy+Oly
455             DO i=1-Olx,sNx+Olx
456              afx(i,j) = af(i,j)
457             ENDDO
458            ENDDO
459    
460  #ifdef ALLOW_OBCS  #ifdef ALLOW_OBCS
461  C--   Apply open boundary conditions  C-     Apply open boundary conditions
462        IF (useOBCS) THEN          IF ( useOBCS ) THEN
463         IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN           IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
464          CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
465         ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
466          CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
467         END IF  #ifdef ALLOW_PTRACERS
468        END IF           ELSEIF (tracerIdentity.GE.GAD_TR1) THEN
469              CALL OBCS_APPLY_PTRACER( bi, bj, k,
470         &         tracerIdentity-GAD_TR1+1, localTij, myThid )
471    #endif /* ALLOW_PTRACERS */
472             ENDIF
473            ENDIF
474  #endif /* ALLOW_OBCS */  #endif /* ALLOW_OBCS */
475    
476    C-     end if/else update overlap-Only
477           ENDIF
478    
479  C--   End of X direction  C--   End of X direction
480        ENDIF        ENDIF
481    
482    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
483  C--   Y direction  C--   Y direction
484    cph-test
485    C-     Advective flux in Y
486            DO j=1-Oly,sNy+Oly
487             DO i=1-Olx,sNx+Olx
488              af(i,j) = 0.
489             ENDDO
490            ENDDO
491    C
492    #ifdef ALLOW_AUTODIFF_TAMC
493    # ifndef DISABLE_MULTIDIM_ADVECTION
494    CADJ STORE localTij(:,:)  =
495    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
496    CADJ STORE af(:,:)  =
497    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
498    # endif
499    #endif /* ALLOW_AUTODIFF_TAMC */
500    C
501        IF (calc_fluxes_Y) THEN        IF (calc_fluxes_Y) THEN
502    
503  C--   Internal exchange for calculations in Y  C-     Do not compute fluxes if
504        IF (useCubedSphereExchange) THEN  C       a) needed in overlap only
505         DO j=1,Oly  C   and b) the overlap of myTile are not cube-face edges
506          DO i=1,Olx         IF ( .NOT.overlapOnly .OR. E_edge .OR. W_edge ) THEN
507           localTij( 1-i , 1-j )=localTij(   j   , 1-i )  
508           localTij( 1-i ,sNy+j)=localTij(   j   ,sNy+i)  C-     Internal exchange for calculations in Y
509           localTij(sNx+i, 1-j )=localTij(sNx+1-j, 1-i )  #ifdef MULTIDIM_OLD_VERSION
510           localTij(sNx+i,sNy+j)=localTij(sNx+1-j,sNy+i)          IF ( useCubedSphereExchange ) THEN
511    #else
512            IF ( overlapOnly ) THEN
513    #endif
514             CALL FILL_CS_CORNER_TR_RL( .FALSE., .FALSE.,
515         &                              localTij, bi,bj, myThid )
516            ENDIF
517    
518    C-     Advective flux in Y
519            DO j=1-Oly,sNy+Oly
520             DO i=1-Olx,sNx+Olx
521              af(i,j) = 0.
522             ENDDO
523          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  
524    
525  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
526  #ifndef DISABLE_MULTIDIM_ADVECTION  #ifndef DISABLE_MULTIDIM_ADVECTION
527  CADJ STORE localTij(:,:)  = comlev1_bibj_pass, key=passkey, byte=isbyte  CADJ STORE localTij(:,:)  =
528    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
529  #endif  #endif
530  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
531    
532        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN          IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
533         CALL GAD_FLUXLIMIT_ADV_Y(       &     .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
534       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)            CALL GAD_DST2U1_ADV_Y( bi,bj,k, advectionScheme, .TRUE.,
535        ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN       I                           dTtracerLev(k),vTrans,vFld,localTij,
536         CALL GAD_DST3_ADV_Y(       O                           af, myThid )
537       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)          ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
538        ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN            CALL GAD_FLUXLIMIT_ADV_Y( bi,bj,k, .TRUE., dTtracerLev(k),
539         CALL GAD_DST3FL_ADV_Y(       I                              vTrans, vFld, maskLocS, localTij,
540       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)       O                              af, myThid )
541        ELSE          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
542         STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'            CALL GAD_DST3_ADV_Y(      bi,bj,k, .TRUE., dTtracerLev(k),
543        ENDIF       I                              vTrans, vFld, maskLocS, localTij,
544         O                              af, myThid )
545            ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
546              CALL GAD_DST3FL_ADV_Y(    bi,bj,k, .TRUE., dTtracerLev(k),
547         I                              vTrans, vFld, maskLocS, localTij,
548         O                              af, myThid )
549    #ifndef ALLOW_AUTODIFF_TAMC
550            ELSEIF (advectionScheme.EQ.ENUM_OS7MP ) THEN
551              CALL GAD_OS7MP_ADV_Y(     bi,bj,k, .TRUE., dTtracerLev(k),
552         I                              vTrans, vFld, maskLocS, localTij,
553         O                              af, myThid )
554    #endif
555            ELSE
556             STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
557            ENDIF
558    
559    C-     Internal exchange for next calculations in X
560           IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
561             CALL FILL_CS_CORNER_TR_RL( .TRUE., .FALSE.,
562         &                              localTij, bi,bj, myThid )
563           ENDIF
564    
565        DO j=1-Oly,sNy+Oly-1  C-     Advective flux in Y : done
566         DO i=1-Olx,sNx+Olx         ENDIF
567          localTij(i,j)=localTij(i,j)-deltaTtracer*  
568       &    _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)  C-     Update the local tracer field where needed:
569       &    *recip_rA(i,j,bi,bj)  
570       &    *( af(i,j+1)-af(i,j)  C      update in overlap-Only
571       &      -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))         IF ( overlapOnly ) THEN
572       &     )          jMinUpd = 1-Oly+1
573         ENDDO          jMaxUpd = sNy+Oly-1
574        ENDDO  C- notes: these 2 lines below have no real effect (because recip_hFac=0
575    C         in corner region) but safer to keep them.
576            IF ( S_edge ) jMinUpd = 1
577            IF ( N_edge ) jMaxUpd = sNy
578    
579            IF ( W_edge ) THEN
580             DO j=jMinUpd,jMaxUpd
581              DO i=1-Olx,0
582               localTij(i,j) = localTij(i,j)
583         &      -dTtracerLev(k)*recip_rhoFacC(k)
584         &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
585         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
586         &       *( af(i,j+1)-af(i,j)
587         &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
588         &        )
589              ENDDO
590             ENDDO
591            ENDIF
592            IF ( E_edge ) THEN
593             DO j=jMinUpd,jMaxUpd
594              DO i=sNx+1,sNx+Olx
595               localTij(i,j) = localTij(i,j)
596         &      -dTtracerLev(k)*recip_rhoFacC(k)
597         &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
598         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
599         &       *( af(i,j+1)-af(i,j)
600         &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
601         &        )
602              ENDDO
603             ENDDO
604            ENDIF
605    
606           ELSE
607    C      do not only update the overlap
608            iMinUpd = 1-Olx
609            iMaxUpd = sNx+Olx
610            IF ( interiorOnly .AND. W_edge ) iMinUpd = 1
611            IF ( interiorOnly .AND. E_edge ) iMaxUpd = sNx
612            DO j=1-Oly+1,sNy+Oly-1
613             DO i=iMinUpd,iMaxUpd
614               localTij(i,j) = localTij(i,j)
615         &      -dTtracerLev(k)*recip_rhoFacC(k)
616         &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
617         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
618         &       *( af(i,j+1)-af(i,j)
619         &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
620         &        )
621             ENDDO
622            ENDDO
623    C-      keep advective flux (for diagnostics)
624            DO j=1-Oly,sNy+Oly
625             DO i=1-Olx,sNx+Olx
626              afy(i,j) = af(i,j)
627             ENDDO
628            ENDDO
629    
630  #ifdef ALLOW_OBCS  #ifdef ALLOW_OBCS
631  C--   Apply open boundary conditions  C-     Apply open boundary conditions
632        IF (useOBCS) THEN          IF (useOBCS) THEN
633         IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN           IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
634          CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
635         ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
636          CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
637         END IF  #ifdef ALLOW_PTRACERS
638        END IF           ELSEIF (tracerIdentity.GE.GAD_TR1) THEN
639              CALL OBCS_APPLY_PTRACER( bi, bj, k,
640         &         tracerIdentity-GAD_TR1+1, localTij, myThid )
641    #endif /* ALLOW_PTRACERS */
642             ENDIF
643            ENDIF
644  #endif /* ALLOW_OBCS */  #endif /* ALLOW_OBCS */
645    
646    C      end if/else update overlap-Only
647           ENDIF
648    
649  C--   End of Y direction  C--   End of Y direction
650        ENDIF        ENDIF
651    
       DO j=1-Oly,sNy+Oly  
        DO i=1-Olx,sNx+Olx  
         localTijk(i,j,k)=localTij(i,j)  
        ENDDO  
       ENDDO  
   
652  C--   End of ipass loop  C--   End of ipass loop
653        ENDDO        ENDDO
654    
655          IF ( implicitAdvection ) THEN
656    C-    explicit advection is done ; store tendency in gTracer:
657            DO j=1-Oly,sNy+Oly
658             DO i=1-Olx,sNx+Olx
659              gTracer(i,j,k,bi,bj)=
660         &     (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)
661             ENDDO
662            ENDDO
663          ELSE
664    C-    horizontal advection done; store intermediate result in 3D array:
665            DO j=1-Oly,sNy+Oly
666             DO i=1-Olx,sNx+Olx
667              localTijk(i,j,k)=localTij(i,j)
668             ENDDO
669            ENDDO
670          ENDIF
671    
672    #ifdef ALLOW_DIAGNOSTICS
673            IF ( useDiagnostics ) THEN
674              diagName = 'ADVx'//diagSufx
675              CALL DIAGNOSTICS_FILL(afx,diagName, k,1, 2,bi,bj, myThid)
676              diagName = 'ADVy'//diagSufx
677              CALL DIAGNOSTICS_FILL(afy,diagName, k,1, 2,bi,bj, myThid)
678            ENDIF
679    #endif
680    
681    #ifdef ALLOW_DEBUG
682          IF ( debugLevel .GE. debLevB
683         &   .AND. tracerIdentity.EQ.GAD_TEMPERATURE
684         &   .AND. k.LE.3 .AND. myIter.EQ.1+nIter0
685         &   .AND. nPx.EQ.1 .AND. nPy.EQ.1
686         &   .AND. useCubedSphereExchange ) THEN
687            CALL DEBUG_CS_CORNER_UV( ' afx,afy from GAD_ADVECTION',
688         &             afx,afy, k, standardMessageUnit,bi,bj,myThid )
689          ENDIF
690    #endif /* ALLOW_DEBUG */
691    
692  C--   End of K loop for horizontal fluxes  C--   End of K loop for horizontal fluxes
693        ENDDO        ENDDO
694    
695    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
696    
697          IF ( .NOT.implicitAdvection ) THEN
698  C--   Start of k loop for vertical flux  C--   Start of k loop for vertical flux
699        DO k=Nr,1,-1         DO k=Nr,1,-1
700  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
701           kkey = (ikey-1)*Nr + k           kkey = (igadkey-1)*Nr + (Nr-k+1)
702  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
703    C--   kUp    Cycles through 1,2 to point to w-layer above
 C--   kup    Cycles through 1,2 to point to w-layer above  
704  C--   kDown  Cycles through 2,1 to point to w-layer below  C--   kDown  Cycles through 2,1 to point to w-layer below
705        kup  = 1+MOD(k+1,2)          kUp  = 1+MOD(k+1,2)
706        kDown= 1+MOD(k,2)          kDown= 1+MOD(k,2)
707    c       kp1=min(Nr,k+1)
708            kp1Msk=1.
709            if (k.EQ.Nr) kp1Msk=0.
710    
711  C--   Get temporary terms used by tendency routines  #ifdef ALLOW_AUTODIFF_TAMC
712        CALL CALC_COMMON_FACTORS (  CADJ STORE rtrans(:,:)  =
713       I         bi,bj,iMin,iMax,jMin,jMax,k,  CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
714       O         xA,yA,uTrans,vTrans,rTrans,maskUp,  cphCADJ STORE wfld(:,:)  =
715       I         myThid)  cphCADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
716    #endif
717  C-    Advective flux in R  
718        DO j=1-Oly,sNy+Oly  C-- Compute Vertical transport
719         DO i=1-Olx,sNx+Olx  #ifdef ALLOW_AIM
720          af(i,j) = 0.  C- a hack to prevent Water-Vapor vert.transport into the stratospheric level Nr
721         ENDDO          IF ( k.EQ.1 .OR.
722        ENDDO       &     (useAIM .AND. tracerIdentity.EQ.GAD_SALINITY .AND. k.EQ.Nr)
723         &              ) THEN
724    #else
725            IF ( k.EQ.1 ) THEN
726    #endif
727    
728  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
729  CADJ STORE localTijk(:,:,k)    cphmultiCADJ STORE wfld(:,:)  =
730  CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte  cphmultiCADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
731    #endif /* ALLOW_AUTODIFF_TAMC */
732    
733    C- Surface interface :
734             DO j=1-Oly,sNy+Oly
735              DO i=1-Olx,sNx+Olx
736               rTransKp1(i,j) = kp1Msk*rTrans(i,j)
737               wFld(i,j)   = 0.
738               rTrans(i,j) = 0.
739               fVerT(i,j,kUp) = 0.
740              ENDDO
741             ENDDO
742    
743            ELSE
744    
745    #ifdef ALLOW_AUTODIFF_TAMC
746    cphmultiCADJ STORE wfld(:,:)  =
747    cphmultiCADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
748    #endif /* ALLOW_AUTODIFF_TAMC */
749    
750    C- Interior interface :
751             DO j=1-Oly,sNy+Oly
752              DO i=1-Olx,sNx+Olx
753               rTransKp1(i,j) = kp1Msk*rTrans(i,j)
754               wFld(i,j)   = wVel(i,j,k,bi,bj)
755               rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)
756         &                 *deepFac2F(k)*rhoFacF(k)
757         &                 *maskC(i,j,k-1,bi,bj)
758               fVerT(i,j,kUp) = 0.
759              ENDDO
760             ENDDO
761    
762    #ifdef ALLOW_GMREDI
763    C--   Residual transp = Bolus transp + Eulerian transp
764             IF (useGMRedi)
765         &     CALL GMREDI_CALC_WFLOW(
766         U                 wFld, rTrans,
767         I                 k, bi, bj, myThid )
768    #endif /* ALLOW_GMREDI */
769    
770    #ifdef ALLOW_AUTODIFF_TAMC
771    cphmultiCADJ STORE localTijk(:,:,k)
772    cphmultiCADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
773    cphmultiCADJ STORE rTrans(:,:)
774    cphmultiCADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
775  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
776    
 C     Note: wVel needs to be masked  
       IF (K.GE.2) THEN  
777  C-    Compute vertical advective flux in the interior:  C-    Compute vertical advective flux in the interior:
778         IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN           IF ( vertAdvecScheme.EQ.ENUM_UPWIND_1RST
779          CALL GAD_FLUXLIMIT_ADV_R(       &      .OR. vertAdvecScheme.EQ.ENUM_DST2 ) THEN
780       &       bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)             CALL GAD_DST2U1_ADV_R( bi,bj,k, advectionScheme,
781         ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN       I                            dTtracerLev(k),rTrans,wFld,localTijk,
782          CALL GAD_DST3_ADV_R(       O                            fVerT(1-Olx,1-Oly,kUp), myThid )
783       &       bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)           ELSEIF( vertAdvecScheme.EQ.ENUM_FLUX_LIMIT) THEN
784         ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN             CALL GAD_FLUXLIMIT_ADV_R( bi,bj,k, dTtracerLev(k),
785          CALL GAD_DST3FL_ADV_R(       I                               rTrans, wFld, localTijk,
786       &       bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)       O                               fVerT(1-Olx,1-Oly,kUp), myThid )
787         ELSE           ELSEIF( vertAdvecScheme.EQ.ENUM_DST3 ) THEN
788          STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'             CALL GAD_DST3_ADV_R(      bi,bj,k, dTtracerLev(k),
789         ENDIF       I                               rTrans, wFld, localTijk,
790  C-    Surface "correction" term at k>1 :       O                               fVerT(1-Olx,1-Oly,kUp), myThid )
791         DO j=1-Oly,sNy+Oly           ELSEIF( vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
792          DO i=1-Olx,sNx+Olx             CALL GAD_DST3FL_ADV_R(    bi,bj,k, dTtracerLev(k),
793           af(i,j) = af(i,j)       I                               rTrans, wFld, localTijk,
794       &           + (maskC(i,j,k,bi,bj)-maskC(i,j,k-1,bi,bj))*       O                               fVerT(1-Olx,1-Oly,kUp), myThid )
795       &             rTrans(i,j)*localTijk(i,j,k)  #ifndef ALLOW_AUTODIFF_TAMC
796          ENDDO           ELSEIF (vertAdvecScheme.EQ.ENUM_OS7MP ) THEN
797         ENDDO             CALL GAD_OS7MP_ADV_R(     bi,bj,k, dTtracerLev(k),
798        ELSE       I                               rTrans, wFld, localTijk,
799  C-    Surface "correction" term at k=1 :       O                               fVerT(1-Olx,1-Oly,kUp), myThid )
800         DO j=1-Oly,sNy+Oly  #endif
801          DO i=1-Olx,sNx+Olx           ELSE
802           af(i,j) = rTrans(i,j)*localTijk(i,j,k)            STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
803             ENDIF
804    
805    C- end Surface/Interior if bloc
806            ENDIF
807    
808    #ifdef ALLOW_AUTODIFF_TAMC
809    cphmultiCADJ STORE rTrans(:,:)
810    cphmultiCADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
811    cphmultiCADJ STORE rTranskp1(:,:)
812    cphmultiCADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
813    cph --- following storing of fVerT is critical for correct
814    cph --- gradient with multiDimAdvection
815    cph --- Without it, kDown component is not properly recomputed
816    cph --- This is a TAF bug (and no warning available)
817    CADJ STORE fVerT(:,:,:)
818    CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
819    #endif /* ALLOW_AUTODIFF_TAMC */
820    
821    C--   Divergence of vertical fluxes
822            DO j=1-Oly,sNy+Oly
823             DO i=1-Olx,sNx+Olx
824              localTij(i,j) = localTijk(i,j,k)
825         &      -dTtracerLev(k)*recip_rhoFacC(k)
826         &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
827         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
828         &       *( fVerT(i,j,kDown)-fVerT(i,j,kUp)
829         &         -tracer(i,j,k,bi,bj)*(rTransKp1(i,j)-rTrans(i,j))
830         &        )*rkSign
831              gTracer(i,j,k,bi,bj)=
832         &     (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)
833             ENDDO
834          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  
835    
836  C--   Divergence of fluxes  #ifdef ALLOW_DIAGNOSTICS
837        kp1=min(Nr,k+1)          IF ( useDiagnostics ) THEN
838        kp1Msk=1.            diagName = 'ADVr'//diagSufx
839        if (k.EQ.Nr) kp1Msk=0.            CALL DIAGNOSTICS_FILL( fVerT(1-Olx,1-Oly,kUp),
840        DO j=1-Oly,sNy+Oly       &                           diagName, k,1, 2,bi,bj, myThid)
841         DO i=1-Olx,sNx+Olx          ENDIF
842          localTij(i,j)=localTijk(i,j,k)-deltaTtracer*  #endif
843       &    _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  
   
844  C--   End of K loop for vertical flux  C--   End of K loop for vertical flux
845        ENDDO         ENDDO
846    C--   end of if not.implicitAdvection block
847          ENDIF
848    
849        RETURN        RETURN
850        END        END

Legend:
Removed from v.1.9  
changed lines
  Added in v.1.55

  ViewVC Help
Powered by ViewVC 1.1.22