/[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.37 by jmc, Sat Oct 22 19:59:45 2005 UTC revision 1.53 by heimbach, Fri Oct 19 19:18:01 2007 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: ====================================================
# Line 92  C  jMin,jMax     :: loop range for calle Line 92  C  jMin,jMax     :: loop range for calle
92  C [iMin,iMax]Upd :: loop range to update tracer field  C [iMin,iMax]Upd :: loop range to update tracer field
93  C [jMin,jMax]Upd :: loop range to update tracer field  C [jMin,jMax]Upd :: loop range to update tracer field
94  C  i,j,k         :: loop indices  C  i,j,k         :: loop indices
95  C  kup           :: index into 2 1/2D array, toggles between 1 and 2  C  kUp           :: index into 2 1/2D array, toggles between 1 and 2
96  C  kdown         :: index into 2 1/2D array, toggles between 2 and 1  C  kDown         :: index into 2 1/2D array, toggles between 2 and 1
97  C  kp1           :: =k+1 for k<Nr, =Nr for k=Nr  C  kp1           :: =k+1 for k<Nr, =Nr for k=Nr
98  C  xA,yA         :: areas of X and Y face of tracer cells  C  xA,yA         :: areas of X and Y face of tracer cells
99    C  uFld,vFld     :: 2-D local copy of horizontal velocity, U,V components
100    C  wFld          :: 2-D local copy of vertical velocity
101  C  uTrans,vTrans :: 2-D arrays of volume transports at U,V points  C  uTrans,vTrans :: 2-D arrays of volume transports at U,V points
102  C  rTrans        :: 2-D arrays of volume transports at W points  C  rTrans        :: 2-D arrays of volume transports at W points
103  C  rTransKp1     :: vertical volume transport at interface k+1  C  rTransKp1     :: vertical volume transport at interface k+1
# Line 112  C  interiorOnly  :: only update the inte Line 114  C  interiorOnly  :: only update the inte
114  C  overlapOnly   :: only update the edges of myTile, but not the interior  C  overlapOnly   :: only update the edges of myTile, but not the interior
115  C  nipass        :: number of passes in multi-dimensional method  C  nipass        :: number of passes in multi-dimensional method
116  C  ipass         :: number of the current pass being made  C  ipass         :: number of the current pass being made
117  C  myTile        :: variables used to determine which cube face  C  myTile        :: variables used to determine which cube face
118  C  nCFace        :: owns a tile for cube grid runs using  C  nCFace        :: owns a tile for cube grid runs using
119  C                :: multi-dim advection.  C                :: multi-dim advection.
120  C [N,S,E,W]_edge :: true if N,S,E,W edge of myTile is an Edge of the cube  C [N,S,E,W]_edge :: true if N,S,E,W edge of myTile is an Edge of the cube
121        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  c     _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
122        _RS maskLocW(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskLocW(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
123        _RS maskLocS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskLocS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
124        INTEGER iMin,iMax,jMin,jMax        INTEGER iMin,iMax,jMin,jMax
125        INTEGER iMinUpd,iMaxUpd,jMinUpd,jMaxUpd        INTEGER iMinUpd,iMaxUpd,jMinUpd,jMaxUpd
126        INTEGER i,j,k,kup,kDown        INTEGER i,j,k,kUp,kDown
127        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
128        _RS yA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS yA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
129          _RL uFld    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
130          _RL vFld    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
131          _RL wFld    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
132        _RL uTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
133        _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
134        _RL rTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 138  C [N,S,E,W]_edge :: true if N,S,E,W edge Line 143  C [N,S,E,W]_edge :: true if N,S,E,W edge
143        LOGICAL calc_fluxes_X, calc_fluxes_Y, withSigns        LOGICAL calc_fluxes_X, calc_fluxes_Y, withSigns
144        LOGICAL interiorOnly, overlapOnly        LOGICAL interiorOnly, overlapOnly
145        INTEGER nipass,ipass        INTEGER nipass,ipass
146        INTEGER myTile, nCFace        INTEGER nCFace
147        LOGICAL N_edge, S_edge, E_edge, W_edge        LOGICAL N_edge, S_edge, E_edge, W_edge
148    #ifdef ALLOW_EXCH2
149          INTEGER myTile
150    #endif
151  #ifdef ALLOW_DIAGNOSTICS  #ifdef ALLOW_DIAGNOSTICS
152        CHARACTER*8 diagName        CHARACTER*8 diagName
153        CHARACTER*4 GAD_DIAG_SUFX, diagSufx        CHARACTER*4 GAD_DIAG_SUFX, diagSufx
# Line 148  C [N,S,E,W]_edge :: true if N,S,E,W edge Line 156  C [N,S,E,W]_edge :: true if N,S,E,W edge
156  CEOP  CEOP
157    
158  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
159            act0 = tracerIdentity - 1            act0 = tracerIdentity
160            max0 = maxpass            max0 = maxpass
161            act1 = bi - myBxLo(myThid)            act1 = bi - myBxLo(myThid)
162            max1 = myBxHi(myThid) - myBxLo(myThid) + 1            max1 = myBxHi(myThid) - myBxLo(myThid) + 1
# Line 157  CEOP Line 165  CEOP
165            act3 = myThid - 1            act3 = myThid - 1
166            max3 = nTx*nTy            max3 = nTx*nTy
167            act4 = ikey_dynamics - 1            act4 = ikey_dynamics - 1
168            igadkey = (act0 + 1)            igadkey = act0
169       &                      + act1*max0       &                      + act1*max0
170       &                      + act2*max0*max1       &                      + act2*max0*max1
171       &                      + act3*max0*max1*max2       &                      + act3*max0*max1*max2
# Line 169  CEOP Line 177  CEOP
177  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
178    
179  #ifdef ALLOW_DIAGNOSTICS  #ifdef ALLOW_DIAGNOSTICS
180  C--   Set diagnostic suffix for the current tracer  C--   Set diagnostic suffix for the current tracer
181        IF ( useDiagnostics ) THEN        IF ( useDiagnostics ) THEN
182          diagSufx = GAD_DIAG_SUFX( tracerIdentity, myThid )          diagSufx = GAD_DIAG_SUFX( tracerIdentity, myThid )
183        ENDIF        ENDIF
# Line 190  C     uninitialised but inert locations. Line 198  C     uninitialised but inert locations.
198          fVerT(i,j,1) = 0. _d 0          fVerT(i,j,1) = 0. _d 0
199          fVerT(i,j,2) = 0. _d 0          fVerT(i,j,2) = 0. _d 0
200          rTransKp1(i,j)= 0. _d 0          rTransKp1(i,j)= 0. _d 0
201    #ifdef ALLOW_AUTODIFF_TAMC
202            localTij(i,j) = 0. _d 0
203            wfld(i,j)    = 0. _d 0
204    #endif
205         ENDDO         ENDDO
206        ENDDO        ENDDO
207    
# Line 215  C--   Set tile-specific parameters for h Line 227  C--   Set tile-specific parameters for h
227  #endif  #endif
228        ELSE        ELSE
229         nipass=2         nipass=2
230           nCFace = bi
231         N_edge = .FALSE.         N_edge = .FALSE.
232         S_edge = .FALSE.         S_edge = .FALSE.
233         E_edge = .FALSE.         E_edge = .FALSE.
# Line 236  CADJ &     comlev1_bibj_k_gad, key=kkey, Line 249  CADJ &     comlev1_bibj_k_gad, key=kkey,
249    
250  C--   Get temporary terms used by tendency routines  C--   Get temporary terms used by tendency routines
251        CALL CALC_COMMON_FACTORS (        CALL CALC_COMMON_FACTORS (
252       I         bi,bj,iMin,iMax,jMin,jMax,k,       I         uVel, vVel,
253       O         xA,yA,uTrans,vTrans,rTrans,maskUp,       O         uFld, vFld, uTrans, vTrans, xA, yA,
254       I         myThid)       I         k,bi,bj, myThid )
255    
256  #ifdef ALLOW_GMREDI  #ifdef ALLOW_GMREDI
257  C--   Residual transp = Bolus transp + Eulerian transp  C--   Residual transp = Bolus transp + Eulerian transp
258        IF (useGMRedi)        IF (useGMRedi)
259       &   CALL GMREDI_CALC_UVFLOW(       &   CALL GMREDI_CALC_UVFLOW(
260       &            uTrans, vTrans, bi, bj, k, myThid)       U                  uFld, vFld, uTrans, vTrans,
261         I                  k, bi, bj, myThid )
262  #endif /* ALLOW_GMREDI */  #endif /* ALLOW_GMREDI */
263    
264  C--   Make local copy of tracer array and mask West & South  C--   Make local copy of tracer array and mask West & South
# Line 256  C--   Make local copy of tracer array an Line 270  C--   Make local copy of tracer array an
270         ENDDO         ENDDO
271        ENDDO        ENDDO
272    
273  #ifndef ALLOW_AUTODIFF_TAMC  cph-exch2#ifndef ALLOW_AUTODIFF_TAMC
274        IF (useCubedSphereExchange) THEN        IF (useCubedSphereExchange) THEN
275          withSigns = .FALSE.          withSigns = .FALSE.
276          CALL FILL_CS_CORNER_UV_RS(          CALL FILL_CS_CORNER_UV_RS(
277       &            withSigns, maskLocW,maskLocS, bi,bj, myThid )       &            withSigns, maskLocW,maskLocS, bi,bj, myThid )
278        ENDIF        ENDIF
279  #endif  cph-exch2#endif
280    
281  C--   Multiple passes for different directions on different tiles  C--   Multiple passes for different directions on different tiles
282  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.
283        DO ipass=1,nipass        DO ipass=1,nipass
284  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
285           passkey = ipass + (k-1)      *maxcube           passkey = ipass
286       &                   + (igadkey-1)*maxcube*Nr       &                   + (k-1)      *maxpass
287         &                   + (igadkey-1)*maxpass*Nr
288           IF (nipass .GT. maxpass) THEN           IF (nipass .GT. maxpass) THEN
289            STOP 'GAD_ADVECTION: nipass > maxcube. check tamc.h'            STOP 'GAD_ADVECTION: nipass > maxcube. check tamc.h'
290           ENDIF           ENDIF
# Line 307  C-    not CubedSphere Line 322  C-    not CubedSphere
322          calc_fluxes_X = MOD(ipass,2).EQ.1          calc_fluxes_X = MOD(ipass,2).EQ.1
323          calc_fluxes_Y = .NOT.calc_fluxes_X          calc_fluxes_Y = .NOT.calc_fluxes_X
324        ENDIF        ENDIF
325    
326  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
327  C--   X direction  C--   X direction
328    C-     Advective flux in X
329            DO j=1-Oly,sNy+Oly
330             DO i=1-Olx,sNx+Olx
331              af(i,j) = 0.
332             ENDDO
333            ENDDO
334    C
335    #ifdef ALLOW_AUTODIFF_TAMC
336    # ifndef DISABLE_MULTIDIM_ADVECTION
337    CADJ STORE localTij(:,:)  =
338    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
339    CADJ STORE af(:,:)  =
340    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
341    # endif
342    #endif /* ALLOW_AUTODIFF_TAMC */
343    C
344        IF (calc_fluxes_X) THEN        IF (calc_fluxes_X) THEN
345    
346  C-     Do not compute fluxes if  C-     Do not compute fluxes if
347  C       a) needed in overlap only  C       a) needed in overlap only
348  C   and b) the overlap of myTile are not cube-face Edges  C   and b) the overlap of myTile are not cube-face Edges
349         IF ( .NOT.overlapOnly .OR. N_edge .OR. S_edge ) THEN         IF ( .NOT.overlapOnly .OR. N_edge .OR. S_edge ) THEN
350    
351  #ifndef ALLOW_AUTODIFF_TAMC  cph-exch2#ifndef ALLOW_AUTODIFF_TAMC
352  C-     Internal exchange for calculations in X  C-     Internal exchange for calculations in X
353  #ifdef MULTIDIM_OLD_VERSION  #ifdef MULTIDIM_OLD_VERSION
354          IF ( useCubedSphereExchange ) THEN          IF ( useCubedSphereExchange ) THEN
# Line 325  C-     Internal exchange for calculation Line 356  C-     Internal exchange for calculation
356          IF ( useCubedSphereExchange .AND.          IF ( useCubedSphereExchange .AND.
357       &       ( overlapOnly .OR. ipass.EQ.1 ) ) THEN       &       ( overlapOnly .OR. ipass.EQ.1 ) ) THEN
358  #endif  #endif
359           CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )           CALL FILL_CS_CORNER_TR_RL( .TRUE., .FALSE.,
360         &                              localTij, bi,bj, myThid )
361          ENDIF          ENDIF
362  #endif  cph-exch2#endif
   
 C-     Advective flux in X  
         DO j=1-Oly,sNy+Oly  
          DO i=1-Olx,sNx+Olx  
           af(i,j) = 0.  
          ENDDO  
         ENDDO  
363    
364  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
365  #ifndef DISABLE_MULTIDIM_ADVECTION  # ifndef DISABLE_MULTIDIM_ADVECTION
366  CADJ STORE localTij(:,:)  =  CADJ STORE localTij(:,:)  =
367  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
368  #endif  # endif
369  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
370    
371          IF ( advectionScheme.EQ.ENUM_UPWIND_1RST          IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
372       &     .OR. advectionScheme.EQ.ENUM_DST2 ) THEN       &     .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
373            CALL GAD_DST2U1_ADV_X( bi,bj,k, advectionScheme,            CALL GAD_DST2U1_ADV_X( bi,bj,k, advectionScheme, .TRUE.,
374       I                           dTtracerLev(k),uTrans,uVel,localTij,       I                           dTtracerLev(k),uTrans,uFld,localTij,
375       O                           af, myThid )       O                           af, myThid )
376          ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN          ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
377            CALL GAD_FLUXLIMIT_ADV_X( bi,bj,k, dTtracerLev(k),            CALL GAD_FLUXLIMIT_ADV_X( bi,bj,k, .TRUE., dTtracerLev(k),
378       I                              uTrans, uVel, maskLocW, localTij,       I                              uTrans, uFld, maskLocW, localTij,
379       O                              af, myThid )       O                              af, myThid )
380          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
381            CALL GAD_DST3_ADV_X(      bi,bj,k, dTtracerLev(k),            CALL GAD_DST3_ADV_X(      bi,bj,k, .TRUE., dTtracerLev(k),
382       I                              uTrans, uVel, maskLocW, localTij,       I                              uTrans, uFld, maskLocW, localTij,
383       O                              af, myThid )       O                              af, myThid )
384          ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN          ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
385            CALL GAD_DST3FL_ADV_X(    bi,bj,k, dTtracerLev(k),            CALL GAD_DST3FL_ADV_X(    bi,bj,k, .TRUE., dTtracerLev(k),
386       I                              uTrans, uVel, maskLocW, localTij,       I                              uTrans, uFld, maskLocW, localTij,
387         O                              af, myThid )
388    #ifndef ALLOW_AUTODIFF_TAMC
389            ELSEIF (advectionScheme.EQ.ENUM_OS7MP ) THEN
390              CALL GAD_OS7MP_ADV_X(     bi,bj,k, .TRUE., dTtracerLev(k),
391         I                              uTrans, uFld, maskLocW, localTij,
392       O                              af, myThid )       O                              af, myThid )
393    #endif
394          ELSE          ELSE
395           STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'           STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'
396          ENDIF          ENDIF
# Line 367  CADJ &     comlev1_bibj_k_gad_pass, key= Line 398  CADJ &     comlev1_bibj_k_gad_pass, key=
398  C-     Advective flux in X : done  C-     Advective flux in X : done
399         ENDIF         ENDIF
400    
401  #ifndef ALLOW_AUTODIFF_TAMC  cph-exch2#ifndef ALLOW_AUTODIFF_TAMC
402  C-     Internal exchange for next calculations in Y  C-     Internal exchange for next calculations in Y
403         IF ( overlapOnly .AND. ipass.EQ.1 ) THEN         IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
404           CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )           CALL FILL_CS_CORNER_TR_RL(.FALSE., .FALSE.,
405         &                              localTij, bi,bj, myThid )
406         ENDIF         ENDIF
407  #endif  cph-exch2#endif
408    
409  C-     Update the local tracer field where needed:  C-     Update the local tracer field where needed:
410    
# Line 380  C      update in overlap-Only Line 412  C      update in overlap-Only
412         IF ( overlapOnly ) THEN         IF ( overlapOnly ) THEN
413          iMinUpd = 1-Olx+1          iMinUpd = 1-Olx+1
414          iMaxUpd = sNx+Olx-1          iMaxUpd = sNx+Olx-1
415  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
416  C         in corner region) but safer to keep them.  C         in corner region) but safer to keep them.
417          IF ( W_edge ) iMinUpd = 1          IF ( W_edge ) iMinUpd = 1
418          IF ( E_edge ) iMaxUpd = sNx          IF ( E_edge ) iMaxUpd = sNx
# Line 388  C         in corner region) but safer to Line 420  C         in corner region) but safer to
420          IF ( S_edge ) THEN          IF ( S_edge ) THEN
421           DO j=1-Oly,0           DO j=1-Oly,0
422            DO i=iMinUpd,iMaxUpd            DO i=iMinUpd,iMaxUpd
423             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
424       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
425       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
426         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
427       &       *( af(i+1,j)-af(i,j)       &       *( af(i+1,j)-af(i,j)
428       &         -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))
429       &        )       &        )
# Line 400  C         in corner region) but safer to Line 433  C         in corner region) but safer to
433          IF ( N_edge ) THEN          IF ( N_edge ) THEN
434           DO j=sNy+1,sNy+Oly           DO j=sNy+1,sNy+Oly
435            DO i=iMinUpd,iMaxUpd            DO i=iMinUpd,iMaxUpd
436             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
437       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
438       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
439         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
440       &       *( af(i+1,j)-af(i,j)       &       *( af(i+1,j)-af(i,j)
441       &         -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))
442       &        )       &        )
# Line 412  C         in corner region) but safer to Line 446  C         in corner region) but safer to
446    
447         ELSE         ELSE
448  C      do not only update the overlap  C      do not only update the overlap
449          jMinUpd = 1-Oly          jMinUpd = 1-Oly
450          jMaxUpd = sNy+Oly          jMaxUpd = sNy+Oly
451          IF ( interiorOnly .AND. S_edge ) jMinUpd = 1          IF ( interiorOnly .AND. S_edge ) jMinUpd = 1
452          IF ( interiorOnly .AND. N_edge ) jMaxUpd = sNy          IF ( interiorOnly .AND. N_edge ) jMaxUpd = sNy
453          DO j=jMinUpd,jMaxUpd          DO j=jMinUpd,jMaxUpd
454           DO i=1-Olx+1,sNx+Olx-1           DO i=1-Olx+1,sNx+Olx-1
455             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
456       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
457       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
458         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
459       &       *( af(i+1,j)-af(i,j)       &       *( af(i+1,j)-af(i,j)
460       &         -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))
461       &        )       &        )
# Line 442  C-     Apply open boundary conditions Line 477  C-     Apply open boundary conditions
477            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
478  #ifdef ALLOW_PTRACERS  #ifdef ALLOW_PTRACERS
479           ELSEIF (tracerIdentity.GE.GAD_TR1) THEN           ELSEIF (tracerIdentity.GE.GAD_TR1) THEN
480            CALL OBCS_APPLY_PTRACER( bi, bj, k,            CALL OBCS_APPLY_PTRACER( bi, bj, k,
481       &         tracerIdentity-GAD_TR1+1, localTij, myThid )       &         tracerIdentity-GAD_TR1+1, localTij, myThid )
482  #endif /* ALLOW_PTRACERS */  #endif /* ALLOW_PTRACERS */
483           ENDIF           ENDIF
# Line 451  C-     Apply open boundary conditions Line 486  C-     Apply open boundary conditions
486    
487  C-     end if/else update overlap-Only  C-     end if/else update overlap-Only
488         ENDIF         ENDIF
489            
490  C--   End of X direction  C--   End of X direction
491        ENDIF        ENDIF
492    
493  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
494  C--   Y direction  C--   Y direction
495    cph-test
496    C-     Advective flux in Y
497            DO j=1-Oly,sNy+Oly
498             DO i=1-Olx,sNx+Olx
499              af(i,j) = 0.
500             ENDDO
501            ENDDO
502    C
503    #ifdef ALLOW_AUTODIFF_TAMC
504    # ifndef DISABLE_MULTIDIM_ADVECTION
505    CADJ STORE localTij(:,:)  =
506    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
507    CADJ STORE af(:,:)  =
508    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
509    # endif
510    #endif /* ALLOW_AUTODIFF_TAMC */
511    C
512        IF (calc_fluxes_Y) THEN        IF (calc_fluxes_Y) THEN
513    
514  C-     Do not compute fluxes if  C-     Do not compute fluxes if
# Line 464  C       a) needed in overlap only Line 516  C       a) needed in overlap only
516  C   and b) the overlap of myTile are not cube-face edges  C   and b) the overlap of myTile are not cube-face edges
517         IF ( .NOT.overlapOnly .OR. E_edge .OR. W_edge ) THEN         IF ( .NOT.overlapOnly .OR. E_edge .OR. W_edge ) THEN
518    
519  #ifndef ALLOW_AUTODIFF_TAMC  cph-exch2#ifndef ALLOW_AUTODIFF_TAMC
520  C-     Internal exchange for calculations in Y  C-     Internal exchange for calculations in Y
521  #ifdef MULTIDIM_OLD_VERSION  #ifdef MULTIDIM_OLD_VERSION
522          IF ( useCubedSphereExchange ) THEN          IF ( useCubedSphereExchange ) THEN
# Line 472  C-     Internal exchange for calculation Line 524  C-     Internal exchange for calculation
524          IF ( useCubedSphereExchange .AND.          IF ( useCubedSphereExchange .AND.
525       &       ( overlapOnly .OR. ipass.EQ.1 ) ) THEN       &       ( overlapOnly .OR. ipass.EQ.1 ) ) THEN
526  #endif  #endif
527           CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )           CALL FILL_CS_CORNER_TR_RL(.FALSE., .FALSE.,
528         &                              localTij, bi,bj, myThid )
529          ENDIF          ENDIF
530  #endif  cph-exch2#endif
531    
532  C-     Advective flux in Y  C-     Advective flux in Y
533          DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
# Line 492  CADJ &     comlev1_bibj_k_gad_pass, key= Line 545  CADJ &     comlev1_bibj_k_gad_pass, key=
545    
546          IF ( advectionScheme.EQ.ENUM_UPWIND_1RST          IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
547       &     .OR. advectionScheme.EQ.ENUM_DST2 ) THEN       &     .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
548            CALL GAD_DST2U1_ADV_Y( bi,bj,k, advectionScheme,            CALL GAD_DST2U1_ADV_Y( bi,bj,k, advectionScheme, .TRUE.,
549       I                           dTtracerLev(k),vTrans,vVel,localTij,       I                           dTtracerLev(k),vTrans,vFld,localTij,
550       O                           af, myThid )       O                           af, myThid )
551          ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN          ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
552            CALL GAD_FLUXLIMIT_ADV_Y( bi,bj,k, dTtracerLev(k),            CALL GAD_FLUXLIMIT_ADV_Y( bi,bj,k, .TRUE., dTtracerLev(k),
553       I                              vTrans, vVel, maskLocS, localTij,       I                              vTrans, vFld, maskLocS, localTij,
554       O                              af, myThid )       O                              af, myThid )
555          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
556            CALL GAD_DST3_ADV_Y(      bi,bj,k, dTtracerLev(k),            CALL GAD_DST3_ADV_Y(      bi,bj,k, .TRUE., dTtracerLev(k),
557       I                              vTrans, vVel, maskLocS, localTij,       I                              vTrans, vFld, maskLocS, localTij,
558       O                              af, myThid )       O                              af, myThid )
559          ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN          ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
560            CALL GAD_DST3FL_ADV_Y(    bi,bj,k, dTtracerLev(k),            CALL GAD_DST3FL_ADV_Y(    bi,bj,k, .TRUE., dTtracerLev(k),
561       I                              vTrans, vVel, maskLocS, localTij,       I                              vTrans, vFld, maskLocS, localTij,
562         O                              af, myThid )
563    #ifndef ALLOW_AUTODIFF_TAMC
564            ELSEIF (advectionScheme.EQ.ENUM_OS7MP ) THEN
565              CALL GAD_OS7MP_ADV_Y(     bi,bj,k, .TRUE., dTtracerLev(k),
566         I                              vTrans, vFld, maskLocS, localTij,
567       O                              af, myThid )       O                              af, myThid )
568    #endif
569          ELSE          ELSE
570           STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'           STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
571          ENDIF          ENDIF
# Line 514  CADJ &     comlev1_bibj_k_gad_pass, key= Line 573  CADJ &     comlev1_bibj_k_gad_pass, key=
573  C-     Advective flux in Y : done  C-     Advective flux in Y : done
574         ENDIF         ENDIF
575    
576  #ifndef ALLOW_AUTODIFF_TAMC  cph-exch2#ifndef ALLOW_AUTODIFF_TAMC
577  C-     Internal exchange for next calculations in X  C-     Internal exchange for next calculations in X
578         IF ( overlapOnly .AND. ipass.EQ.1 ) THEN         IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
579           CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )           CALL FILL_CS_CORNER_TR_RL( .TRUE., .FALSE.,
580         &                              localTij, bi,bj, myThid )
581         ENDIF         ENDIF
582  #endif  cph-exch2#endif
583    
584  C-     Update the local tracer field where needed:  C-     Update the local tracer field where needed:
585    
586  C      update in overlap-Only  C      update in overlap-Only
587         IF ( overlapOnly ) THEN         IF ( overlapOnly ) THEN
588          jMinUpd = 1-Oly+1          jMinUpd = 1-Oly+1
589          jMaxUpd = sNy+Oly-1          jMaxUpd = sNy+Oly-1
590  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
591  C         in corner region) but safer to keep them.  C         in corner region) but safer to keep them.
592          IF ( S_edge ) jMinUpd = 1          IF ( S_edge ) jMinUpd = 1
593          IF ( N_edge ) jMaxUpd = sNy          IF ( N_edge ) jMaxUpd = sNy
# Line 535  C         in corner region) but safer to Line 595  C         in corner region) but safer to
595          IF ( W_edge ) THEN          IF ( W_edge ) THEN
596           DO j=jMinUpd,jMaxUpd           DO j=jMinUpd,jMaxUpd
597            DO i=1-Olx,0            DO i=1-Olx,0
598             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
599       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
600       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
601         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
602       &       *( af(i,j+1)-af(i,j)       &       *( af(i,j+1)-af(i,j)
603       &         -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))
604       &        )       &        )
# Line 547  C         in corner region) but safer to Line 608  C         in corner region) but safer to
608          IF ( E_edge ) THEN          IF ( E_edge ) THEN
609           DO j=jMinUpd,jMaxUpd           DO j=jMinUpd,jMaxUpd
610            DO i=sNx+1,sNx+Olx            DO i=sNx+1,sNx+Olx
611             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
612       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
613       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
614         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
615       &       *( af(i,j+1)-af(i,j)       &       *( af(i,j+1)-af(i,j)
616       &         -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))
617       &        )       &        )
# Line 565  C      do not only update the overlap Line 627  C      do not only update the overlap
627          IF ( interiorOnly .AND. E_edge ) iMaxUpd = sNx          IF ( interiorOnly .AND. E_edge ) iMaxUpd = sNx
628          DO j=1-Oly+1,sNy+Oly-1          DO j=1-Oly+1,sNy+Oly-1
629           DO i=iMinUpd,iMaxUpd           DO i=iMinUpd,iMaxUpd
630             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
631       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
632       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
633         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
634       &       *( af(i,j+1)-af(i,j)       &       *( af(i,j+1)-af(i,j)
635       &         -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))
636       &        )       &        )
# Line 589  C-     Apply open boundary conditions Line 652  C-     Apply open boundary conditions
652            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
653  #ifdef ALLOW_PTRACERS  #ifdef ALLOW_PTRACERS
654           ELSEIF (tracerIdentity.GE.GAD_TR1) THEN           ELSEIF (tracerIdentity.GE.GAD_TR1) THEN
655            CALL OBCS_APPLY_PTRACER( bi, bj, k,            CALL OBCS_APPLY_PTRACER( bi, bj, k,
656       &         tracerIdentity-GAD_TR1+1, localTij, myThid )       &         tracerIdentity-GAD_TR1+1, localTij, myThid )
657  #endif /* ALLOW_PTRACERS */  #endif /* ALLOW_PTRACERS */
658           ENDIF           ENDIF
# Line 615  C-    explicit advection is done ; store Line 678  C-    explicit advection is done ; store
678          ENDDO          ENDDO
679        ELSE        ELSE
680  C-    horizontal advection done; store intermediate result in 3D array:  C-    horizontal advection done; store intermediate result in 3D array:
681         DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
682          DO i=1-Olx,sNx+Olx           DO i=1-Olx,sNx+Olx
683           localTijk(i,j,k)=localTij(i,j)            localTijk(i,j,k)=localTij(i,j)
684             ENDDO
685          ENDDO          ENDDO
        ENDDO  
686        ENDIF        ENDIF
687    
688  #ifdef ALLOW_DIAGNOSTICS  #ifdef ALLOW_DIAGNOSTICS
# Line 651  C---+----1----+----2----+----3----+----4 Line 714  C---+----1----+----2----+----3----+----4
714  C--   Start of k loop for vertical flux  C--   Start of k loop for vertical flux
715         DO k=Nr,1,-1         DO k=Nr,1,-1
716  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
717           kkey = (igadkey-1)*Nr + k           kkey = (igadkey-1)*Nr + (Nr-k+1)
718  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
719  C--   kup    Cycles through 1,2 to point to w-layer above  C--   kUp    Cycles through 1,2 to point to w-layer above
720  C--   kDown  Cycles through 2,1 to point to w-layer below  C--   kDown  Cycles through 2,1 to point to w-layer below
721          kup  = 1+MOD(k+1,2)          kUp  = 1+MOD(k+1,2)
722          kDown= 1+MOD(k,2)          kDown= 1+MOD(k,2)
723  c       kp1=min(Nr,k+1)  c       kp1=min(Nr,k+1)
724          kp1Msk=1.          kp1Msk=1.
725          if (k.EQ.Nr) kp1Msk=0.          if (k.EQ.Nr) kp1Msk=0.
726    
727    #ifdef ALLOW_AUTODIFF_TAMC
728    CADJ STORE rtrans(:,:)  =
729    CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
730    cphCADJ STORE wfld(:,:)  =
731    cphCADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
732    #endif
733    
734  C-- Compute Vertical transport  C-- Compute Vertical transport
735  #ifdef ALLOW_AIM  #ifdef ALLOW_AIM
736  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 671  C- a hack to prevent Water-Vapor vert.tr Line 741  C- a hack to prevent Water-Vapor vert.tr
741          IF ( k.EQ.1 ) THEN          IF ( k.EQ.1 ) THEN
742  #endif  #endif
743    
744    #ifdef ALLOW_AUTODIFF_TAMC
745    cphmultiCADJ STORE wfld(:,:)  =
746    cphmultiCADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
747    #endif /* ALLOW_AUTODIFF_TAMC */
748    
749  C- Surface interface :  C- Surface interface :
750           DO j=1-Oly,sNy+Oly           DO j=1-Oly,sNy+Oly
751            DO i=1-Olx,sNx+Olx            DO i=1-Olx,sNx+Olx
752             rTransKp1(i,j) = kp1Msk*rTrans(i,j)             rTransKp1(i,j) = kp1Msk*rTrans(i,j)
753               wFld(i,j)   = 0.
754             rTrans(i,j) = 0.             rTrans(i,j) = 0.
755             fVerT(i,j,kUp) = 0.             fVerT(i,j,kUp) = 0.
756            ENDDO            ENDDO
757           ENDDO           ENDDO
758    
759          ELSE          ELSE
 C- Interior interface :  
760    
761    #ifdef ALLOW_AUTODIFF_TAMC
762    cphmultiCADJ STORE wfld(:,:)  =
763    cphmultiCADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
764    #endif /* ALLOW_AUTODIFF_TAMC */
765    
766    C- Interior interface :
767           DO j=1-Oly,sNy+Oly           DO j=1-Oly,sNy+Oly
768            DO i=1-Olx,sNx+Olx            DO i=1-Olx,sNx+Olx
769             rTransKp1(i,j) = kp1Msk*rTrans(i,j)             rTransKp1(i,j) = kp1Msk*rTrans(i,j)
770               wFld(i,j)   = wVel(i,j,k,bi,bj)
771             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)
772         &                 *deepFac2F(k)*rhoFacF(k)
773       &                 *maskC(i,j,k-1,bi,bj)       &                 *maskC(i,j,k-1,bi,bj)
774             fVerT(i,j,kUp) = 0.             fVerT(i,j,kUp) = 0.
775            ENDDO            ENDDO
# Line 694  C- Interior interface : Line 777  C- Interior interface :
777    
778  #ifdef ALLOW_GMREDI  #ifdef ALLOW_GMREDI
779  C--   Residual transp = Bolus transp + Eulerian transp  C--   Residual transp = Bolus transp + Eulerian transp
780           IF (useGMRedi)           IF (useGMRedi)
781       &   CALL GMREDI_CALC_WFLOW(       &     CALL GMREDI_CALC_WFLOW(
782       &                    rTrans, bi, bj, k, myThid)       U                 wFld, rTrans,
783         I                 k, bi, bj, myThid )
784  #endif /* ALLOW_GMREDI */  #endif /* ALLOW_GMREDI */
785    
786  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
787  CADJ STORE localTijk(:,:,k)    cphmultiCADJ STORE localTijk(:,:,k)  
788  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte  cphmultiCADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
789  CADJ STORE rTrans(:,:)    cphmultiCADJ STORE rTrans(:,:)  
790  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte  cphmultiCADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
791  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
792    
793  C-    Compute vertical advective flux in the interior:  C-    Compute vertical advective flux in the interior:
794           IF ( advectionScheme.EQ.ENUM_UPWIND_1RST           IF ( vertAdvecScheme.EQ.ENUM_UPWIND_1RST
795       &      .OR. advectionScheme.EQ.ENUM_DST2 ) THEN       &      .OR. vertAdvecScheme.EQ.ENUM_DST2 ) THEN
796             CALL GAD_DST2U1_ADV_R( bi,bj,k, advectionScheme,             CALL GAD_DST2U1_ADV_R( bi,bj,k, advectionScheme,
797       I                            dTtracerLev(k),rTrans,wVel,localTijk,       I                            dTtracerLev(k),rTrans,wFld,localTijk,
798       O                            fVerT(1-Olx,1-Oly,kUp), myThid )       O                            fVerT(1-Olx,1-Oly,kUp), myThid )
799           ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN           ELSEIF( vertAdvecScheme.EQ.ENUM_FLUX_LIMIT) THEN
800             CALL GAD_FLUXLIMIT_ADV_R( bi,bj,k, dTtracerLev(k),             CALL GAD_FLUXLIMIT_ADV_R( bi,bj,k, dTtracerLev(k),
801       I                               rTrans, wVel, localTijk,       I                               rTrans, wFld, localTijk,
802       O                               fVerT(1-Olx,1-Oly,kUp), myThid )       O                               fVerT(1-Olx,1-Oly,kUp), myThid )
803           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3 ) THEN           ELSEIF( vertAdvecScheme.EQ.ENUM_DST3 ) THEN
804             CALL GAD_DST3_ADV_R(      bi,bj,k, dTtracerLev(k),             CALL GAD_DST3_ADV_R(      bi,bj,k, dTtracerLev(k),
805       I                               rTrans, wVel, localTijk,       I                               rTrans, wFld, localTijk,
806       O                               fVerT(1-Olx,1-Oly,kUp), myThid )       O                               fVerT(1-Olx,1-Oly,kUp), myThid )
807           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN           ELSEIF( vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
808             CALL GAD_DST3FL_ADV_R(    bi,bj,k, dTtracerLev(k),             CALL GAD_DST3FL_ADV_R(    bi,bj,k, dTtracerLev(k),
809       I                               rTrans, wVel, localTijk,       I                               rTrans, wFld, localTijk,
810         O                               fVerT(1-Olx,1-Oly,kUp), myThid )
811    #ifndef ALLOW_AUTODIFF_TAMC
812             ELSEIF (vertAdvecScheme.EQ.ENUM_OS7MP ) THEN
813               CALL GAD_OS7MP_ADV_R(     bi,bj,k, dTtracerLev(k),
814         I                               rTrans, wFld, localTijk,
815       O                               fVerT(1-Olx,1-Oly,kUp), myThid )       O                               fVerT(1-Olx,1-Oly,kUp), myThid )
816    #endif
817           ELSE           ELSE
818            STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'            STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
819           ENDIF           ENDIF
# Line 732  C- end Surface/Interior if bloc Line 822  C- end Surface/Interior if bloc
822          ENDIF          ENDIF
823    
824  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
825  CADJ STORE rTrans(:,:)    cphmultiCADJ STORE rTrans(:,:)  
826  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte  cphmultiCADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
827  CADJ STORE rTranskp1(:,:)    cphmultiCADJ STORE rTranskp1(:,:)  
828    cphmultiCADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
829    cph --- following storing of fVerT is critical for correct
830    cph --- gradient with multiDimAdvection
831    cph --- Without it, kDown component is not properly recomputed
832    cph --- This is a TAF bug (and no warning available)
833    CADJ STORE fVerT(:,:,:)  
834  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
835  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
836    
837  C--   Divergence of vertical fluxes  C--   Divergence of vertical fluxes
838          DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
839           DO i=1-Olx,sNx+Olx           DO i=1-Olx,sNx+Olx
840            localTij(i,j)=localTijk(i,j,k)-dTtracerLev(k)*            localTij(i,j) = localTijk(i,j,k)
841       &     _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
842       &     *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
843       &     *( fVerT(i,j,kDown)-fVerT(i,j,kUp)       &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
844       &       -tracer(i,j,k,bi,bj)*(rTransKp1(i,j)-rTrans(i,j))       &       *( fVerT(i,j,kDown)-fVerT(i,j,kUp)
845       &      )*rkSign       &         -tracer(i,j,k,bi,bj)*(rTransKp1(i,j)-rTrans(i,j))
846         &        )*rkSign
847            gTracer(i,j,k,bi,bj)=            gTracer(i,j,k,bi,bj)=
848       &     (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)       &     (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)
849           ENDDO           ENDDO
850          ENDDO          ENDDO
851    
852  #ifdef ALLOW_DIAGNOSTICS  #ifdef ALLOW_DIAGNOSTICS
853          IF ( useDiagnostics ) THEN          IF ( useDiagnostics ) THEN
854            diagName = 'ADVr'//diagSufx            diagName = 'ADVr'//diagSufx
# Line 763  C--   Divergence of vertical fluxes Line 860  C--   Divergence of vertical fluxes
860  C--   End of K loop for vertical flux  C--   End of K loop for vertical flux
861         ENDDO         ENDDO
862  C--   end of if not.implicitAdvection block  C--   end of if not.implicitAdvection block
863        ENDIF        ENDIF
864    
865        RETURN        RETURN
866        END        END

Legend:
Removed from v.1.37  
changed lines
  Added in v.1.53

  ViewVC Help
Powered by ViewVC 1.1.22