/[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.26 by cnh, Wed Jul 7 20:09:42 2004 UTC revision 1.31 by heimbach, Wed Sep 29 04:53:30 2004 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 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  #ifdef ALLOW_EXCH2
53  #include "W2_EXCH2_TOPOLOGY.h"  #include "W2_EXCH2_TOPOLOGY.h"
# Line 81  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
# Line 92  C  uTrans,vTrans :: 2-D arrays of volume Line 100  C  uTrans,vTrans :: 2-D arrays of volume
100  C  rTrans        :: 2-D arrays of volume transports at W points  C  rTrans        :: 2-D arrays of volume transports at W points
101  C  rTransKp1     :: vertical volume transport at interface k+1  C  rTransKp1     :: vertical volume transport at interface k+1
102  C  af            :: 2-D array for horizontal advective flux  C  af            :: 2-D array for horizontal advective flux
103    C  afx           :: 2-D array for horizontal advective flux, x direction
104    C  afy           :: 2-D array for horizontal advective flux, y direction
105  C  fVerT         :: 2 1/2D arrays for vertical advective flux  C  fVerT         :: 2 1/2D arrays for vertical advective flux
106  C  localTij      :: 2-D array, temporary local copy of tracer fld  C  localTij      :: 2-D array, temporary local copy of tracer fld
107  C  localTijk     :: 3-D array, temporary local copy of tracer fld  C  localTijk     :: 3-D array, temporary local copy of tracer fld
108  C  kp1Msk        :: flag (0,1) for over-riding mask for W levels  C  kp1Msk        :: flag (0,1) for over-riding mask for W levels
109  C  calc_fluxes_X :: logical to indicate to calculate fluxes in X dir  C  calc_fluxes_X :: logical to indicate to calculate fluxes in X dir
110  C  calc_fluxes_Y :: logical to indicate to calculate fluxes in Y dir  C  calc_fluxes_Y :: logical to indicate to calculate fluxes in Y dir
111    C  interiorOnly  :: only update the interior of myTile, but not the edges
112    C  overlapOnly   :: only update the edges of myTile, but not the interior
113  C  nipass        :: number of passes in multi-dimensional method  C  nipass        :: number of passes in multi-dimensional method
114  C  ipass         :: number of the current pass being made  C  ipass         :: number of the current pass being made
115  C  myTile        :: variables used to determine which cube face  C  myTile        :: variables used to determine which cube face
116  C  nCFace        :: owns a tile for cube grid runs using  C  nCFace        :: owns a tile for cube grid runs using
117  C                :: multi-dim advection.  C                :: multi-dim advection.
118    C [N,S,E,W]_edge :: true if N,S,E,W edge of myTile is an Edge of the cube
119        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
120          _RS maskLocW(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
121          _RS maskLocS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
122        INTEGER iMin,iMax,jMin,jMax        INTEGER iMin,iMax,jMin,jMax
123          INTEGER iMinUpd,iMaxUpd,jMinUpd,jMaxUpd
124        INTEGER i,j,k,kup,kDown        INTEGER i,j,k,kup,kDown
125        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
126        _RS yA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS yA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 113  C                :: multi-dim advection. Line 129  C                :: multi-dim advection.
129        _RL rTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
130        _RL rTransKp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rTransKp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
131        _RL af      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL af      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
132          _RL afx     (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
133          _RL afy     (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
134        _RL fVerT   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerT   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
135        _RL localTij(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL localTij(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
136        _RL localTijk(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL localTijk(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
137        _RL kp1Msk        _RL kp1Msk
138        LOGICAL calc_fluxes_X,calc_fluxes_Y        LOGICAL calc_fluxes_X, calc_fluxes_Y, withSigns
139          LOGICAL interiorOnly, overlapOnly
140        INTEGER nipass,ipass        INTEGER nipass,ipass
141        INTEGER myTile, nCFace        INTEGER myTile, nCFace
142        LOGICAL southWestCorner        LOGICAL N_edge, S_edge, E_edge, W_edge
       LOGICAL southEastCorner  
       LOGICAL northWestCorner  
       LOGICAL northEastCorner  
143  CEOP  CEOP
144    
145  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
# Line 165  C     uninitialised but inert locations. Line 181  C     uninitialised but inert locations.
181         ENDDO         ENDDO
182        ENDDO        ENDDO
183    
184    C--   Set tile-specific parameters for horizontal fluxes
185          IF (useCubedSphereExchange) THEN
186           nipass=3
187    #ifdef ALLOW_AUTODIFF_TAMC
188           IF ( nipass.GT.maxcube ) STOP 'maxcube needs to be = 3'
189    #endif
190    #ifdef ALLOW_EXCH2
191           myTile = W2_myTileList(bi)
192           nCFace = exch2_myFace(myTile)
193           N_edge = exch2_isNedge(myTile).EQ.1
194           S_edge = exch2_isSedge(myTile).EQ.1
195           E_edge = exch2_isEedge(myTile).EQ.1
196           W_edge = exch2_isWedge(myTile).EQ.1
197    #else
198           nCFace = bi
199           N_edge = .TRUE.
200           S_edge = .TRUE.
201           E_edge = .TRUE.
202           W_edge = .TRUE.
203    #endif
204          ELSE
205           nipass=2
206           N_edge = .FALSE.
207           S_edge = .FALSE.
208           E_edge = .FALSE.
209           W_edge = .FALSE.
210          ENDIF
211    
212        iMin = 1-OLx        iMin = 1-OLx
213        iMax = sNx+OLx        iMax = sNx+OLx
214        jMin = 1-OLy        jMin = 1-OLy
# Line 186  C--   Get temporary terms used by tenden Line 230  C--   Get temporary terms used by tenden
230    
231  #ifdef ALLOW_GMREDI  #ifdef ALLOW_GMREDI
232  C--   Residual transp = Bolus transp + Eulerian transp  C--   Residual transp = Bolus transp + Eulerian transp
233         IF (useGMRedi)        IF (useGMRedi)
234       &   CALL GMREDI_CALC_UVFLOW(       &   CALL GMREDI_CALC_UVFLOW(
235       &            uTrans, vTrans, bi, bj, k, myThid)       &            uTrans, vTrans, bi, bj, k, myThid)
236  #endif /* ALLOW_GMREDI */  #endif /* ALLOW_GMREDI */
237    
238  C--   Make local copy of tracer array  C--   Make local copy of tracer array and mask West & South
239        DO j=1-OLy,sNy+OLy        DO j=1-OLy,sNy+OLy
240         DO i=1-OLx,sNx+OLx         DO i=1-OLx,sNx+OLx
241          localTij(i,j)=tracer(i,j,k,bi,bj)           localTij(i,j)=tracer(i,j,k,bi,bj)
242             maskLocW(i,j)=maskW(i,j,k,bi,bj)
243             maskLocS(i,j)=maskS(i,j,k,bi,bj)
244         ENDDO         ENDDO
245        ENDDO        ENDDO
246    
247  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  
248        IF (useCubedSphereExchange) THEN        IF (useCubedSphereExchange) THEN
249            withSigns = .FALSE.
250         nipass=3          CALL FILL_CS_CORNER_UV_RS(
251  #ifdef ALLOW_AUTODIFF_TAMC       &            withSigns, maskLocW,maskLocS, bi,bj, myThid )
        if ( nipass.GT.maxcube )  
      &      STOP 'maxcube needs to be = 3'  
 #endif  
       ELSE  
        nipass=1  
252        ENDIF        ENDIF
253  cph       nipass=1  #endif
254    
255  C--   Multiple passes for different directions on different tiles  C--   Multiple passes for different directions on different tiles
256  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 242  C--   For cube need one pass for each of Line 263  C--   For cube need one pass for each of
263           ENDIF           ENDIF
264  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
265    
266        IF (nipass.EQ.3) THEN        interiorOnly = .FALSE.
267         calc_fluxes_X=.FALSE.        overlapOnly  = .FALSE.
268         calc_fluxes_Y=.FALSE.        IF (useCubedSphereExchange) THEN
269         IF (ipass.EQ.1 .AND. (nCFace.EQ.1 .OR. nCFace.EQ.2) ) THEN  #ifdef MULTIDIM_OLD_VERSION
270          calc_fluxes_X=.TRUE.  C-    CubedSphere : pass 3 times, with full update of local tracer field
271         ELSEIF (ipass.EQ.1 .AND. (nCFace.EQ.4 .OR. nCFace.EQ.5) ) THEN         IF (ipass.EQ.1) THEN
272          calc_fluxes_Y=.TRUE.          calc_fluxes_X = nCFace.EQ.1 .OR. nCFace.EQ.2
273         ELSEIF (ipass.EQ.2 .AND. (nCFace.EQ.1 .OR. nCFace.EQ.6) ) THEN          calc_fluxes_Y = nCFace.EQ.4 .OR. nCFace.EQ.5
274          calc_fluxes_Y=.TRUE.         ELSEIF (ipass.EQ.2) THEN
275         ELSEIF (ipass.EQ.2 .AND. (nCFace.EQ.3 .OR. nCFace.EQ.4) ) THEN          calc_fluxes_X = nCFace.EQ.3 .OR. nCFace.EQ.4
276          calc_fluxes_X=.TRUE.          calc_fluxes_Y = nCFace.EQ.6 .OR. nCFace.EQ.1
277         ELSEIF (ipass.EQ.3 .AND. (nCFace.EQ.2 .OR. nCFace.EQ.3) ) THEN  #else /* MULTIDIM_OLD_VERSION */
278          calc_fluxes_Y=.TRUE.  C-    CubedSphere : pass 3 times, with partial update of local tracer field
279         ELSEIF (ipass.EQ.3 .AND. (nCFace.EQ.5 .OR. nCFace.EQ.6) ) THEN         IF (ipass.EQ.1) THEN
280          calc_fluxes_X=.TRUE.          overlapOnly  = MOD(nCFace,3).EQ.0
281            interiorOnly = MOD(nCFace,3).NE.0
282            calc_fluxes_X = nCFace.EQ.6 .OR. nCFace.EQ.1 .OR. nCFace.EQ.2
283            calc_fluxes_Y = nCFace.EQ.3 .OR. nCFace.EQ.4 .OR. nCFace.EQ.5
284           ELSEIF (ipass.EQ.2) THEN
285            overlapOnly  = MOD(nCFace,3).EQ.2
286            calc_fluxes_X = nCFace.EQ.2 .OR. nCFace.EQ.3 .OR. nCFace.EQ.4
287            calc_fluxes_Y = nCFace.EQ.5 .OR. nCFace.EQ.6 .OR. nCFace.EQ.1
288    #endif /* MULTIDIM_OLD_VERSION */
289           ELSE
290            calc_fluxes_X = nCFace.EQ.5 .OR. nCFace.EQ.6
291            calc_fluxes_Y = nCFace.EQ.2 .OR. nCFace.EQ.3
292         ENDIF         ENDIF
293        ELSE        ELSE
294         calc_fluxes_X=.TRUE.  C-    not CubedSphere
295         calc_fluxes_Y=.TRUE.          calc_fluxes_X = MOD(ipass,2).EQ.1
296            calc_fluxes_Y = .NOT.calc_fluxes_X
297        ENDIF        ENDIF
298    
299    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
300  C--   X direction  C--   X direction
301        IF (calc_fluxes_X) THEN        IF (calc_fluxes_X) THEN
302    
303  C--   Internal exchange for calculations in X  C-     Do not compute fluxes if
304        IF (useCubedSphereExchange) THEN  C       a) needed in overlap only
305  C--    For cube face corners we need to duplicate the  C   and b) the overlap of myTile are not cube-face Edges
306  C--    i-1 and i+1 values into the null space as follows:         IF ( .NOT.overlapOnly .OR. N_edge .OR. S_edge ) THEN
307  C  
308  C  #ifndef ALLOW_AUTODIFF_TAMC
309  C      o NW corner: copy T(    0,sNy  ) into T(    0,sNy+1) e.g.  C-     Internal exchange for calculations in X
310  C                      |  #ifdef MULTIDIM_OLD_VERSION
311  C         x T(0,sNy+1) |          IF ( useCubedSphereExchange ) THEN
312  C        /\            |  #else
313  C      --||------------|-----------          IF ( useCubedSphereExchange .AND.
314  C        ||            |       &       ( overlapOnly .OR. ipass.EQ.1 ) ) THEN
315  C         x T(0,sNy)   |   x T(1,sNy)  #endif
316  C                      |           CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )
317  C          ENDIF
318  C      o SW corner: copy T(0,1) into T(0,0) e.g.  #endif
319  C                      |  
320  C         x T(0,1)     |  x T(1,1)  C-     Advective flux in X
321  C        ||            |          DO j=1-Oly,sNy+Oly
322  C      --||------------|-----------           DO i=1-Olx,sNx+Olx
323  C        \/            |            af(i,j) = 0.
 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  ,1  )  
          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 )  
324           ENDDO           ENDDO
325          ENDDO          ENDDO
        ENDIF  
       ENDIF  
   
 C-    Advective flux in X  
       DO j=1-Oly,sNy+Oly  
        DO i=1-Olx,sNx+Olx  
         af(i,j) = 0.  
        ENDDO  
       ENDDO  
326    
327  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
328  #ifndef DISABLE_MULTIDIM_ADVECTION  #ifndef DISABLE_MULTIDIM_ADVECTION
# Line 349  CADJ &     comlev1_bibj_k_gad_pass, key= Line 331  CADJ &     comlev1_bibj_k_gad_pass, key=
331  #endif  #endif
332  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
333    
334        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN          IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
335         CALL GAD_FLUXLIMIT_ADV_X(            CALL GAD_FLUXLIMIT_ADV_X( bi,bj,k, deltaTtracer,
336       &      bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)       I                              uTrans, uVel, maskLocW, localTij,
337        ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN       O                              af, myThid )
338         CALL GAD_DST3_ADV_X(          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
339       &       bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)            CALL GAD_DST3_ADV_X(      bi,bj,k, deltaTtracer,
340        ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN       I                              uTrans, uVel, maskLocW, localTij,
341         CALL GAD_DST3FL_ADV_X(       O                              af, myThid )
342       &       bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)          ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
343        ELSE            CALL GAD_DST3FL_ADV_X(    bi,bj,k, deltaTtracer,
344         STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'       I                              uTrans, uVel, maskLocW, localTij,
345        ENDIF       O                              af, myThid )
346            ELSE
347        DO j=1-Oly,sNy+Oly           STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'
348         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  
349    
350  #ifdef ALLOW_OBCS  C-     Advective flux in X : done
351  C--   Apply open boundary conditions         ENDIF
       IF (useOBCS) THEN  
        IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN  
         CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )  
        ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN  
         CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )  
        END IF  
       END IF  
 #endif /* ALLOW_OBCS */  
352    
353  C--   End of X direction  #ifndef ALLOW_AUTODIFF_TAMC
354        ENDIF  C-     Internal exchange for next calculations in Y
355           IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
356             CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )
357           ENDIF
358    #endif
359    
360  C--   Y direction  C-     Update the local tracer field where needed:
       IF (calc_fluxes_Y) THEN  
361    
362        IF (useCubedSphereExchange) THEN  C      update in overlap-Only
363  C--   Internal exchange for calculations in Y         IF ( overlapOnly ) THEN
364  C--    For cube face corners we need to duplicate the          iMinUpd = 1-Olx+1
365  C--    j-1 and j+1 values into the null space as follows:          iMaxUpd = sNx+Olx-1
366  C  C- notes: these 2 lines below have no real effect (because recip_hFac=0
367  C      o SW corner: copy T(0,1) into T(0,0) e.g.  C         in corner region) but safer to keep them.
368  C                      |          IF ( W_edge ) iMinUpd = 1
369  C                      |  x T(1,1)          IF ( E_edge ) iMaxUpd = sNx
370  C                      |  
371  C      ----------------|-----------          IF ( S_edge ) THEN
372  C                      |           DO j=1-Oly,0
373  C         x T(0,0)<====== x T(1,0)            DO i=iMinUpd,iMaxUpd
374  C                      |             localTij(i,j)=localTij(i,j)-deltaTtracer*
375  C       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
376  C      o NW corner: copy T(    0,sNy  ) into T(    0,sNy+1) e.g.       &       *recip_rA(i,j,bi,bj)
377  C                      |       &       *( af(i+1,j)-af(i,j)
378  C         x T(0,sNy+1)<=== x T(1,sNy+1)       &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
379  C                      |       &        )
380  C      ----------------|-----------            ENDDO
 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 )  
381           ENDDO           ENDDO
382          ENDDO          ENDIF
383         ENDIF          IF ( N_edge ) THEN
384         IF ( southEastCorner ) THEN           DO j=sNy+1,sNy+Oly
385          DO J=1,Oly            DO i=iMinUpd,iMaxUpd
386           DO I=1,Olx             localTij(i,j)=localTij(i,j)-deltaTtracer*
387            localTij(sNx+i, 1-j ) = localTij(sNx+1-j, 1-i )       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
388         &       *recip_rA(i,j,bi,bj)
389         &       *( af(i+1,j)-af(i,j)
390         &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
391         &        )
392              ENDDO
393           ENDDO           ENDDO
394          ENDDO          ENDIF
395         ENDIF  
396         IF ( northWestCorner ) THEN         ELSE
397          DO J=1,Oly  C      do not only update the overlap
398           DO I=1,Olx          jMinUpd = 1-Oly
399            localTij( 1-i ,sNy+j) = localTij(j   ,sNy+i)          jMaxUpd = sNy+Oly
400            IF ( interiorOnly .AND. S_edge ) jMinUpd = 1
401            IF ( interiorOnly .AND. N_edge ) jMaxUpd = sNy
402            DO j=jMinUpd,jMaxUpd
403             DO i=1-Olx+1,sNx+Olx-1
404               localTij(i,j)=localTij(i,j)-deltaTtracer*
405         &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
406         &       *recip_rA(i,j,bi,bj)
407         &       *( af(i+1,j)-af(i,j)
408         &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
409         &        )
410           ENDDO           ENDDO
411          ENDDO          ENDDO
412         ENDIF  C-      keep advective flux (for diagnostics)
413         IF ( northEastCorner ) THEN          DO j=1-Oly,sNy+Oly
414          DO J=1,Oly           DO i=1-Olx,sNx+Olx
415           DO I=1,Olx            afx(i,j) = af(i,j)
           localTij(sNx+i,sNy+j) = localTij(sNx+1-j,sNy+i)  
416           ENDDO           ENDDO
417          ENDDO          ENDDO
418    
419    #ifdef ALLOW_OBCS
420    C-     Apply open boundary conditions
421            IF ( useOBCS ) THEN
422             IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
423              CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
424             ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
425              CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
426             ENDIF
427            ENDIF
428    #endif /* ALLOW_OBCS */
429    
430    C-     end if/else update overlap-Only
431         ENDIF         ENDIF
432            
433    C--   End of X direction
434        ENDIF        ENDIF
435    
436  C-    Advective flux in Y  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
437        DO j=1-Oly,sNy+Oly  C--   Y direction
438         DO i=1-Olx,sNx+Olx        IF (calc_fluxes_Y) THEN
439          af(i,j) = 0.  
440         ENDDO  C-     Do not compute fluxes if
441        ENDDO  C       a) needed in overlap only
442    C   and b) the overlap of myTile are not cube-face edges
443           IF ( .NOT.overlapOnly .OR. E_edge .OR. W_edge ) THEN
444    
445    #ifndef ALLOW_AUTODIFF_TAMC
446    C-     Internal exchange for calculations in Y
447    #ifdef MULTIDIM_OLD_VERSION
448            IF ( useCubedSphereExchange ) THEN
449    #else
450            IF ( useCubedSphereExchange .AND.
451         &       ( overlapOnly .OR. ipass.EQ.1 ) ) THEN
452    #endif
453             CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )
454            ENDIF
455    #endif
456    
457    C-     Advective flux in Y
458            DO j=1-Oly,sNy+Oly
459             DO i=1-Olx,sNx+Olx
460              af(i,j) = 0.
461             ENDDO
462            ENDDO
463    
464  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
465  #ifndef DISABLE_MULTIDIM_ADVECTION  #ifndef DISABLE_MULTIDIM_ADVECTION
# Line 472  CADJ &     comlev1_bibj_k_gad_pass, key= Line 468  CADJ &     comlev1_bibj_k_gad_pass, key=
468  #endif  #endif
469  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
470    
471        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN          IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
472         CALL GAD_FLUXLIMIT_ADV_Y(            CALL GAD_FLUXLIMIT_ADV_Y( bi,bj,k, deltaTtracer,
473       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)       I                              vTrans, vVel, maskLocS, localTij,
474        ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN       O                              af, myThid )
475         CALL GAD_DST3_ADV_Y(          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
476       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)            CALL GAD_DST3_ADV_Y(      bi,bj,k, deltaTtracer,
477        ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN       I                              vTrans, vVel, maskLocS, localTij,
478         CALL GAD_DST3FL_ADV_Y(       O                              af, myThid )
479       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)          ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
480        ELSE            CALL GAD_DST3FL_ADV_Y(    bi,bj,k, deltaTtracer,
481         STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'       I                              vTrans, vVel, maskLocS, localTij,
482        ENDIF       O                              af, myThid )
483            ELSE
484             STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
485            ENDIF
486    
487        DO j=1-Oly,sNy+Oly-1  C-     Advective flux in Y : done
488         DO i=1-Olx,sNx+Olx         ENDIF
489          localTij(i,j)=localTij(i,j)-deltaTtracer*  
490       &    _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)  #ifndef ALLOW_AUTODIFF_TAMC
491       &    *recip_rA(i,j,bi,bj)  C-     Internal exchange for next calculations in X
492       &    *( af(i,j+1)-af(i,j)         IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
493       &      -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))           CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )
494       &     )         ENDIF
495         ENDDO  #endif
496        ENDDO  
497    C-     Update the local tracer field where needed:
498    
499    C      update in overlap-Only
500           IF ( overlapOnly ) THEN
501            jMinUpd = 1-Oly+1
502            jMaxUpd = sNy+Oly-1
503    C- notes: these 2 lines below have no real effect (because recip_hFac=0
504    C         in corner region) but safer to keep them.
505            IF ( S_edge ) jMinUpd = 1
506            IF ( N_edge ) jMaxUpd = sNy
507    
508            IF ( W_edge ) THEN
509             DO j=jMinUpd,jMaxUpd
510              DO i=1-Olx,0
511               localTij(i,j)=localTij(i,j)-deltaTtracer*
512         &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
513         &       *recip_rA(i,j,bi,bj)
514         &       *( af(i,j+1)-af(i,j)
515         &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
516         &        )
517              ENDDO
518             ENDDO
519            ENDIF
520            IF ( E_edge ) THEN
521             DO j=jMinUpd,jMaxUpd
522              DO i=sNx+1,sNx+Olx
523               localTij(i,j)=localTij(i,j)-deltaTtracer*
524         &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
525         &       *recip_rA(i,j,bi,bj)
526         &       *( af(i,j+1)-af(i,j)
527         &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
528         &        )
529              ENDDO
530             ENDDO
531            ENDIF
532    
533           ELSE
534    C      do not only update the overlap
535            iMinUpd = 1-Olx
536            iMaxUpd = sNx+Olx
537            IF ( interiorOnly .AND. W_edge ) iMinUpd = 1
538            IF ( interiorOnly .AND. E_edge ) iMaxUpd = sNx
539            DO j=1-Oly+1,sNy+Oly-1
540             DO i=iMinUpd,iMaxUpd
541               localTij(i,j)=localTij(i,j)-deltaTtracer*
542         &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
543         &       *recip_rA(i,j,bi,bj)
544         &       *( af(i,j+1)-af(i,j)
545         &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
546         &        )
547             ENDDO
548            ENDDO
549    C-      keep advective flux (for diagnostics)
550            DO j=1-Oly,sNy+Oly
551             DO i=1-Olx,sNx+Olx
552              afy(i,j) = af(i,j)
553             ENDDO
554            ENDDO
555    
556  #ifdef ALLOW_OBCS  #ifdef ALLOW_OBCS
557  C--   Apply open boundary conditions  C-     Apply open boundary conditions
558        IF (useOBCS) THEN          IF (useOBCS) THEN
559         IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN           IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
560          CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
561         ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
562          CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
563         END IF           ENDIF
564        END IF          ENDIF
565  #endif /* ALLOW_OBCS */  #endif /* ALLOW_OBCS */
566    
567    C      end if/else update overlap-Only
568           ENDIF
569    
570  C--   End of Y direction  C--   End of Y direction
571        ENDIF        ENDIF
572    
# Line 530  C-    horizontal advection done; store i Line 590  C-    horizontal advection done; store i
590         ENDDO         ENDDO
591        ENDIF        ENDIF
592    
593    #ifdef ALLOW_DEBUG
594          IF ( debugLevel .GE. debLevB
595         &   .AND. tracerIdentity.EQ.GAD_TEMPERATURE
596         &   .AND. k.LE.3 .AND. myIter.EQ.1+nIter0
597         &   .AND. nPx.EQ.1 .AND. nPy.EQ.1
598         &   .AND. useCubedSphereExchange ) THEN
599            CALL DEBUG_CS_CORNER_UV( ' afx,afy from GAD_ADVECTION',
600         &             afx,afy, k, standardMessageUnit,bi,bj,myThid )
601          ENDIF
602    #endif /* ALLOW_DEBUG */
603    
604  C--   End of K loop for horizontal fluxes  C--   End of K loop for horizontal fluxes
605        ENDDO        ENDDO
606    
607    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
608    
609        IF ( .NOT.implicitAdvection ) THEN        IF ( .NOT.implicitAdvection ) THEN
610  C--   Start of k loop for vertical flux  C--   Start of k loop for vertical flux
611         DO k=Nr,1,-1         DO k=Nr,1,-1
# Line 563  C- Surface interface : Line 636  C- Surface interface :
636             rTransKp1(i,j) = kp1Msk*rTrans(i,j)             rTransKp1(i,j) = kp1Msk*rTrans(i,j)
637             rTrans(i,j) = 0.             rTrans(i,j) = 0.
638             fVerT(i,j,kUp) = 0.             fVerT(i,j,kUp) = 0.
            af(i,j) = 0.  
639            ENDDO            ENDDO
640           ENDDO           ENDDO
641    
# Line 575  C- Interior interface : Line 647  C- Interior interface :
647             rTransKp1(i,j) = kp1Msk*rTrans(i,j)             rTransKp1(i,j) = kp1Msk*rTrans(i,j)
648             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)
649       &                 *maskC(i,j,k-1,bi,bj)       &                 *maskC(i,j,k-1,bi,bj)
650             af(i,j) = 0.             fVerT(i,j,kUp) = 0.
651            ENDDO            ENDDO
652           ENDDO           ENDDO
653    
# Line 595  CADJ &     = comlev1_bibj_k_gad, key=kke Line 667  CADJ &     = comlev1_bibj_k_gad, key=kke
667    
668  C-    Compute vertical advective flux in the interior:  C-    Compute vertical advective flux in the interior:
669           IF (vertAdvecScheme.EQ.ENUM_FLUX_LIMIT) THEN           IF (vertAdvecScheme.EQ.ENUM_FLUX_LIMIT) THEN
670            CALL GAD_FLUXLIMIT_ADV_R(  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
671       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)             CALL GAD_FLUXLIMIT_ADV_R( bi,bj,k, deltaTtracer,
672         I                               rTrans, wVel, localTijk,
673         O                               fVerT(1-Olx,1-Oly,kUp), myThid )
674           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3 ) THEN           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3 ) THEN
675            CALL GAD_DST3_ADV_R(             CALL GAD_DST3_ADV_R(      bi,bj,k, deltaTtracer,
676       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)       I                               rTrans, wVel, localTijk,
677         O                               fVerT(1-Olx,1-Oly,kUp), myThid )
678           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
679            CALL GAD_DST3FL_ADV_R(             CALL GAD_DST3FL_ADV_R(    bi,bj,k, deltaTtracer,
680       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)       I                               rTrans, wVel, localTijk,
681         O                               fVerT(1-Olx,1-Oly,kUp), myThid )
682           ELSE           ELSE
683            STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'            STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
684           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  
685    
686  C- end Surface/Interior if bloc  C- end Surface/Interior if bloc
687          ENDIF          ENDIF

Legend:
Removed from v.1.26  
changed lines
  Added in v.1.31

  ViewVC Help
Powered by ViewVC 1.1.22