/[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.23 by jmc, Sat Jun 26 02:38:54 2004 UTC revision 1.41 by jmc, Sun Jun 18 23:27:44 2006 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 19  C !DESCRIPTION: Line 20  C !DESCRIPTION:
20  C Calculates the tendancy of a tracer due to advection.  C Calculates the tendancy 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 44  C !USES: =============================== Line 45  C !USES: ===============================
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  implicitAdvection :: implicit vertical advection (later on)  C  implicitAdvection :: implicit vertical advection (later on)
# Line 77  C  gTracer           :: tendancy array Line 85  C  gTracer           :: tendancy array
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        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  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
# Line 135  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 150  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    #endif
204         ENDDO         ENDDO
205        ENDDO        ENDDO
206    
207    C--   Set tile-specific parameters for horizontal fluxes
208          IF (useCubedSphereExchange) THEN
209           nipass=3
210    #ifdef ALLOW_AUTODIFF_TAMC
211           IF ( nipass.GT.maxcube ) STOP 'maxcube needs to be = 3'
212    #endif
213    #ifdef ALLOW_EXCH2
214           myTile = W2_myTileList(bi)
215           nCFace = exch2_myFace(myTile)
216           N_edge = exch2_isNedge(myTile).EQ.1
217           S_edge = exch2_isSedge(myTile).EQ.1
218           E_edge = exch2_isEedge(myTile).EQ.1
219           W_edge = exch2_isWedge(myTile).EQ.1
220    #else
221           nCFace = bi
222           N_edge = .TRUE.
223           S_edge = .TRUE.
224           E_edge = .TRUE.
225           W_edge = .TRUE.
226    #endif
227          ELSE
228           nipass=2
229           nCFace = bi
230           N_edge = .FALSE.
231           S_edge = .FALSE.
232           E_edge = .FALSE.
233           W_edge = .FALSE.
234          ENDIF
235    
236        iMin = 1-OLx        iMin = 1-OLx
237        iMax = sNx+OLx        iMax = sNx+OLx
238        jMin = 1-OLy        jMin = 1-OLy
# Line 168  CADJ &     comlev1_bibj_k_gad, key=kkey, Line 248  CADJ &     comlev1_bibj_k_gad, key=kkey,
248    
249  C--   Get temporary terms used by tendency routines  C--   Get temporary terms used by tendency routines
250        CALL CALC_COMMON_FACTORS (        CALL CALC_COMMON_FACTORS (
251       I         bi,bj,iMin,iMax,jMin,jMax,k,       I         uVel, vVel,
252       O         xA,yA,uTrans,vTrans,rTrans,maskUp,       O         uFld, vFld, uTrans, vTrans, xA, yA,
253       I         myThid)       I         k,bi,bj, myThid )
254    
255  #ifdef ALLOW_GMREDI  #ifdef ALLOW_GMREDI
256  C--   Residual transp = Bolus transp + Eulerian transp  C--   Residual transp = Bolus transp + Eulerian transp
257         IF (useGMRedi)        IF (useGMRedi)
258       &   CALL GMREDI_CALC_UVFLOW(       &   CALL GMREDI_CALC_UVFLOW(
259       &            uTrans, vTrans, bi, bj, k, myThid)       U                  uFld, vFld, uTrans, vTrans,
260         I                  k, bi, bj, myThid )
261  #endif /* ALLOW_GMREDI */  #endif /* ALLOW_GMREDI */
262    
263  C--   Make local copy of tracer array  C--   Make local copy of tracer array and mask West & South
264        DO j=1-OLy,sNy+OLy        DO j=1-OLy,sNy+OLy
265         DO i=1-OLx,sNx+OLx         DO i=1-OLx,sNx+OLx
266          localTij(i,j)=tracer(i,j,k,bi,bj)           localTij(i,j)=tracer(i,j,k,bi,bj)
267             maskLocW(i,j)=maskW(i,j,k,bi,bj)
268             maskLocS(i,j)=maskS(i,j,k,bi,bj)
269         ENDDO         ENDDO
270        ENDDO        ENDDO
271    
272    #ifndef ALLOW_AUTODIFF_TAMC
273        IF (useCubedSphereExchange) THEN        IF (useCubedSphereExchange) THEN
274         nipass=3          withSigns = .FALSE.
275  #ifdef ALLOW_AUTODIFF_TAMC          CALL FILL_CS_CORNER_UV_RS(
276         if ( nipass.GT.maxcube )       &            withSigns, maskLocW,maskLocS, bi,bj, myThid )
      &      STOP 'maxcube needs to be = 3'  
 #endif  
       ELSE  
        nipass=1  
277        ENDIF        ENDIF
278  cph       nipass=1  #endif
279    
280  C--   Multiple passes for different directions on different tiles  C--   Multiple passes for different directions on different tiles
281    C--   For cube need one pass for each of red, green and blue axes.
282        DO ipass=1,nipass        DO ipass=1,nipass
283  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
284           passkey = ipass + (k-1)      *maxcube           passkey = ipass + (k-1)      *maxcube
# Line 207  C--   Multiple passes for different dire Line 288  C--   Multiple passes for different dire
288           ENDIF           ENDIF
289  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
290    
291        IF (nipass.EQ.3) THEN        interiorOnly = .FALSE.
292         calc_fluxes_X=.FALSE.        overlapOnly  = .FALSE.
293         calc_fluxes_Y=.FALSE.        IF (useCubedSphereExchange) THEN
294         IF (ipass.EQ.1 .AND. (bi.EQ.1 .OR. bi.EQ.2) ) THEN  #ifdef MULTIDIM_OLD_VERSION
295          calc_fluxes_X=.TRUE.  C-    CubedSphere : pass 3 times, with full update of local tracer field
296         ELSEIF (ipass.EQ.1 .AND. (bi.EQ.4 .OR. bi.EQ.5) ) THEN         IF (ipass.EQ.1) THEN
297          calc_fluxes_Y=.TRUE.          calc_fluxes_X = nCFace.EQ.1 .OR. nCFace.EQ.2
298         ELSEIF (ipass.EQ.2 .AND. (bi.EQ.1 .OR. bi.EQ.6) ) THEN          calc_fluxes_Y = nCFace.EQ.4 .OR. nCFace.EQ.5
299          calc_fluxes_Y=.TRUE.         ELSEIF (ipass.EQ.2) THEN
300         ELSEIF (ipass.EQ.2 .AND. (bi.EQ.3 .OR. bi.EQ.4) ) THEN          calc_fluxes_X = nCFace.EQ.3 .OR. nCFace.EQ.4
301          calc_fluxes_X=.TRUE.          calc_fluxes_Y = nCFace.EQ.6 .OR. nCFace.EQ.1
302         ELSEIF (ipass.EQ.3 .AND. (bi.EQ.2 .OR. bi.EQ.3) ) THEN  #else /* MULTIDIM_OLD_VERSION */
303          calc_fluxes_Y=.TRUE.  C-    CubedSphere : pass 3 times, with partial update of local tracer field
304         ELSEIF (ipass.EQ.3 .AND. (bi.EQ.5 .OR. bi.EQ.6) ) THEN         IF (ipass.EQ.1) THEN
305          calc_fluxes_X=.TRUE.          overlapOnly  = MOD(nCFace,3).EQ.0
306            interiorOnly = MOD(nCFace,3).NE.0
307            calc_fluxes_X = nCFace.EQ.6 .OR. nCFace.EQ.1 .OR. nCFace.EQ.2
308            calc_fluxes_Y = nCFace.EQ.3 .OR. nCFace.EQ.4 .OR. nCFace.EQ.5
309           ELSEIF (ipass.EQ.2) THEN
310            overlapOnly  = MOD(nCFace,3).EQ.2
311            calc_fluxes_X = nCFace.EQ.2 .OR. nCFace.EQ.3 .OR. nCFace.EQ.4
312            calc_fluxes_Y = nCFace.EQ.5 .OR. nCFace.EQ.6 .OR. nCFace.EQ.1
313    #endif /* MULTIDIM_OLD_VERSION */
314           ELSE
315            calc_fluxes_X = nCFace.EQ.5 .OR. nCFace.EQ.6
316            calc_fluxes_Y = nCFace.EQ.2 .OR. nCFace.EQ.3
317         ENDIF         ENDIF
318        ELSE        ELSE
319         calc_fluxes_X=.TRUE.  C-    not CubedSphere
320         calc_fluxes_Y=.TRUE.          calc_fluxes_X = MOD(ipass,2).EQ.1
321            calc_fluxes_Y = .NOT.calc_fluxes_X
322        ENDIF        ENDIF
   
 C--   X direction  
       IF (calc_fluxes_X) THEN  
323    
324  C--   Internal exchange for calculations in X  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
325        IF (useCubedSphereExchange) THEN  C--   X direction
326         DO j=1,Oly  C-     Advective flux in X
327          DO i=1,Olx          DO j=1-Oly,sNy+Oly
328           localTij( 1-i , 1-j )=localTij( 1-j ,    i    )           DO i=1-Olx,sNx+Olx
329           localTij( 1-i ,sNy+j)=localTij( 1-j , sNy+1-i )            af(i,j) = 0.
330           localTij(sNx+i, 1-j )=localTij(sNx+j,    i    )           ENDDO
          localTij(sNx+i,sNy+j)=localTij(sNx+j, sNy+1-i )  
331          ENDDO          ENDDO
332         ENDDO  C
333        ENDIF  #ifdef ALLOW_AUTODIFF_TAMC
334    # ifndef DISABLE_MULTIDIM_ADVECTION
335    CADJ STORE localTij(:,:)  =
336    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
337    CADJ STORE af(:,:)  =
338    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
339    # endif
340    #endif /* ALLOW_AUTODIFF_TAMC */
341    C
342          IF (calc_fluxes_X) THEN
343    
344  C-    Advective flux in X  C-     Do not compute fluxes if
345        DO j=1-Oly,sNy+Oly  C       a) needed in overlap only
346         DO i=1-Olx,sNx+Olx  C   and b) the overlap of myTile are not cube-face Edges
347          af(i,j) = 0.         IF ( .NOT.overlapOnly .OR. N_edge .OR. S_edge ) THEN
348         ENDDO  
349        ENDDO  #ifndef ALLOW_AUTODIFF_TAMC
350    C-     Internal exchange for calculations in X
351    #ifdef MULTIDIM_OLD_VERSION
352            IF ( useCubedSphereExchange ) THEN
353    #else
354            IF ( useCubedSphereExchange .AND.
355         &       ( overlapOnly .OR. ipass.EQ.1 ) ) THEN
356    #endif
357             CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )
358            ENDIF
359    #endif
360    
361  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
362  #ifndef DISABLE_MULTIDIM_ADVECTION  # ifndef DISABLE_MULTIDIM_ADVECTION
363  CADJ STORE localTij(:,:)  =  CADJ STORE localTij(:,:)  =
364  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
365  #endif  # endif
366  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
367    
368        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN          IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
369         CALL GAD_FLUXLIMIT_ADV_X(       &     .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
370       &      bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)            CALL GAD_DST2U1_ADV_X( bi,bj,k, advectionScheme,
371        ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN       I                           dTtracerLev(k),uTrans,uFld,localTij,
372         CALL GAD_DST3_ADV_X(       O                           af, myThid )
373       &       bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)          ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
374        ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN            CALL GAD_FLUXLIMIT_ADV_X( bi,bj,k, dTtracerLev(k),
375         CALL GAD_DST3FL_ADV_X(       I                              uTrans, uFld, maskLocW, localTij,
376       &       bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)       O                              af, myThid )
377        ELSE          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
378         STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'            CALL GAD_DST3_ADV_X(      bi,bj,k, dTtracerLev(k),
379        ENDIF       I                              uTrans, uFld, maskLocW, localTij,
380         O                              af, myThid )
381            ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
382              CALL GAD_DST3FL_ADV_X(    bi,bj,k, dTtracerLev(k),
383         I                              uTrans, uFld, maskLocW, localTij,
384         O                              af, myThid )
385            ELSE
386             STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'
387            ENDIF
388    
389        DO j=1-Oly,sNy+Oly  C-     Advective flux in X : done
390         DO i=1-Olx,sNx+Olx-1         ENDIF
391          localTij(i,j)=localTij(i,j)-deltaTtracer*  
392       &    _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)  #ifndef ALLOW_AUTODIFF_TAMC
393       &    *recip_rA(i,j,bi,bj)  C-     Internal exchange for next calculations in Y
394       &    *( af(i+1,j)-af(i,j)         IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
395       &      -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))           CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )
396       &     )         ENDIF
397         ENDDO  #endif
398        ENDDO  
399    C-     Update the local tracer field where needed:
400    
401    C      update in overlap-Only
402           IF ( overlapOnly ) THEN
403            iMinUpd = 1-Olx+1
404            iMaxUpd = sNx+Olx-1
405    C- notes: these 2 lines below have no real effect (because recip_hFac=0
406    C         in corner region) but safer to keep them.
407            IF ( W_edge ) iMinUpd = 1
408            IF ( E_edge ) iMaxUpd = sNx
409    
410            IF ( S_edge ) THEN
411             DO j=1-Oly,0
412              DO i=iMinUpd,iMaxUpd
413               localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
414         &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
415         &       *recip_rA(i,j,bi,bj)
416         &       *( af(i+1,j)-af(i,j)
417         &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
418         &        )
419              ENDDO
420             ENDDO
421            ENDIF
422            IF ( N_edge ) THEN
423             DO j=sNy+1,sNy+Oly
424              DO i=iMinUpd,iMaxUpd
425               localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
426         &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
427         &       *recip_rA(i,j,bi,bj)
428         &       *( af(i+1,j)-af(i,j)
429         &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
430         &        )
431              ENDDO
432             ENDDO
433            ENDIF
434    
435           ELSE
436    C      do not only update the overlap
437            jMinUpd = 1-Oly
438            jMaxUpd = sNy+Oly
439            IF ( interiorOnly .AND. S_edge ) jMinUpd = 1
440            IF ( interiorOnly .AND. N_edge ) jMaxUpd = sNy
441            DO j=jMinUpd,jMaxUpd
442             DO i=1-Olx+1,sNx+Olx-1
443               localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
444         &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
445         &       *recip_rA(i,j,bi,bj)
446         &       *( af(i+1,j)-af(i,j)
447         &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
448         &        )
449             ENDDO
450            ENDDO
451    C-      keep advective flux (for diagnostics)
452            DO j=1-Oly,sNy+Oly
453             DO i=1-Olx,sNx+Olx
454              afx(i,j) = af(i,j)
455             ENDDO
456            ENDDO
457    
458  #ifdef ALLOW_OBCS  #ifdef ALLOW_OBCS
459  C--   Apply open boundary conditions  C-     Apply open boundary conditions
460        IF (useOBCS) THEN          IF ( useOBCS ) THEN
461         IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN           IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
462          CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
463         ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
464          CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
465         END IF  #ifdef ALLOW_PTRACERS
466        END IF           ELSEIF (tracerIdentity.GE.GAD_TR1) THEN
467              CALL OBCS_APPLY_PTRACER( bi, bj, k,
468         &         tracerIdentity-GAD_TR1+1, localTij, myThid )
469    #endif /* ALLOW_PTRACERS */
470             ENDIF
471            ENDIF
472  #endif /* ALLOW_OBCS */  #endif /* ALLOW_OBCS */
473    
474    C-     end if/else update overlap-Only
475           ENDIF
476    
477  C--   End of X direction  C--   End of X direction
478        ENDIF        ENDIF
479    
480    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
481  C--   Y direction  C--   Y direction
482    cph-test
483    C-     Advective flux in Y
484            DO j=1-Oly,sNy+Oly
485             DO i=1-Olx,sNx+Olx
486              af(i,j) = 0.
487             ENDDO
488            ENDDO
489    C
490    #ifdef ALLOW_AUTODIFF_TAMC
491    # ifndef DISABLE_MULTIDIM_ADVECTION
492    CADJ STORE localTij(:,:)  =
493    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
494    CADJ STORE af(:,:)  =
495    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
496    # endif
497    #endif /* ALLOW_AUTODIFF_TAMC */
498    C
499        IF (calc_fluxes_Y) THEN        IF (calc_fluxes_Y) THEN
500    
501  C--   Internal exchange for calculations in Y  C-     Do not compute fluxes if
502        IF (useCubedSphereExchange) THEN  C       a) needed in overlap only
503         DO j=1,Oly  C   and b) the overlap of myTile are not cube-face edges
504          DO i=1,Olx         IF ( .NOT.overlapOnly .OR. E_edge .OR. W_edge ) THEN
505           localTij( 1-i , 1-j )=localTij(   j   , 1-i )  
506           localTij( 1-i ,sNy+j)=localTij(   j   ,sNy+i)  #ifndef ALLOW_AUTODIFF_TAMC
507           localTij(sNx+i, 1-j )=localTij(sNx+1-j, 1-i )  C-     Internal exchange for calculations in Y
508           localTij(sNx+i,sNy+j)=localTij(sNx+1-j,sNy+i)  #ifdef MULTIDIM_OLD_VERSION
509          ENDDO          IF ( useCubedSphereExchange ) THEN
510         ENDDO  #else
511        ENDIF          IF ( useCubedSphereExchange .AND.
512         &       ( overlapOnly .OR. ipass.EQ.1 ) ) THEN
513    #endif
514             CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )
515            ENDIF
516    #endif
517    
518  C-    Advective flux in Y  C-     Advective flux in Y
519        DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
520         DO i=1-Olx,sNx+Olx           DO i=1-Olx,sNx+Olx
521          af(i,j) = 0.            af(i,j) = 0.
522         ENDDO           ENDDO
523        ENDDO          ENDDO
524    
525  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
526  #ifndef DISABLE_MULTIDIM_ADVECTION  #ifndef DISABLE_MULTIDIM_ADVECTION
# Line 324  CADJ &     comlev1_bibj_k_gad_pass, key= Line 529  CADJ &     comlev1_bibj_k_gad_pass, key=
529  #endif  #endif
530  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
531    
532        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN          IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
533         CALL GAD_FLUXLIMIT_ADV_Y(       &     .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
534       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)            CALL GAD_DST2U1_ADV_Y( bi,bj,k, advectionScheme,
535        ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN       I                           dTtracerLev(k),vTrans,vFld,localTij,
536         CALL GAD_DST3_ADV_Y(       O                           af, myThid )
537       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)          ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
538        ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN            CALL GAD_FLUXLIMIT_ADV_Y( bi,bj,k, dTtracerLev(k),
539         CALL GAD_DST3FL_ADV_Y(       I                              vTrans, vFld, maskLocS, localTij,
540       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)       O                              af, myThid )
541        ELSE          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
542         STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'            CALL GAD_DST3_ADV_Y(      bi,bj,k, dTtracerLev(k),
543        ENDIF       I                              vTrans, vFld, maskLocS, localTij,
544         O                              af, myThid )
545            ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
546              CALL GAD_DST3FL_ADV_Y(    bi,bj,k, dTtracerLev(k),
547         I                              vTrans, vFld, maskLocS, localTij,
548         O                              af, myThid )
549            ELSE
550             STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
551            ENDIF
552    
553        DO j=1-Oly,sNy+Oly-1  C-     Advective flux in Y : done
554         DO i=1-Olx,sNx+Olx         ENDIF
555          localTij(i,j)=localTij(i,j)-deltaTtracer*  
556       &    _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)  #ifndef ALLOW_AUTODIFF_TAMC
557       &    *recip_rA(i,j,bi,bj)  C-     Internal exchange for next calculations in X
558       &    *( af(i,j+1)-af(i,j)         IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
559       &      -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))           CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )
560       &     )         ENDIF
561         ENDDO  #endif
562        ENDDO  
563    C-     Update the local tracer field where needed:
564    
565    C      update in overlap-Only
566           IF ( overlapOnly ) THEN
567            jMinUpd = 1-Oly+1
568            jMaxUpd = sNy+Oly-1
569    C- notes: these 2 lines below have no real effect (because recip_hFac=0
570    C         in corner region) but safer to keep them.
571            IF ( S_edge ) jMinUpd = 1
572            IF ( N_edge ) jMaxUpd = sNy
573    
574            IF ( W_edge ) THEN
575             DO j=jMinUpd,jMaxUpd
576              DO i=1-Olx,0
577               localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
578         &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
579         &       *recip_rA(i,j,bi,bj)
580         &       *( af(i,j+1)-af(i,j)
581         &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
582         &        )
583              ENDDO
584             ENDDO
585            ENDIF
586            IF ( E_edge ) THEN
587             DO j=jMinUpd,jMaxUpd
588              DO i=sNx+1,sNx+Olx
589               localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
590         &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
591         &       *recip_rA(i,j,bi,bj)
592         &       *( af(i,j+1)-af(i,j)
593         &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
594         &        )
595              ENDDO
596             ENDDO
597            ENDIF
598    
599           ELSE
600    C      do not only update the overlap
601            iMinUpd = 1-Olx
602            iMaxUpd = sNx+Olx
603            IF ( interiorOnly .AND. W_edge ) iMinUpd = 1
604            IF ( interiorOnly .AND. E_edge ) iMaxUpd = sNx
605            DO j=1-Oly+1,sNy+Oly-1
606             DO i=iMinUpd,iMaxUpd
607               localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
608         &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
609         &       *recip_rA(i,j,bi,bj)
610         &       *( af(i,j+1)-af(i,j)
611         &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
612         &        )
613             ENDDO
614            ENDDO
615    C-      keep advective flux (for diagnostics)
616            DO j=1-Oly,sNy+Oly
617             DO i=1-Olx,sNx+Olx
618              afy(i,j) = af(i,j)
619             ENDDO
620            ENDDO
621    
622  #ifdef ALLOW_OBCS  #ifdef ALLOW_OBCS
623  C--   Apply open boundary conditions  C-     Apply open boundary conditions
624        IF (useOBCS) THEN          IF (useOBCS) THEN
625         IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN           IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
626          CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
627         ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
628          CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
629         END IF  #ifdef ALLOW_PTRACERS
630        END IF           ELSEIF (tracerIdentity.GE.GAD_TR1) THEN
631              CALL OBCS_APPLY_PTRACER( bi, bj, k,
632         &         tracerIdentity-GAD_TR1+1, localTij, myThid )
633    #endif /* ALLOW_PTRACERS */
634             ENDIF
635            ENDIF
636  #endif /* ALLOW_OBCS */  #endif /* ALLOW_OBCS */
637    
638    C      end if/else update overlap-Only
639           ENDIF
640    
641  C--   End of Y direction  C--   End of Y direction
642        ENDIF        ENDIF
643    
# Line 370  C-    explicit advection is done ; store Line 649  C-    explicit advection is done ; store
649          DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
650           DO i=1-Olx,sNx+Olx           DO i=1-Olx,sNx+Olx
651            gTracer(i,j,k,bi,bj)=            gTracer(i,j,k,bi,bj)=
652       &     (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer       &     (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)
653           ENDDO           ENDDO
654          ENDDO          ENDDO
655        ELSE        ELSE
# Line 382  C-    horizontal advection done; store i Line 661  C-    horizontal advection done; store i
661         ENDDO         ENDDO
662        ENDIF        ENDIF
663    
664    #ifdef ALLOW_DIAGNOSTICS
665            IF ( useDiagnostics ) THEN
666              diagName = 'ADVx'//diagSufx
667              CALL DIAGNOSTICS_FILL(afx,diagName, k,1, 2,bi,bj, myThid)
668              diagName = 'ADVy'//diagSufx
669              CALL DIAGNOSTICS_FILL(afy,diagName, k,1, 2,bi,bj, myThid)
670            ENDIF
671    #endif
672    
673    #ifdef ALLOW_DEBUG
674          IF ( debugLevel .GE. debLevB
675         &   .AND. tracerIdentity.EQ.GAD_TEMPERATURE
676         &   .AND. k.LE.3 .AND. myIter.EQ.1+nIter0
677         &   .AND. nPx.EQ.1 .AND. nPy.EQ.1
678         &   .AND. useCubedSphereExchange ) THEN
679            CALL DEBUG_CS_CORNER_UV( ' afx,afy from GAD_ADVECTION',
680         &             afx,afy, k, standardMessageUnit,bi,bj,myThid )
681          ENDIF
682    #endif /* ALLOW_DEBUG */
683    
684  C--   End of K loop for horizontal fluxes  C--   End of K loop for horizontal fluxes
685        ENDDO        ENDDO
686    
687    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
688    
689        IF ( .NOT.implicitAdvection ) THEN        IF ( .NOT.implicitAdvection ) THEN
690  C--   Start of k loop for vertical flux  C--   Start of k loop for vertical flux
691         DO k=Nr,1,-1         DO k=Nr,1,-1
692  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
693           kkey = (igadkey-1)*Nr + k           kkey = (igadkey-1)*Nr + k
694  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
695  C--   kup    Cycles through 1,2 to point to w-layer above  C--   kUp    Cycles through 1,2 to point to w-layer above
696  C--   kDown  Cycles through 2,1 to point to w-layer below  C--   kDown  Cycles through 2,1 to point to w-layer below
697          kup  = 1+MOD(k+1,2)          kUp  = 1+MOD(k+1,2)
698          kDown= 1+MOD(k,2)          kDown= 1+MOD(k,2)
699  c       kp1=min(Nr,k+1)  c       kp1=min(Nr,k+1)
700          kp1Msk=1.          kp1Msk=1.
# Line 413  C- Surface interface : Line 714  C- Surface interface :
714           DO j=1-Oly,sNy+Oly           DO j=1-Oly,sNy+Oly
715            DO i=1-Olx,sNx+Olx            DO i=1-Olx,sNx+Olx
716             rTransKp1(i,j) = kp1Msk*rTrans(i,j)             rTransKp1(i,j) = kp1Msk*rTrans(i,j)
717               wFld(i,j)   = 0.
718             rTrans(i,j) = 0.             rTrans(i,j) = 0.
719             fVerT(i,j,kUp) = 0.             fVerT(i,j,kUp) = 0.
            af(i,j) = 0.  
720            ENDDO            ENDDO
721           ENDDO           ENDDO
722    
# Line 425  C- Interior interface : Line 726  C- Interior interface :
726           DO j=1-Oly,sNy+Oly           DO j=1-Oly,sNy+Oly
727            DO i=1-Olx,sNx+Olx            DO i=1-Olx,sNx+Olx
728             rTransKp1(i,j) = kp1Msk*rTrans(i,j)             rTransKp1(i,j) = kp1Msk*rTrans(i,j)
729               wFld(i,j)   = wVel(i,j,k,bi,bj)
730             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)
731       &                 *maskC(i,j,k-1,bi,bj)       &                 *maskC(i,j,k-1,bi,bj)
732             af(i,j) = 0.             fVerT(i,j,kUp) = 0.
733            ENDDO            ENDDO
734           ENDDO           ENDDO
735    
736  #ifdef ALLOW_GMREDI  #ifdef ALLOW_GMREDI
737  C--   Residual transp = Bolus transp + Eulerian transp  C--   Residual transp = Bolus transp + Eulerian transp
738           IF (useGMRedi)           IF (useGMRedi)
739       &   CALL GMREDI_CALC_WFLOW(       &     CALL GMREDI_CALC_WFLOW(
740       &                    rTrans, bi, bj, k, myThid)       U                 wFld, rTrans,
741         I                 k, bi, bj, myThid )
742  #endif /* ALLOW_GMREDI */  #endif /* ALLOW_GMREDI */
743    
744  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
# Line 446  CADJ &     = comlev1_bibj_k_gad, key=kke Line 749  CADJ &     = comlev1_bibj_k_gad, key=kke
749  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
750    
751  C-    Compute vertical advective flux in the interior:  C-    Compute vertical advective flux in the interior:
752           IF (vertAdvecScheme.EQ.ENUM_FLUX_LIMIT) THEN           IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
753            CALL GAD_FLUXLIMIT_ADV_R(       &      .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
754       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)             CALL GAD_DST2U1_ADV_R( bi,bj,k, advectionScheme,
755         I                            dTtracerLev(k),rTrans,wFld,localTijk,
756         O                            fVerT(1-Olx,1-Oly,kUp), myThid )
757             ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
758               CALL GAD_FLUXLIMIT_ADV_R( bi,bj,k, dTtracerLev(k),
759         I                               rTrans, wFld, localTijk,
760         O                               fVerT(1-Olx,1-Oly,kUp), myThid )
761           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3 ) THEN           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3 ) THEN
762            CALL GAD_DST3_ADV_R(             CALL GAD_DST3_ADV_R(      bi,bj,k, dTtracerLev(k),
763       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)       I                               rTrans, wFld, localTijk,
764         O                               fVerT(1-Olx,1-Oly,kUp), myThid )
765           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
766            CALL GAD_DST3FL_ADV_R(             CALL GAD_DST3FL_ADV_R(    bi,bj,k, dTtracerLev(k),
767       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)       I                               rTrans, wFld, localTijk,
768         O                               fVerT(1-Olx,1-Oly,kUp), myThid )
769           ELSE           ELSE
770            STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'            STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
771           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  
772    
773  C- end Surface/Interior if bloc  C- end Surface/Interior if bloc
774          ENDIF          ENDIF
# Line 478  CADJ &     = comlev1_bibj_k_gad, key=kke Line 783  CADJ &     = comlev1_bibj_k_gad, key=kke
783  C--   Divergence of vertical fluxes  C--   Divergence of vertical fluxes
784          DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
785           DO i=1-Olx,sNx+Olx           DO i=1-Olx,sNx+Olx
786            localTij(i,j)=localTijk(i,j,k)-deltaTtracer*            localTij(i,j)=localTijk(i,j,k)-dTtracerLev(k)*
787       &     _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &     _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
788       &     *recip_rA(i,j,bi,bj)       &     *recip_rA(i,j,bi,bj)
789       &     *( fVerT(i,j,kUp)-fVerT(i,j,kDown)       &     *( fVerT(i,j,kDown)-fVerT(i,j,kUp)
790       &       -tracer(i,j,k,bi,bj)*(rTrans(i,j)-rTransKp1(i,j))       &       -tracer(i,j,k,bi,bj)*(rTransKp1(i,j)-rTrans(i,j))
791       &      )*rkFac       &      )*rkSign
792            gTracer(i,j,k,bi,bj)=            gTracer(i,j,k,bi,bj)=
793       &     (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer       &     (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)
794           ENDDO           ENDDO
795          ENDDO          ENDDO
796    
797    #ifdef ALLOW_DIAGNOSTICS
798            IF ( useDiagnostics ) THEN
799              diagName = 'ADVr'//diagSufx
800              CALL DIAGNOSTICS_FILL( fVerT(1-Olx,1-Oly,kUp),
801         &                           diagName, k,1, 2,bi,bj, myThid)
802            ENDIF
803    #endif
804    
805  C--   End of K loop for vertical flux  C--   End of K loop for vertical flux
806         ENDDO         ENDDO
807  C--   end of if not.implicitAdvection block  C--   end of if not.implicitAdvection block
808        ENDIF        ENDIF
809    
810        RETURN        RETURN
811        END        END

Legend:
Removed from v.1.23  
changed lines
  Added in v.1.41

  ViewVC Help
Powered by ViewVC 1.1.22