/[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.29 by jmc, Fri Sep 24 16:52:44 2004 UTC revision 1.30 by jmc, Mon Sep 27 14:42:40 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 88  C  maskLocW      :: 2-D array for mask a Line 89  C  maskLocW      :: 2-D array for mask a
89  C  maskLocS      :: 2-D array for mask at South points  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 96  C  xA,yA         :: areas of X and Y fac Line 99  C  xA,yA         :: areas of X and Y fac
99  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
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
103  C  afx           :: 2-D array for horizontal advective flux, x direction  C  afx           :: 2-D array for horizontal advective flux, x direction
104  C  afy           :: 2-D array for horizontal advective flux, y direction  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
# Line 104  C  localTijk     :: 3-D array, temporary Line 108  C  localTijk     :: 3-D array, temporary
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)        _RS maskLocW(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
121        _RS maskLocS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _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 120  C                :: multi-dim advection. Line 128  C                :: multi-dim advection.
128        _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
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)
132        _RL afx     (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL afx     (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
133        _RL afy     (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _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)
# Line 127  C                :: multi-dim advection. Line 136  C                :: multi-dim advection.
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, withSigns        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 N_edge, S_edge, E_edge, W_edge
143  CEOP  CEOP
144    
145  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
# Line 170  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 191  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 */
# Line 199  C--   Residual transp = Bolus transp + E Line 238  C--   Residual transp = Bolus transp + E
238  C--   Make local copy of tracer array and mask West & South  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)           maskLocW(i,j)=maskW(i,j,k,bi,bj)
243          maskLocS(i,j)=maskS(i,j,k,bi,bj)           maskLocS(i,j)=maskS(i,j,k,bi,bj)
244         ENDDO         ENDDO
245        ENDDO        ENDDO
246    
# Line 210  C--   Make local copy of tracer array an Line 249  C--   Make local copy of tracer array an
249          CALL FILL_CS_CORNER_UV_RS(          CALL FILL_CS_CORNER_UV_RS(
250       &            withSigns, maskLocW,maskLocS, bi,bj, myThid )       &            withSigns, maskLocW,maskLocS, bi,bj, myThid )
251        ENDIF        ENDIF
 #ifdef ALLOW_EXCH2  
        myTile = W2_myTileList(bi)  
        nCFace = exch2_myFace(myTile)  
 #else  
        nCFace = bi  
 #endif  
       IF (useCubedSphereExchange) THEN  
   
        nipass=3  
 #ifdef ALLOW_AUTODIFF_TAMC  
        if ( nipass.GT.maxcube )  
      &      STOP 'maxcube needs to be = 3'  
 #endif  
       ELSE  
        nipass=1  
       ENDIF  
252    
253  C--   Multiple passes for different directions on different tiles  C--   Multiple passes for different directions on different tiles
254  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 238  C--   For cube need one pass for each of Line 261  C--   For cube need one pass for each of
261           ENDIF           ENDIF
262  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
263    
264        IF (nipass.EQ.3) THEN        interiorOnly = .FALSE.
265         calc_fluxes_X=.FALSE.        overlapOnly  = .FALSE.
266         calc_fluxes_Y=.FALSE.        IF (useCubedSphereExchange) THEN
267         IF (ipass.EQ.1 .AND. (nCFace.EQ.1 .OR. nCFace.EQ.2) ) THEN  #ifdef MULTIDIM_OLD_VERSION
268          calc_fluxes_X=.TRUE.  C-    CubedSphere : pass 3 times, with full update of local tracer field
269         ELSEIF (ipass.EQ.1 .AND. (nCFace.EQ.4 .OR. nCFace.EQ.5) ) THEN         IF (ipass.EQ.1) THEN
270          calc_fluxes_Y=.TRUE.          calc_fluxes_X = nCFace.EQ.1 .OR. nCFace.EQ.2
271         ELSEIF (ipass.EQ.2 .AND. (nCFace.EQ.1 .OR. nCFace.EQ.6) ) THEN          calc_fluxes_Y = nCFace.EQ.4 .OR. nCFace.EQ.5
272          calc_fluxes_Y=.TRUE.         ELSEIF (ipass.EQ.2) THEN
273         ELSEIF (ipass.EQ.2 .AND. (nCFace.EQ.3 .OR. nCFace.EQ.4) ) THEN          calc_fluxes_X = nCFace.EQ.3 .OR. nCFace.EQ.4
274          calc_fluxes_X=.TRUE.          calc_fluxes_Y = nCFace.EQ.6 .OR. nCFace.EQ.1
275         ELSEIF (ipass.EQ.3 .AND. (nCFace.EQ.2 .OR. nCFace.EQ.3) ) THEN  #else /* MULTIDIM_OLD_VERSION */
276          calc_fluxes_Y=.TRUE.  C-    CubedSphere : pass 3 times, with partial update of local tracer field
277         ELSEIF (ipass.EQ.3 .AND. (nCFace.EQ.5 .OR. nCFace.EQ.6) ) THEN         IF (ipass.EQ.1) THEN
278          calc_fluxes_X=.TRUE.          overlapOnly  = MOD(nCFace,3).EQ.0
279            interiorOnly = MOD(nCFace,3).NE.0
280            calc_fluxes_X = nCFace.EQ.6 .OR. nCFace.EQ.1 .OR. nCFace.EQ.2
281            calc_fluxes_Y = nCFace.EQ.3 .OR. nCFace.EQ.4 .OR. nCFace.EQ.5
282           ELSEIF (ipass.EQ.2) THEN
283            overlapOnly  = MOD(nCFace,3).EQ.2
284            calc_fluxes_X = nCFace.EQ.2 .OR. nCFace.EQ.3 .OR. nCFace.EQ.4
285            calc_fluxes_Y = nCFace.EQ.5 .OR. nCFace.EQ.6 .OR. nCFace.EQ.1
286    #endif /* MULTIDIM_OLD_VERSION */
287           ELSE
288            calc_fluxes_X = nCFace.EQ.5 .OR. nCFace.EQ.6
289            calc_fluxes_Y = nCFace.EQ.2 .OR. nCFace.EQ.3
290         ENDIF         ENDIF
291        ELSE        ELSE
292         calc_fluxes_X=.TRUE.  C-    not CubedSphere
293         calc_fluxes_Y=.TRUE.          calc_fluxes_X = MOD(ipass,2).EQ.1
294            calc_fluxes_Y = .NOT.calc_fluxes_X
295        ENDIF        ENDIF
296    
297  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
298  C--   X direction  C--   X direction
299        IF (calc_fluxes_X) THEN        IF (calc_fluxes_X) THEN
300    
301  C--   Internal exchange for calculations in X  C-     Do not compute fluxes if
302        IF (useCubedSphereExchange) THEN  C       a) needed in overlap only
303    C   and b) the overlap of myTile are not cube-face Edges
304           IF ( .NOT.overlapOnly .OR. N_edge .OR. S_edge ) THEN
305    
306    C-     Internal exchange for calculations in X
307    #ifdef MULTIDIM_OLD_VERSION
308            IF ( useCubedSphereExchange ) THEN
309    #else
310            IF ( useCubedSphereExchange .AND.
311         &       ( overlapOnly .OR. ipass.EQ.1 ) ) THEN
312    #endif
313           CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )           CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )
314        ENDIF          ENDIF
315    
316  C-    Advective flux in X  C-     Advective flux in X
317        DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
318         DO i=1-Olx,sNx+Olx           DO i=1-Olx,sNx+Olx
319          afx(i,j) = 0.            af(i,j) = 0.
320         ENDDO           ENDDO
321        ENDDO          ENDDO
322    
323  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
324  #ifndef DISABLE_MULTIDIM_ADVECTION  #ifndef DISABLE_MULTIDIM_ADVECTION
# Line 282  CADJ &     comlev1_bibj_k_gad_pass, key= Line 327  CADJ &     comlev1_bibj_k_gad_pass, key=
327  #endif  #endif
328  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
329    
330        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN          IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
331          CALL GAD_FLUXLIMIT_ADV_X( bi,bj,k, deltaTtracer,            CALL GAD_FLUXLIMIT_ADV_X( bi,bj,k, deltaTtracer,
332       I                            uTrans, uVel, maskLocW, localTij,       I                              uTrans, uVel, maskLocW, localTij,
333       O                            afx, myThid )       O                              af, myThid )
334        ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
335          CALL GAD_DST3_ADV_X(      bi,bj,k, deltaTtracer,            CALL GAD_DST3_ADV_X(      bi,bj,k, deltaTtracer,
336       I                            uTrans, uVel, maskLocW, localTij,       I                              uTrans, uVel, maskLocW, localTij,
337       O                            afx, myThid )       O                              af, myThid )
338        ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN          ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
339          CALL GAD_DST3FL_ADV_X(    bi,bj,k, deltaTtracer,            CALL GAD_DST3FL_ADV_X(    bi,bj,k, deltaTtracer,
340       I                            uTrans, uVel, maskLocW, localTij,       I                              uTrans, uVel, maskLocW, localTij,
341       O                            afx, myThid )       O                              af, myThid )
342        ELSE          ELSE
343         STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'           STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'
344        ENDIF          ENDIF
345    
346        DO j=1-Oly,sNy+Oly  C-     Advective flux in X : done
347         DO i=1-Olx,sNx+Olx-1         ENDIF
348          localTij(i,j)=localTij(i,j)-deltaTtracer*  
349       &    _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)  C-     Internal exchange for next calculations in Y
350       &    *recip_rA(i,j,bi,bj)         IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
351       &    *( afx(i+1,j)-afx(i,j)           CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )
352       &      -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))         ENDIF
353       &     )  
354         ENDDO  C-     Update the local tracer field where needed:
355        ENDDO  
356    C      update in overlap-Only
357           IF ( overlapOnly ) THEN
358            iMinUpd = 1-Olx+1
359            iMaxUpd = sNx+Olx-1
360    C- notes: these 2 lines below have no real effect (because recip_hFac=0
361    C         in corner region) but safer to keep them.
362            IF ( W_edge ) iMinUpd = 1
363            IF ( E_edge ) iMaxUpd = sNx
364    
365            IF ( S_edge ) THEN
366             DO j=1-Oly,0
367              DO i=iMinUpd,iMaxUpd
368               localTij(i,j)=localTij(i,j)-deltaTtracer*
369         &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
370         &       *recip_rA(i,j,bi,bj)
371         &       *( af(i+1,j)-af(i,j)
372         &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
373         &        )
374              ENDDO
375             ENDDO
376            ENDIF
377            IF ( N_edge ) THEN
378             DO j=sNy+1,sNy+Oly
379              DO i=iMinUpd,iMaxUpd
380               localTij(i,j)=localTij(i,j)-deltaTtracer*
381         &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
382         &       *recip_rA(i,j,bi,bj)
383         &       *( af(i+1,j)-af(i,j)
384         &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
385         &        )
386              ENDDO
387             ENDDO
388            ENDIF
389    
390           ELSE
391    C      do not only update the overlap
392            jMinUpd = 1-Oly
393            jMaxUpd = sNy+Oly
394            IF ( interiorOnly .AND. S_edge ) jMinUpd = 1
395            IF ( interiorOnly .AND. N_edge ) jMaxUpd = sNy
396            DO j=jMinUpd,jMaxUpd
397             DO i=1-Olx+1,sNx+Olx-1
398               localTij(i,j)=localTij(i,j)-deltaTtracer*
399         &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
400         &       *recip_rA(i,j,bi,bj)
401         &       *( af(i+1,j)-af(i,j)
402         &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
403         &        )
404             ENDDO
405            ENDDO
406    C-      keep advective flux (for diagnostics)
407            DO j=1-Oly,sNy+Oly
408             DO i=1-Olx,sNx+Olx
409              afx(i,j) = af(i,j)
410             ENDDO
411            ENDDO
412    
413  #ifdef ALLOW_OBCS  #ifdef ALLOW_OBCS
414  C--   Apply open boundary conditions  C-     Apply open boundary conditions
415        IF (useOBCS) THEN          IF ( useOBCS ) THEN
416         IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN           IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
417          CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
418         ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
419          CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
420         END IF           ENDIF
421        END IF          ENDIF
422  #endif /* ALLOW_OBCS */  #endif /* ALLOW_OBCS */
423    
424    C-     end if/else update overlap-Only
425           ENDIF
426            
427  C--   End of X direction  C--   End of X direction
428        ENDIF        ENDIF
429    
# Line 327  C---+----1----+----2----+----3----+----4 Line 431  C---+----1----+----2----+----3----+----4
431  C--   Y direction  C--   Y direction
432        IF (calc_fluxes_Y) THEN        IF (calc_fluxes_Y) THEN
433    
434  C--   Internal exchange for calculations in Y  C-     Do not compute fluxes if
435        IF (useCubedSphereExchange) THEN  C       a) needed in overlap only
436    C   and b) the overlap of myTile are not cube-face edges
437           IF ( .NOT.overlapOnly .OR. E_edge .OR. W_edge ) THEN
438    
439    C-     Internal exchange for calculations in Y
440    #ifdef MULTIDIM_OLD_VERSION
441            IF ( useCubedSphereExchange ) THEN
442    #else
443            IF ( useCubedSphereExchange .AND.
444         &       ( overlapOnly .OR. ipass.EQ.1 ) ) THEN
445    #endif
446           CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )           CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )
447        ENDIF          ENDIF
448    
449  C-    Advective flux in Y  C-     Advective flux in Y
450        DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
451         DO i=1-Olx,sNx+Olx           DO i=1-Olx,sNx+Olx
452          afy(i,j) = 0.            af(i,j) = 0.
453         ENDDO           ENDDO
454        ENDDO          ENDDO
455    
456  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
457  #ifndef DISABLE_MULTIDIM_ADVECTION  #ifndef DISABLE_MULTIDIM_ADVECTION
# Line 346  CADJ &     comlev1_bibj_k_gad_pass, key= Line 460  CADJ &     comlev1_bibj_k_gad_pass, key=
460  #endif  #endif
461  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
462    
463        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN          IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
464          CALL GAD_FLUXLIMIT_ADV_Y( bi,bj,k, deltaTtracer,            CALL GAD_FLUXLIMIT_ADV_Y( bi,bj,k, deltaTtracer,
465       I                            vTrans, vVel, maskLocS, localTij,       I                              vTrans, vVel, maskLocS, localTij,
466       O                            afy, myThid )       O                              af, myThid )
467        ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
468          CALL GAD_DST3_ADV_Y(      bi,bj,k, deltaTtracer,            CALL GAD_DST3_ADV_Y(      bi,bj,k, deltaTtracer,
469       I                            vTrans, vVel, maskLocS, localTij,       I                              vTrans, vVel, maskLocS, localTij,
470       O                            afy, myThid )       O                              af, myThid )
471        ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN          ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
472          CALL GAD_DST3FL_ADV_Y(    bi,bj,k, deltaTtracer,            CALL GAD_DST3FL_ADV_Y(    bi,bj,k, deltaTtracer,
473       I                            vTrans, vVel, maskLocS, localTij,       I                              vTrans, vVel, maskLocS, localTij,
474       O                            afy, myThid )       O                              af, myThid )
475        ELSE          ELSE
476         STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'           STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
477        ENDIF          ENDIF
478    
479        DO j=1-Oly,sNy+Oly-1  C-     Advective flux in Y : done
480         DO i=1-Olx,sNx+Olx         ENDIF
481          localTij(i,j)=localTij(i,j)-deltaTtracer*  
482       &    _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)  C-     Internal exchange for next calculations in X
483       &    *recip_rA(i,j,bi,bj)         IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
484       &    *( afy(i,j+1)-afy(i,j)           CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )
485       &      -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))         ENDIF
486       &     )  
487         ENDDO  C-     Update the local tracer field where needed:
488        ENDDO  
489    C      update in overlap-Only
490           IF ( overlapOnly ) THEN
491            jMinUpd = 1-Oly+1
492            jMaxUpd = sNy+Oly-1
493    C- notes: these 2 lines below have no real effect (because recip_hFac=0
494    C         in corner region) but safer to keep them.
495            IF ( S_edge ) jMinUpd = 1
496            IF ( N_edge ) jMaxUpd = sNy
497    
498            IF ( W_edge ) THEN
499             DO j=jMinUpd,jMaxUpd
500              DO i=1-Olx,0
501               localTij(i,j)=localTij(i,j)-deltaTtracer*
502         &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
503         &       *recip_rA(i,j,bi,bj)
504         &       *( af(i,j+1)-af(i,j)
505         &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
506         &        )
507              ENDDO
508             ENDDO
509            ENDIF
510            IF ( E_edge ) THEN
511             DO j=jMinUpd,jMaxUpd
512              DO i=sNx+1,sNx+Olx
513               localTij(i,j)=localTij(i,j)-deltaTtracer*
514         &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
515         &       *recip_rA(i,j,bi,bj)
516         &       *( af(i,j+1)-af(i,j)
517         &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
518         &        )
519              ENDDO
520             ENDDO
521            ENDIF
522    
523           ELSE
524    C      do not only update the overlap
525            iMinUpd = 1-Olx
526            iMaxUpd = sNx+Olx
527            IF ( interiorOnly .AND. W_edge ) iMinUpd = 1
528            IF ( interiorOnly .AND. E_edge ) iMaxUpd = sNx
529            DO j=1-Oly+1,sNy+Oly-1
530             DO i=iMinUpd,iMaxUpd
531               localTij(i,j)=localTij(i,j)-deltaTtracer*
532         &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
533         &       *recip_rA(i,j,bi,bj)
534         &       *( af(i,j+1)-af(i,j)
535         &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
536         &        )
537             ENDDO
538            ENDDO
539    C-      keep advective flux (for diagnostics)
540            DO j=1-Oly,sNy+Oly
541             DO i=1-Olx,sNx+Olx
542              afy(i,j) = af(i,j)
543             ENDDO
544            ENDDO
545    
546  #ifdef ALLOW_OBCS  #ifdef ALLOW_OBCS
547  C--   Apply open boundary conditions  C-     Apply open boundary conditions
548        IF (useOBCS) THEN          IF (useOBCS) THEN
549         IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN           IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
550          CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
551         ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
552          CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
553         END IF           ENDIF
554        END IF          ENDIF
555  #endif /* ALLOW_OBCS */  #endif /* ALLOW_OBCS */
556    
557    C      end if/else update overlap-Only
558           ENDIF
559    
560  C--   End of Y direction  C--   End of Y direction
561        ENDIF        ENDIF
562    
# Line 409  C-    horizontal advection done; store i Line 582  C-    horizontal advection done; store i
582    
583  #ifdef ALLOW_DEBUG  #ifdef ALLOW_DEBUG
584        IF ( debugLevel .GE. debLevB        IF ( debugLevel .GE. debLevB
585       &   .AND. k.EQ.3 .AND. myIter.EQ.1+nIter0       &   .AND. tracerIdentity.EQ.GAD_TEMPERATURE
586         &   .AND. k.LE.3 .AND. myIter.EQ.1+nIter0
587       &   .AND. nPx.EQ.1 .AND. nPy.EQ.1       &   .AND. nPx.EQ.1 .AND. nPy.EQ.1
588       &   .AND. useCubedSphereExchange ) THEN       &   .AND. useCubedSphereExchange ) THEN
589          CALL DEBUG_CS_CORNER_UV( ' afx,afy from GAD_ADVECTION',          CALL DEBUG_CS_CORNER_UV( ' afx,afy from GAD_ADVECTION',

Legend:
Removed from v.1.29  
changed lines
  Added in v.1.30

  ViewVC Help
Powered by ViewVC 1.1.22