/[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.3 by adcroft, Mon Sep 17 19:48:04 2001 UTC revision 1.24 by dimitri, Mon Jun 28 21:10:55 2004 UTC
# Line 3  C $Name$ Line 3  C $Name$
3    
4  #include "GAD_OPTIONS.h"  #include "GAD_OPTIONS.h"
5    
6        SUBROUTINE GAD_ADVECTION(bi,bj,advectionScheme,tracerIdentity,  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7       U                         Tracer,Gtracer,  CBOP
8       I                         myTime,myIter,myThid)  C !ROUTINE: GAD_ADVECTION
9  C     /==========================================================\  
10  C     | SUBROUTINE GAD_ADVECTION                                 |  C !INTERFACE: ==========================================================
11  C     | o Solves the pure advection tracer equation.             |        SUBROUTINE GAD_ADVECTION(
12  C     |==========================================================|       I     implicitAdvection, advectionScheme, vertAdvecScheme,
13  C     \==========================================================/       I     tracerIdentity,
14        IMPLICIT NONE       I     uVel, vVel, wVel, tracer,
15         O     gTracer,
16         I     bi,bj, myTime,myIter,myThid)
17    
18    C !DESCRIPTION:
19    C Calculates the tendancy of a tracer due to advection.
20    C It uses the multi-dimensional method given in \ref{sect:multiDimAdvection}
21    C and can only be used for the non-linear advection schemes such as the
22    C direct-space-time method and flux-limiters.
23    C
24    C The algorithm is as follows:
25    C \begin{itemize}
26    C \item{$\theta^{(n+1/3)} = \theta^{(n)}
27    C      - \Delta t \partial_x (u\theta^{(n)}) + \theta^{(n)} \partial_x u$}
28    C \item{$\theta^{(n+2/3)} = \theta^{(n+1/3)}
29    C      - \Delta t \partial_y (v\theta^{(n+1/3)}) + \theta^{(n)} \partial_y v$}
30    C \item{$\theta^{(n+3/3)} = \theta^{(n+2/3)}
31    C      - \Delta t \partial_r (w\theta^{(n+2/3)}) + \theta^{(n)} \partial_r w$}
32    C \item{$G_\theta = ( \theta^{(n+3/3)} - \theta^{(n)} )/\Delta t$}
33    C \end{itemize}
34    C
35    C The tendancy (output) is over-written by this routine.
36    
37  C     == Global variables ===  C !USES: ===============================================================
38          IMPLICIT NONE
39  #include "SIZE.h"  #include "SIZE.h"
40  #include "EEPARAMS.h"  #include "EEPARAMS.h"
41  #include "PARAMS.h"  #include "PARAMS.h"
 #include "DYNVARS.h"  
42  #include "GRID.h"  #include "GRID.h"
43  #include "GAD.h"  #include "GAD.h"
44    #ifdef ALLOW_AUTODIFF_TAMC
45  C     == Routine arguments ==  # include "tamc.h"
46        INTEGER bi,bj  # include "tamc_keys.h"
47        INTEGER advectionScheme  #endif
48    #ifdef ALLOW_EXCH2
49    #include "W2_EXCH2_TOPOLOGY.h"
50    #include "W2_EXCH2_PARAMS.h"
51    #endif /* ALLOW_EXCH2 */
52    
53    C !INPUT PARAMETERS: ===================================================
54    C  implicitAdvection :: implicit vertical advection (later on)
55    C  advectionScheme   :: advection scheme to use (Horizontal plane)
56    C  vertAdvecScheme   :: advection scheme to use (vertical direction)
57    C  tracerIdentity    :: tracer identifier (required only for OBCS)
58    C  uVel              :: velocity, zonal component
59    C  vVel              :: velocity, meridional component
60    C  wVel              :: velocity, vertical component
61    C  tracer            :: tracer field
62    C  bi,bj             :: tile indices
63    C  myTime            :: current time
64    C  myIter            :: iteration number
65    C  myThid            :: thread number
66          LOGICAL implicitAdvection
67          INTEGER advectionScheme, vertAdvecScheme
68        INTEGER tracerIdentity        INTEGER tracerIdentity
69        _RL Tracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)        _RL uVel  (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
70        _RL Gtracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)        _RL vVel  (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
71          _RL wVel  (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
72          _RL tracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
73          INTEGER bi,bj
74        _RL myTime        _RL myTime
75        INTEGER myIter        INTEGER myIter
76        INTEGER myThid        INTEGER myThid
77    
78  C     == Local variables  C !OUTPUT PARAMETERS: ==================================================
79    C  gTracer           :: tendancy array
80          _RL gTracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
81    
82    C !LOCAL VARIABLES: ====================================================
83    C  maskUp        :: 2-D array for mask at W points
84    C  iMin,iMax,    :: loop range for called routines
85    C  jMin,jMax     :: loop range for called routines
86    C  i,j,k         :: loop indices
87    C  kup           :: index into 2 1/2D array, toggles between 1 and 2
88    C  kdown         :: index into 2 1/2D array, toggles between 2 and 1
89    C  kp1           :: =k+1 for k<Nr, =Nr for k=Nr
90    C  xA,yA         :: areas of X and Y face of tracer cells
91    C  uTrans,vTrans :: 2-D arrays of volume transports at U,V points
92    C  rTrans        :: 2-D arrays of volume transports at W points
93    C  rTransKp1     :: vertical volume transport at interface k+1
94    C  af            :: 2-D array for horizontal advective flux
95    C  fVerT         :: 2 1/2D arrays for vertical advective flux
96    C  localTij      :: 2-D array, temporary local copy of tracer fld
97    C  localTijk     :: 3-D array, temporary local copy of tracer fld
98    C  kp1Msk        :: flag (0,1) for over-riding mask for W levels
99    C  calc_fluxes_X :: logical to indicate to calculate fluxes in X dir
100    C  calc_fluxes_Y :: logical to indicate to calculate fluxes in Y dir
101    C  nipass        :: number of passes in multi-dimensional method
102    C  ipass         :: number of the current pass being made
103    C  myTile        :: variables used to determine which cube face
104    C  nCFace        :: owns a tile for cube grid runs using
105    C                :: multi-dim advection.
106        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
107        INTEGER iMin,iMax,jMin,jMax        INTEGER iMin,iMax,jMin,jMax
108        INTEGER i,j,k,kup,kDown,kp1        INTEGER i,j,k,kup,kDown
109        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
110        _RS yA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS yA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
111        _RL uTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
112        _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
113        _RL rTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
114          _RL rTransKp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
115        _RL af      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL af      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
116        _RL fVerT   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerT   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
117        _RL localTij(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL localTij(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 47  C     == Local variables Line 119  C     == Local variables
119        _RL kp1Msk        _RL kp1Msk
120        LOGICAL calc_fluxes_X,calc_fluxes_Y        LOGICAL calc_fluxes_X,calc_fluxes_Y
121        INTEGER nipass,ipass        INTEGER nipass,ipass
122          INTEGER myTile, nCFace
123          LOGICAL southWestCorner
124          LOGICAL southEastCorner
125          LOGICAL northWestCorner
126          LOGICAL northEastCorner
127    CEOP
128    
129    #ifdef ALLOW_AUTODIFF_TAMC
130              act0 = tracerIdentity - 1
131              max0 = maxpass
132              act1 = bi - myBxLo(myThid)
133              max1 = myBxHi(myThid) - myBxLo(myThid) + 1
134              act2 = bj - myByLo(myThid)
135              max2 = myByHi(myThid) - myByLo(myThid) + 1
136              act3 = myThid - 1
137              max3 = nTx*nTy
138              act4 = ikey_dynamics - 1
139              igadkey = (act0 + 1)
140         &                      + act1*max0
141         &                      + act2*max0*max1
142         &                      + act3*max0*max1*max2
143         &                      + act4*max0*max1*max2*max3
144              if (tracerIdentity.GT.maxpass) then
145                 print *, 'ph-pass gad_advection ', maxpass, tracerIdentity
146                 STOP 'maxpass seems smaller than tracerIdentity'
147              endif
148    #endif /* ALLOW_AUTODIFF_TAMC */
149    
150  C--   Set up work arrays with valid (i.e. not NaN) values  C--   Set up work arrays with valid (i.e. not NaN) values
151  C     These inital values do not alter the numerical results. They  C     These inital values do not alter the numerical results. They
# Line 62  C     uninitialised but inert locations. Line 161  C     uninitialised but inert locations.
161          rTrans(i,j)  = 0. _d 0          rTrans(i,j)  = 0. _d 0
162          fVerT(i,j,1) = 0. _d 0          fVerT(i,j,1) = 0. _d 0
163          fVerT(i,j,2) = 0. _d 0          fVerT(i,j,2) = 0. _d 0
164            rTransKp1(i,j)= 0. _d 0
165         ENDDO         ENDDO
166        ENDDO        ENDDO
167    
# Line 72  C     uninitialised but inert locations. Line 172  C     uninitialised but inert locations.
172    
173  C--   Start of k loop for horizontal fluxes  C--   Start of k loop for horizontal fluxes
174        DO k=1,Nr        DO k=1,Nr
175    #ifdef ALLOW_AUTODIFF_TAMC
176             kkey = (igadkey-1)*Nr + k
177    CADJ STORE tracer(:,:,k,bi,bj) =
178    CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
179    #endif /* ALLOW_AUTODIFF_TAMC */
180    
181  C--   Get temporary terms used by tendency routines  C--   Get temporary terms used by tendency routines
182        CALL CALC_COMMON_FACTORS (        CALL CALC_COMMON_FACTORS (
# Line 79  C--   Get temporary terms used by tenden Line 184  C--   Get temporary terms used by tenden
184       O         xA,yA,uTrans,vTrans,rTrans,maskUp,       O         xA,yA,uTrans,vTrans,rTrans,maskUp,
185       I         myThid)       I         myThid)
186    
187    #ifdef ALLOW_GMREDI
188    C--   Residual transp = Bolus transp + Eulerian transp
189           IF (useGMRedi)
190         &   CALL GMREDI_CALC_UVFLOW(
191         &            uTrans, vTrans, bi, bj, k, myThid)
192    #endif /* ALLOW_GMREDI */
193    
194  C--   Make local copy of tracer array  C--   Make local copy of tracer array
195        DO j=1-OLy,sNy+OLy        DO j=1-OLy,sNy+OLy
196         DO i=1-OLx,sNx+OLx         DO i=1-OLx,sNx+OLx
# Line 87  C--   Make local copy of tracer array Line 199  C--   Make local copy of tracer array
199        ENDDO        ENDDO
200    
201        IF (useCubedSphereExchange) THEN        IF (useCubedSphereExchange) THEN
202           southWestCorner = .TRUE.
203           southEastCorner = .TRUE.
204           northWestCorner = .TRUE.
205           northEastCorner = .TRUE.
206    #ifdef ALLOW_EXCH2
207           myTile = W2_myTileList(bi)
208           nCFace = exch2_myFace(myTile)
209           southWestCorner = exch2_isWedge(myTile).EQ.1
210         &             .AND. exch2_isSedge(myTile).EQ.1
211           southEastCorner = exch2_isEedge(myTile).EQ.1
212         &             .AND. exch2_isSedge(myTile).EQ.1
213           northEastCorner = exch2_isEedge(myTile).EQ.1
214         &             .AND. exch2_isNedge(myTile).EQ.1
215           northWestCorner = exch2_isWedge(myTile).EQ.1
216         &             .AND. exch2_isNedge(myTile).EQ.1
217    #else
218           nCFace = bi
219    #endif
220    
221         nipass=3         nipass=3
222    #ifdef ALLOW_AUTODIFF_TAMC
223           if ( nipass.GT.maxcube )
224         &      STOP 'maxcube needs to be = 3'
225    #endif
226        ELSE        ELSE
227         nipass=1         nipass=1
228        ENDIF        ENDIF
229         nipass=1  cph       nipass=1
230    
231  C--   Multiple passes for different directions on different tiles  C--   Multiple passes for different directions on different tiles
232    C--   For cube need one pass for each of red, green and blue axes.
233        DO ipass=1,nipass        DO ipass=1,nipass
234    #ifdef ALLOW_AUTODIFF_TAMC
235             passkey = ipass + (k-1)      *maxcube
236         &                   + (igadkey-1)*maxcube*Nr
237             IF (nipass .GT. maxpass) THEN
238              STOP 'GAD_ADVECTION: nipass > maxcube. check tamc.h'
239             ENDIF
240    #endif /* ALLOW_AUTODIFF_TAMC */
241    
242        IF (nipass.EQ.3) THEN        IF (nipass.EQ.3) THEN
243         calc_fluxes_X=.FALSE.         calc_fluxes_X=.FALSE.
244         calc_fluxes_Y=.FALSE.         calc_fluxes_Y=.FALSE.
245         IF (ipass.EQ.1 .AND. (bi.EQ.1 .OR. bi.EQ.2) ) THEN         IF (ipass.EQ.1 .AND. (nCFace.EQ.1 .OR. nCFace.EQ.2) ) THEN
246          calc_fluxes_X=.TRUE.          calc_fluxes_X=.TRUE.
247         ELSEIF (ipass.EQ.1 .AND. (bi.EQ.4 .OR. bi.EQ.5) ) THEN         ELSEIF (ipass.EQ.1 .AND. (nCFace.EQ.4 .OR. nCFace.EQ.5) ) THEN
248          calc_fluxes_Y=.TRUE.          calc_fluxes_Y=.TRUE.
249         ELSEIF (ipass.EQ.2 .AND. (bi.EQ.1 .OR. bi.EQ.6) ) THEN         ELSEIF (ipass.EQ.2 .AND. (nCFace.EQ.1 .OR. nCFace.EQ.6) ) THEN
250          calc_fluxes_Y=.TRUE.          calc_fluxes_Y=.TRUE.
251         ELSEIF (ipass.EQ.2 .AND. (bi.EQ.3 .OR. bi.EQ.4) ) THEN         ELSEIF (ipass.EQ.2 .AND. (nCFace.EQ.3 .OR. nCFace.EQ.4) ) THEN
252          calc_fluxes_X=.TRUE.          calc_fluxes_X=.TRUE.
253         ELSEIF (ipass.EQ.3 .AND. (bi.EQ.2 .OR. bi.EQ.3) ) THEN         ELSEIF (ipass.EQ.3 .AND. (nCFace.EQ.2 .OR. nCFace.EQ.3) ) THEN
254          calc_fluxes_Y=.TRUE.          calc_fluxes_Y=.TRUE.
255         ELSEIF (ipass.EQ.3 .AND. (bi.EQ.5 .OR. bi.EQ.6) ) THEN         ELSEIF (ipass.EQ.3 .AND. (nCFace.EQ.5 .OR. nCFace.EQ.6) ) THEN
256          calc_fluxes_X=.TRUE.          calc_fluxes_X=.TRUE.
257         ENDIF         ENDIF
258        ELSE        ELSE
# Line 122  C--   X direction Line 265  C--   X direction
265    
266  C--   Internal exchange for calculations in X  C--   Internal exchange for calculations in X
267        IF (useCubedSphereExchange) THEN        IF (useCubedSphereExchange) THEN
268         DO j=1,Oly  C--    For cube face corners we need to duplicate the
269          DO i=1,Olx  C--    i-1 and i+1 values into the null space as follows:
270           localTij( 1-i , 1-j )=localTij( 1-j ,    i    )  C
271           localTij( 1-i ,sNy+j)=localTij( 1-j , sNy+1-i )  C
272           localTij(sNx+i, 1-j )=localTij(sNx+j,    i    )  C      o NW corner: copy T(    0,sNy  ) into T(    0,sNy+1) e.g.
273           localTij(sNx+i,sNy+j)=localTij(sNx+j, sNy+1-i )  C                      |
274          ENDDO  C         x T(0,sNy+1) |
275         ENDDO  C        /\            |
276    C      --||------------|-----------
277    C        ||            |
278    C         x T(0,sNy)   |   x T(1,sNy)
279    C                      |
280    C
281    C      o SW corner: copy T(0,1) into T(0,0) e.g.
282    C                      |
283    C         x T(0,1)     |  x T(1,1)
284    C        ||            |
285    C      --||------------|-----------
286    C        \/            |
287    C         x T(0,0)     |
288    C                      |
289    C
290    C      o NE corner: copy T(sNx+1,sNy  ) into T(sNx+1,sNy+1) e.g.
291    C                      |
292    C                      |   x T(sNx+1,sNy+1)
293    C                      |  /\
294    C      ----------------|--||-------
295    C                      |  ||
296    C         x T(sNx,sNy) |   x T(sNx+1,sNy  )
297    C                      |
298    C      o SE corner: copy T(sNx+1,1    ) into T(sNx+1,0    ) e.g.
299    C                      |
300    C         x T(sNx,1)   |   x T(sNx+1,    1)
301    C                      |  ||
302    C      ----------------|--||-------
303    C                      |  \/
304    C                      |   x T(sNx+1,    0)
305           IF ( southWestCorner ) THEN
306            localTij(0    ,0    )= localTij(0    ,1  )
307           ENDIF
308           IF ( southEastCorner ) THEN
309            localTij(sNx+1,0    )= localTij(sNx+1,1  )
310           ENDIF
311           IF ( northWestCorner ) THEN
312            localTij(0    ,sNy+1)= localTij(0    ,sNy)
313           ENDIF
314           IF ( northEastCorner ) THEN
315            localTij(sNx+1,sNy+1)= localTij(sNx+1,sNy)
316           ENDIF
317        ENDIF        ENDIF
318    
319  C-    Advective flux in X  C-    Advective flux in X
# Line 138  C-    Advective flux in X Line 322  C-    Advective flux in X
322          af(i,j) = 0.          af(i,j) = 0.
323         ENDDO         ENDDO
324        ENDDO        ENDDO
325    
326    #ifdef ALLOW_AUTODIFF_TAMC
327    #ifndef DISABLE_MULTIDIM_ADVECTION
328    CADJ STORE localTij(:,:)  =
329    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
330    #endif
331    #endif /* ALLOW_AUTODIFF_TAMC */
332    
333        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
334         CALL GAD_FLUXLIMIT_ADV_X(         CALL GAD_FLUXLIMIT_ADV_X(
335       &      bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)       &      bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
# Line 148  C-    Advective flux in X Line 340  C-    Advective flux in X
340         CALL GAD_DST3FL_ADV_X(         CALL GAD_DST3FL_ADV_X(
341       &       bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)       &       bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
342        ELSE        ELSE
343         STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'         STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'
344        ENDIF        ENDIF
345    
346        DO j=1-Oly,sNy+Oly        DO j=1-Oly,sNy+Oly
347         DO i=1-Olx,sNx+Olx-1         DO i=1-Olx,sNx+Olx-1
348          localTij(i,j)=localTij(i,j)-deltaTtracer*          localTij(i,j)=localTij(i,j)-deltaTtracer*
# Line 178  C--   End of X direction Line 371  C--   End of X direction
371  C--   Y direction  C--   Y direction
372        IF (calc_fluxes_Y) THEN        IF (calc_fluxes_Y) THEN
373    
 C--   Internal exchange for calculations in Y  
374        IF (useCubedSphereExchange) THEN        IF (useCubedSphereExchange) THEN
375         DO j=1,Oly  C--   Internal exchange for calculations in Y
376          DO i=1,Olx  C--    For cube face corners we need to duplicate the
377           localTij( 1-i , 1-j )=localTij(   j   , 1-i )  C--    j-1 and j+1 values into the null space as follows:
378           localTij( 1-i ,sNy+j)=localTij(   j   ,sNy+i)  C
379           localTij(sNx+i, 1-j )=localTij(sNx+1-j, 1-i )  C      o SW corner: copy T(0,1) into T(0,0) e.g.
380           localTij(sNx+i,sNy+j)=localTij(sNx+1-j,sNy+i)  C                      |
381          ENDDO  C                      |  x T(1,1)
382         ENDDO  C                      |
383    C      ----------------|-----------
384    C                      |
385    C         x T(0,0)<====== x T(1,0)
386    C                      |
387    C
388    C      o NW corner: copy T(    0,sNy  ) into T(    0,sNy+1) e.g.
389    C                      |
390    C         x T(0,sNy+1)<=== x T(1,sNy+1)
391    C                      |
392    C      ----------------|-----------
393    C                      |
394    C                      |   x T(1,sNy)
395    C                      |
396    C
397    C      o NE corner: copy T(sNx+1,sNy  ) into T(sNx+1,sNy+1) e.g.
398    C                      |
399    C      x T(sNx,sNy+1)=====>x T(sNx+1,sNy+1)
400    C                      |    
401    C      ----------------|-----------
402    C                      |    
403    C      x T(sNx,sNy)    |                      
404    C                      |
405    C      o SE corner: copy T(sNx+1,1    ) into T(sNx+1,0    ) e.g.
406    C                      |
407    C         x T(sNx,1)   |                    
408    C                      |    
409    C      ----------------|-----------
410    C                      |    
411    C         x T(sNx,0) =====>x T(sNx+1,    0)
412           IF ( southWestCorner ) THEN
413             localTij(    0,0    ) = localTij(  1,0    )
414           ENDIF
415           IF ( southEastCorner ) THEN
416             localTij(sNx+1,0    ) = localTij(sNx,0    )
417           ENDIF
418           IF ( northWestCorner ) THEN
419             localTij(0    ,sNy+1) = localTij(  1,sNy+1)
420           ENDIF
421           IF ( northEastCorner ) THEN
422             localTij(sNx+1,sNy+1) = localTij(sNx,sNy+1)
423           ENDIF
424        ENDIF        ENDIF
425    
426  C-    Advective flux in Y  C-    Advective flux in Y
# Line 196  C-    Advective flux in Y Line 429  C-    Advective flux in Y
429          af(i,j) = 0.          af(i,j) = 0.
430         ENDDO         ENDDO
431        ENDDO        ENDDO
432    
433    #ifdef ALLOW_AUTODIFF_TAMC
434    #ifndef DISABLE_MULTIDIM_ADVECTION
435    CADJ STORE localTij(:,:)  =
436    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
437    #endif
438    #endif /* ALLOW_AUTODIFF_TAMC */
439    
440        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
441         CALL GAD_FLUXLIMIT_ADV_Y(         CALL GAD_FLUXLIMIT_ADV_Y(
442       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)
# Line 208  C-    Advective flux in Y Line 449  C-    Advective flux in Y
449        ELSE        ELSE
450         STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'         STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
451        ENDIF        ENDIF
452    
453        DO j=1-Oly,sNy+Oly-1        DO j=1-Oly,sNy+Oly-1
454         DO i=1-Olx,sNx+Olx         DO i=1-Olx,sNx+Olx
455          localTij(i,j)=localTij(i,j)-deltaTtracer*          localTij(i,j)=localTij(i,j)-deltaTtracer*
# Line 233  C--   Apply open boundary conditions Line 475  C--   Apply open boundary conditions
475  C--   End of Y direction  C--   End of Y direction
476        ENDIF        ENDIF
477    
       DO j=1-Oly,sNy+Oly  
        DO i=1-Olx,sNx+Olx  
         localTijk(i,j,k)=localTij(i,j)  
        ENDDO  
       ENDDO  
   
478  C--   End of ipass loop  C--   End of ipass loop
479        ENDDO        ENDDO
480    
481          IF ( implicitAdvection ) THEN
482    C-    explicit advection is done ; store tendency in gTracer:
483            DO j=1-Oly,sNy+Oly
484             DO i=1-Olx,sNx+Olx
485              gTracer(i,j,k,bi,bj)=
486         &     (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer
487             ENDDO
488            ENDDO
489          ELSE
490    C-    horizontal advection done; store intermediate result in 3D array:
491           DO j=1-Oly,sNy+Oly
492            DO i=1-Olx,sNx+Olx
493             localTijk(i,j,k)=localTij(i,j)
494            ENDDO
495           ENDDO
496          ENDIF
497    
498  C--   End of K loop for horizontal fluxes  C--   End of K loop for horizontal fluxes
499        ENDDO        ENDDO
500    
501          IF ( .NOT.implicitAdvection ) THEN
502  C--   Start of k loop for vertical flux  C--   Start of k loop for vertical flux
503        DO k=Nr,1,-1         DO k=Nr,1,-1
504    #ifdef ALLOW_AUTODIFF_TAMC
505             kkey = (igadkey-1)*Nr + k
506    #endif /* ALLOW_AUTODIFF_TAMC */
507  C--   kup    Cycles through 1,2 to point to w-layer above  C--   kup    Cycles through 1,2 to point to w-layer above
508  C--   kDown  Cycles through 2,1 to point to w-layer below  C--   kDown  Cycles through 2,1 to point to w-layer below
509        kup  = 1+MOD(k+1,2)          kup  = 1+MOD(k+1,2)
510        kDown= 1+MOD(k,2)          kDown= 1+MOD(k,2)
511    c       kp1=min(Nr,k+1)
512  C--   Get temporary terms used by tendency routines          kp1Msk=1.
513        CALL CALC_COMMON_FACTORS (          if (k.EQ.Nr) kp1Msk=0.
514       I         bi,bj,iMin,iMax,jMin,jMax,k,  
515       O         xA,yA,uTrans,vTrans,rTrans,maskUp,  C-- Compute Vertical transport
516       I         myThid)  #ifdef ALLOW_AIM
517    C- a hack to prevent Water-Vapor vert.transport into the stratospheric level Nr
518            IF ( k.EQ.1 .OR.
519         &     (useAIM .AND. tracerIdentity.EQ.GAD_SALINITY .AND. k.EQ.Nr)
520         &              ) THEN
521    #else
522            IF ( k.EQ.1 ) THEN
523    #endif
524    
525    C- Surface interface :
526             DO j=1-Oly,sNy+Oly
527              DO i=1-Olx,sNx+Olx
528               rTransKp1(i,j) = kp1Msk*rTrans(i,j)
529               rTrans(i,j) = 0.
530               fVerT(i,j,kUp) = 0.
531               af(i,j) = 0.
532              ENDDO
533             ENDDO
534    
535            ELSE
536    C- Interior interface :
537    
538             DO j=1-Oly,sNy+Oly
539              DO i=1-Olx,sNx+Olx
540               rTransKp1(i,j) = kp1Msk*rTrans(i,j)
541               rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)
542         &                 *maskC(i,j,k-1,bi,bj)
543               af(i,j) = 0.
544              ENDDO
545             ENDDO
546    
547    #ifdef ALLOW_GMREDI
548    C--   Residual transp = Bolus transp + Eulerian transp
549             IF (useGMRedi)
550         &   CALL GMREDI_CALC_WFLOW(
551         &                    rTrans, bi, bj, k, myThid)
552    #endif /* ALLOW_GMREDI */
553    
554    #ifdef ALLOW_AUTODIFF_TAMC
555    CADJ STORE localTijk(:,:,k)  
556    CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
557    CADJ STORE rTrans(:,:)  
558    CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
559    #endif /* ALLOW_AUTODIFF_TAMC */
560    
 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  
561  C-    Compute vertical advective flux in the interior:  C-    Compute vertical advective flux in the interior:
562         IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN           IF (vertAdvecScheme.EQ.ENUM_FLUX_LIMIT) THEN
563          CALL GAD_FLUXLIMIT_ADV_R(            CALL GAD_FLUXLIMIT_ADV_R(
564       &       bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
565         ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3 ) THEN
566          CALL GAD_DST3_ADV_R(            CALL GAD_DST3_ADV_R(
567       &       bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
568         ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
569          CALL GAD_DST3FL_ADV_R(            CALL GAD_DST3FL_ADV_R(
570       &       bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
571         ELSE           ELSE
572          STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'            STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
573         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  
574  C-    add the advective flux to fVerT  C-    add the advective flux to fVerT
575        DO j=1-Oly,sNy+Oly           DO j=1-Oly,sNy+Oly
576         DO i=1-Olx,sNx+Olx            DO i=1-Olx,sNx+Olx
577          fVerT(i,j,kUp) = af(i,j)             fVerT(i,j,kUp) = af(i,j)
578         ENDDO            ENDDO
579        ENDDO           ENDDO
580    
581  C--   Divergence of fluxes  C- end Surface/Interior if bloc
582        kp1=min(Nr,k+1)          ENDIF
583        kp1Msk=1.  
584        if (k.EQ.Nr) kp1Msk=0.  #ifdef ALLOW_AUTODIFF_TAMC
585        DO j=1-Oly,sNy+Oly  CADJ STORE rTrans(:,:)  
586         DO i=1-Olx,sNx+Olx  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
587          localTij(i,j)=localTijk(i,j,k)-deltaTtracer*  CADJ STORE rTranskp1(:,:)  
588       &    _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
589       &    *recip_rA(i,j,bi,bj)  #endif /* ALLOW_AUTODIFF_TAMC */
590       &    *( fVerT(i,j,kUp)-fVerT(i,j,kDown)  
591       &      -tracer(i,j,k,bi,bj)*rA(i,j,bi,bj)*  C--   Divergence of vertical fluxes
592       &        (wVel(i,j,k,bi,bj)-kp1Msk*wVel(i,j,kp1,bi,bj))          DO j=1-Oly,sNy+Oly
593       &     )*rkFac           DO i=1-Olx,sNx+Olx
594          gTracer(i,j,k,bi,bj)=            localTij(i,j)=localTijk(i,j,k)-deltaTtracer*
595       &   (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer       &     _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
596         ENDDO       &     *recip_rA(i,j,bi,bj)
597        ENDDO       &     *( fVerT(i,j,kUp)-fVerT(i,j,kDown)
598         &       -tracer(i,j,k,bi,bj)*(rTrans(i,j)-rTransKp1(i,j))
599         &      )*rkFac
600              gTracer(i,j,k,bi,bj)=
601         &     (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer
602             ENDDO
603            ENDDO
604    
605  C--   End of K loop for vertical flux  C--   End of K loop for vertical flux
606        ENDDO         ENDDO
607    C--   end of if not.implicitAdvection block
608          ENDIF
609    
610        RETURN        RETURN
611        END        END

Legend:
Removed from v.1.3  
changed lines
  Added in v.1.24

  ViewVC Help
Powered by ViewVC 1.1.22