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

Legend:
Removed from v.1.15  
changed lines
  Added in v.1.51

  ViewVC Help
Powered by ViewVC 1.1.22