/[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.32 by jmc, Sat Dec 4 00:20:27 2004 UTC revision 1.55 by jmc, Thu Feb 7 23:59:02 2008 UTC
# Line 17  C !INTERFACE: ========================== Line 17  C !INTERFACE: ==========================
17       I     bi,bj, myTime,myIter,myThid)       I     bi,bj, myTime,myIter,myThid)
18    
19  C !DESCRIPTION:  C !DESCRIPTION:
20  C Calculates the tendancy of a tracer due to advection.  C Calculates the tendency of a tracer due to advection.
21  C It uses the multi-dimensional method given in \ref{sect:multiDimAdvection}  C It uses the multi-dimensional method given in \ref{sect:multiDimAdvection}
22  C and can only be used for the non-linear advection schemes such as the  C and can only be used for the non-linear advection schemes such as the
23  C direct-space-time method and flux-limiters.  C direct-space-time method and flux-limiters.
24  C  C
25  C The algorithm is as follows:  C The algorithm is as follows:
26  C \begin{itemize}  C \begin{itemize}
# Line 33  C      - \Delta t \partial_r (w\theta^{( Line 33  C      - \Delta t \partial_r (w\theta^{(
33  C \item{$G_\theta = ( \theta^{(n+3/3)} - \theta^{(n)} )/\Delta t$}  C \item{$G_\theta = ( \theta^{(n+3/3)} - \theta^{(n)} )/\Delta t$}
34  C \end{itemize}  C \end{itemize}
35  C  C
36  C The tendancy (output) is over-written by this routine.  C The tendency (output) is over-written by this routine.
37    
38  C !USES: ===============================================================  C !USES: ===============================================================
39        IMPLICIT NONE        IMPLICIT NONE
# Line 80  C  myThid            :: thread number Line 80  C  myThid            :: thread number
80        INTEGER myThid        INTEGER myThid
81    
82  C !OUTPUT PARAMETERS: ==================================================  C !OUTPUT PARAMETERS: ==================================================
83  C  gTracer           :: tendancy array  C  gTracer           :: tendency array
84        _RL gTracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)        _RL gTracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
85    
86  C !LOCAL VARIABLES: ====================================================  C !LOCAL VARIABLES: ====================================================
87  C  maskUp        :: 2-D array for mask at W points  C  maskUp        :: 2-D array for mask at W points
88  C  maskLocW      :: 2-D array for mask at West points  C  maskLocW      :: 2-D array for mask at West points
89  C  maskLocS      :: 2-D array for mask at South points  C  maskLocS      :: 2-D array for mask at South points
 C  iMin,iMax,    :: loop range for called routines  
 C  jMin,jMax     :: loop range for called routines  
90  C [iMin,iMax]Upd :: loop range to update tracer field  C [iMin,iMax]Upd :: loop range to update tracer field
91  C [jMin,jMax]Upd :: loop range to update tracer field  C [jMin,jMax]Upd :: loop range to update tracer field
92  C  i,j,k         :: loop indices  C  i,j,k         :: loop indices
93  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
94  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
95  C  kp1           :: =k+1 for k<Nr, =Nr for k=Nr  C  kp1           :: =k+1 for k<Nr, =Nr for k=Nr
96  C  xA,yA         :: areas of X and Y face of tracer cells  C  xA,yA         :: areas of X and Y face of tracer cells
97    C  uFld,vFld     :: 2-D local copy of horizontal velocity, U,V components
98    C  wFld          :: 2-D local copy of vertical velocity
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
# Line 110  C  calc_fluxes_X :: logical to indicate Line 110  C  calc_fluxes_X :: logical to indicate
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  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  C  overlapOnly   :: only update the edges of myTile, but not the interior
113  C  nipass        :: number of passes in multi-dimensional method  C  npass         :: 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  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)  c     _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)
       INTEGER iMin,iMax,jMin,jMax  
122        INTEGER iMinUpd,iMaxUpd,jMinUpd,jMaxUpd        INTEGER iMinUpd,iMaxUpd,jMinUpd,jMaxUpd
123        INTEGER i,j,k,kup,kDown        INTEGER i,j,k,kUp,kDown
124        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
125        _RS yA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS yA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
126          _RL uFld    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
127          _RL vFld    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
128          _RL wFld    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
129        _RL uTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
130        _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
131        _RL rTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 137  C [N,S,E,W]_edge :: true if N,S,E,W edge Line 139  C [N,S,E,W]_edge :: true if N,S,E,W edge
139        _RL kp1Msk        _RL kp1Msk
140        LOGICAL calc_fluxes_X, calc_fluxes_Y, withSigns        LOGICAL calc_fluxes_X, calc_fluxes_Y, withSigns
141        LOGICAL interiorOnly, overlapOnly        LOGICAL interiorOnly, overlapOnly
142        INTEGER nipass,ipass        INTEGER npass, ipass
143        INTEGER myTile, nCFace        INTEGER nCFace
144        LOGICAL N_edge, S_edge, E_edge, W_edge        LOGICAL N_edge, S_edge, E_edge, W_edge
145    #ifdef ALLOW_EXCH2
146          INTEGER myTile
147    #endif
148    #ifdef ALLOW_DIAGNOSTICS
149          CHARACTER*8 diagName
150          CHARACTER*4 GAD_DIAG_SUFX, diagSufx
151          EXTERNAL    GAD_DIAG_SUFX
152    #endif
153  CEOP  CEOP
154    
155  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
156            act0 = tracerIdentity - 1            act0 = tracerIdentity
157            max0 = maxpass            max0 = maxpass
158            act1 = bi - myBxLo(myThid)            act1 = bi - myBxLo(myThid)
159            max1 = myBxHi(myThid) - myBxLo(myThid) + 1            max1 = myBxHi(myThid) - myBxLo(myThid) + 1
# Line 152  CEOP Line 162  CEOP
162            act3 = myThid - 1            act3 = myThid - 1
163            max3 = nTx*nTy            max3 = nTx*nTy
164            act4 = ikey_dynamics - 1            act4 = ikey_dynamics - 1
165            igadkey = (act0 + 1)            igadkey = act0
166       &                      + act1*max0       &                      + act1*max0
167       &                      + act2*max0*max1       &                      + act2*max0*max1
168       &                      + act3*max0*max1*max2       &                      + act3*max0*max1*max2
# Line 163  CEOP Line 173  CEOP
173            endif            endif
174  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
175    
176    #ifdef ALLOW_DIAGNOSTICS
177    C--   Set diagnostic suffix for the current tracer
178          IF ( useDiagnostics ) THEN
179            diagSufx = GAD_DIAG_SUFX( tracerIdentity, myThid )
180          ENDIF
181    #endif
182    
183  C--   Set up work arrays with valid (i.e. not NaN) values  C--   Set up work arrays with valid (i.e. not NaN) values
184  C     These inital values do not alter the numerical results. They  C     These inital values do not alter the numerical results. They
185  C     just ensure that all memory references are to valid floating  C     just ensure that all memory references are to valid floating
# Line 178  C     uninitialised but inert locations. Line 195  C     uninitialised but inert locations.
195          fVerT(i,j,1) = 0. _d 0          fVerT(i,j,1) = 0. _d 0
196          fVerT(i,j,2) = 0. _d 0          fVerT(i,j,2) = 0. _d 0
197          rTransKp1(i,j)= 0. _d 0          rTransKp1(i,j)= 0. _d 0
198    #ifdef ALLOW_AUTODIFF_TAMC
199            localTij(i,j) = 0. _d 0
200            wfld(i,j)    = 0. _d 0
201    #endif
202         ENDDO         ENDDO
203        ENDDO        ENDDO
204    
205  C--   Set tile-specific parameters for horizontal fluxes  C--   Set tile-specific parameters for horizontal fluxes
206        IF (useCubedSphereExchange) THEN        IF (useCubedSphereExchange) THEN
207         nipass=3         npass  = 3
208  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
209         IF ( nipass.GT.maxcube ) STOP 'maxcube needs to be = 3'         IF ( npass.GT.maxcube ) STOP 'maxcube needs to be = 3'
210  #endif  #endif
211  #ifdef ALLOW_EXCH2  #ifdef ALLOW_EXCH2
212         myTile = W2_myTileList(bi)         myTile = W2_myTileList(bi)
# Line 202  C--   Set tile-specific parameters for h Line 223  C--   Set tile-specific parameters for h
223         W_edge = .TRUE.         W_edge = .TRUE.
224  #endif  #endif
225        ELSE        ELSE
226         nipass=2         npass  = 2
227           nCFace = 0
228         N_edge = .FALSE.         N_edge = .FALSE.
229         S_edge = .FALSE.         S_edge = .FALSE.
230         E_edge = .FALSE.         E_edge = .FALSE.
231         W_edge = .FALSE.         W_edge = .FALSE.
232        ENDIF        ENDIF
233    
       iMin = 1-OLx  
       iMax = sNx+OLx  
       jMin = 1-OLy  
       jMax = sNy+OLy  
   
234  C--   Start of k loop for horizontal fluxes  C--   Start of k loop for horizontal fluxes
235        DO k=1,Nr        DO k=1,Nr
236  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
237           kkey = (igadkey-1)*Nr + k           kkey = (igadkey-1)*Nr + k
238  CADJ STORE tracer(:,:,k,bi,bj) =  CADJ STORE tracer(:,:,k,bi,bj) =
239  CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte  CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
240  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
241    
242  C--   Get temporary terms used by tendency routines  C--   Get temporary terms used by tendency routines
243        CALL CALC_COMMON_FACTORS (        CALL CALC_COMMON_FACTORS (
244       I         bi,bj,iMin,iMax,jMin,jMax,k,       I         uVel, vVel,
245       O         xA,yA,uTrans,vTrans,rTrans,maskUp,       O         uFld, vFld, uTrans, vTrans, xA, yA,
246       I         myThid)       I         k,bi,bj, myThid )
247    
248  #ifdef ALLOW_GMREDI  #ifdef ALLOW_GMREDI
249  C--   Residual transp = Bolus transp + Eulerian transp  C--   Residual transp = Bolus transp + Eulerian transp
250        IF (useGMRedi)        IF (useGMRedi)
251       &   CALL GMREDI_CALC_UVFLOW(       &   CALL GMREDI_CALC_UVFLOW(
252       &            uTrans, vTrans, bi, bj, k, myThid)       U                  uFld, vFld, uTrans, vTrans,
253         I                  k, bi, bj, myThid )
254  #endif /* ALLOW_GMREDI */  #endif /* ALLOW_GMREDI */
255    
256  C--   Make local copy of tracer array and mask West & South  C--   Make local copy of tracer array and mask West & South
257        DO j=1-OLy,sNy+OLy        DO j=1-OLy,sNy+OLy
258         DO i=1-OLx,sNx+OLx         DO i=1-OLx,sNx+OLx
259           localTij(i,j)=tracer(i,j,k,bi,bj)           localTij(i,j)=tracer(i,j,k,bi,bj)
260           maskLocW(i,j)=maskW(i,j,k,bi,bj)           maskLocW(i,j)=_maskW(i,j,k,bi,bj)
261           maskLocS(i,j)=maskS(i,j,k,bi,bj)           maskLocS(i,j)=_maskS(i,j,k,bi,bj)
262         ENDDO         ENDDO
263        ENDDO        ENDDO
264    
265  #ifndef ALLOW_AUTODIFF_TAMC  cph-exch2#ifndef ALLOW_AUTODIFF_TAMC
266        IF (useCubedSphereExchange) THEN        IF (useCubedSphereExchange) THEN
267          withSigns = .FALSE.          withSigns = .FALSE.
268          CALL FILL_CS_CORNER_UV_RS(          CALL FILL_CS_CORNER_UV_RS(
269       &            withSigns, maskLocW,maskLocS, bi,bj, myThid )       &            withSigns, maskLocW,maskLocS, bi,bj, myThid )
270        ENDIF        ENDIF
271  #endif  cph-exch2#endif
272    
273  C--   Multiple passes for different directions on different tiles  C--   Multiple passes for different directions on different tiles
274  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.
275        DO ipass=1,nipass        DO ipass=1,npass
276  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
277           passkey = ipass + (k-1)      *maxcube           passkey = ipass
278       &                   + (igadkey-1)*maxcube*Nr       &                   + (k-1)      *maxpass
279           IF (nipass .GT. maxpass) THEN       &                   + (igadkey-1)*maxpass*Nr
280            STOP 'GAD_ADVECTION: nipass > maxcube. check tamc.h'           IF (npass .GT. maxpass) THEN
281              STOP 'GAD_ADVECTION: npass > maxcube. check tamc.h'
282           ENDIF           ENDIF
283  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
284    
# Line 283  C-    CubedSphere : pass 3 times, with p Line 302  C-    CubedSphere : pass 3 times, with p
302          calc_fluxes_Y = nCFace.EQ.3 .OR. nCFace.EQ.4 .OR. nCFace.EQ.5          calc_fluxes_Y = nCFace.EQ.3 .OR. nCFace.EQ.4 .OR. nCFace.EQ.5
303         ELSEIF (ipass.EQ.2) THEN         ELSEIF (ipass.EQ.2) THEN
304          overlapOnly  = MOD(nCFace,3).EQ.2          overlapOnly  = MOD(nCFace,3).EQ.2
305            interiorOnly = MOD(nCFace,3).EQ.1
306          calc_fluxes_X = nCFace.EQ.2 .OR. nCFace.EQ.3 .OR. nCFace.EQ.4          calc_fluxes_X = nCFace.EQ.2 .OR. nCFace.EQ.3 .OR. nCFace.EQ.4
307          calc_fluxes_Y = nCFace.EQ.5 .OR. nCFace.EQ.6 .OR. nCFace.EQ.1          calc_fluxes_Y = nCFace.EQ.5 .OR. nCFace.EQ.6 .OR. nCFace.EQ.1
308  #endif /* MULTIDIM_OLD_VERSION */  #endif /* MULTIDIM_OLD_VERSION */
309         ELSE         ELSE
310            interiorOnly = .TRUE.
311          calc_fluxes_X = nCFace.EQ.5 .OR. nCFace.EQ.6          calc_fluxes_X = nCFace.EQ.5 .OR. nCFace.EQ.6
312          calc_fluxes_Y = nCFace.EQ.2 .OR. nCFace.EQ.3          calc_fluxes_Y = nCFace.EQ.2 .OR. nCFace.EQ.3
313         ENDIF         ENDIF
# Line 295  C-    not CubedSphere Line 316  C-    not CubedSphere
316          calc_fluxes_X = MOD(ipass,2).EQ.1          calc_fluxes_X = MOD(ipass,2).EQ.1
317          calc_fluxes_Y = .NOT.calc_fluxes_X          calc_fluxes_Y = .NOT.calc_fluxes_X
318        ENDIF        ENDIF
319    
320  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
321  C--   X direction  C--   X direction
322    C-     Advective flux in X
323            DO j=1-Oly,sNy+Oly
324             DO i=1-Olx,sNx+Olx
325              af(i,j) = 0.
326             ENDDO
327            ENDDO
328    C
329    #ifdef ALLOW_AUTODIFF_TAMC
330    # ifndef DISABLE_MULTIDIM_ADVECTION
331    CADJ STORE localTij(:,:)  =
332    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
333    CADJ STORE af(:,:)  =
334    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
335    # endif
336    #endif /* ALLOW_AUTODIFF_TAMC */
337    C
338        IF (calc_fluxes_X) THEN        IF (calc_fluxes_X) THEN
339    
340  C-     Do not compute fluxes if  C-     Do not compute fluxes if
341  C       a) needed in overlap only  C       a) needed in overlap only
342  C   and b) the overlap of myTile are not cube-face Edges  C   and b) the overlap of myTile are not cube-face Edges
343         IF ( .NOT.overlapOnly .OR. N_edge .OR. S_edge ) THEN         IF ( .NOT.overlapOnly .OR. N_edge .OR. S_edge ) THEN
344    
 #ifndef ALLOW_AUTODIFF_TAMC  
345  C-     Internal exchange for calculations in X  C-     Internal exchange for calculations in X
346  #ifdef MULTIDIM_OLD_VERSION  #ifdef MULTIDIM_OLD_VERSION
347          IF ( useCubedSphereExchange ) THEN          IF ( useCubedSphereExchange ) THEN
348  #else  #else
349          IF ( useCubedSphereExchange .AND.          IF ( overlapOnly ) THEN
      &       ( overlapOnly .OR. ipass.EQ.1 ) ) THEN  
350  #endif  #endif
351           CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )           CALL FILL_CS_CORNER_TR_RL( .TRUE., .FALSE.,
352         &                              localTij, bi,bj, myThid )
353          ENDIF          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  
354    
355  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
356  #ifndef DISABLE_MULTIDIM_ADVECTION  # ifndef DISABLE_MULTIDIM_ADVECTION
357  CADJ STORE localTij(:,:)  =  CADJ STORE localTij(:,:)  =
358  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
359  #endif  # endif
360  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
361    
362          IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN          IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
363            CALL GAD_FLUXLIMIT_ADV_X( bi,bj,k, dTtracerLev(k),       &     .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
364       I                              uTrans, uVel, maskLocW, localTij,            CALL GAD_DST2U1_ADV_X( bi,bj,k, advectionScheme, .TRUE.,
365         I                           dTtracerLev(k),uTrans,uFld,localTij,
366         O                           af, myThid )
367            ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
368              CALL GAD_FLUXLIMIT_ADV_X( bi,bj,k, .TRUE., dTtracerLev(k),
369         I                              uTrans, uFld, maskLocW, localTij,
370       O                              af, myThid )       O                              af, myThid )
371          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
372            CALL GAD_DST3_ADV_X(      bi,bj,k, dTtracerLev(k),            CALL GAD_DST3_ADV_X(      bi,bj,k, .TRUE., dTtracerLev(k),
373       I                              uTrans, uVel, maskLocW, localTij,       I                              uTrans, uFld, maskLocW, localTij,
374       O                              af, myThid )       O                              af, myThid )
375          ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN          ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
376            CALL GAD_DST3FL_ADV_X(    bi,bj,k, dTtracerLev(k),            CALL GAD_DST3FL_ADV_X(    bi,bj,k, .TRUE., dTtracerLev(k),
377       I                              uTrans, uVel, maskLocW, localTij,       I                              uTrans, uFld, maskLocW, localTij,
378       O                              af, myThid )       O                              af, myThid )
379    #ifndef ALLOW_AUTODIFF_TAMC
380            ELSEIF (advectionScheme.EQ.ENUM_OS7MP ) THEN
381              CALL GAD_OS7MP_ADV_X(     bi,bj,k, .TRUE., dTtracerLev(k),
382         I                              uTrans, uFld, maskLocW, localTij,
383         O                              af, myThid )
384    #endif
385          ELSE          ELSE
386           STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'           STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'
387          ENDIF          ENDIF
388    
 C-     Advective flux in X : done  
        ENDIF  
   
 #ifndef ALLOW_AUTODIFF_TAMC  
389  C-     Internal exchange for next calculations in Y  C-     Internal exchange for next calculations in Y
390         IF ( overlapOnly .AND. ipass.EQ.1 ) THEN          IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
391           CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )           CALL FILL_CS_CORNER_TR_RL( .FALSE., .FALSE.,
392         &                              localTij, bi,bj, myThid )
393            ENDIF
394    
395    C-     Advective flux in X : done
396         ENDIF         ENDIF
 #endif  
397    
398  C-     Update the local tracer field where needed:  C-     Update the local tracer field where needed:
399    
# Line 363  C      update in overlap-Only Line 401  C      update in overlap-Only
401         IF ( overlapOnly ) THEN         IF ( overlapOnly ) THEN
402          iMinUpd = 1-Olx+1          iMinUpd = 1-Olx+1
403          iMaxUpd = sNx+Olx-1          iMaxUpd = sNx+Olx-1
404  C- notes: these 2 lines below have no real effect (because recip_hFac=0  C- notes: these 2 lines below have no real effect (because recip_hFac=0
405  C         in corner region) but safer to keep them.  C         in corner region) but safer to keep them.
406          IF ( W_edge ) iMinUpd = 1          IF ( W_edge ) iMinUpd = 1
407          IF ( E_edge ) iMaxUpd = sNx          IF ( E_edge ) iMaxUpd = sNx
# Line 371  C         in corner region) but safer to Line 409  C         in corner region) but safer to
409          IF ( S_edge ) THEN          IF ( S_edge ) THEN
410           DO j=1-Oly,0           DO j=1-Oly,0
411            DO i=iMinUpd,iMaxUpd            DO i=iMinUpd,iMaxUpd
412             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
413       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
414       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
415         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
416       &       *( af(i+1,j)-af(i,j)       &       *( af(i+1,j)-af(i,j)
417       &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))       &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
418       &        )       &        )
# Line 383  C         in corner region) but safer to Line 422  C         in corner region) but safer to
422          IF ( N_edge ) THEN          IF ( N_edge ) THEN
423           DO j=sNy+1,sNy+Oly           DO j=sNy+1,sNy+Oly
424            DO i=iMinUpd,iMaxUpd            DO i=iMinUpd,iMaxUpd
425             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
426       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
427       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
428         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
429       &       *( af(i+1,j)-af(i,j)       &       *( af(i+1,j)-af(i,j)
430       &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))       &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
431       &        )       &        )
# Line 395  C         in corner region) but safer to Line 435  C         in corner region) but safer to
435    
436         ELSE         ELSE
437  C      do not only update the overlap  C      do not only update the overlap
438          jMinUpd = 1-Oly          jMinUpd = 1-Oly
439          jMaxUpd = sNy+Oly          jMaxUpd = sNy+Oly
440          IF ( interiorOnly .AND. S_edge ) jMinUpd = 1          IF ( interiorOnly .AND. S_edge ) jMinUpd = 1
441          IF ( interiorOnly .AND. N_edge ) jMaxUpd = sNy          IF ( interiorOnly .AND. N_edge ) jMaxUpd = sNy
442          DO j=jMinUpd,jMaxUpd          DO j=jMinUpd,jMaxUpd
443           DO i=1-Olx+1,sNx+Olx-1           DO i=1-Olx+1,sNx+Olx-1
444             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
445       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
446       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
447         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
448       &       *( af(i+1,j)-af(i,j)       &       *( af(i+1,j)-af(i,j)
449       &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))       &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
450       &        )       &        )
# Line 423  C-     Apply open boundary conditions Line 464  C-     Apply open boundary conditions
464            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
465           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
466            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
467    #ifdef ALLOW_PTRACERS
468             ELSEIF (tracerIdentity.GE.GAD_TR1) THEN
469              CALL OBCS_APPLY_PTRACER( bi, bj, k,
470         &         tracerIdentity-GAD_TR1+1, localTij, myThid )
471    #endif /* ALLOW_PTRACERS */
472           ENDIF           ENDIF
473          ENDIF          ENDIF
474  #endif /* ALLOW_OBCS */  #endif /* ALLOW_OBCS */
475    
476  C-     end if/else update overlap-Only  C-     end if/else update overlap-Only
477         ENDIF         ENDIF
478            
479  C--   End of X direction  C--   End of X direction
480        ENDIF        ENDIF
481    
482  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
483  C--   Y direction  C--   Y direction
484    cph-test
485    C-     Advective flux in Y
486            DO j=1-Oly,sNy+Oly
487             DO i=1-Olx,sNx+Olx
488              af(i,j) = 0.
489             ENDDO
490            ENDDO
491    C
492    #ifdef ALLOW_AUTODIFF_TAMC
493    # ifndef DISABLE_MULTIDIM_ADVECTION
494    CADJ STORE localTij(:,:)  =
495    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
496    CADJ STORE af(:,:)  =
497    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
498    # endif
499    #endif /* ALLOW_AUTODIFF_TAMC */
500    C
501        IF (calc_fluxes_Y) THEN        IF (calc_fluxes_Y) THEN
502    
503  C-     Do not compute fluxes if  C-     Do not compute fluxes if
# Line 442  C       a) needed in overlap only Line 505  C       a) needed in overlap only
505  C   and b) the overlap of myTile are not cube-face edges  C   and b) the overlap of myTile are not cube-face edges
506         IF ( .NOT.overlapOnly .OR. E_edge .OR. W_edge ) THEN         IF ( .NOT.overlapOnly .OR. E_edge .OR. W_edge ) THEN
507    
 #ifndef ALLOW_AUTODIFF_TAMC  
508  C-     Internal exchange for calculations in Y  C-     Internal exchange for calculations in Y
509  #ifdef MULTIDIM_OLD_VERSION  #ifdef MULTIDIM_OLD_VERSION
510          IF ( useCubedSphereExchange ) THEN          IF ( useCubedSphereExchange ) THEN
511  #else  #else
512          IF ( useCubedSphereExchange .AND.          IF ( overlapOnly ) THEN
      &       ( overlapOnly .OR. ipass.EQ.1 ) ) THEN  
513  #endif  #endif
514           CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )           CALL FILL_CS_CORNER_TR_RL( .FALSE., .FALSE.,
515         &                              localTij, bi,bj, myThid )
516          ENDIF          ENDIF
 #endif  
517    
518  C-     Advective flux in Y  C-     Advective flux in Y
519          DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
# Line 461  C-     Advective flux in Y Line 522  C-     Advective flux in Y
522           ENDDO           ENDDO
523          ENDDO          ENDDO
524    
525  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
526  #ifndef DISABLE_MULTIDIM_ADVECTION  #ifndef DISABLE_MULTIDIM_ADVECTION
527  CADJ STORE localTij(:,:)  =  CADJ STORE localTij(:,:)  =
528  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
529  #endif  #endif
530  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
531    
532          IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN          IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
533            CALL GAD_FLUXLIMIT_ADV_Y( bi,bj,k, dTtracerLev(k),       &     .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
534       I                              vTrans, vVel, maskLocS, localTij,            CALL GAD_DST2U1_ADV_Y( bi,bj,k, advectionScheme, .TRUE.,
535         I                           dTtracerLev(k),vTrans,vFld,localTij,
536         O                           af, myThid )
537            ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
538              CALL GAD_FLUXLIMIT_ADV_Y( bi,bj,k, .TRUE., dTtracerLev(k),
539         I                              vTrans, vFld, maskLocS, localTij,
540       O                              af, myThid )       O                              af, myThid )
541          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
542            CALL GAD_DST3_ADV_Y(      bi,bj,k, dTtracerLev(k),            CALL GAD_DST3_ADV_Y(      bi,bj,k, .TRUE., dTtracerLev(k),
543       I                              vTrans, vVel, maskLocS, localTij,       I                              vTrans, vFld, maskLocS, localTij,
544       O                              af, myThid )       O                              af, myThid )
545          ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN          ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
546            CALL GAD_DST3FL_ADV_Y(    bi,bj,k, dTtracerLev(k),            CALL GAD_DST3FL_ADV_Y(    bi,bj,k, .TRUE., dTtracerLev(k),
547       I                              vTrans, vVel, maskLocS, localTij,       I                              vTrans, vFld, maskLocS, localTij,
548       O                              af, myThid )       O                              af, myThid )
549    #ifndef ALLOW_AUTODIFF_TAMC
550            ELSEIF (advectionScheme.EQ.ENUM_OS7MP ) THEN
551              CALL GAD_OS7MP_ADV_Y(     bi,bj,k, .TRUE., dTtracerLev(k),
552         I                              vTrans, vFld, maskLocS, localTij,
553         O                              af, myThid )
554    #endif
555          ELSE          ELSE
556           STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'           STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
557          ENDIF          ENDIF
558    
 C-     Advective flux in Y : done  
        ENDIF  
   
 #ifndef ALLOW_AUTODIFF_TAMC  
559  C-     Internal exchange for next calculations in X  C-     Internal exchange for next calculations in X
560         IF ( overlapOnly .AND. ipass.EQ.1 ) THEN         IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
561           CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )           CALL FILL_CS_CORNER_TR_RL( .TRUE., .FALSE.,
562         &                              localTij, bi,bj, myThid )
563           ENDIF
564    
565    C-     Advective flux in Y : done
566         ENDIF         ENDIF
 #endif  
567    
568  C-     Update the local tracer field where needed:  C-     Update the local tracer field where needed:
569    
570  C      update in overlap-Only  C      update in overlap-Only
571         IF ( overlapOnly ) THEN         IF ( overlapOnly ) THEN
572          jMinUpd = 1-Oly+1          jMinUpd = 1-Oly+1
573          jMaxUpd = sNy+Oly-1          jMaxUpd = sNy+Oly-1
574  C- notes: these 2 lines below have no real effect (because recip_hFac=0  C- notes: these 2 lines below have no real effect (because recip_hFac=0
575  C         in corner region) but safer to keep them.  C         in corner region) but safer to keep them.
576          IF ( S_edge ) jMinUpd = 1          IF ( S_edge ) jMinUpd = 1
577          IF ( N_edge ) jMaxUpd = sNy          IF ( N_edge ) jMaxUpd = sNy
# Line 508  C         in corner region) but safer to Line 579  C         in corner region) but safer to
579          IF ( W_edge ) THEN          IF ( W_edge ) THEN
580           DO j=jMinUpd,jMaxUpd           DO j=jMinUpd,jMaxUpd
581            DO i=1-Olx,0            DO i=1-Olx,0
582             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
583       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
584       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
585         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
586       &       *( af(i,j+1)-af(i,j)       &       *( af(i,j+1)-af(i,j)
587       &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))       &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
588       &        )       &        )
# Line 520  C         in corner region) but safer to Line 592  C         in corner region) but safer to
592          IF ( E_edge ) THEN          IF ( E_edge ) THEN
593           DO j=jMinUpd,jMaxUpd           DO j=jMinUpd,jMaxUpd
594            DO i=sNx+1,sNx+Olx            DO i=sNx+1,sNx+Olx
595             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
596       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
597       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
598         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
599       &       *( af(i,j+1)-af(i,j)       &       *( af(i,j+1)-af(i,j)
600       &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))       &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
601       &        )       &        )
# Line 538  C      do not only update the overlap Line 611  C      do not only update the overlap
611          IF ( interiorOnly .AND. E_edge ) iMaxUpd = sNx          IF ( interiorOnly .AND. E_edge ) iMaxUpd = sNx
612          DO j=1-Oly+1,sNy+Oly-1          DO j=1-Oly+1,sNy+Oly-1
613           DO i=iMinUpd,iMaxUpd           DO i=iMinUpd,iMaxUpd
614             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
615       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
616       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
617         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
618       &       *( af(i,j+1)-af(i,j)       &       *( af(i,j+1)-af(i,j)
619       &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))       &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
620       &        )       &        )
# Line 560  C-     Apply open boundary conditions Line 634  C-     Apply open boundary conditions
634            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
635           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
636            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
637    #ifdef ALLOW_PTRACERS
638             ELSEIF (tracerIdentity.GE.GAD_TR1) THEN
639              CALL OBCS_APPLY_PTRACER( bi, bj, k,
640         &         tracerIdentity-GAD_TR1+1, localTij, myThid )
641    #endif /* ALLOW_PTRACERS */
642           ENDIF           ENDIF
643          ENDIF          ENDIF
644  #endif /* ALLOW_OBCS */  #endif /* ALLOW_OBCS */
# Line 583  C-    explicit advection is done ; store Line 662  C-    explicit advection is done ; store
662          ENDDO          ENDDO
663        ELSE        ELSE
664  C-    horizontal advection done; store intermediate result in 3D array:  C-    horizontal advection done; store intermediate result in 3D array:
665         DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
666          DO i=1-Olx,sNx+Olx           DO i=1-Olx,sNx+Olx
667           localTijk(i,j,k)=localTij(i,j)            localTijk(i,j,k)=localTij(i,j)
668             ENDDO
669          ENDDO          ENDDO
        ENDDO  
670        ENDIF        ENDIF
671    
672    #ifdef ALLOW_DIAGNOSTICS
673            IF ( useDiagnostics ) THEN
674              diagName = 'ADVx'//diagSufx
675              CALL DIAGNOSTICS_FILL(afx,diagName, k,1, 2,bi,bj, myThid)
676              diagName = 'ADVy'//diagSufx
677              CALL DIAGNOSTICS_FILL(afy,diagName, k,1, 2,bi,bj, myThid)
678            ENDIF
679    #endif
680    
681  #ifdef ALLOW_DEBUG  #ifdef ALLOW_DEBUG
682        IF ( debugLevel .GE. debLevB        IF ( debugLevel .GE. debLevB
683       &   .AND. tracerIdentity.EQ.GAD_TEMPERATURE       &   .AND. tracerIdentity.EQ.GAD_TEMPERATURE
# Line 609  C---+----1----+----2----+----3----+----4 Line 697  C---+----1----+----2----+----3----+----4
697        IF ( .NOT.implicitAdvection ) THEN        IF ( .NOT.implicitAdvection ) THEN
698  C--   Start of k loop for vertical flux  C--   Start of k loop for vertical flux
699         DO k=Nr,1,-1         DO k=Nr,1,-1
700  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
701           kkey = (igadkey-1)*Nr + k           kkey = (igadkey-1)*Nr + (Nr-k+1)
702  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
703  C--   kup    Cycles through 1,2 to point to w-layer above  C--   kUp    Cycles through 1,2 to point to w-layer above
704  C--   kDown  Cycles through 2,1 to point to w-layer below  C--   kDown  Cycles through 2,1 to point to w-layer below
705          kup  = 1+MOD(k+1,2)          kUp  = 1+MOD(k+1,2)
706          kDown= 1+MOD(k,2)          kDown= 1+MOD(k,2)
707  c       kp1=min(Nr,k+1)  c       kp1=min(Nr,k+1)
708          kp1Msk=1.          kp1Msk=1.
709          if (k.EQ.Nr) kp1Msk=0.          if (k.EQ.Nr) kp1Msk=0.
710    
711    #ifdef ALLOW_AUTODIFF_TAMC
712    CADJ STORE rtrans(:,:)  =
713    CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
714    cphCADJ STORE wfld(:,:)  =
715    cphCADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
716    #endif
717    
718  C-- Compute Vertical transport  C-- Compute Vertical transport
719  #ifdef ALLOW_AIM  #ifdef ALLOW_AIM
720  C- a hack to prevent Water-Vapor vert.transport into the stratospheric level Nr  C- a hack to prevent Water-Vapor vert.transport into the stratospheric level Nr
# Line 630  C- a hack to prevent Water-Vapor vert.tr Line 725  C- a hack to prevent Water-Vapor vert.tr
725          IF ( k.EQ.1 ) THEN          IF ( k.EQ.1 ) THEN
726  #endif  #endif
727    
728    #ifdef ALLOW_AUTODIFF_TAMC
729    cphmultiCADJ STORE wfld(:,:)  =
730    cphmultiCADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
731    #endif /* ALLOW_AUTODIFF_TAMC */
732    
733  C- Surface interface :  C- Surface interface :
734           DO j=1-Oly,sNy+Oly           DO j=1-Oly,sNy+Oly
735            DO i=1-Olx,sNx+Olx            DO i=1-Olx,sNx+Olx
736             rTransKp1(i,j) = kp1Msk*rTrans(i,j)             rTransKp1(i,j) = kp1Msk*rTrans(i,j)
737               wFld(i,j)   = 0.
738             rTrans(i,j) = 0.             rTrans(i,j) = 0.
739             fVerT(i,j,kUp) = 0.             fVerT(i,j,kUp) = 0.
740            ENDDO            ENDDO
741           ENDDO           ENDDO
742    
743          ELSE          ELSE
 C- Interior interface :  
744    
745    #ifdef ALLOW_AUTODIFF_TAMC
746    cphmultiCADJ STORE wfld(:,:)  =
747    cphmultiCADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
748    #endif /* ALLOW_AUTODIFF_TAMC */
749    
750    C- Interior interface :
751           DO j=1-Oly,sNy+Oly           DO j=1-Oly,sNy+Oly
752            DO i=1-Olx,sNx+Olx            DO i=1-Olx,sNx+Olx
753             rTransKp1(i,j) = kp1Msk*rTrans(i,j)             rTransKp1(i,j) = kp1Msk*rTrans(i,j)
754               wFld(i,j)   = wVel(i,j,k,bi,bj)
755             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)
756         &                 *deepFac2F(k)*rhoFacF(k)
757       &                 *maskC(i,j,k-1,bi,bj)       &                 *maskC(i,j,k-1,bi,bj)
758             fVerT(i,j,kUp) = 0.             fVerT(i,j,kUp) = 0.
759            ENDDO            ENDDO
# Line 653  C- Interior interface : Line 761  C- Interior interface :
761    
762  #ifdef ALLOW_GMREDI  #ifdef ALLOW_GMREDI
763  C--   Residual transp = Bolus transp + Eulerian transp  C--   Residual transp = Bolus transp + Eulerian transp
764           IF (useGMRedi)           IF (useGMRedi)
765       &   CALL GMREDI_CALC_WFLOW(       &     CALL GMREDI_CALC_WFLOW(
766       &                    rTrans, bi, bj, k, myThid)       U                 wFld, rTrans,
767         I                 k, bi, bj, myThid )
768  #endif /* ALLOW_GMREDI */  #endif /* ALLOW_GMREDI */
769    
770  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
771  CADJ STORE localTijk(:,:,k)    cphmultiCADJ STORE localTijk(:,:,k)
772  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte  cphmultiCADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
773  CADJ STORE rTrans(:,:)    cphmultiCADJ STORE rTrans(:,:)
774  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte  cphmultiCADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
775  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
776    
777  C-    Compute vertical advective flux in the interior:  C-    Compute vertical advective flux in the interior:
778           IF (vertAdvecScheme.EQ.ENUM_FLUX_LIMIT) THEN           IF ( vertAdvecScheme.EQ.ENUM_UPWIND_1RST
779  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|       &      .OR. vertAdvecScheme.EQ.ENUM_DST2 ) THEN
780               CALL GAD_DST2U1_ADV_R( bi,bj,k, advectionScheme,
781         I                            dTtracerLev(k),rTrans,wFld,localTijk,
782         O                            fVerT(1-Olx,1-Oly,kUp), myThid )
783             ELSEIF( vertAdvecScheme.EQ.ENUM_FLUX_LIMIT) THEN
784             CALL GAD_FLUXLIMIT_ADV_R( bi,bj,k, dTtracerLev(k),             CALL GAD_FLUXLIMIT_ADV_R( bi,bj,k, dTtracerLev(k),
785       I                               rTrans, wVel, localTijk,       I                               rTrans, wFld, localTijk,
786       O                               fVerT(1-Olx,1-Oly,kUp), myThid )       O                               fVerT(1-Olx,1-Oly,kUp), myThid )
787           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3 ) THEN           ELSEIF( vertAdvecScheme.EQ.ENUM_DST3 ) THEN
788             CALL GAD_DST3_ADV_R(      bi,bj,k, dTtracerLev(k),             CALL GAD_DST3_ADV_R(      bi,bj,k, dTtracerLev(k),
789       I                               rTrans, wVel, localTijk,       I                               rTrans, wFld, localTijk,
790       O                               fVerT(1-Olx,1-Oly,kUp), myThid )       O                               fVerT(1-Olx,1-Oly,kUp), myThid )
791           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN           ELSEIF( vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
792             CALL GAD_DST3FL_ADV_R(    bi,bj,k, dTtracerLev(k),             CALL GAD_DST3FL_ADV_R(    bi,bj,k, dTtracerLev(k),
793       I                               rTrans, wVel, localTijk,       I                               rTrans, wFld, localTijk,
794       O                               fVerT(1-Olx,1-Oly,kUp), myThid )       O                               fVerT(1-Olx,1-Oly,kUp), myThid )
795    #ifndef ALLOW_AUTODIFF_TAMC
796             ELSEIF (vertAdvecScheme.EQ.ENUM_OS7MP ) THEN
797               CALL GAD_OS7MP_ADV_R(     bi,bj,k, dTtracerLev(k),
798         I                               rTrans, wFld, localTijk,
799         O                               fVerT(1-Olx,1-Oly,kUp), myThid )
800    #endif
801           ELSE           ELSE
802            STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'            STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
803           ENDIF           ENDIF
# Line 686  C---+----1----+----2----+----3----+----4 Line 805  C---+----1----+----2----+----3----+----4
805  C- end Surface/Interior if bloc  C- end Surface/Interior if bloc
806          ENDIF          ENDIF
807    
808  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
809  CADJ STORE rTrans(:,:)    cphmultiCADJ STORE rTrans(:,:)
810  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte  cphmultiCADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
811  CADJ STORE rTranskp1(:,:)    cphmultiCADJ STORE rTranskp1(:,:)
812    cphmultiCADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
813    cph --- following storing of fVerT is critical for correct
814    cph --- gradient with multiDimAdvection
815    cph --- Without it, kDown component is not properly recomputed
816    cph --- This is a TAF bug (and no warning available)
817    CADJ STORE fVerT(:,:,:)
818  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
819  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
820    
821  C--   Divergence of vertical fluxes  C--   Divergence of vertical fluxes
822          DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
823           DO i=1-Olx,sNx+Olx           DO i=1-Olx,sNx+Olx
824            localTij(i,j)=localTijk(i,j,k)-dTtracerLev(k)*            localTij(i,j) = localTijk(i,j,k)
825       &     _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
826       &     *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
827       &     *( fVerT(i,j,kUp)-fVerT(i,j,kDown)       &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
828       &       -tracer(i,j,k,bi,bj)*(rTrans(i,j)-rTransKp1(i,j))       &       *( fVerT(i,j,kDown)-fVerT(i,j,kUp)
829       &      )*rkFac       &         -tracer(i,j,k,bi,bj)*(rTransKp1(i,j)-rTrans(i,j))
830         &        )*rkSign
831            gTracer(i,j,k,bi,bj)=            gTracer(i,j,k,bi,bj)=
832       &     (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)       &     (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)
833           ENDDO           ENDDO
834          ENDDO          ENDDO
835    
836    #ifdef ALLOW_DIAGNOSTICS
837            IF ( useDiagnostics ) THEN
838              diagName = 'ADVr'//diagSufx
839              CALL DIAGNOSTICS_FILL( fVerT(1-Olx,1-Oly,kUp),
840         &                           diagName, k,1, 2,bi,bj, myThid)
841            ENDIF
842    #endif
843    
844  C--   End of K loop for vertical flux  C--   End of K loop for vertical flux
845         ENDDO         ENDDO
846  C--   end of if not.implicitAdvection block  C--   end of if not.implicitAdvection block
847        ENDIF        ENDIF
848    
849        RETURN        RETURN
850        END        END

Legend:
Removed from v.1.32  
changed lines
  Added in v.1.55

  ViewVC Help
Powered by ViewVC 1.1.22