/[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.34 by jmc, Mon Dec 20 19:10:13 2004 UTC revision 1.51 by heimbach, Fri Oct 19 14:45:10 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.
# Line 307  C-    not CubedSphere Line 321  C-    not CubedSphere
321          calc_fluxes_X = MOD(ipass,2).EQ.1          calc_fluxes_X = MOD(ipass,2).EQ.1
322          calc_fluxes_Y = .NOT.calc_fluxes_X          calc_fluxes_Y = .NOT.calc_fluxes_X
323        ENDIF        ENDIF
324    
325  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
326  C--   X direction  C--   X direction
327    C-     Advective flux in X
328            DO j=1-Oly,sNy+Oly
329             DO i=1-Olx,sNx+Olx
330              af(i,j) = 0.
331             ENDDO
332            ENDDO
333    C
334    #ifdef ALLOW_AUTODIFF_TAMC
335    # ifndef DISABLE_MULTIDIM_ADVECTION
336    CADJ STORE localTij(:,:)  =
337    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
338    CADJ STORE af(:,:)  =
339    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
340    # endif
341    #endif /* ALLOW_AUTODIFF_TAMC */
342    C
343        IF (calc_fluxes_X) THEN        IF (calc_fluxes_X) THEN
344    
345  C-     Do not compute fluxes if  C-     Do not compute fluxes if
346  C       a) needed in overlap only  C       a) needed in overlap only
347  C   and b) the overlap of myTile are not cube-face Edges  C   and b) the overlap of myTile are not cube-face Edges
348         IF ( .NOT.overlapOnly .OR. N_edge .OR. S_edge ) THEN         IF ( .NOT.overlapOnly .OR. N_edge .OR. S_edge ) THEN
349    
350  #ifndef ALLOW_AUTODIFF_TAMC  cph-exch2#ifndef ALLOW_AUTODIFF_TAMC
351  C-     Internal exchange for calculations in X  C-     Internal exchange for calculations in X
352  #ifdef MULTIDIM_OLD_VERSION  #ifdef MULTIDIM_OLD_VERSION
353          IF ( useCubedSphereExchange ) THEN          IF ( useCubedSphereExchange ) THEN
# Line 325  C-     Internal exchange for calculation Line 355  C-     Internal exchange for calculation
355          IF ( useCubedSphereExchange .AND.          IF ( useCubedSphereExchange .AND.
356       &       ( overlapOnly .OR. ipass.EQ.1 ) ) THEN       &       ( overlapOnly .OR. ipass.EQ.1 ) ) THEN
357  #endif  #endif
358           CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )           CALL FILL_CS_CORNER_TR_RL( .TRUE., .FALSE.,
359         &                              localTij, bi,bj, myThid )
360          ENDIF          ENDIF
361  #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  
362    
363  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
364  #ifndef DISABLE_MULTIDIM_ADVECTION  # ifndef DISABLE_MULTIDIM_ADVECTION
365  CADJ STORE localTij(:,:)  =  CADJ STORE localTij(:,:)  =
366  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
367  #endif  # endif
368  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
369    
370          IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN          IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
371            CALL GAD_FLUXLIMIT_ADV_X( bi,bj,k, dTtracerLev(k),       &     .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
372       I                              uTrans, uVel, maskLocW, localTij,            CALL GAD_DST2U1_ADV_X( bi,bj,k, advectionScheme, .TRUE.,
373         I                           dTtracerLev(k),uTrans,uFld,localTij,
374         O                           af, myThid )
375            ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
376              CALL GAD_FLUXLIMIT_ADV_X( bi,bj,k, .TRUE., dTtracerLev(k),
377         I                              uTrans, uFld, maskLocW, localTij,
378       O                              af, myThid )       O                              af, myThid )
379          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
380            CALL GAD_DST3_ADV_X(      bi,bj,k, dTtracerLev(k),            CALL GAD_DST3_ADV_X(      bi,bj,k, .TRUE., dTtracerLev(k),
381       I                              uTrans, uVel, maskLocW, localTij,       I                              uTrans, uFld, maskLocW, localTij,
382       O                              af, myThid )       O                              af, myThid )
383          ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN          ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
384            CALL GAD_DST3FL_ADV_X(    bi,bj,k, dTtracerLev(k),            CALL GAD_DST3FL_ADV_X(    bi,bj,k, .TRUE., dTtracerLev(k),
385       I                              uTrans, uVel, maskLocW, localTij,       I                              uTrans, uFld, maskLocW, localTij,
386       O                              af, myThid )       O                              af, myThid )
387    #ifndef ALLOW_AUTODIFF_TAMC
388            ELSEIF (advectionScheme.EQ.ENUM_OS7MP ) THEN
389              CALL GAD_OS7MP_ADV_X(     bi,bj,k, .TRUE., dTtracerLev(k),
390         I                              uTrans, uFld, maskLocW, localTij,
391         O                              af, myThid )
392    #endif
393          ELSE          ELSE
394           STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'           STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'
395          ENDIF          ENDIF
# Line 362  CADJ &     comlev1_bibj_k_gad_pass, key= Line 397  CADJ &     comlev1_bibj_k_gad_pass, key=
397  C-     Advective flux in X : done  C-     Advective flux in X : done
398         ENDIF         ENDIF
399    
400  #ifndef ALLOW_AUTODIFF_TAMC  cph-exch2#ifndef ALLOW_AUTODIFF_TAMC
401  C-     Internal exchange for next calculations in Y  C-     Internal exchange for next calculations in Y
402         IF ( overlapOnly .AND. ipass.EQ.1 ) THEN         IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
403           CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )           CALL FILL_CS_CORNER_TR_RL(.FALSE., .FALSE.,
404         &                              localTij, bi,bj, myThid )
405         ENDIF         ENDIF
406  #endif  cph-exch2#endif
407    
408  C-     Update the local tracer field where needed:  C-     Update the local tracer field where needed:
409    
# Line 375  C      update in overlap-Only Line 411  C      update in overlap-Only
411         IF ( overlapOnly ) THEN         IF ( overlapOnly ) THEN
412          iMinUpd = 1-Olx+1          iMinUpd = 1-Olx+1
413          iMaxUpd = sNx+Olx-1          iMaxUpd = sNx+Olx-1
414  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
415  C         in corner region) but safer to keep them.  C         in corner region) but safer to keep them.
416          IF ( W_edge ) iMinUpd = 1          IF ( W_edge ) iMinUpd = 1
417          IF ( E_edge ) iMaxUpd = sNx          IF ( E_edge ) iMaxUpd = sNx
# Line 383  C         in corner region) but safer to Line 419  C         in corner region) but safer to
419          IF ( S_edge ) THEN          IF ( S_edge ) THEN
420           DO j=1-Oly,0           DO j=1-Oly,0
421            DO i=iMinUpd,iMaxUpd            DO i=iMinUpd,iMaxUpd
422             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
423       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
424       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
425         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
426       &       *( af(i+1,j)-af(i,j)       &       *( af(i+1,j)-af(i,j)
427       &         -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))
428       &        )       &        )
# Line 395  C         in corner region) but safer to Line 432  C         in corner region) but safer to
432          IF ( N_edge ) THEN          IF ( N_edge ) THEN
433           DO j=sNy+1,sNy+Oly           DO j=sNy+1,sNy+Oly
434            DO i=iMinUpd,iMaxUpd            DO i=iMinUpd,iMaxUpd
435             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
436       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
437       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
438         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
439       &       *( af(i+1,j)-af(i,j)       &       *( af(i+1,j)-af(i,j)
440       &         -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))
441       &        )       &        )
# Line 407  C         in corner region) but safer to Line 445  C         in corner region) but safer to
445    
446         ELSE         ELSE
447  C      do not only update the overlap  C      do not only update the overlap
448          jMinUpd = 1-Oly          jMinUpd = 1-Oly
449          jMaxUpd = sNy+Oly          jMaxUpd = sNy+Oly
450          IF ( interiorOnly .AND. S_edge ) jMinUpd = 1          IF ( interiorOnly .AND. S_edge ) jMinUpd = 1
451          IF ( interiorOnly .AND. N_edge ) jMaxUpd = sNy          IF ( interiorOnly .AND. N_edge ) jMaxUpd = sNy
452          DO j=jMinUpd,jMaxUpd          DO j=jMinUpd,jMaxUpd
453           DO i=1-Olx+1,sNx+Olx-1           DO i=1-Olx+1,sNx+Olx-1
454             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
455       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
456       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
457         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
458       &       *( af(i+1,j)-af(i,j)       &       *( af(i+1,j)-af(i,j)
459       &         -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))
460       &        )       &        )
# Line 435  C-     Apply open boundary conditions Line 474  C-     Apply open boundary conditions
474            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
475           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
476            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
477    #ifdef ALLOW_PTRACERS
478             ELSEIF (tracerIdentity.GE.GAD_TR1) THEN
479              CALL OBCS_APPLY_PTRACER( bi, bj, k,
480         &         tracerIdentity-GAD_TR1+1, localTij, myThid )
481    #endif /* ALLOW_PTRACERS */
482           ENDIF           ENDIF
483          ENDIF          ENDIF
484  #endif /* ALLOW_OBCS */  #endif /* ALLOW_OBCS */
485    
486  C-     end if/else update overlap-Only  C-     end if/else update overlap-Only
487         ENDIF         ENDIF
488            
489  C--   End of X direction  C--   End of X direction
490        ENDIF        ENDIF
491    
492  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
493  C--   Y direction  C--   Y direction
494    cph-test
495    C-     Advective flux in Y
496            DO j=1-Oly,sNy+Oly
497             DO i=1-Olx,sNx+Olx
498              af(i,j) = 0.
499             ENDDO
500            ENDDO
501    C
502    #ifdef ALLOW_AUTODIFF_TAMC
503    # ifndef DISABLE_MULTIDIM_ADVECTION
504    CADJ STORE localTij(:,:)  =
505    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
506    CADJ STORE af(:,:)  =
507    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
508    # endif
509    #endif /* ALLOW_AUTODIFF_TAMC */
510    C
511        IF (calc_fluxes_Y) THEN        IF (calc_fluxes_Y) THEN
512    
513  C-     Do not compute fluxes if  C-     Do not compute fluxes if
# Line 454  C       a) needed in overlap only Line 515  C       a) needed in overlap only
515  C   and b) the overlap of myTile are not cube-face edges  C   and b) the overlap of myTile are not cube-face edges
516         IF ( .NOT.overlapOnly .OR. E_edge .OR. W_edge ) THEN         IF ( .NOT.overlapOnly .OR. E_edge .OR. W_edge ) THEN
517    
518  #ifndef ALLOW_AUTODIFF_TAMC  cph-exch2#ifndef ALLOW_AUTODIFF_TAMC
519  C-     Internal exchange for calculations in Y  C-     Internal exchange for calculations in Y
520  #ifdef MULTIDIM_OLD_VERSION  #ifdef MULTIDIM_OLD_VERSION
521          IF ( useCubedSphereExchange ) THEN          IF ( useCubedSphereExchange ) THEN
# Line 462  C-     Internal exchange for calculation Line 523  C-     Internal exchange for calculation
523          IF ( useCubedSphereExchange .AND.          IF ( useCubedSphereExchange .AND.
524       &       ( overlapOnly .OR. ipass.EQ.1 ) ) THEN       &       ( overlapOnly .OR. ipass.EQ.1 ) ) THEN
525  #endif  #endif
526           CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )           CALL FILL_CS_CORNER_TR_RL(.FALSE., .FALSE.,
527         &                              localTij, bi,bj, myThid )
528          ENDIF          ENDIF
529  #endif  cph-exch2#endif
530    
531  C-     Advective flux in Y  C-     Advective flux in Y
532          DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
# Line 480  CADJ &     comlev1_bibj_k_gad_pass, key= Line 542  CADJ &     comlev1_bibj_k_gad_pass, key=
542  #endif  #endif
543  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
544    
545          IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN          IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
546            CALL GAD_FLUXLIMIT_ADV_Y( bi,bj,k, dTtracerLev(k),       &     .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
547       I                              vTrans, vVel, maskLocS, localTij,            CALL GAD_DST2U1_ADV_Y( bi,bj,k, advectionScheme, .TRUE.,
548         I                           dTtracerLev(k),vTrans,vFld,localTij,
549         O                           af, myThid )
550            ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
551              CALL GAD_FLUXLIMIT_ADV_Y( bi,bj,k, .TRUE., dTtracerLev(k),
552         I                              vTrans, vFld, maskLocS, localTij,
553       O                              af, myThid )       O                              af, myThid )
554          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
555            CALL GAD_DST3_ADV_Y(      bi,bj,k, dTtracerLev(k),            CALL GAD_DST3_ADV_Y(      bi,bj,k, .TRUE., dTtracerLev(k),
556       I                              vTrans, vVel, maskLocS, localTij,       I                              vTrans, vFld, maskLocS, localTij,
557       O                              af, myThid )       O                              af, myThid )
558          ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN          ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
559            CALL GAD_DST3FL_ADV_Y(    bi,bj,k, dTtracerLev(k),            CALL GAD_DST3FL_ADV_Y(    bi,bj,k, .TRUE., dTtracerLev(k),
560       I                              vTrans, vVel, maskLocS, localTij,       I                              vTrans, vFld, maskLocS, localTij,
561       O                              af, myThid )       O                              af, myThid )
562    #ifndef ALLOW_AUTODIFF_TAMC
563            ELSEIF (advectionScheme.EQ.ENUM_OS7MP ) THEN
564              CALL GAD_OS7MP_ADV_Y(     bi,bj,k, .TRUE., dTtracerLev(k),
565         I                              vTrans, vFld, maskLocS, localTij,
566         O                              af, myThid )
567    #endif
568          ELSE          ELSE
569           STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'           STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
570          ENDIF          ENDIF
# Line 499  CADJ &     comlev1_bibj_k_gad_pass, key= Line 572  CADJ &     comlev1_bibj_k_gad_pass, key=
572  C-     Advective flux in Y : done  C-     Advective flux in Y : done
573         ENDIF         ENDIF
574    
575  #ifndef ALLOW_AUTODIFF_TAMC  cph-exch2#ifndef ALLOW_AUTODIFF_TAMC
576  C-     Internal exchange for next calculations in X  C-     Internal exchange for next calculations in X
577         IF ( overlapOnly .AND. ipass.EQ.1 ) THEN         IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
578           CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )           CALL FILL_CS_CORNER_TR_RL( .TRUE., .FALSE.,
579         &                              localTij, bi,bj, myThid )
580         ENDIF         ENDIF
581  #endif  cph-exch2#endif
582    
583  C-     Update the local tracer field where needed:  C-     Update the local tracer field where needed:
584    
585  C      update in overlap-Only  C      update in overlap-Only
586         IF ( overlapOnly ) THEN         IF ( overlapOnly ) THEN
587          jMinUpd = 1-Oly+1          jMinUpd = 1-Oly+1
588          jMaxUpd = sNy+Oly-1          jMaxUpd = sNy+Oly-1
589  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
590  C         in corner region) but safer to keep them.  C         in corner region) but safer to keep them.
591          IF ( S_edge ) jMinUpd = 1          IF ( S_edge ) jMinUpd = 1
592          IF ( N_edge ) jMaxUpd = sNy          IF ( N_edge ) jMaxUpd = sNy
# Line 520  C         in corner region) but safer to Line 594  C         in corner region) but safer to
594          IF ( W_edge ) THEN          IF ( W_edge ) THEN
595           DO j=jMinUpd,jMaxUpd           DO j=jMinUpd,jMaxUpd
596            DO i=1-Olx,0            DO i=1-Olx,0
597             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
598       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
599       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
600         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
601       &       *( af(i,j+1)-af(i,j)       &       *( af(i,j+1)-af(i,j)
602       &         -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))
603       &        )       &        )
# Line 532  C         in corner region) but safer to Line 607  C         in corner region) but safer to
607          IF ( E_edge ) THEN          IF ( E_edge ) THEN
608           DO j=jMinUpd,jMaxUpd           DO j=jMinUpd,jMaxUpd
609            DO i=sNx+1,sNx+Olx            DO i=sNx+1,sNx+Olx
610             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
611       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
612       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
613         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
614       &       *( af(i,j+1)-af(i,j)       &       *( af(i,j+1)-af(i,j)
615       &         -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))
616       &        )       &        )
# Line 550  C      do not only update the overlap Line 626  C      do not only update the overlap
626          IF ( interiorOnly .AND. E_edge ) iMaxUpd = sNx          IF ( interiorOnly .AND. E_edge ) iMaxUpd = sNx
627          DO j=1-Oly+1,sNy+Oly-1          DO j=1-Oly+1,sNy+Oly-1
628           DO i=iMinUpd,iMaxUpd           DO i=iMinUpd,iMaxUpd
629             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
630       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
631       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
632         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
633       &       *( af(i,j+1)-af(i,j)       &       *( af(i,j+1)-af(i,j)
634       &         -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))
635       &        )       &        )
# Line 572  C-     Apply open boundary conditions Line 649  C-     Apply open boundary conditions
649            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
650           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
651            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
652    #ifdef ALLOW_PTRACERS
653             ELSEIF (tracerIdentity.GE.GAD_TR1) THEN
654              CALL OBCS_APPLY_PTRACER( bi, bj, k,
655         &         tracerIdentity-GAD_TR1+1, localTij, myThid )
656    #endif /* ALLOW_PTRACERS */
657           ENDIF           ENDIF
658          ENDIF          ENDIF
659  #endif /* ALLOW_OBCS */  #endif /* ALLOW_OBCS */
# Line 595  C-    explicit advection is done ; store Line 677  C-    explicit advection is done ; store
677          ENDDO          ENDDO
678        ELSE        ELSE
679  C-    horizontal advection done; store intermediate result in 3D array:  C-    horizontal advection done; store intermediate result in 3D array:
680         DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
681          DO i=1-Olx,sNx+Olx           DO i=1-Olx,sNx+Olx
682           localTijk(i,j,k)=localTij(i,j)            localTijk(i,j,k)=localTij(i,j)
683             ENDDO
684          ENDDO          ENDDO
        ENDDO  
685        ENDIF        ENDIF
686    
687  #ifdef ALLOW_DIAGNOSTICS  #ifdef ALLOW_DIAGNOSTICS
# Line 631  C---+----1----+----2----+----3----+----4 Line 713  C---+----1----+----2----+----3----+----4
713  C--   Start of k loop for vertical flux  C--   Start of k loop for vertical flux
714         DO k=Nr,1,-1         DO k=Nr,1,-1
715  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
716           kkey = (igadkey-1)*Nr + k           kkey = (igadkey-1)*Nr + (Nr-k+1)
717  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
718  C--   kup    Cycles through 1,2 to point to w-layer above  C--   kUp    Cycles through 1,2 to point to w-layer above
719  C--   kDown  Cycles through 2,1 to point to w-layer below  C--   kDown  Cycles through 2,1 to point to w-layer below
720          kup  = 1+MOD(k+1,2)          kUp  = 1+MOD(k+1,2)
721          kDown= 1+MOD(k,2)          kDown= 1+MOD(k,2)
722  c       kp1=min(Nr,k+1)  c       kp1=min(Nr,k+1)
723          kp1Msk=1.          kp1Msk=1.
724          if (k.EQ.Nr) kp1Msk=0.          if (k.EQ.Nr) kp1Msk=0.
725    
726    #ifdef ALLOW_AUTODIFF_TAMC
727    CADJ STORE rtrans(:,:)  =
728    CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
729    CADJ STORE wfld(:,:)  =
730    CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
731    #endif
732    
733  C-- Compute Vertical transport  C-- Compute Vertical transport
734  #ifdef ALLOW_AIM  #ifdef ALLOW_AIM
735  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 651  C- a hack to prevent Water-Vapor vert.tr Line 740  C- a hack to prevent Water-Vapor vert.tr
740          IF ( k.EQ.1 ) THEN          IF ( k.EQ.1 ) THEN
741  #endif  #endif
742    
743    #ifdef ALLOW_AUTODIFF_TAMC
744    cphmultiCADJ STORE wfld(:,:)  =
745    cphmultiCADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
746    #endif /* ALLOW_AUTODIFF_TAMC */
747    
748  C- Surface interface :  C- Surface interface :
749           DO j=1-Oly,sNy+Oly           DO j=1-Oly,sNy+Oly
750            DO i=1-Olx,sNx+Olx            DO i=1-Olx,sNx+Olx
751             rTransKp1(i,j) = kp1Msk*rTrans(i,j)             rTransKp1(i,j) = kp1Msk*rTrans(i,j)
752               wFld(i,j)   = 0.
753             rTrans(i,j) = 0.             rTrans(i,j) = 0.
754             fVerT(i,j,kUp) = 0.             fVerT(i,j,kUp) = 0.
755            ENDDO            ENDDO
756           ENDDO           ENDDO
757    
758          ELSE          ELSE
 C- Interior interface :  
759    
760    #ifdef ALLOW_AUTODIFF_TAMC
761    cphmultiCADJ STORE wfld(:,:)  =
762    cphmultiCADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
763    #endif /* ALLOW_AUTODIFF_TAMC */
764    
765    C- Interior interface :
766           DO j=1-Oly,sNy+Oly           DO j=1-Oly,sNy+Oly
767            DO i=1-Olx,sNx+Olx            DO i=1-Olx,sNx+Olx
768             rTransKp1(i,j) = kp1Msk*rTrans(i,j)             rTransKp1(i,j) = kp1Msk*rTrans(i,j)
769               wFld(i,j)   = wVel(i,j,k,bi,bj)
770             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)
771         &                 *deepFac2F(k)*rhoFacF(k)
772       &                 *maskC(i,j,k-1,bi,bj)       &                 *maskC(i,j,k-1,bi,bj)
773             fVerT(i,j,kUp) = 0.             fVerT(i,j,kUp) = 0.
774            ENDDO            ENDDO
# Line 674  C- Interior interface : Line 776  C- Interior interface :
776    
777  #ifdef ALLOW_GMREDI  #ifdef ALLOW_GMREDI
778  C--   Residual transp = Bolus transp + Eulerian transp  C--   Residual transp = Bolus transp + Eulerian transp
779           IF (useGMRedi)           IF (useGMRedi)
780       &   CALL GMREDI_CALC_WFLOW(       &     CALL GMREDI_CALC_WFLOW(
781       &                    rTrans, bi, bj, k, myThid)       U                 wFld, rTrans,
782         I                 k, bi, bj, myThid )
783  #endif /* ALLOW_GMREDI */  #endif /* ALLOW_GMREDI */
784    
785  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
786  CADJ STORE localTijk(:,:,k)    cphmultiCADJ STORE localTijk(:,:,k)  
787  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte  cphmultiCADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
788  CADJ STORE rTrans(:,:)    cphmultiCADJ STORE rTrans(:,:)  
789  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte  cphmultiCADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
790  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
791    
792  C-    Compute vertical advective flux in the interior:  C-    Compute vertical advective flux in the interior:
793           IF (vertAdvecScheme.EQ.ENUM_FLUX_LIMIT) THEN           IF ( vertAdvecScheme.EQ.ENUM_UPWIND_1RST
794  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|       &      .OR. vertAdvecScheme.EQ.ENUM_DST2 ) THEN
795               CALL GAD_DST2U1_ADV_R( bi,bj,k, advectionScheme,
796         I                            dTtracerLev(k),rTrans,wFld,localTijk,
797         O                            fVerT(1-Olx,1-Oly,kUp), myThid )
798             ELSEIF( vertAdvecScheme.EQ.ENUM_FLUX_LIMIT) THEN
799             CALL GAD_FLUXLIMIT_ADV_R( bi,bj,k, dTtracerLev(k),             CALL GAD_FLUXLIMIT_ADV_R( bi,bj,k, dTtracerLev(k),
800       I                               rTrans, wVel, localTijk,       I                               rTrans, wFld, localTijk,
801       O                               fVerT(1-Olx,1-Oly,kUp), myThid )       O                               fVerT(1-Olx,1-Oly,kUp), myThid )
802           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3 ) THEN           ELSEIF( vertAdvecScheme.EQ.ENUM_DST3 ) THEN
803             CALL GAD_DST3_ADV_R(      bi,bj,k, dTtracerLev(k),             CALL GAD_DST3_ADV_R(      bi,bj,k, dTtracerLev(k),
804       I                               rTrans, wVel, localTijk,       I                               rTrans, wFld, localTijk,
805       O                               fVerT(1-Olx,1-Oly,kUp), myThid )       O                               fVerT(1-Olx,1-Oly,kUp), myThid )
806           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN           ELSEIF( vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
807             CALL GAD_DST3FL_ADV_R(    bi,bj,k, dTtracerLev(k),             CALL GAD_DST3FL_ADV_R(    bi,bj,k, dTtracerLev(k),
808       I                               rTrans, wVel, localTijk,       I                               rTrans, wFld, localTijk,
809       O                               fVerT(1-Olx,1-Oly,kUp), myThid )       O                               fVerT(1-Olx,1-Oly,kUp), myThid )
810    #ifndef ALLOW_AUTODIFF_TAMC
811             ELSEIF (vertAdvecScheme.EQ.ENUM_OS7MP ) THEN
812               CALL GAD_OS7MP_ADV_R(     bi,bj,k, dTtracerLev(k),
813         I                               rTrans, wFld, localTijk,
814         O                               fVerT(1-Olx,1-Oly,kUp), myThid )
815    #endif
816           ELSE           ELSE
817            STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'            STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
818           ENDIF           ENDIF
# Line 708  C- end Surface/Interior if bloc Line 821  C- end Surface/Interior if bloc
821          ENDIF          ENDIF
822    
823  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
824  CADJ STORE rTrans(:,:)    cphmultiCADJ STORE rTrans(:,:)  
825  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte  cphmultiCADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
826  CADJ STORE rTranskp1(:,:)    cphmultiCADJ STORE rTranskp1(:,:)  
827  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte  cphmultiCADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
828  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
829    
830  C--   Divergence of vertical fluxes  C--   Divergence of vertical fluxes
831          DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
832           DO i=1-Olx,sNx+Olx           DO i=1-Olx,sNx+Olx
833            localTij(i,j)=localTijk(i,j,k)-dTtracerLev(k)*            localTij(i,j) = localTijk(i,j,k)
834       &     _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
835       &     *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
836       &     *( fVerT(i,j,kUp)-fVerT(i,j,kDown)       &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
837       &       -tracer(i,j,k,bi,bj)*(rTrans(i,j)-rTransKp1(i,j))       &       *( fVerT(i,j,kDown)-fVerT(i,j,kUp)
838       &      )*rkFac       &         -tracer(i,j,k,bi,bj)*(rTransKp1(i,j)-rTrans(i,j))
839         &        )*rkSign
840            gTracer(i,j,k,bi,bj)=            gTracer(i,j,k,bi,bj)=
841       &     (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)       &     (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)
842           ENDDO           ENDDO
843          ENDDO          ENDDO
844    
845  #ifdef ALLOW_DIAGNOSTICS  #ifdef ALLOW_DIAGNOSTICS
846          IF ( useDiagnostics ) THEN          IF ( useDiagnostics ) THEN
847            diagName = 'ADVr'//diagSufx            diagName = 'ADVr'//diagSufx
# Line 739  C--   Divergence of vertical fluxes Line 853  C--   Divergence of vertical fluxes
853  C--   End of K loop for vertical flux  C--   End of K loop for vertical flux
854         ENDDO         ENDDO
855  C--   end of if not.implicitAdvection block  C--   end of if not.implicitAdvection block
856        ENDIF        ENDIF
857    
858        RETURN        RETURN
859        END        END

Legend:
Removed from v.1.34  
changed lines
  Added in v.1.51

  ViewVC Help
Powered by ViewVC 1.1.22