/[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.4 by adcroft, Wed Sep 19 20:45:09 2001 UTC revision 1.18 by jmc, Wed Jan 7 21:35:00 2004 UTC
# Line 4  C $Name$ Line 4  C $Name$
4  CBOI  CBOI
5  C !TITLE: pkg/generic\_advdiff  C !TITLE: pkg/generic\_advdiff
6  C !AUTHORS: adcroft@mit.edu  C !AUTHORS: adcroft@mit.edu
7  C !INTRODUCTION:  C !INTRODUCTION: Generic Advection Diffusion Package
 C \section{Generica Advection Diffusion Package}  
8  C  C
9  C Package "generic\_advdiff" provides a common set of routines for calculating  C Package "generic\_advdiff" provides a common set of routines for calculating
10  C advective/diffusive fluxes for tracers (cell centered quantities on a C-grid).  C advective/diffusive fluxes for tracers (cell centered quantities on a C-grid).
# Line 35  CBOP Line 34  CBOP
34  C !ROUTINE: GAD_ADVECTION  C !ROUTINE: GAD_ADVECTION
35    
36  C !INTERFACE: ==========================================================  C !INTERFACE: ==========================================================
37        SUBROUTINE GAD_ADVECTION(bi,bj,advectionScheme,tracerIdentity,        SUBROUTINE GAD_ADVECTION(
38       U                         Tracer,Gtracer,       I           implicitAdvection, advectionScheme, tracerIdentity,
39       I                         myTime,myIter,myThid)       I           uVel, vVel, wVel, tracer,
40         O           gTracer,
41         I           bi,bj, myTime,myIter,myThid)
42    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
43    
44  C !DESCRIPTION:  C !DESCRIPTION:
45  C Calculates the tendancy of a tracer due to advection.  C Calculates the tendancy of a tracer due to advection.
# Line 48  C Line 50  C
50  C The algorithm is as follows:  C The algorithm is as follows:
51  C \begin{itemize}  C \begin{itemize}
52  C \item{$\theta^{(n+1/3)} = \theta^{(n)}  C \item{$\theta^{(n+1/3)} = \theta^{(n)}
53  C      - \Delta t \partial_x (u\theta) + \theta \partial_x u$}  C      - \Delta t \partial_x (u\theta^{(n)}) + \theta^{(n)} \partial_x u$}
54  C \item{$\theta^{(n+2/3)} = \theta^{(n+1/3)}  C \item{$\theta^{(n+2/3)} = \theta^{(n+1/3)}
55  C      - \Delta t \partial_y (v\theta) + \theta \partial_y v$}  C      - \Delta t \partial_y (v\theta^{(n+1/3)}) + \theta^{(n)} \partial_y v$}
56  C \item{$\theta^{(n+3/3)} = \theta^{(n+2/3)}  C \item{$\theta^{(n+3/3)} = \theta^{(n+2/3)}
57  C      - \Delta t \partial_r (w\theta) + \theta \partial_r w$}  C      - \Delta t \partial_r (w\theta^{(n+2/3)}) + \theta^{(n)} \partial_r w$}
58  C \item{$G_\theta = ( \theta^{(n+3/3)} - \theta^{(n)} )/\Delta t$}  C \item{$G_\theta = ( \theta^{(n+3/3)} - \theta^{(n)} )/\Delta t$}
59  C \end{itemize}  C \end{itemize}
60  C  C
# Line 63  C !USES: =============================== Line 65  C !USES: ===============================
65  #include "SIZE.h"  #include "SIZE.h"
66  #include "EEPARAMS.h"  #include "EEPARAMS.h"
67  #include "PARAMS.h"  #include "PARAMS.h"
 #include "DYNVARS.h"  
68  #include "GRID.h"  #include "GRID.h"
69  #include "GAD.h"  #include "GAD.h"
70    #ifdef ALLOW_AUTODIFF_TAMC
71    # include "tamc.h"
72    # include "tamc_keys.h"
73    #endif
74    
75  C !INPUT PARAMETERS: ===================================================  C !INPUT PARAMETERS: ===================================================
76  C  bi,bj                :: tile indices  C  implicitAdvection    :: vertical advection treated implicitly (later on)
77  C  advectionScheme      :: advection scheme to use  C  advectionScheme      :: advection scheme to use
78  C  tracerIdentity       :: identifier for the tracer (required only for OBCS)  C  tracerIdentity       :: identifier for the tracer (required only for OBCS)
79  C  Tracer               :: tracer field  C  uVel                 :: velocity, zonal component
80    C  vVel                 :: velocity, meridional component
81    C  wVel                 :: velocity, vertical component
82    C  tracer               :: tracer field
83    C  bi,bj                :: tile indices
84  C  myTime               :: current time  C  myTime               :: current time
85  C  myIter               :: iteration number  C  myIter               :: iteration number
86  C  myThid               :: thread number  C  myThid               :: thread number
87        INTEGER bi,bj        LOGICAL implicitAdvection
88        INTEGER advectionScheme        INTEGER advectionScheme
89        INTEGER tracerIdentity        INTEGER tracerIdentity
90        _RL Gtracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)        _RL uVel  (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
91          _RL vVel  (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
92          _RL wVel  (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
93          _RL tracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
94          INTEGER bi,bj
95        _RL myTime        _RL myTime
96        INTEGER myIter        INTEGER myIter
97        INTEGER myThid        INTEGER myThid
98    
99  C !OUTPUT PARAMETERS: ==================================================  C !OUTPUT PARAMETERS: ==================================================
100  C  gTracer              :: tendancy array  C  gTracer              :: tendancy array
101        _RL Tracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)        _RL gTracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
102    
103  C !LOCAL VARIABLES: ====================================================  C !LOCAL VARIABLES: ====================================================
104  C  maskUp               :: 2-D array for mask at W points  C  maskUp               :: 2-D array for mask at W points
# Line 96  C  kdown                :: index into 2 Line 109  C  kdown                :: index into 2
109  C  kp1                  :: =k+1 for k<Nr, =Nr for k=Nr  C  kp1                  :: =k+1 for k<Nr, =Nr for k=Nr
110  C  xA,yA                :: areas of X and Y face of tracer cells  C  xA,yA                :: areas of X and Y face of tracer cells
111  C  uTrans,vTrans,rTrans :: 2-D arrays of volume transports at U,V and W points  C  uTrans,vTrans,rTrans :: 2-D arrays of volume transports at U,V and W points
112    C  rTransKp1            :: vertical volume transport at interface k+1
113  C  af                   :: 2-D array for horizontal advective flux  C  af                   :: 2-D array for horizontal advective flux
114  C  fVerT                :: 2 1/2D arrays for vertical advective flux  C  fVerT                :: 2 1/2D arrays for vertical advective flux
115  C  localTij             :: 2-D array used as temporary local copy of tracer fld  C  localTij             :: 2-D array used as temporary local copy of tracer fld
# Line 107  C  nipass               :: number of pas Line 121  C  nipass               :: number of pas
121  C  ipass                :: number of the current pass being made  C  ipass                :: number of the current pass being made
122        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
123        INTEGER iMin,iMax,jMin,jMax        INTEGER iMin,iMax,jMin,jMax
124        INTEGER i,j,k,kup,kDown,kp1        INTEGER i,j,k,kup,kDown
125        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
126        _RS yA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS yA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
127        _RL uTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
128        _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
129        _RL rTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
130          _RL rTransKp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
131        _RL af      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL af      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
132        _RL fVerT   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerT   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
133        _RL localTij(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL localTij(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 122  C  ipass                :: number of the Line 137  C  ipass                :: number of the
137        INTEGER nipass,ipass        INTEGER nipass,ipass
138  CEOP  CEOP
139    
140    #ifdef ALLOW_AUTODIFF_TAMC
141              act0 = tracerIdentity - 1
142              max0 = maxpass
143              act1 = bi - myBxLo(myThid)
144              max1 = myBxHi(myThid) - myBxLo(myThid) + 1
145              act2 = bj - myByLo(myThid)
146              max2 = myByHi(myThid) - myByLo(myThid) + 1
147              act3 = myThid - 1
148              max3 = nTx*nTy
149              act4 = ikey_dynamics - 1
150              igadkey = (act0 + 1)
151         &                      + act1*max0
152         &                      + act2*max0*max1
153         &                      + act3*max0*max1*max2
154         &                      + act4*max0*max1*max2*max3
155              if (tracerIdentity.GT.maxpass) then
156                 print *, 'ph-pass gad_advection ', maxpass, tracerIdentity
157                 STOP 'maxpass seems smaller than tracerIdentity'
158              endif
159    #endif /* ALLOW_AUTODIFF_TAMC */
160    
161  C--   Set up work arrays with valid (i.e. not NaN) values  C--   Set up work arrays with valid (i.e. not NaN) values
162  C     These inital values do not alter the numerical results. They  C     These inital values do not alter the numerical results. They
163  C     just ensure that all memory references are to valid floating  C     just ensure that all memory references are to valid floating
# Line 136  C     uninitialised but inert locations. Line 172  C     uninitialised but inert locations.
172          rTrans(i,j)  = 0. _d 0          rTrans(i,j)  = 0. _d 0
173          fVerT(i,j,1) = 0. _d 0          fVerT(i,j,1) = 0. _d 0
174          fVerT(i,j,2) = 0. _d 0          fVerT(i,j,2) = 0. _d 0
175            rTransKp1(i,j)= 0. _d 0
176         ENDDO         ENDDO
177        ENDDO        ENDDO
178    
# Line 146  C     uninitialised but inert locations. Line 183  C     uninitialised but inert locations.
183    
184  C--   Start of k loop for horizontal fluxes  C--   Start of k loop for horizontal fluxes
185        DO k=1,Nr        DO k=1,Nr
186    #ifdef ALLOW_AUTODIFF_TAMC
187             kkey = (igadkey-1)*Nr + k
188    CADJ STORE tracer(:,:,k,bi,bj) =
189    CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
190    #endif /* ALLOW_AUTODIFF_TAMC */
191    
192  C--   Get temporary terms used by tendency routines  C--   Get temporary terms used by tendency routines
193        CALL CALC_COMMON_FACTORS (        CALL CALC_COMMON_FACTORS (
# Line 153  C--   Get temporary terms used by tenden Line 195  C--   Get temporary terms used by tenden
195       O         xA,yA,uTrans,vTrans,rTrans,maskUp,       O         xA,yA,uTrans,vTrans,rTrans,maskUp,
196       I         myThid)       I         myThid)
197    
198    #ifdef ALLOW_GMREDI
199    C--   Residual transp = Bolus transp + Eulerian transp
200           IF (useGMRedi)
201         &   CALL GMREDI_CALC_UVFLOW(
202         &            uTrans, vTrans, bi, bj, k, myThid)
203    #endif /* ALLOW_GMREDI */
204    
205  C--   Make local copy of tracer array  C--   Make local copy of tracer array
206        DO j=1-OLy,sNy+OLy        DO j=1-OLy,sNy+OLy
207         DO i=1-OLx,sNx+OLx         DO i=1-OLx,sNx+OLx
# Line 162  C--   Make local copy of tracer array Line 211  C--   Make local copy of tracer array
211    
212        IF (useCubedSphereExchange) THEN        IF (useCubedSphereExchange) THEN
213         nipass=3         nipass=3
214    #ifdef ALLOW_AUTODIFF_TAMC
215           if ( nipass.GT.maxcube )
216         &      STOP 'maxcube needs to be = 3'
217    #endif
218        ELSE        ELSE
219         nipass=1         nipass=1
220        ENDIF        ENDIF
221         nipass=1  cph       nipass=1
222    
223  C--   Multiple passes for different directions on different tiles  C--   Multiple passes for different directions on different tiles
224        DO ipass=1,nipass        DO ipass=1,nipass
225    #ifdef ALLOW_AUTODIFF_TAMC
226             passkey = ipass + (k-1)      *maxcube
227         &                   + (igadkey-1)*maxcube*Nr
228             IF (nipass .GT. maxpass) THEN
229              STOP 'GAD_ADVECTION: nipass > maxcube. check tamc.h'
230             ENDIF
231    #endif /* ALLOW_AUTODIFF_TAMC */
232    
233        IF (nipass.EQ.3) THEN        IF (nipass.EQ.3) THEN
234         calc_fluxes_X=.FALSE.         calc_fluxes_X=.FALSE.
# Line 212  C-    Advective flux in X Line 272  C-    Advective flux in X
272          af(i,j) = 0.          af(i,j) = 0.
273         ENDDO         ENDDO
274        ENDDO        ENDDO
275    
276    #ifdef ALLOW_AUTODIFF_TAMC
277    #ifndef DISABLE_MULTIDIM_ADVECTION
278    CADJ STORE localTij(:,:)  =
279    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
280    #endif
281    #endif /* ALLOW_AUTODIFF_TAMC */
282    
283        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
284         CALL GAD_FLUXLIMIT_ADV_X(         CALL GAD_FLUXLIMIT_ADV_X(
285       &      bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)       &      bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
# Line 222  C-    Advective flux in X Line 290  C-    Advective flux in X
290         CALL GAD_DST3FL_ADV_X(         CALL GAD_DST3FL_ADV_X(
291       &       bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)       &       bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
292        ELSE        ELSE
293         STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'         STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'
294        ENDIF        ENDIF
295    
296        DO j=1-Oly,sNy+Oly        DO j=1-Oly,sNy+Oly
297         DO i=1-Olx,sNx+Olx-1         DO i=1-Olx,sNx+Olx-1
298          localTij(i,j)=localTij(i,j)-deltaTtracer*          localTij(i,j)=localTij(i,j)-deltaTtracer*
# Line 270  C-    Advective flux in Y Line 339  C-    Advective flux in Y
339          af(i,j) = 0.          af(i,j) = 0.
340         ENDDO         ENDDO
341        ENDDO        ENDDO
342    
343    #ifdef ALLOW_AUTODIFF_TAMC
344    #ifndef DISABLE_MULTIDIM_ADVECTION
345    CADJ STORE localTij(:,:)  =
346    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
347    #endif
348    #endif /* ALLOW_AUTODIFF_TAMC */
349    
350        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
351         CALL GAD_FLUXLIMIT_ADV_Y(         CALL GAD_FLUXLIMIT_ADV_Y(
352       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)
# Line 282  C-    Advective flux in Y Line 359  C-    Advective flux in Y
359        ELSE        ELSE
360         STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'         STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
361        ENDIF        ENDIF
362    
363        DO j=1-Oly,sNy+Oly-1        DO j=1-Oly,sNy+Oly-1
364         DO i=1-Olx,sNx+Olx         DO i=1-Olx,sNx+Olx
365          localTij(i,j)=localTij(i,j)-deltaTtracer*          localTij(i,j)=localTij(i,j)-deltaTtracer*
# Line 307  C--   Apply open boundary conditions Line 385  C--   Apply open boundary conditions
385  C--   End of Y direction  C--   End of Y direction
386        ENDIF        ENDIF
387    
       DO j=1-Oly,sNy+Oly  
        DO i=1-Olx,sNx+Olx  
         localTijk(i,j,k)=localTij(i,j)  
        ENDDO  
       ENDDO  
   
388  C--   End of ipass loop  C--   End of ipass loop
389        ENDDO        ENDDO
390    
391          IF ( implicitAdvection ) THEN
392    C-    explicit advection is done ; store tendency in gTracer:
393            DO j=1-Oly,sNy+Oly
394             DO i=1-Olx,sNx+Olx
395              gTracer(i,j,k,bi,bj)=
396         &     (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer
397             ENDDO
398            ENDDO
399          ELSE
400    C-    horizontal advection done; store intermediate result in 3D array:
401           DO j=1-Oly,sNy+Oly
402            DO i=1-Olx,sNx+Olx
403             localTijk(i,j,k)=localTij(i,j)
404            ENDDO
405           ENDDO
406          ENDIF
407    
408  C--   End of K loop for horizontal fluxes  C--   End of K loop for horizontal fluxes
409        ENDDO        ENDDO
410    
411          IF ( .NOT.implicitAdvection ) THEN
412  C--   Start of k loop for vertical flux  C--   Start of k loop for vertical flux
413        DO k=Nr,1,-1         DO k=Nr,1,-1
414    #ifdef ALLOW_AUTODIFF_TAMC
415             kkey = (igadkey-1)*Nr + k
416    #endif /* ALLOW_AUTODIFF_TAMC */
417  C--   kup    Cycles through 1,2 to point to w-layer above  C--   kup    Cycles through 1,2 to point to w-layer above
418  C--   kDown  Cycles through 2,1 to point to w-layer below  C--   kDown  Cycles through 2,1 to point to w-layer below
419        kup  = 1+MOD(k+1,2)          kup  = 1+MOD(k+1,2)
420        kDown= 1+MOD(k,2)          kDown= 1+MOD(k,2)
421    c       kp1=min(Nr,k+1)
422            kp1Msk=1.
423            if (k.EQ.Nr) kp1Msk=0.
424    
425    C-- Compute Vertical transport
426            IF (k.EQ.1) THEN
427    
428    C- Surface interface :
429             DO j=1-Oly,sNy+Oly
430              DO i=1-Olx,sNx+Olx
431               rTransKp1(i,j) = rTrans(i,j)
432               rTrans(i,j) = 0.
433               fVerT(i,j,kUp) = 0.
434               af(i,j) = 0.
435              ENDDO
436             ENDDO
437    
438            ELSE
439    C- Interior interface :
440    
441             DO j=1-Oly,sNy+Oly
442              DO i=1-Olx,sNx+Olx
443               rTransKp1(i,j) = kp1Msk*rTrans(i,j)
444               rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)
445         &                 *maskC(i,j,k-1,bi,bj)
446               af(i,j) = 0.
447              ENDDO
448             ENDDO
449    
450    #ifdef ALLOW_GMREDI
451    C--   Residual transp = Bolus transp + Eulerian transp
452             IF (useGMRedi)
453         &   CALL GMREDI_CALC_WFLOW(
454         &                    rTrans, bi, bj, k, myThid)
455    #endif /* ALLOW_GMREDI */
456    
457    #ifdef ALLOW_AUTODIFF_TAMC
458    CADJ STORE localTijk(:,:,k)  
459    CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
460    CADJ STORE rTrans(:,:)  
461    CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
462    #endif /* ALLOW_AUTODIFF_TAMC */
463    
 C--   Get temporary terms used by tendency routines  
       CALL CALC_COMMON_FACTORS (  
      I         bi,bj,iMin,iMax,jMin,jMax,k,  
      O         xA,yA,uTrans,vTrans,rTrans,maskUp,  
      I         myThid)  
   
 C-    Advective flux in R  
       DO j=1-Oly,sNy+Oly  
        DO i=1-Olx,sNx+Olx  
         af(i,j) = 0.  
        ENDDO  
       ENDDO  
   
 C     Note: wVel needs to be masked  
       IF (K.GE.2) THEN  
464  C-    Compute vertical advective flux in the interior:  C-    Compute vertical advective flux in the interior:
465         IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN           IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
466          CALL GAD_FLUXLIMIT_ADV_R(            CALL GAD_FLUXLIMIT_ADV_R(
467       &       bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
468         ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN           ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
469          CALL GAD_DST3_ADV_R(            CALL GAD_DST3_ADV_R(
470       &       bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
471         ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN           ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
472          CALL GAD_DST3FL_ADV_R(            CALL GAD_DST3FL_ADV_R(
473       &       bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
474         ELSE           ELSE
475          STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'            STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
476         ENDIF           ENDIF
 C-    Surface "correction" term at k>1 :  
        DO j=1-Oly,sNy+Oly  
         DO i=1-Olx,sNx+Olx  
          af(i,j) = af(i,j)  
      &           + (maskC(i,j,k,bi,bj)-maskC(i,j,k-1,bi,bj))*  
      &             rTrans(i,j)*localTijk(i,j,k)  
         ENDDO  
        ENDDO  
       ELSE  
 C-    Surface "correction" term at k=1 :  
        DO j=1-Oly,sNy+Oly  
         DO i=1-Olx,sNx+Olx  
          af(i,j) = rTrans(i,j)*localTijk(i,j,k)  
         ENDDO  
        ENDDO  
       ENDIF  
477  C-    add the advective flux to fVerT  C-    add the advective flux to fVerT
478        DO j=1-Oly,sNy+Oly           DO j=1-Oly,sNy+Oly
479         DO i=1-Olx,sNx+Olx            DO i=1-Olx,sNx+Olx
480          fVerT(i,j,kUp) = af(i,j)             fVerT(i,j,kUp) = af(i,j)
481         ENDDO            ENDDO
482        ENDDO           ENDDO
483    
484  C--   Divergence of fluxes  C- end Surface/Interior if bloc
485        kp1=min(Nr,k+1)          ENDIF
486        kp1Msk=1.  
487        if (k.EQ.Nr) kp1Msk=0.  #ifdef ALLOW_AUTODIFF_TAMC
488        DO j=1-Oly,sNy+Oly  CADJ STORE rTrans(:,:)  
489         DO i=1-Olx,sNx+Olx  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
490          localTij(i,j)=localTijk(i,j,k)-deltaTtracer*  CADJ STORE rTranskp1(:,:)  
491       &    _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
492       &    *recip_rA(i,j,bi,bj)  #endif /* ALLOW_AUTODIFF_TAMC */
493       &    *( fVerT(i,j,kUp)-fVerT(i,j,kDown)  
494       &      -tracer(i,j,k,bi,bj)*rA(i,j,bi,bj)*  C--   Divergence of vertical fluxes
495       &        (wVel(i,j,k,bi,bj)-kp1Msk*wVel(i,j,kp1,bi,bj))          DO j=1-Oly,sNy+Oly
496       &     )*rkFac           DO i=1-Olx,sNx+Olx
497          gTracer(i,j,k,bi,bj)=            localTij(i,j)=localTijk(i,j,k)-deltaTtracer*
498       &   (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer       &     _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
499         ENDDO       &     *recip_rA(i,j,bi,bj)
500        ENDDO       &     *( fVerT(i,j,kUp)-fVerT(i,j,kDown)
501         &       -tracer(i,j,k,bi,bj)*(rTrans(i,j)-rTransKp1(i,j))
502         &      )*rkFac
503              gTracer(i,j,k,bi,bj)=
504         &     (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer
505             ENDDO
506            ENDDO
507    
508  C--   End of K loop for vertical flux  C--   End of K loop for vertical flux
509        ENDDO         ENDDO
510    C--   end of if not.implicitAdvection block
511          ENDIF
512    
513        RETURN        RETURN
514        END        END

Legend:
Removed from v.1.4  
changed lines
  Added in v.1.18

  ViewVC Help
Powered by ViewVC 1.1.22