/[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.28 by jmc, Tue Sep 21 12:13:44 2004 UTC revision 1.45 by jmc, Wed Jan 10 18:53:25 2007 UTC
# Line 2  C $Header$ Line 2  C $Header$
2  C $Name$  C $Name$
3    
4  #include "GAD_OPTIONS.h"  #include "GAD_OPTIONS.h"
5    #undef MULTIDIM_OLD_VERSION
6    
7  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
8  CBOP  CBOP
# Line 16  C !INTERFACE: ========================== Line 17  C !INTERFACE: ==========================
17       I     bi,bj, myTime,myIter,myThid)       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 32  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
# Line 79  C  myThid            :: thread number Line 80  C  myThid            :: thread number
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  maskLocW      :: 2-D array for mask at West points
89    C  maskLocS      :: 2-D array for mask at South points
90  C  iMin,iMax,    :: loop range for called routines  C  iMin,iMax,    :: loop range for called routines
91  C  jMin,jMax     :: loop range for called routines  C  jMin,jMax     :: loop range for called routines
92    C [iMin,iMax]Upd :: loop range to update tracer field
93    C [jMin,jMax]Upd :: loop range to update tracer field
94  C  i,j,k         :: loop indices  C  i,j,k         :: loop indices
95  C  kup           :: index into 2 1/2D array, toggles between 1 and 2  C  kUp           :: index into 2 1/2D array, toggles between 1 and 2
96  C  kdown         :: index into 2 1/2D array, toggles between 2 and 1  C  kDown         :: index into 2 1/2D array, toggles between 2 and 1
97  C  kp1           :: =k+1 for k<Nr, =Nr for k=Nr  C  kp1           :: =k+1 for k<Nr, =Nr for k=Nr
98  C  xA,yA         :: areas of X and Y face of tracer cells  C  xA,yA         :: areas of X and Y face of tracer cells
99    C  uFld,vFld     :: 2-D local copy of horizontal velocity, U,V components
100    C  wFld          :: 2-D local copy of vertical velocity
101  C  uTrans,vTrans :: 2-D arrays of volume transports at U,V points  C  uTrans,vTrans :: 2-D arrays of volume transports at U,V points
102  C  rTrans        :: 2-D arrays of volume transports at W points  C  rTrans        :: 2-D arrays of volume transports at W points
103  C  rTransKp1     :: vertical volume transport at interface k+1  C  rTransKp1     :: vertical volume transport at interface k+1
104  C  af            :: 2-D array for horizontal advective flux  C  af            :: 2-D array for horizontal advective flux
105    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  C  fVerT         :: 2 1/2D arrays for vertical advective flux
108  C  localTij      :: 2-D array, temporary local copy of tracer fld  C  localTij      :: 2-D array, temporary local copy of tracer fld
109  C  localTijk     :: 3-D array, temporary local copy of tracer fld  C  localTijk     :: 3-D array, temporary local copy of tracer fld
110  C  kp1Msk        :: flag (0,1) for over-riding mask for W levels  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  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  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  C  nipass        :: number of passes in multi-dimensional method
116  C  ipass         :: number of the current pass being made  C  ipass         :: number of the current pass being made
117  C  myTile        :: variables used to determine which cube face  C  myTile        :: variables used to determine which cube face
118  C  nCFace        :: owns a tile for cube grid runs using  C  nCFace        :: owns a tile for cube grid runs using
119  C                :: multi-dim advection.  C                :: multi-dim advection.
120        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  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 myTile, nCFace        INTEGER nCFace
147        LOGICAL southWestCorner        LOGICAL N_edge, S_edge, E_edge, W_edge
148        LOGICAL southEastCorner  #ifdef ALLOW_EXCH2
149        LOGICAL northWestCorner        INTEGER myTile
150        LOGICAL northEastCorner  #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
# Line 150  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 165  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 183  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  The following block is needed for useCubedSphereExchange only,  #ifndef ALLOW_AUTODIFF_TAMC
 cph  but needs to be set for all cases to avoid spurious  
 cph  TAF dependencies  
        southWestCorner = .TRUE.  
        southEastCorner = .TRUE.  
        northWestCorner = .TRUE.  
        northEastCorner = .TRUE.  
 #ifdef ALLOW_EXCH2  
        myTile = W2_myTileList(bi)  
        nCFace = exch2_myFace(myTile)  
        southWestCorner = exch2_isWedge(myTile).EQ.1  
      &             .AND. exch2_isSedge(myTile).EQ.1  
        southEastCorner = exch2_isEedge(myTile).EQ.1  
      &             .AND. exch2_isSedge(myTile).EQ.1  
        northEastCorner = exch2_isEedge(myTile).EQ.1  
      &             .AND. exch2_isNedge(myTile).EQ.1  
        northWestCorner = exch2_isWedge(myTile).EQ.1  
      &             .AND. exch2_isNedge(myTile).EQ.1  
 #else  
        nCFace = bi  
 #endif  
274        IF (useCubedSphereExchange) THEN        IF (useCubedSphereExchange) THEN
275            withSigns = .FALSE.
276         nipass=3          CALL FILL_CS_CORNER_UV_RS(
277  #ifdef ALLOW_AUTODIFF_TAMC       &            withSigns, maskLocW,maskLocS, bi,bj, myThid )
        if ( nipass.GT.maxcube )  
      &      STOP 'maxcube needs to be = 3'  
 #endif  
       ELSE  
        nipass=1  
278        ENDIF        ENDIF
279  cph       nipass=1  #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.  C--   For cube need one pass for each of red, green and blue axes.
# Line 245  C--   For cube need one pass for each of Line 289  C--   For cube need one pass for each of
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. (nCFace.EQ.1 .OR. nCFace.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. (nCFace.EQ.4 .OR. nCFace.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. (nCFace.EQ.1 .OR. nCFace.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. (nCFace.EQ.3 .OR. nCFace.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. (nCFace.EQ.2 .OR. nCFace.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. (nCFace.EQ.5 .OR. nCFace.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  C--    For cube face corners we need to duplicate the  C-     Advective flux in X
328  C--    i-1 and i+1 values into the null space as follows:          DO j=1-Oly,sNy+Oly
329  C           DO i=1-Olx,sNx+Olx
330  C            af(i,j) = 0.
 C      o NW corner: copy T(    0,sNy  ) into T(    0,sNy+1) e.g.  
 C                      |  
 C         x T(0,sNy+1) |  
 C        /\            |  
 C      --||------------|-----------  
 C        ||            |  
 C         x T(0,sNy)   |   x T(1,sNy)  
 C                      |  
 C  
 C      o SW corner: copy T(0,1) into T(0,0) e.g.  
 C                      |  
 C         x T(0,1)     |  x T(1,1)  
 C        ||            |  
 C      --||------------|-----------  
 C        \/            |  
 C         x T(0,0)     |  
 C                      |  
 C  
 C      o NE corner: copy T(sNx+1,sNy  ) into T(sNx+1,sNy+1) e.g.  
 C                      |  
 C                      |   x T(sNx+1,sNy+1)  
 C                      |  /\  
 C      ----------------|--||-------  
 C                      |  ||  
 C         x T(sNx,sNy) |   x T(sNx+1,sNy  )  
 C                      |  
 C      o SE corner: copy T(sNx+1,1    ) into T(sNx+1,0    ) e.g.  
 C                      |  
 C         x T(sNx,1)   |   x T(sNx+1,    1)  
 C                      |  ||  
 C      ----------------|--||-------  
 C                      |  \/  
 C                      |   x T(sNx+1,    0)  
        IF ( southWestCorner ) THEN  
         DO j=1,OLy  
          DO i=1,OLx  
           localTij( 1-i , 1-j )=localTij( 1-j , i  )  
          ENDDO  
         ENDDO  
        ENDIF  
        IF ( southEastCorner ) THEN  
         DO J=1,OLy  
          DO I=1,OLx  
           localTij(sNx+I, 1-J )=localTij(sNx+J, I  )  
          ENDDO  
         ENDDO  
        ENDIF  
        IF ( northWestCorner ) THEN  
         DO J=1,OLy  
          DO I=1,OLx  
           localTij( 1-I ,sNy+J)=localTij( 1-J , sNy+1-I )  
          ENDDO  
         ENDDO  
        ENDIF  
        IF ( northEastCorner ) THEN  
         DO J=1,OLy  
          DO I=1,OLx  
           localTij(sNx+I,sNy+J)=localTij(sNx+J, sNy+1-I )  
331           ENDDO           ENDDO
332          ENDDO          ENDDO
333         ENDIF  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  #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., localTij, bi,bj, myThid )
359            ENDIF
360    #endif
361    
362  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
363  #ifndef DISABLE_MULTIDIM_ADVECTION  # ifndef DISABLE_MULTIDIM_ADVECTION
364  CADJ STORE localTij(:,:)  =  CADJ STORE localTij(:,:)  =
365  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
366  #endif  # endif
367  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
368    
369        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN          IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
370         CALL GAD_FLUXLIMIT_ADV_X(       &     .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
371       &      bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)            CALL GAD_DST2U1_ADV_X( bi,bj,k, advectionScheme,
372        ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN       I                           dTtracerLev(k),uTrans,uFld,localTij,
373         CALL GAD_DST3_ADV_X(       O                           af, myThid )
374       &       bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)          ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
375        ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN            CALL GAD_FLUXLIMIT_ADV_X( bi,bj,k, dTtracerLev(k),
376         CALL GAD_DST3FL_ADV_X(       I                              uTrans, uFld, maskLocW, localTij,
377       &       bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)       O                              af, myThid )
378        ELSE          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
379         STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'            CALL GAD_DST3_ADV_X(      bi,bj,k, dTtracerLev(k),
380        ENDIF       I                              uTrans, uFld, maskLocW, localTij,
381         O                              af, myThid )
382            ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
383              CALL GAD_DST3FL_ADV_X(    bi,bj,k, dTtracerLev(k),
384         I                              uTrans, uFld, maskLocW, localTij,
385         O                              af, myThid )
386            ELSE
387             STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'
388            ENDIF
389    
390        DO j=1-Oly,sNy+Oly  C-     Advective flux in X : done
391         DO i=1-Olx,sNx+Olx-1         ENDIF
         localTij(i,j)=localTij(i,j)-deltaTtracer*  
      &    _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)  
      &    *recip_rA(i,j,bi,bj)  
      &    *( af(i+1,j)-af(i,j)  
      &      -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))  
      &     )  
        ENDDO  
       ENDDO  
392    
393  #ifdef ALLOW_OBCS  #ifndef ALLOW_AUTODIFF_TAMC
394  C--   Apply open boundary conditions  C-     Internal exchange for next calculations in Y
395        IF (useOBCS) THEN         IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
396         IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN           CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )
397          CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )         ENDIF
398         ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN  #endif
         CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )  
        END IF  
       END IF  
 #endif /* ALLOW_OBCS */  
399    
400  C--   End of X direction  C-     Update the local tracer field where needed:
       ENDIF  
401    
402  C--   Y direction  C      update in overlap-Only
403        IF (calc_fluxes_Y) THEN         IF ( overlapOnly ) THEN
404            iMinUpd = 1-Olx+1
405            iMaxUpd = sNx+Olx-1
406    C- notes: these 2 lines below have no real effect (because recip_hFac=0
407    C         in corner region) but safer to keep them.
408            IF ( W_edge ) iMinUpd = 1
409            IF ( E_edge ) iMaxUpd = sNx
410    
411            IF ( S_edge ) THEN
412             DO j=1-Oly,0
413              DO i=iMinUpd,iMaxUpd
414               localTij(i,j) = localTij(i,j)
415         &      -dTtracerLev(k)*recip_rhoFacC(k)
416         &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
417         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
418         &       *( af(i+1,j)-af(i,j)
419         &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
420         &        )
421              ENDDO
422             ENDDO
423            ENDIF
424            IF ( N_edge ) THEN
425             DO j=sNy+1,sNy+Oly
426              DO i=iMinUpd,iMaxUpd
427               localTij(i,j) = localTij(i,j)
428         &      -dTtracerLev(k)*recip_rhoFacC(k)
429         &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
430         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
431         &       *( af(i+1,j)-af(i,j)
432         &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
433         &        )
434              ENDDO
435             ENDDO
436            ENDIF
437    
438        IF (useCubedSphereExchange) THEN         ELSE
439  C--   Internal exchange for calculations in Y  C      do not only update the overlap
440  C--    For cube face corners we need to duplicate the          jMinUpd = 1-Oly
441  C--    j-1 and j+1 values into the null space as follows:          jMaxUpd = sNy+Oly
442  C          IF ( interiorOnly .AND. S_edge ) jMinUpd = 1
443  C      o SW corner: copy T(0,1) into T(0,0) e.g.          IF ( interiorOnly .AND. N_edge ) jMaxUpd = sNy
444  C                      |          DO j=jMinUpd,jMaxUpd
445  C                      |  x T(1,1)           DO i=1-Olx+1,sNx+Olx-1
446  C                      |             localTij(i,j) = localTij(i,j)
447  C      ----------------|-----------       &      -dTtracerLev(k)*recip_rhoFacC(k)
448  C                      |       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
449  C         x T(0,0)<====== x T(1,0)       &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
450  C                      |       &       *( af(i+1,j)-af(i,j)
451  C       &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
452  C      o NW corner: copy T(    0,sNy  ) into T(    0,sNy+1) e.g.       &        )
 C                      |  
 C         x T(0,sNy+1)<=== x T(1,sNy+1)  
 C                      |  
 C      ----------------|-----------  
 C                      |  
 C                      |   x T(1,sNy)  
 C                      |  
 C  
 C      o NE corner: copy T(sNx+1,sNy  ) into T(sNx+1,sNy+1) e.g.  
 C                      |  
 C      x T(sNx,sNy+1)=====>x T(sNx+1,sNy+1)  
 C                      |      
 C      ----------------|-----------  
 C                      |      
 C      x T(sNx,sNy)    |                        
 C                      |  
 C      o SE corner: copy T(sNx+1,1    ) into T(sNx+1,0    ) e.g.  
 C                      |  
 C         x T(sNx,1)   |                      
 C                      |      
 C      ----------------|-----------  
 C                      |      
 C         x T(sNx,0) =====>x T(sNx+1,    0)  
        IF ( southWestCorner ) THEN  
         DO J=1,Oly  
          DO I=1,Olx  
           localTij( 1-i , 1-j ) = localTij(j   , 1-i )  
453           ENDDO           ENDDO
454          ENDDO          ENDDO
455         ENDIF  C-      keep advective flux (for diagnostics)
456         IF ( southEastCorner ) THEN          DO j=1-Oly,sNy+Oly
457          DO J=1,Oly           DO i=1-Olx,sNx+Olx
458           DO I=1,Olx            afx(i,j) = af(i,j)
           localTij(sNx+i, 1-j ) = localTij(sNx+1-j, 1-i )  
459           ENDDO           ENDDO
460          ENDDO          ENDDO
461    
462    #ifdef ALLOW_OBCS
463    C-     Apply open boundary conditions
464            IF ( useOBCS ) THEN
465             IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
466              CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
467             ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
468              CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
469    #ifdef ALLOW_PTRACERS
470             ELSEIF (tracerIdentity.GE.GAD_TR1) THEN
471              CALL OBCS_APPLY_PTRACER( bi, bj, k,
472         &         tracerIdentity-GAD_TR1+1, localTij, myThid )
473    #endif /* ALLOW_PTRACERS */
474             ENDIF
475            ENDIF
476    #endif /* ALLOW_OBCS */
477    
478    C-     end if/else update overlap-Only
479         ENDIF         ENDIF
480         IF ( northWestCorner ) THEN  
481          DO J=1,Oly  C--   End of X direction
482           DO I=1,Olx        ENDIF
483            localTij( 1-i ,sNy+j) = localTij(j   ,sNy+i)  
484    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
485    C--   Y direction
486    cph-test
487    C-     Advective flux in Y
488            DO j=1-Oly,sNy+Oly
489             DO i=1-Olx,sNx+Olx
490              af(i,j) = 0.
491           ENDDO           ENDDO
492          ENDDO          ENDDO
493         ENDIF  C
494         IF ( northEastCorner ) THEN  #ifdef ALLOW_AUTODIFF_TAMC
495          DO J=1,Oly  # ifndef DISABLE_MULTIDIM_ADVECTION
496           DO I=1,Olx  CADJ STORE localTij(:,:)  =
497            localTij(sNx+i,sNy+j) = localTij(sNx+1-j,sNy+i)  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
498    CADJ STORE af(:,:)  =
499    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
500    # endif
501    #endif /* ALLOW_AUTODIFF_TAMC */
502    C
503          IF (calc_fluxes_Y) THEN
504    
505    C-     Do not compute fluxes if
506    C       a) needed in overlap only
507    C   and b) the overlap of myTile are not cube-face edges
508           IF ( .NOT.overlapOnly .OR. E_edge .OR. W_edge ) THEN
509    
510    #ifndef ALLOW_AUTODIFF_TAMC
511    C-     Internal exchange for calculations in Y
512    #ifdef MULTIDIM_OLD_VERSION
513            IF ( useCubedSphereExchange ) THEN
514    #else
515            IF ( useCubedSphereExchange .AND.
516         &       ( overlapOnly .OR. ipass.EQ.1 ) ) THEN
517    #endif
518             CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )
519            ENDIF
520    #endif
521    
522    C-     Advective flux in Y
523            DO j=1-Oly,sNy+Oly
524             DO i=1-Olx,sNx+Olx
525              af(i,j) = 0.
526           ENDDO           ENDDO
527          ENDDO          ENDDO
        ENDIF  
       ENDIF  
   
 C-    Advective flux in Y  
       DO j=1-Oly,sNy+Oly  
        DO i=1-Olx,sNx+Olx  
         af(i,j) = 0.  
        ENDDO  
       ENDDO  
528    
529  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
530  #ifndef DISABLE_MULTIDIM_ADVECTION  #ifndef DISABLE_MULTIDIM_ADVECTION
# Line 475  CADJ &     comlev1_bibj_k_gad_pass, key= Line 533  CADJ &     comlev1_bibj_k_gad_pass, key=
533  #endif  #endif
534  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
535    
536        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN          IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
537         CALL GAD_FLUXLIMIT_ADV_Y(       &     .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
538       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)            CALL GAD_DST2U1_ADV_Y( bi,bj,k, advectionScheme,
539        ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN       I                           dTtracerLev(k),vTrans,vFld,localTij,
540         CALL GAD_DST3_ADV_Y(       O                           af, myThid )
541       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)          ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
542        ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN            CALL GAD_FLUXLIMIT_ADV_Y( bi,bj,k, dTtracerLev(k),
543         CALL GAD_DST3FL_ADV_Y(       I                              vTrans, vFld, maskLocS, localTij,
544       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)       O                              af, myThid )
545        ELSE          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
546         STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'            CALL GAD_DST3_ADV_Y(      bi,bj,k, dTtracerLev(k),
547        ENDIF       I                              vTrans, vFld, maskLocS, localTij,
548         O                              af, myThid )
549            ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
550              CALL GAD_DST3FL_ADV_Y(    bi,bj,k, dTtracerLev(k),
551         I                              vTrans, vFld, maskLocS, localTij,
552         O                              af, myThid )
553            ELSE
554             STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
555            ENDIF
556    
557        DO j=1-Oly,sNy+Oly-1  C-     Advective flux in Y : done
558         DO i=1-Olx,sNx+Olx         ENDIF
559          localTij(i,j)=localTij(i,j)-deltaTtracer*  
560       &    _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)  #ifndef ALLOW_AUTODIFF_TAMC
561       &    *recip_rA(i,j,bi,bj)  C-     Internal exchange for next calculations in X
562       &    *( af(i,j+1)-af(i,j)         IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
563       &      -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))           CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )
564       &     )         ENDIF
565         ENDDO  #endif
566        ENDDO  
567    C-     Update the local tracer field where needed:
568    
569    C      update in overlap-Only
570           IF ( overlapOnly ) THEN
571            jMinUpd = 1-Oly+1
572            jMaxUpd = sNy+Oly-1
573    C- notes: these 2 lines below have no real effect (because recip_hFac=0
574    C         in corner region) but safer to keep them.
575            IF ( S_edge ) jMinUpd = 1
576            IF ( N_edge ) jMaxUpd = sNy
577    
578            IF ( W_edge ) THEN
579             DO j=jMinUpd,jMaxUpd
580              DO i=1-Olx,0
581               localTij(i,j) = localTij(i,j)
582         &      -dTtracerLev(k)*recip_rhoFacC(k)
583         &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
584         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
585         &       *( af(i,j+1)-af(i,j)
586         &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
587         &        )
588              ENDDO
589             ENDDO
590            ENDIF
591            IF ( E_edge ) THEN
592             DO j=jMinUpd,jMaxUpd
593              DO i=sNx+1,sNx+Olx
594               localTij(i,j) = localTij(i,j)
595         &      -dTtracerLev(k)*recip_rhoFacC(k)
596         &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
597         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
598         &       *( af(i,j+1)-af(i,j)
599         &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
600         &        )
601              ENDDO
602             ENDDO
603            ENDIF
604    
605           ELSE
606    C      do not only update the overlap
607            iMinUpd = 1-Olx
608            iMaxUpd = sNx+Olx
609            IF ( interiorOnly .AND. W_edge ) iMinUpd = 1
610            IF ( interiorOnly .AND. E_edge ) iMaxUpd = sNx
611            DO j=1-Oly+1,sNy+Oly-1
612             DO i=iMinUpd,iMaxUpd
613               localTij(i,j) = localTij(i,j)
614         &      -dTtracerLev(k)*recip_rhoFacC(k)
615         &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
616         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
617         &       *( af(i,j+1)-af(i,j)
618         &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
619         &        )
620             ENDDO
621            ENDDO
622    C-      keep advective flux (for diagnostics)
623            DO j=1-Oly,sNy+Oly
624             DO i=1-Olx,sNx+Olx
625              afy(i,j) = af(i,j)
626             ENDDO
627            ENDDO
628    
629  #ifdef ALLOW_OBCS  #ifdef ALLOW_OBCS
630  C--   Apply open boundary conditions  C-     Apply open boundary conditions
631        IF (useOBCS) THEN          IF (useOBCS) THEN
632         IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN           IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
633          CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
634         ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
635          CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
636         END IF  #ifdef ALLOW_PTRACERS
637        END IF           ELSEIF (tracerIdentity.GE.GAD_TR1) THEN
638              CALL OBCS_APPLY_PTRACER( bi, bj, k,
639         &         tracerIdentity-GAD_TR1+1, localTij, myThid )
640    #endif /* ALLOW_PTRACERS */
641             ENDIF
642            ENDIF
643  #endif /* ALLOW_OBCS */  #endif /* ALLOW_OBCS */
644    
645    C      end if/else update overlap-Only
646           ENDIF
647    
648  C--   End of Y direction  C--   End of Y direction
649        ENDIF        ENDIF
650    
# Line 521  C-    explicit advection is done ; store Line 656  C-    explicit advection is done ; store
656          DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
657           DO i=1-Olx,sNx+Olx           DO i=1-Olx,sNx+Olx
658            gTracer(i,j,k,bi,bj)=            gTracer(i,j,k,bi,bj)=
659       &     (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer       &     (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)
660           ENDDO           ENDDO
661          ENDDO          ENDDO
662        ELSE        ELSE
663  C-    horizontal advection done; store intermediate result in 3D array:  C-    horizontal advection done; store intermediate result in 3D array:
664         DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
665          DO i=1-Olx,sNx+Olx           DO i=1-Olx,sNx+Olx
666           localTijk(i,j,k)=localTij(i,j)            localTijk(i,j,k)=localTij(i,j)
667             ENDDO
668          ENDDO          ENDDO
        ENDDO  
669        ENDIF        ENDIF
670    
671    #ifdef ALLOW_DIAGNOSTICS
672            IF ( useDiagnostics ) THEN
673              diagName = 'ADVx'//diagSufx
674              CALL DIAGNOSTICS_FILL(afx,diagName, k,1, 2,bi,bj, myThid)
675              diagName = 'ADVy'//diagSufx
676              CALL DIAGNOSTICS_FILL(afy,diagName, k,1, 2,bi,bj, myThid)
677            ENDIF
678    #endif
679    
680    #ifdef ALLOW_DEBUG
681          IF ( debugLevel .GE. debLevB
682         &   .AND. tracerIdentity.EQ.GAD_TEMPERATURE
683         &   .AND. k.LE.3 .AND. myIter.EQ.1+nIter0
684         &   .AND. nPx.EQ.1 .AND. nPy.EQ.1
685         &   .AND. useCubedSphereExchange ) THEN
686            CALL DEBUG_CS_CORNER_UV( ' afx,afy from GAD_ADVECTION',
687         &             afx,afy, k, standardMessageUnit,bi,bj,myThid )
688          ENDIF
689    #endif /* ALLOW_DEBUG */
690    
691  C--   End of K loop for horizontal fluxes  C--   End of K loop for horizontal fluxes
692        ENDDO        ENDDO
693    
694    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
695    
696        IF ( .NOT.implicitAdvection ) THEN        IF ( .NOT.implicitAdvection ) THEN
697  C--   Start of k loop for vertical flux  C--   Start of k loop for vertical flux
698         DO k=Nr,1,-1         DO k=Nr,1,-1
699  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
700           kkey = (igadkey-1)*Nr + k           kkey = (igadkey-1)*Nr + k
701  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
702  C--   kup    Cycles through 1,2 to point to w-layer above  C--   kUp    Cycles through 1,2 to point to w-layer above
703  C--   kDown  Cycles through 2,1 to point to w-layer below  C--   kDown  Cycles through 2,1 to point to w-layer below
704          kup  = 1+MOD(k+1,2)          kUp  = 1+MOD(k+1,2)
705          kDown= 1+MOD(k,2)          kDown= 1+MOD(k,2)
706  c       kp1=min(Nr,k+1)  c       kp1=min(Nr,k+1)
707          kp1Msk=1.          kp1Msk=1.
# Line 560  C- a hack to prevent Water-Vapor vert.tr Line 717  C- a hack to prevent Water-Vapor vert.tr
717          IF ( k.EQ.1 ) THEN          IF ( k.EQ.1 ) THEN
718  #endif  #endif
719    
720    #ifdef ALLOW_AUTODIFF_TAMC
721    CADJ STORE rtrans(:,:)  =
722    CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
723    CADJ STORE wfld(:,:)  =
724    CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
725    #endif /* ALLOW_AUTODIFF_TAMC */
726    
727  C- Surface interface :  C- Surface interface :
728           DO j=1-Oly,sNy+Oly           DO j=1-Oly,sNy+Oly
729            DO i=1-Olx,sNx+Olx            DO i=1-Olx,sNx+Olx
730             rTransKp1(i,j) = kp1Msk*rTrans(i,j)             rTransKp1(i,j) = kp1Msk*rTrans(i,j)
731               wFld(i,j)   = 0.
732             rTrans(i,j) = 0.             rTrans(i,j) = 0.
733             fVerT(i,j,kUp) = 0.             fVerT(i,j,kUp) = 0.
            af(i,j) = 0.  
734            ENDDO            ENDDO
735           ENDDO           ENDDO
736    
737          ELSE          ELSE
 C- Interior interface :  
738    
739    #ifdef ALLOW_AUTODIFF_TAMC
740    CADJ STORE rtrans(:,:)  =
741    CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
742    CADJ STORE wfld(:,:)  =
743    CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
744    #endif /* ALLOW_AUTODIFF_TAMC */
745    
746    C- Interior interface :
747           DO j=1-Oly,sNy+Oly           DO j=1-Oly,sNy+Oly
748            DO i=1-Olx,sNx+Olx            DO i=1-Olx,sNx+Olx
749             rTransKp1(i,j) = kp1Msk*rTrans(i,j)             rTransKp1(i,j) = kp1Msk*rTrans(i,j)
750               wFld(i,j)   = wVel(i,j,k,bi,bj)
751             rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)             rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)
752         &                 *deepFac2F(k)*rhoFacF(k)
753       &                 *maskC(i,j,k-1,bi,bj)       &                 *maskC(i,j,k-1,bi,bj)
754             af(i,j) = 0.             fVerT(i,j,kUp) = 0.
755            ENDDO            ENDDO
756           ENDDO           ENDDO
757    
758  #ifdef ALLOW_GMREDI  #ifdef ALLOW_GMREDI
759  C--   Residual transp = Bolus transp + Eulerian transp  C--   Residual transp = Bolus transp + Eulerian transp
760           IF (useGMRedi)           IF (useGMRedi)
761       &   CALL GMREDI_CALC_WFLOW(       &     CALL GMREDI_CALC_WFLOW(
762       &                    rTrans, bi, bj, k, myThid)       U                 wFld, rTrans,
763         I                 k, bi, bj, myThid )
764  #endif /* ALLOW_GMREDI */  #endif /* ALLOW_GMREDI */
765    
766  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
# Line 597  CADJ &     = comlev1_bibj_k_gad, key=kke Line 771  CADJ &     = comlev1_bibj_k_gad, key=kke
771  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
772    
773  C-    Compute vertical advective flux in the interior:  C-    Compute vertical advective flux in the interior:
774           IF (vertAdvecScheme.EQ.ENUM_FLUX_LIMIT) THEN           IF ( vertAdvecScheme.EQ.ENUM_UPWIND_1RST
775            CALL GAD_FLUXLIMIT_ADV_R(       &      .OR. vertAdvecScheme.EQ.ENUM_DST2 ) THEN
776       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)             CALL GAD_DST2U1_ADV_R( bi,bj,k, advectionScheme,
777           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3 ) THEN       I                            dTtracerLev(k),rTrans,wFld,localTijk,
778            CALL GAD_DST3_ADV_R(       O                            fVerT(1-Olx,1-Oly,kUp), myThid )
779       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)           ELSEIF( vertAdvecScheme.EQ.ENUM_FLUX_LIMIT) THEN
780           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN             CALL GAD_FLUXLIMIT_ADV_R( bi,bj,k, dTtracerLev(k),
781            CALL GAD_DST3FL_ADV_R(       I                               rTrans, wFld, localTijk,
782       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)       O                               fVerT(1-Olx,1-Oly,kUp), myThid )
783             ELSEIF( vertAdvecScheme.EQ.ENUM_DST3 ) THEN
784               CALL GAD_DST3_ADV_R(      bi,bj,k, dTtracerLev(k),
785         I                               rTrans, wFld, localTijk,
786         O                               fVerT(1-Olx,1-Oly,kUp), myThid )
787             ELSEIF( vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
788               CALL GAD_DST3FL_ADV_R(    bi,bj,k, dTtracerLev(k),
789         I                               rTrans, wFld, localTijk,
790         O                               fVerT(1-Olx,1-Oly,kUp), myThid )
791           ELSE           ELSE
792            STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'            STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
793           ENDIF           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  
794    
795  C- end Surface/Interior if bloc  C- end Surface/Interior if bloc
796          ENDIF          ENDIF
# Line 629  CADJ &     = comlev1_bibj_k_gad, key=kke Line 805  CADJ &     = comlev1_bibj_k_gad, key=kke
805  C--   Divergence of vertical fluxes  C--   Divergence of vertical fluxes
806          DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
807           DO i=1-Olx,sNx+Olx           DO i=1-Olx,sNx+Olx
808            localTij(i,j)=localTijk(i,j,k)-deltaTtracer*            localTij(i,j) = localTijk(i,j,k)
809       &     _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
810       &     *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
811       &     *( fVerT(i,j,kUp)-fVerT(i,j,kDown)       &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
812       &       -tracer(i,j,k,bi,bj)*(rTrans(i,j)-rTransKp1(i,j))       &       *( fVerT(i,j,kDown)-fVerT(i,j,kUp)
813       &      )*rkFac       &         -tracer(i,j,k,bi,bj)*(rTransKp1(i,j)-rTrans(i,j))
814         &        )*rkSign
815            gTracer(i,j,k,bi,bj)=            gTracer(i,j,k,bi,bj)=
816       &     (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer       &     (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)
817           ENDDO           ENDDO
818          ENDDO          ENDDO
819    
820    #ifdef ALLOW_DIAGNOSTICS
821            IF ( useDiagnostics ) THEN
822              diagName = 'ADVr'//diagSufx
823              CALL DIAGNOSTICS_FILL( fVerT(1-Olx,1-Oly,kUp),
824         &                           diagName, k,1, 2,bi,bj, myThid)
825            ENDIF
826    #endif
827    
828  C--   End of K loop for vertical flux  C--   End of K loop for vertical flux
829         ENDDO         ENDDO
830  C--   end of if not.implicitAdvection block  C--   end of if not.implicitAdvection block
831        ENDIF        ENDIF
832    
833        RETURN        RETURN
834        END        END

Legend:
Removed from v.1.28  
changed lines
  Added in v.1.45

  ViewVC Help
Powered by ViewVC 1.1.22