/[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.36 by mlosch, Mon Oct 10 05:53:49 2005 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
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
# Line 88  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
116    C  nCFace        :: owns a tile for cube grid runs using
117    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 106  C  ipass         :: number of the curren Line 129  C  ipass         :: number of the curren
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
142          LOGICAL N_edge, S_edge, E_edge, W_edge
143    #ifdef ALLOW_DIAGNOSTICS
144          CHARACTER*8 diagName
145          CHARACTER*4 GAD_DIAG_SUFX, diagSufx
146          EXTERNAL    GAD_DIAG_SUFX
147    #endif
148  CEOP  CEOP
149    
150  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
# Line 135  CEOP Line 168  CEOP
168            endif            endif
169  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
170    
171    #ifdef ALLOW_DIAGNOSTICS
172    C--   Set diagnostic suffix for the current tracer
173          IF ( useDiagnostics ) THEN
174            diagSufx = GAD_DIAG_SUFX( tracerIdentity, myThid )
175          ENDIF
176    #endif
177    
178  C--   Set up work arrays with valid (i.e. not NaN) values  C--   Set up work arrays with valid (i.e. not NaN) values
179  C     These inital values do not alter the numerical results. They  C     These inital values do not alter the numerical results. They
180  C     just ensure that all memory references are to valid floating  C     just ensure that all memory references are to valid floating
# Line 153  C     uninitialised but inert locations. Line 193  C     uninitialised but inert locations.
193         ENDDO         ENDDO
194        ENDDO        ENDDO
195    
196    C--   Set tile-specific parameters for horizontal fluxes
197          IF (useCubedSphereExchange) THEN
198           nipass=3
199    #ifdef ALLOW_AUTODIFF_TAMC
200           IF ( nipass.GT.maxcube ) STOP 'maxcube needs to be = 3'
201    #endif
202    #ifdef ALLOW_EXCH2
203           myTile = W2_myTileList(bi)
204           nCFace = exch2_myFace(myTile)
205           N_edge = exch2_isNedge(myTile).EQ.1
206           S_edge = exch2_isSedge(myTile).EQ.1
207           E_edge = exch2_isEedge(myTile).EQ.1
208           W_edge = exch2_isWedge(myTile).EQ.1
209    #else
210           nCFace = bi
211           N_edge = .TRUE.
212           S_edge = .TRUE.
213           E_edge = .TRUE.
214           W_edge = .TRUE.
215    #endif
216          ELSE
217           nipass=2
218           N_edge = .FALSE.
219           S_edge = .FALSE.
220           E_edge = .FALSE.
221           W_edge = .FALSE.
222          ENDIF
223    
224        iMin = 1-OLx        iMin = 1-OLx
225        iMax = sNx+OLx        iMax = sNx+OLx
226        jMin = 1-OLy        jMin = 1-OLy
# Line 174  C--   Get temporary terms used by tenden Line 242  C--   Get temporary terms used by tenden
242    
243  #ifdef ALLOW_GMREDI  #ifdef ALLOW_GMREDI
244  C--   Residual transp = Bolus transp + Eulerian transp  C--   Residual transp = Bolus transp + Eulerian transp
245         IF (useGMRedi)        IF (useGMRedi)
246       &   CALL GMREDI_CALC_UVFLOW(       &   CALL GMREDI_CALC_UVFLOW(
247       &            uTrans, vTrans, bi, bj, k, myThid)       &            uTrans, vTrans, bi, bj, k, myThid)
248  #endif /* ALLOW_GMREDI */  #endif /* ALLOW_GMREDI */
249    
250  C--   Make local copy of tracer array  C--   Make local copy of tracer array and mask West & South
251        DO j=1-OLy,sNy+OLy        DO j=1-OLy,sNy+OLy
252         DO i=1-OLx,sNx+OLx         DO i=1-OLx,sNx+OLx
253          localTij(i,j)=tracer(i,j,k,bi,bj)           localTij(i,j)=tracer(i,j,k,bi,bj)
254             maskLocW(i,j)=maskW(i,j,k,bi,bj)
255             maskLocS(i,j)=maskS(i,j,k,bi,bj)
256         ENDDO         ENDDO
257        ENDDO        ENDDO
258    
259    #ifndef ALLOW_AUTODIFF_TAMC
260        IF (useCubedSphereExchange) THEN        IF (useCubedSphereExchange) THEN
261         nipass=3          withSigns = .FALSE.
262  #ifdef ALLOW_AUTODIFF_TAMC          CALL FILL_CS_CORNER_UV_RS(
263         if ( nipass.GT.maxcube )       &            withSigns, maskLocW,maskLocS, bi,bj, myThid )
      &      STOP 'maxcube needs to be = 3'  
 #endif  
       ELSE  
        nipass=1  
264        ENDIF        ENDIF
265  cph       nipass=1  #endif
266    
267  C--   Multiple passes for different directions on different tiles  C--   Multiple passes for different directions on different tiles
268    C--   For cube need one pass for each of red, green and blue axes.
269        DO ipass=1,nipass        DO ipass=1,nipass
270  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
271           passkey = ipass + (k-1)      *maxcube           passkey = ipass + (k-1)      *maxcube
# Line 207  C--   Multiple passes for different dire Line 275  C--   Multiple passes for different dire
275           ENDIF           ENDIF
276  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
277    
278        IF (nipass.EQ.3) THEN        interiorOnly = .FALSE.
279         calc_fluxes_X=.FALSE.        overlapOnly  = .FALSE.
280         calc_fluxes_Y=.FALSE.        IF (useCubedSphereExchange) THEN
281         IF (ipass.EQ.1 .AND. (bi.EQ.1 .OR. bi.EQ.2) ) THEN  #ifdef MULTIDIM_OLD_VERSION
282          calc_fluxes_X=.TRUE.  C-    CubedSphere : pass 3 times, with full update of local tracer field
283         ELSEIF (ipass.EQ.1 .AND. (bi.EQ.4 .OR. bi.EQ.5) ) THEN         IF (ipass.EQ.1) THEN
284          calc_fluxes_Y=.TRUE.          calc_fluxes_X = nCFace.EQ.1 .OR. nCFace.EQ.2
285         ELSEIF (ipass.EQ.2 .AND. (bi.EQ.1 .OR. bi.EQ.6) ) THEN          calc_fluxes_Y = nCFace.EQ.4 .OR. nCFace.EQ.5
286          calc_fluxes_Y=.TRUE.         ELSEIF (ipass.EQ.2) THEN
287         ELSEIF (ipass.EQ.2 .AND. (bi.EQ.3 .OR. bi.EQ.4) ) THEN          calc_fluxes_X = nCFace.EQ.3 .OR. nCFace.EQ.4
288          calc_fluxes_X=.TRUE.          calc_fluxes_Y = nCFace.EQ.6 .OR. nCFace.EQ.1
289         ELSEIF (ipass.EQ.3 .AND. (bi.EQ.2 .OR. bi.EQ.3) ) THEN  #else /* MULTIDIM_OLD_VERSION */
290          calc_fluxes_Y=.TRUE.  C-    CubedSphere : pass 3 times, with partial update of local tracer field
291         ELSEIF (ipass.EQ.3 .AND. (bi.EQ.5 .OR. bi.EQ.6) ) THEN         IF (ipass.EQ.1) THEN
292          calc_fluxes_X=.TRUE.          overlapOnly  = MOD(nCFace,3).EQ.0
293            interiorOnly = MOD(nCFace,3).NE.0
294            calc_fluxes_X = nCFace.EQ.6 .OR. nCFace.EQ.1 .OR. nCFace.EQ.2
295            calc_fluxes_Y = nCFace.EQ.3 .OR. nCFace.EQ.4 .OR. nCFace.EQ.5
296           ELSEIF (ipass.EQ.2) THEN
297            overlapOnly  = MOD(nCFace,3).EQ.2
298            calc_fluxes_X = nCFace.EQ.2 .OR. nCFace.EQ.3 .OR. nCFace.EQ.4
299            calc_fluxes_Y = nCFace.EQ.5 .OR. nCFace.EQ.6 .OR. nCFace.EQ.1
300    #endif /* MULTIDIM_OLD_VERSION */
301           ELSE
302            calc_fluxes_X = nCFace.EQ.5 .OR. nCFace.EQ.6
303            calc_fluxes_Y = nCFace.EQ.2 .OR. nCFace.EQ.3
304         ENDIF         ENDIF
305        ELSE        ELSE
306         calc_fluxes_X=.TRUE.  C-    not CubedSphere
307         calc_fluxes_Y=.TRUE.          calc_fluxes_X = MOD(ipass,2).EQ.1
308            calc_fluxes_Y = .NOT.calc_fluxes_X
309        ENDIF        ENDIF
310    
311    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
312  C--   X direction  C--   X direction
313        IF (calc_fluxes_X) THEN        IF (calc_fluxes_X) THEN
314    
315  C--   Internal exchange for calculations in X  C-     Do not compute fluxes if
316        IF (useCubedSphereExchange) THEN  C       a) needed in overlap only
317         DO j=1,Oly  C   and b) the overlap of myTile are not cube-face Edges
318          DO i=1,Olx         IF ( .NOT.overlapOnly .OR. N_edge .OR. S_edge ) THEN
319           localTij( 1-i , 1-j )=localTij( 1-j ,    i    )  
320           localTij( 1-i ,sNy+j)=localTij( 1-j , sNy+1-i )  #ifndef ALLOW_AUTODIFF_TAMC
321           localTij(sNx+i, 1-j )=localTij(sNx+j,    i    )  C-     Internal exchange for calculations in X
322           localTij(sNx+i,sNy+j)=localTij(sNx+j, sNy+1-i )  #ifdef MULTIDIM_OLD_VERSION
323          ENDDO          IF ( useCubedSphereExchange ) THEN
324         ENDDO  #else
325        ENDIF          IF ( useCubedSphereExchange .AND.
326         &       ( overlapOnly .OR. ipass.EQ.1 ) ) THEN
327    #endif
328             CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )
329            ENDIF
330    #endif
331    
332  C-    Advective flux in X  C-     Advective flux in X
333        DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
334         DO i=1-Olx,sNx+Olx           DO i=1-Olx,sNx+Olx
335          af(i,j) = 0.            af(i,j) = 0.
336         ENDDO           ENDDO
337        ENDDO          ENDDO
338    
339  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
340  #ifndef DISABLE_MULTIDIM_ADVECTION  #ifndef DISABLE_MULTIDIM_ADVECTION
# Line 257  CADJ &     comlev1_bibj_k_gad_pass, key= Line 343  CADJ &     comlev1_bibj_k_gad_pass, key=
343  #endif  #endif
344  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
345    
346        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN          IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
347         CALL GAD_FLUXLIMIT_ADV_X(            CALL GAD_FLUXLIMIT_ADV_X( bi,bj,k, dTtracerLev(k),
348       &      bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)       I                              uTrans, uVel, maskLocW, localTij,
349        ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN       O                              af, myThid )
350         CALL GAD_DST3_ADV_X(          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
351       &       bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)            CALL GAD_DST3_ADV_X(      bi,bj,k, dTtracerLev(k),
352        ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN       I                              uTrans, uVel, maskLocW, localTij,
353         CALL GAD_DST3FL_ADV_X(       O                              af, myThid )
354       &       bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)          ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
355        ELSE            CALL GAD_DST3FL_ADV_X(    bi,bj,k, dTtracerLev(k),
356         STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'       I                              uTrans, uVel, maskLocW, localTij,
357        ENDIF       O                              af, myThid )
358            ELSE
359             STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'
360            ENDIF
361    
362        DO j=1-Oly,sNy+Oly  C-     Advective flux in X : done
363         DO i=1-Olx,sNx+Olx-1         ENDIF
364          localTij(i,j)=localTij(i,j)-deltaTtracer*  
365       &    _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)  #ifndef ALLOW_AUTODIFF_TAMC
366       &    *recip_rA(i,j,bi,bj)  C-     Internal exchange for next calculations in Y
367       &    *( af(i+1,j)-af(i,j)         IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
368       &      -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))           CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )
369       &     )         ENDIF
370         ENDDO  #endif
371        ENDDO  
372    C-     Update the local tracer field where needed:
373    
374    C      update in overlap-Only
375           IF ( overlapOnly ) THEN
376            iMinUpd = 1-Olx+1
377            iMaxUpd = sNx+Olx-1
378    C- notes: these 2 lines below have no real effect (because recip_hFac=0
379    C         in corner region) but safer to keep them.
380            IF ( W_edge ) iMinUpd = 1
381            IF ( E_edge ) iMaxUpd = sNx
382    
383            IF ( S_edge ) THEN
384             DO j=1-Oly,0
385              DO i=iMinUpd,iMaxUpd
386               localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
387         &       _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
394            ENDIF
395            IF ( N_edge ) THEN
396             DO j=sNy+1,sNy+Oly
397              DO i=iMinUpd,iMaxUpd
398               localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
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            ENDIF
407    
408           ELSE
409    C      do not only update the overlap
410            jMinUpd = 1-Oly
411            jMaxUpd = sNy+Oly
412            IF ( interiorOnly .AND. S_edge ) jMinUpd = 1
413            IF ( interiorOnly .AND. N_edge ) jMaxUpd = sNy
414            DO j=jMinUpd,jMaxUpd
415             DO i=1-Olx+1,sNx+Olx-1
416               localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
417         &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
418         &       *recip_rA(i,j,bi,bj)
419         &       *( af(i+1,j)-af(i,j)
420         &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
421         &        )
422             ENDDO
423            ENDDO
424    C-      keep advective flux (for diagnostics)
425            DO j=1-Oly,sNy+Oly
426             DO i=1-Olx,sNx+Olx
427              afx(i,j) = af(i,j)
428             ENDDO
429            ENDDO
430    
431  #ifdef ALLOW_OBCS  #ifdef ALLOW_OBCS
432  C--   Apply open boundary conditions  C-     Apply open boundary conditions
433        IF (useOBCS) THEN          IF ( useOBCS ) THEN
434         IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN           IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
435          CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
436         ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
437          CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
438         END IF  #ifdef ALLOW_PTRACERS
439        END IF           ELSEIF (tracerIdentity.GE.GAD_TR1) THEN
440              CALL OBCS_APPLY_PTRACER( bi, bj, k,
441         &         tracerIdentity-GAD_TR1+1, localTij, myThid )
442    #endif /* ALLOW_PTRACERS */
443             ENDIF
444            ENDIF
445  #endif /* ALLOW_OBCS */  #endif /* ALLOW_OBCS */
446    
447    C-     end if/else update overlap-Only
448           ENDIF
449            
450  C--   End of X direction  C--   End of X direction
451        ENDIF        ENDIF
452    
453    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
454  C--   Y direction  C--   Y direction
455        IF (calc_fluxes_Y) THEN        IF (calc_fluxes_Y) THEN
456    
457  C--   Internal exchange for calculations in Y  C-     Do not compute fluxes if
458        IF (useCubedSphereExchange) THEN  C       a) needed in overlap only
459         DO j=1,Oly  C   and b) the overlap of myTile are not cube-face edges
460          DO i=1,Olx         IF ( .NOT.overlapOnly .OR. E_edge .OR. W_edge ) THEN
461           localTij( 1-i , 1-j )=localTij(   j   , 1-i )  
462           localTij( 1-i ,sNy+j)=localTij(   j   ,sNy+i)  #ifndef ALLOW_AUTODIFF_TAMC
463           localTij(sNx+i, 1-j )=localTij(sNx+1-j, 1-i )  C-     Internal exchange for calculations in Y
464           localTij(sNx+i,sNy+j)=localTij(sNx+1-j,sNy+i)  #ifdef MULTIDIM_OLD_VERSION
465          ENDDO          IF ( useCubedSphereExchange ) THEN
466         ENDDO  #else
467        ENDIF          IF ( useCubedSphereExchange .AND.
468         &       ( overlapOnly .OR. ipass.EQ.1 ) ) THEN
469    #endif
470             CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )
471            ENDIF
472    #endif
473    
474  C-    Advective flux in Y  C-     Advective flux in Y
475        DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
476         DO i=1-Olx,sNx+Olx           DO i=1-Olx,sNx+Olx
477          af(i,j) = 0.            af(i,j) = 0.
478         ENDDO           ENDDO
479        ENDDO          ENDDO
480    
481  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
482  #ifndef DISABLE_MULTIDIM_ADVECTION  #ifndef DISABLE_MULTIDIM_ADVECTION
# Line 324  CADJ &     comlev1_bibj_k_gad_pass, key= Line 485  CADJ &     comlev1_bibj_k_gad_pass, key=
485  #endif  #endif
486  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
487    
488        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN          IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
489         CALL GAD_FLUXLIMIT_ADV_Y(            CALL GAD_FLUXLIMIT_ADV_Y( bi,bj,k, dTtracerLev(k),
490       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)       I                              vTrans, vVel, maskLocS, localTij,
491        ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN       O                              af, myThid )
492         CALL GAD_DST3_ADV_Y(          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
493       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)            CALL GAD_DST3_ADV_Y(      bi,bj,k, dTtracerLev(k),
494        ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN       I                              vTrans, vVel, maskLocS, localTij,
495         CALL GAD_DST3FL_ADV_Y(       O                              af, myThid )
496       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)          ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
497        ELSE            CALL GAD_DST3FL_ADV_Y(    bi,bj,k, dTtracerLev(k),
498         STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'       I                              vTrans, vVel, maskLocS, localTij,
499        ENDIF       O                              af, myThid )
500            ELSE
501             STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
502            ENDIF
503    
504        DO j=1-Oly,sNy+Oly-1  C-     Advective flux in Y : done
505         DO i=1-Olx,sNx+Olx         ENDIF
506          localTij(i,j)=localTij(i,j)-deltaTtracer*  
507       &    _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)  #ifndef ALLOW_AUTODIFF_TAMC
508       &    *recip_rA(i,j,bi,bj)  C-     Internal exchange for next calculations in X
509       &    *( af(i,j+1)-af(i,j)         IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
510       &      -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))           CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )
511       &     )         ENDIF
512         ENDDO  #endif
513        ENDDO  
514    C-     Update the local tracer field where needed:
515    
516    C      update in overlap-Only
517           IF ( overlapOnly ) THEN
518            jMinUpd = 1-Oly+1
519            jMaxUpd = sNy+Oly-1
520    C- notes: these 2 lines below have no real effect (because recip_hFac=0
521    C         in corner region) but safer to keep them.
522            IF ( S_edge ) jMinUpd = 1
523            IF ( N_edge ) jMaxUpd = sNy
524    
525            IF ( W_edge ) THEN
526             DO j=jMinUpd,jMaxUpd
527              DO i=1-Olx,0
528               localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
529         &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
530         &       *recip_rA(i,j,bi,bj)
531         &       *( af(i,j+1)-af(i,j)
532         &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
533         &        )
534              ENDDO
535             ENDDO
536            ENDIF
537            IF ( E_edge ) THEN
538             DO j=jMinUpd,jMaxUpd
539              DO i=sNx+1,sNx+Olx
540               localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
541         &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
542         &       *recip_rA(i,j,bi,bj)
543         &       *( af(i,j+1)-af(i,j)
544         &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
545         &        )
546              ENDDO
547             ENDDO
548            ENDIF
549    
550           ELSE
551    C      do not only update the overlap
552            iMinUpd = 1-Olx
553            iMaxUpd = sNx+Olx
554            IF ( interiorOnly .AND. W_edge ) iMinUpd = 1
555            IF ( interiorOnly .AND. E_edge ) iMaxUpd = sNx
556            DO j=1-Oly+1,sNy+Oly-1
557             DO i=iMinUpd,iMaxUpd
558               localTij(i,j)=localTij(i,j)-dTtracerLev(k)*
559         &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
560         &       *recip_rA(i,j,bi,bj)
561         &       *( af(i,j+1)-af(i,j)
562         &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
563         &        )
564             ENDDO
565            ENDDO
566    C-      keep advective flux (for diagnostics)
567            DO j=1-Oly,sNy+Oly
568             DO i=1-Olx,sNx+Olx
569              afy(i,j) = af(i,j)
570             ENDDO
571            ENDDO
572    
573  #ifdef ALLOW_OBCS  #ifdef ALLOW_OBCS
574  C--   Apply open boundary conditions  C-     Apply open boundary conditions
575        IF (useOBCS) THEN          IF (useOBCS) THEN
576         IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN           IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
577          CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
578         ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
579          CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
580         END IF  #ifdef ALLOW_PTRACERS
581        END IF           ELSEIF (tracerIdentity.GE.GAD_TR1) THEN
582              CALL OBCS_APPLY_PTRACER( bi, bj, k,
583         &         tracerIdentity-GAD_TR1+1, localTij, myThid )
584    #endif /* ALLOW_PTRACERS */
585             ENDIF
586            ENDIF
587  #endif /* ALLOW_OBCS */  #endif /* ALLOW_OBCS */
588    
589    C      end if/else update overlap-Only
590           ENDIF
591    
592  C--   End of Y direction  C--   End of Y direction
593        ENDIF        ENDIF
594    
# Line 370  C-    explicit advection is done ; store Line 600  C-    explicit advection is done ; store
600          DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
601           DO i=1-Olx,sNx+Olx           DO i=1-Olx,sNx+Olx
602            gTracer(i,j,k,bi,bj)=            gTracer(i,j,k,bi,bj)=
603       &     (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer       &     (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)
604           ENDDO           ENDDO
605          ENDDO          ENDDO
606        ELSE        ELSE
# Line 382  C-    horizontal advection done; store i Line 612  C-    horizontal advection done; store i
612         ENDDO         ENDDO
613        ENDIF        ENDIF
614    
615    #ifdef ALLOW_DIAGNOSTICS
616            IF ( useDiagnostics ) THEN
617              diagName = 'ADVx'//diagSufx
618              CALL DIAGNOSTICS_FILL(afx,diagName, k,1, 2,bi,bj, myThid)
619              diagName = 'ADVy'//diagSufx
620              CALL DIAGNOSTICS_FILL(afy,diagName, k,1, 2,bi,bj, myThid)
621            ENDIF
622    #endif
623    
624    #ifdef ALLOW_DEBUG
625          IF ( debugLevel .GE. debLevB
626         &   .AND. tracerIdentity.EQ.GAD_TEMPERATURE
627         &   .AND. k.LE.3 .AND. myIter.EQ.1+nIter0
628         &   .AND. nPx.EQ.1 .AND. nPy.EQ.1
629         &   .AND. useCubedSphereExchange ) THEN
630            CALL DEBUG_CS_CORNER_UV( ' afx,afy from GAD_ADVECTION',
631         &             afx,afy, k, standardMessageUnit,bi,bj,myThid )
632          ENDIF
633    #endif /* ALLOW_DEBUG */
634    
635  C--   End of K loop for horizontal fluxes  C--   End of K loop for horizontal fluxes
636        ENDDO        ENDDO
637    
638    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
639    
640        IF ( .NOT.implicitAdvection ) THEN        IF ( .NOT.implicitAdvection ) THEN
641  C--   Start of k loop for vertical flux  C--   Start of k loop for vertical flux
642         DO k=Nr,1,-1         DO k=Nr,1,-1
# Line 415  C- Surface interface : Line 667  C- Surface interface :
667             rTransKp1(i,j) = kp1Msk*rTrans(i,j)             rTransKp1(i,j) = kp1Msk*rTrans(i,j)
668             rTrans(i,j) = 0.             rTrans(i,j) = 0.
669             fVerT(i,j,kUp) = 0.             fVerT(i,j,kUp) = 0.
            af(i,j) = 0.  
670            ENDDO            ENDDO
671           ENDDO           ENDDO
672    
# Line 427  C- Interior interface : Line 678  C- Interior interface :
678             rTransKp1(i,j) = kp1Msk*rTrans(i,j)             rTransKp1(i,j) = kp1Msk*rTrans(i,j)
679             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)
680       &                 *maskC(i,j,k-1,bi,bj)       &                 *maskC(i,j,k-1,bi,bj)
681             af(i,j) = 0.             fVerT(i,j,kUp) = 0.
682            ENDDO            ENDDO
683           ENDDO           ENDDO
684    
# Line 447  CADJ &     = comlev1_bibj_k_gad, key=kke Line 698  CADJ &     = comlev1_bibj_k_gad, key=kke
698    
699  C-    Compute vertical advective flux in the interior:  C-    Compute vertical advective flux in the interior:
700           IF (vertAdvecScheme.EQ.ENUM_FLUX_LIMIT) THEN           IF (vertAdvecScheme.EQ.ENUM_FLUX_LIMIT) THEN
701            CALL GAD_FLUXLIMIT_ADV_R(  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
702       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)             CALL GAD_FLUXLIMIT_ADV_R( bi,bj,k, dTtracerLev(k),
703         I                               rTrans, wVel, localTijk,
704         O                               fVerT(1-Olx,1-Oly,kUp), myThid )
705           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3 ) THEN           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3 ) THEN
706            CALL GAD_DST3_ADV_R(             CALL GAD_DST3_ADV_R(      bi,bj,k, dTtracerLev(k),
707       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)       I                               rTrans, wVel, localTijk,
708         O                               fVerT(1-Olx,1-Oly,kUp), myThid )
709           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
710            CALL GAD_DST3FL_ADV_R(             CALL GAD_DST3FL_ADV_R(    bi,bj,k, dTtracerLev(k),
711       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)       I                               rTrans, wVel, localTijk,
712         O                               fVerT(1-Olx,1-Oly,kUp), myThid )
713           ELSE           ELSE
714            STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'            STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
715           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  
716    
717  C- end Surface/Interior if bloc  C- end Surface/Interior if bloc
718          ENDIF          ENDIF
# Line 478  CADJ &     = comlev1_bibj_k_gad, key=kke Line 727  CADJ &     = comlev1_bibj_k_gad, key=kke
727  C--   Divergence of vertical fluxes  C--   Divergence of vertical fluxes
728          DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
729           DO i=1-Olx,sNx+Olx           DO i=1-Olx,sNx+Olx
730            localTij(i,j)=localTijk(i,j,k)-deltaTtracer*            localTij(i,j)=localTijk(i,j,k)-dTtracerLev(k)*
731       &     _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &     _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
732       &     *recip_rA(i,j,bi,bj)       &     *recip_rA(i,j,bi,bj)
733       &     *( fVerT(i,j,kUp)-fVerT(i,j,kDown)       &     *( fVerT(i,j,kDown)-fVerT(i,j,kUp)
734       &       -tracer(i,j,k,bi,bj)*(rTrans(i,j)-rTransKp1(i,j))       &       -tracer(i,j,k,bi,bj)*(rTransKp1(i,j)-rTrans(i,j))
735       &      )*rkFac       &      )*rkSign
736            gTracer(i,j,k,bi,bj)=            gTracer(i,j,k,bi,bj)=
737       &     (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer       &     (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)
738           ENDDO           ENDDO
739          ENDDO          ENDDO
740    
741    #ifdef ALLOW_DIAGNOSTICS
742            IF ( useDiagnostics ) THEN
743              diagName = 'ADVr'//diagSufx
744              CALL DIAGNOSTICS_FILL( fVerT(1-Olx,1-Oly,kUp),
745         &                           diagName, k,1, 2,bi,bj, myThid)
746            ENDIF
747    #endif
748    
749  C--   End of K loop for vertical flux  C--   End of K loop for vertical flux
750         ENDDO         ENDDO
751  C--   end of if not.implicitAdvection block  C--   end of if not.implicitAdvection block

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

  ViewVC Help
Powered by ViewVC 1.1.22