/[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.8 by adcroft, Fri Sep 28 16:49:54 2001 UTC revision 1.22 by jmc, Fri Jun 25 18:19:20 2004 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2  C $Name$  C $Name$
3    
 CBOI  
 C !TITLE: pkg/generic\_advdiff  
 C !AUTHORS: adcroft@mit.edu  
 C !INTRODUCTION: Generic Advection Diffusion Package  
 C  
 C Package "generic\_advdiff" provides a common set of routines for calculating  
 C advective/diffusive fluxes for tracers (cell centered quantities on a C-grid).  
 C  
 C Many different advection schemes are available: the standard centered  
 C second order, centered fourth order and upwind biased third order schemes  
 C are known as linear methods and require some stable time-stepping method  
 C such as Adams-Bashforth. Alternatives such as flux-limited schemes are  
 C stable in the forward sense and are best combined with the multi-dimensional  
 C method provided in gad\_advection.  
 C  
 C There are two high-level routines:  
 C  \begin{itemize}  
 C  \item{GAD\_CALC\_RHS} calculates all fluxes at time level "n" and is used  
 C  for the standard linear schemes. This must be used in conjuction with  
 C  Adams-Bashforth time-stepping. Diffusive and parameterized fluxes are  
 C  always calculated here.  
 C  \item{GAD\_ADVECTION} calculates just the advective fluxes using the  
 C  non-linear schemes and can not be used in conjuction with Adams-Bashforth  
 C  time-stepping.  
 C  \end{itemize}  
 CEOI  
   
4  #include "GAD_OPTIONS.h"  #include "GAD_OPTIONS.h"
5    
6    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7  CBOP  CBOP
8  C !ROUTINE: GAD_ADVECTION  C !ROUTINE: GAD_ADVECTION
9    
10  C !INTERFACE: ==========================================================  C !INTERFACE: ==========================================================
11        SUBROUTINE GAD_ADVECTION(bi,bj,advectionScheme,tracerIdentity,        SUBROUTINE GAD_ADVECTION(
12       U                         Tracer,Gtracer,       I     implicitAdvection, advectionScheme, tracerIdentity,
13       I                         myTime,myIter,myThid)       I     uVel, vVel, wVel, tracer,
14         O     gTracer,
15         I     bi,bj, myTime,myIter,myThid)
16    
17  C !DESCRIPTION:  C !DESCRIPTION:
18  C Calculates the tendancy of a tracer due to advection.  C Calculates the tendancy of a tracer due to advection.
# Line 62  C !USES: =============================== Line 38  C !USES: ===============================
38  #include "SIZE.h"  #include "SIZE.h"
39  #include "EEPARAMS.h"  #include "EEPARAMS.h"
40  #include "PARAMS.h"  #include "PARAMS.h"
 #include "DYNVARS.h"  
41  #include "GRID.h"  #include "GRID.h"
42  #include "GAD.h"  #include "GAD.h"
43  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
# Line 71  C !USES: =============================== Line 46  C !USES: ===============================
46  #endif  #endif
47    
48  C !INPUT PARAMETERS: ===================================================  C !INPUT PARAMETERS: ===================================================
49  C  bi,bj                :: tile indices  C  implicitAdvection :: implicit vertical advection (later on)
50  C  advectionScheme      :: advection scheme to use  C  advectionScheme   :: advection scheme to use
51  C  tracerIdentity       :: identifier for the tracer (required only for OBCS)  C  tracerIdentity    :: tracer identifier (required only for OBCS)
52  C  Tracer               :: tracer field  C  uVel              :: velocity, zonal component
53  C  myTime               :: current time  C  vVel              :: velocity, meridional component
54  C  myIter               :: iteration number  C  wVel              :: velocity, vertical component
55  C  myThid               :: thread number  C  tracer            :: tracer field
56        INTEGER bi,bj  C  bi,bj             :: tile indices
57    C  myTime            :: current time
58    C  myIter            :: iteration number
59    C  myThid            :: thread number
60          LOGICAL implicitAdvection
61        INTEGER advectionScheme        INTEGER advectionScheme
62        INTEGER tracerIdentity        INTEGER tracerIdentity
63        _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)
64          _RL vVel  (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
65          _RL wVel  (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
66          _RL tracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
67          INTEGER bi,bj
68        _RL myTime        _RL myTime
69        INTEGER myIter        INTEGER myIter
70        INTEGER myThid        INTEGER myThid
71    
72  C !OUTPUT PARAMETERS: ==================================================  C !OUTPUT PARAMETERS: ==================================================
73  C  gTracer              :: tendancy array  C  gTracer           :: tendancy array
74        _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)
75    
76  C !LOCAL VARIABLES: ====================================================  C !LOCAL VARIABLES: ====================================================
77  C  maskUp               :: 2-D array for mask at W points  C  maskUp        :: 2-D array for mask at W points
78  C  iMin,iMax,jMin,jMax  :: loop range for called routines  C  iMin,iMax,    :: loop range for called routines
79  C  i,j,k                :: loop indices  C  jMin,jMax     :: loop range for called routines
80  C  kup                  :: index into 2 1/2D array, toggles between 1 and 2  C  i,j,k         :: loop indices
81  C  kdown                :: index into 2 1/2D array, toggles between 2 and 1  C  kup           :: index into 2 1/2D array, toggles between 1 and 2
82  C  kp1                  :: =k+1 for k<Nr, =Nr for k=Nr  C  kdown         :: index into 2 1/2D array, toggles between 2 and 1
83  C  xA,yA                :: areas of X and Y face of tracer cells  C  kp1           :: =k+1 for k<Nr, =Nr for k=Nr
84  C  uTrans,vTrans,rTrans :: 2-D arrays of volume transports at U,V and W points  C  xA,yA         :: areas of X and Y face of tracer cells
85  C  af                   :: 2-D array for horizontal advective flux  C  uTrans,vTrans :: 2-D arrays of volume transports at U,V points
86  C  fVerT                :: 2 1/2D arrays for vertical advective flux  C  rTrans        :: 2-D arrays of volume transports at W points
87  C  localTij             :: 2-D array used as temporary local copy of tracer fld  C  rTransKp1     :: vertical volume transport at interface k+1
88  C  localTijk            :: 3-D array used as temporary local copy of tracer fld  C  af            :: 2-D array for horizontal advective flux
89  C  kp1Msk               :: flag (0,1) to act as over-riding mask for W levels  C  fVerT         :: 2 1/2D arrays for vertical advective flux
90  C  calc_fluxes_X        :: logical to indicate to calculate fluxes in X dir  C  localTij      :: 2-D array, temporary local copy of tracer fld
91  C  calc_fluxes_Y        :: logical to indicate to calculate fluxes in Y dir  C  localTijk     :: 3-D array, temporary local copy of tracer fld
92  C  nipass               :: number of passes to make in multi-dimensional method  C  kp1Msk        :: flag (0,1) for over-riding mask for W levels
93  C  ipass                :: number of the current pass being made  C  calc_fluxes_X :: logical to indicate to calculate fluxes in X dir
94    C  calc_fluxes_Y :: logical to indicate to calculate fluxes in Y dir
95    C  nipass        :: number of passes in multi-dimensional method
96    C  ipass         :: number of the current pass being made
97        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
98        INTEGER iMin,iMax,jMin,jMax        INTEGER iMin,iMax,jMin,jMax
99        INTEGER i,j,k,kup,kDown,kp1        INTEGER i,j,k,kup,kDown
100        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
101        _RS yA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS yA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
102        _RL uTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
103        _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
104        _RL rTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
105          _RL rTransKp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
106        _RL af      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL af      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
107        _RL fVerT   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerT   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
108        _RL localTij(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL localTij(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 126  C  ipass                :: number of the Line 113  C  ipass                :: number of the
113  CEOP  CEOP
114    
115  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
116              act0 = tracerIdentity - 1
117              max0 = maxpass
118            act1 = bi - myBxLo(myThid)            act1 = bi - myBxLo(myThid)
119            max1 = myBxHi(myThid) - myBxLo(myThid) + 1            max1 = myBxHi(myThid) - myBxLo(myThid) + 1
120            act2 = bj - myByLo(myThid)            act2 = bj - myByLo(myThid)
# Line 133  CEOP Line 122  CEOP
122            act3 = myThid - 1            act3 = myThid - 1
123            max3 = nTx*nTy            max3 = nTx*nTy
124            act4 = ikey_dynamics - 1            act4 = ikey_dynamics - 1
125            ikey = (act1 + 1) + act2*max1            igadkey = (act0 + 1)
126       &                      + act3*max1*max2       &                      + act1*max0
127       &                      + act4*max1*max2*max3       &                      + act2*max0*max1
128         &                      + act3*max0*max1*max2
129         &                      + act4*max0*max1*max2*max3
130              if (tracerIdentity.GT.maxpass) then
131                 print *, 'ph-pass gad_advection ', maxpass, tracerIdentity
132                 STOP 'maxpass seems smaller than tracerIdentity'
133              endif
134  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
135    
136  C--   Set up work arrays with valid (i.e. not NaN) values  C--   Set up work arrays with valid (i.e. not NaN) values
# Line 152  C     uninitialised but inert locations. Line 147  C     uninitialised but inert locations.
147          rTrans(i,j)  = 0. _d 0          rTrans(i,j)  = 0. _d 0
148          fVerT(i,j,1) = 0. _d 0          fVerT(i,j,1) = 0. _d 0
149          fVerT(i,j,2) = 0. _d 0          fVerT(i,j,2) = 0. _d 0
150            rTransKp1(i,j)= 0. _d 0
151         ENDDO         ENDDO
152        ENDDO        ENDDO
153    
# Line 163  C     uninitialised but inert locations. Line 159  C     uninitialised but inert locations.
159  C--   Start of k loop for horizontal fluxes  C--   Start of k loop for horizontal fluxes
160        DO k=1,Nr        DO k=1,Nr
161  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
162           kkey = (ikey-1)*Nr + k           kkey = (igadkey-1)*Nr + k
163  CADJ STORE tracer(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte  CADJ STORE tracer(:,:,k,bi,bj) =
164    CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
165  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
166    
167  C--   Get temporary terms used by tendency routines  C--   Get temporary terms used by tendency routines
# Line 173  C--   Get temporary terms used by tenden Line 170  C--   Get temporary terms used by tenden
170       O         xA,yA,uTrans,vTrans,rTrans,maskUp,       O         xA,yA,uTrans,vTrans,rTrans,maskUp,
171       I         myThid)       I         myThid)
172    
173    #ifdef ALLOW_GMREDI
174    C--   Residual transp = Bolus transp + Eulerian transp
175           IF (useGMRedi)
176         &   CALL GMREDI_CALC_UVFLOW(
177         &            uTrans, vTrans, bi, bj, k, myThid)
178    #endif /* ALLOW_GMREDI */
179    
180  C--   Make local copy of tracer array  C--   Make local copy of tracer array
181        DO j=1-OLy,sNy+OLy        DO j=1-OLy,sNy+OLy
182         DO i=1-OLx,sNx+OLx         DO i=1-OLx,sNx+OLx
# Line 182  C--   Make local copy of tracer array Line 186  C--   Make local copy of tracer array
186    
187        IF (useCubedSphereExchange) THEN        IF (useCubedSphereExchange) THEN
188         nipass=3         nipass=3
189    #ifdef ALLOW_AUTODIFF_TAMC
190           if ( nipass.GT.maxcube )
191         &      STOP 'maxcube needs to be = 3'
192    #endif
193        ELSE        ELSE
194         nipass=1         nipass=1
195        ENDIF        ENDIF
# Line 190  cph       nipass=1 Line 198  cph       nipass=1
198  C--   Multiple passes for different directions on different tiles  C--   Multiple passes for different directions on different tiles
199        DO ipass=1,nipass        DO ipass=1,nipass
200  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
201           passkey = ipass + (k-1)   *maxpass           passkey = ipass + (k-1)      *maxcube
202       &                   + (ikey-1)*maxpass*Nr       &                   + (igadkey-1)*maxcube*Nr
203           IF (nipass .GT. maxpass) THEN           IF (nipass .GT. maxpass) THEN
204            STOP 'GAD_ADVECTION: nipass > maxpass. check tamc.h'            STOP 'GAD_ADVECTION: nipass > maxcube. check tamc.h'
205           ENDIF           ENDIF
206  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
207    
# Line 242  C-    Advective flux in X Line 250  C-    Advective flux in X
250    
251  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
252  #ifndef DISABLE_MULTIDIM_ADVECTION  #ifndef DISABLE_MULTIDIM_ADVECTION
253  CADJ STORE localTij(:,:)  = comlev1_bibj_pass, key=passkey, byte=isbyte  CADJ STORE localTij(:,:)  =
254    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
255  #endif  #endif
256  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
257    
# Line 256  CADJ STORE localTij(:,:)  = comlev1_bibj Line 265  CADJ STORE localTij(:,:)  = comlev1_bibj
265         CALL GAD_DST3FL_ADV_X(         CALL GAD_DST3FL_ADV_X(
266       &       bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)       &       bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
267        ELSE        ELSE
268         STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'         STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'
269        ENDIF        ENDIF
270    
271        DO j=1-Oly,sNy+Oly        DO j=1-Oly,sNy+Oly
# Line 308  C-    Advective flux in Y Line 317  C-    Advective flux in Y
317    
318  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
319  #ifndef DISABLE_MULTIDIM_ADVECTION  #ifndef DISABLE_MULTIDIM_ADVECTION
320  CADJ STORE localTij(:,:)  = comlev1_bibj_pass, key=passkey, byte=isbyte  CADJ STORE localTij(:,:)  =
321    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
322  #endif  #endif
323  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
324    
# Line 350  C--   Apply open boundary conditions Line 360  C--   Apply open boundary conditions
360  C--   End of Y direction  C--   End of Y direction
361        ENDIF        ENDIF
362    
       DO j=1-Oly,sNy+Oly  
        DO i=1-Olx,sNx+Olx  
         localTijk(i,j,k)=localTij(i,j)  
        ENDDO  
       ENDDO  
   
363  C--   End of ipass loop  C--   End of ipass loop
364        ENDDO        ENDDO
365    
366          IF ( implicitAdvection ) THEN
367    C-    explicit advection is done ; store tendency in gTracer:
368            DO j=1-Oly,sNy+Oly
369             DO i=1-Olx,sNx+Olx
370              gTracer(i,j,k,bi,bj)=
371         &     (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer
372             ENDDO
373            ENDDO
374          ELSE
375    C-    horizontal advection done; store intermediate result in 3D array:
376           DO j=1-Oly,sNy+Oly
377            DO i=1-Olx,sNx+Olx
378             localTijk(i,j,k)=localTij(i,j)
379            ENDDO
380           ENDDO
381          ENDIF
382    
383  C--   End of K loop for horizontal fluxes  C--   End of K loop for horizontal fluxes
384        ENDDO        ENDDO
385    
386          IF ( .NOT.implicitAdvection ) THEN
387  C--   Start of k loop for vertical flux  C--   Start of k loop for vertical flux
388        DO k=Nr,1,-1         DO k=Nr,1,-1
389  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
390           kkey = (ikey-1)*Nr + k           kkey = (igadkey-1)*Nr + k
391  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
   
392  C--   kup    Cycles through 1,2 to point to w-layer above  C--   kup    Cycles through 1,2 to point to w-layer above
393  C--   kDown  Cycles through 2,1 to point to w-layer below  C--   kDown  Cycles through 2,1 to point to w-layer below
394        kup  = 1+MOD(k+1,2)          kup  = 1+MOD(k+1,2)
395        kDown= 1+MOD(k,2)          kDown= 1+MOD(k,2)
396    c       kp1=min(Nr,k+1)
397            kp1Msk=1.
398            if (k.EQ.Nr) kp1Msk=0.
399    
400    C-- Compute Vertical transport
401    #ifdef ALLOW_AIM
402    C- a hack to prevent Water-Vapor vert.transport into the stratospheric level Nr
403            IF ( k.EQ.1 .OR.
404         &     (useAIM .AND. tracerIdentity.EQ.GAD_SALINITY .AND. k.EQ.Nr)
405         &              ) THEN
406    #else
407            IF ( k.EQ.1 ) THEN
408    #endif
409    
410  C--   Get temporary terms used by tendency routines  C- Surface interface :
411        CALL CALC_COMMON_FACTORS (           DO j=1-Oly,sNy+Oly
412       I         bi,bj,iMin,iMax,jMin,jMax,k,            DO i=1-Olx,sNx+Olx
413       O         xA,yA,uTrans,vTrans,rTrans,maskUp,             rTransKp1(i,j) = kp1Msk*rTrans(i,j)
414       I         myThid)             rTrans(i,j) = 0.
415               fVerT(i,j,kUp) = 0.
416  C-    Advective flux in R             af(i,j) = 0.
417        DO j=1-Oly,sNy+Oly            ENDDO
418         DO i=1-Olx,sNx+Olx           ENDDO
419          af(i,j) = 0.  
420         ENDDO          ELSE
421        ENDDO  C- Interior interface :
422    
423             DO j=1-Oly,sNy+Oly
424              DO i=1-Olx,sNx+Olx
425               rTransKp1(i,j) = kp1Msk*rTrans(i,j)
426               rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)
427         &                 *maskC(i,j,k-1,bi,bj)
428               af(i,j) = 0.
429              ENDDO
430             ENDDO
431    
432    #ifdef ALLOW_GMREDI
433    C--   Residual transp = Bolus transp + Eulerian transp
434             IF (useGMRedi)
435         &   CALL GMREDI_CALC_WFLOW(
436         &                    rTrans, bi, bj, k, myThid)
437    #endif /* ALLOW_GMREDI */
438    
439  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
440  CADJ STORE localTijk(:,:,k)    CADJ STORE localTijk(:,:,k)  
441  CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
442    CADJ STORE rTrans(:,:)  
443    CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
444  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
445    
 C     Note: wVel needs to be masked  
       IF (K.GE.2) THEN  
446  C-    Compute vertical advective flux in the interior:  C-    Compute vertical advective flux in the interior:
447         IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN           IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
448          CALL GAD_FLUXLIMIT_ADV_R(            CALL GAD_FLUXLIMIT_ADV_R(
449       &       bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
450         ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN           ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
451          CALL GAD_DST3_ADV_R(            CALL GAD_DST3_ADV_R(
452       &       bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
453         ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN           ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
454          CALL GAD_DST3FL_ADV_R(            CALL GAD_DST3FL_ADV_R(
455       &       bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
456         ELSE           ELSE
457          STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'            STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
458         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  
459  C-    add the advective flux to fVerT  C-    add the advective flux to fVerT
460        DO j=1-Oly,sNy+Oly           DO j=1-Oly,sNy+Oly
461         DO i=1-Olx,sNx+Olx            DO i=1-Olx,sNx+Olx
462          fVerT(i,j,kUp) = af(i,j)             fVerT(i,j,kUp) = af(i,j)
463         ENDDO            ENDDO
464        ENDDO           ENDDO
465    
466  C--   Divergence of fluxes  C- end Surface/Interior if bloc
467        kp1=min(Nr,k+1)          ENDIF
468        kp1Msk=1.  
469        if (k.EQ.Nr) kp1Msk=0.  #ifdef ALLOW_AUTODIFF_TAMC
470        DO j=1-Oly,sNy+Oly  CADJ STORE rTrans(:,:)  
471         DO i=1-Olx,sNx+Olx  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
472          localTij(i,j)=localTijk(i,j,k)-deltaTtracer*  CADJ STORE rTranskp1(:,:)  
473       &    _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
474       &    *recip_rA(i,j,bi,bj)  #endif /* ALLOW_AUTODIFF_TAMC */
475       &    *( fVerT(i,j,kUp)-fVerT(i,j,kDown)  
476       &      -tracer(i,j,k,bi,bj)*rA(i,j,bi,bj)*  C--   Divergence of vertical fluxes
477       &        (wVel(i,j,k,bi,bj)-kp1Msk*wVel(i,j,kp1,bi,bj))          DO j=1-Oly,sNy+Oly
478       &     )*rkFac           DO i=1-Olx,sNx+Olx
479          gTracer(i,j,k,bi,bj)=            localTij(i,j)=localTijk(i,j,k)-deltaTtracer*
480       &   (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer       &     _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
481         ENDDO       &     *recip_rA(i,j,bi,bj)
482        ENDDO       &     *( fVerT(i,j,kUp)-fVerT(i,j,kDown)
483         &       -tracer(i,j,k,bi,bj)*(rTrans(i,j)-rTransKp1(i,j))
484         &      )*rkFac
485              gTracer(i,j,k,bi,bj)=
486         &     (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer
487             ENDDO
488            ENDDO
489    
490  C--   End of K loop for vertical flux  C--   End of K loop for vertical flux
491        ENDDO         ENDDO
492    C--   end of if not.implicitAdvection block
493          ENDIF
494    
495        RETURN        RETURN
496        END        END

Legend:
Removed from v.1.8  
changed lines
  Added in v.1.22

  ViewVC Help
Powered by ViewVC 1.1.22