/[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.1 by adcroft, Mon Sep 10 01:22:48 2001 UTC revision 1.10 by jmc, Tue Mar 5 15:17:45 2002 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2  C $Name$  C $Name$
3    
4    CBOI
5    C !TITLE: pkg/generic\_advdiff
6    C !AUTHORS: adcroft@mit.edu
7    C !INTRODUCTION: Generic Advection Diffusion Package
8    C
9    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).
11    C
12    C Many different advection schemes are available: the standard centered
13    C second order, centered fourth order and upwind biased third order schemes
14    C are known as linear methods and require some stable time-stepping method
15    C such as Adams-Bashforth. Alternatives such as flux-limited schemes are
16    C stable in the forward sense and are best combined with the multi-dimensional
17    C method provided in gad\_advection.
18    C
19    C There are two high-level routines:
20    C  \begin{itemize}
21    C  \item{GAD\_CALC\_RHS} calculates all fluxes at time level "n" and is used
22    C  for the standard linear schemes. This must be used in conjuction with
23    C  Adams-Bashforth time-stepping. Diffusive and parameterized fluxes are
24    C  always calculated here.
25    C  \item{GAD\_ADVECTION} calculates just the advective fluxes using the
26    C  non-linear schemes and can not be used in conjuction with Adams-Bashforth
27    C  time-stepping.
28    C  \end{itemize}
29    CEOI
30    
31  #include "GAD_OPTIONS.h"  #include "GAD_OPTIONS.h"
32    
33    CBOP
34    C !ROUTINE: GAD_ADVECTION
35    
36    C !INTERFACE: ==========================================================
37        SUBROUTINE GAD_ADVECTION(bi,bj,advectionScheme,tracerIdentity,        SUBROUTINE GAD_ADVECTION(bi,bj,advectionScheme,tracerIdentity,
38       U                         Tracer,Gtracer,       U                         Tracer,Gtracer,
39       I                         myTime,myIter,myThid)       I                         myTime,myIter,myThid)
 C     /==========================================================\  
 C     | SUBROUTINE GAD_ADVECTION                                 |  
 C     | o Solves the pure advection tracer equation.             |  
 C     |==========================================================|  
 C     \==========================================================/  
       IMPLICIT NONE  
40    
41  C     == Global variables ===  C !DESCRIPTION:
42    C Calculates the tendancy of a tracer due to advection.
43    C It uses the multi-dimensional method given in \ref{sect:multiDimAdvection}
44    C and can only be used for the non-linear advection schemes such as the
45    C direct-space-time method and flux-limiters.
46    C
47    C The algorithm is as follows:
48    C \begin{itemize}
49    C \item{$\theta^{(n+1/3)} = \theta^{(n)}
50    C      - \Delta t \partial_x (u\theta^{(n)}) + \theta^{(n)} \partial_x u$}
51    C \item{$\theta^{(n+2/3)} = \theta^{(n+1/3)}
52    C      - \Delta t \partial_y (v\theta^{(n+1/3)}) + \theta^{(n)} \partial_y v$}
53    C \item{$\theta^{(n+3/3)} = \theta^{(n+2/3)}
54    C      - \Delta t \partial_r (w\theta^{(n+2/3)}) + \theta^{(n)} \partial_r w$}
55    C \item{$G_\theta = ( \theta^{(n+3/3)} - \theta^{(n)} )/\Delta t$}
56    C \end{itemize}
57    C
58    C The tendancy (output) is over-written by this routine.
59    
60    C !USES: ===============================================================
61          IMPLICIT NONE
62  #include "SIZE.h"  #include "SIZE.h"
63  #include "EEPARAMS.h"  #include "EEPARAMS.h"
64  #include "PARAMS.h"  #include "PARAMS.h"
65  #include "DYNVARS.h"  #include "DYNVARS.h"
66  #include "GRID.h"  #include "GRID.h"
67  #include "GAD.h"  #include "GAD.h"
68    #ifdef ALLOW_AUTODIFF_TAMC
69  C     == Routine arguments ==  # include "tamc.h"
70    # include "tamc_keys.h"
71    #endif
72    
73    C !INPUT PARAMETERS: ===================================================
74    C  bi,bj                :: tile indices
75    C  advectionScheme      :: advection scheme to use
76    C  tracerIdentity       :: identifier for the tracer (required only for OBCS)
77    C  Tracer               :: tracer field
78    C  myTime               :: current time
79    C  myIter               :: iteration number
80    C  myThid               :: thread number
81        INTEGER bi,bj        INTEGER bi,bj
82        INTEGER advectionScheme        INTEGER advectionScheme
83        INTEGER tracerIdentity        INTEGER tracerIdentity
84        _RL Tracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)        _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)  
85        _RL myTime        _RL myTime
86        INTEGER myIter        INTEGER myIter
87        INTEGER myThid        INTEGER myThid
88    
89  C     == Local variables  C !OUTPUT PARAMETERS: ==================================================
90    C  gTracer              :: tendancy array
91          _RL gTracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
92    
93    C !LOCAL VARIABLES: ====================================================
94    C  maskUp               :: 2-D array for mask at W points
95    C  iMin,iMax,jMin,jMax  :: loop range for called routines
96    C  i,j,k                :: loop indices
97    C  kup                  :: index into 2 1/2D array, toggles between 1 and 2
98    C  kdown                :: index into 2 1/2D array, toggles between 2 and 1
99    C  kp1                  :: =k+1 for k<Nr, =Nr for k=Nr
100    C  xA,yA                :: areas of X and Y face of tracer cells
101    C  uTrans,vTrans,rTrans :: 2-D arrays of volume transports at U,V and W points
102    C  af                   :: 2-D array for horizontal advective flux
103    C  fVerT                :: 2 1/2D arrays for vertical advective flux
104    C  localTij             :: 2-D array used as temporary local copy of tracer fld
105    C  localTijk            :: 3-D array used as temporary local copy of tracer fld
106    C  kp1Msk               :: flag (0,1) to act as over-riding mask for W levels
107    C  calc_fluxes_X        :: logical to indicate to calculate fluxes in X dir
108    C  calc_fluxes_Y        :: logical to indicate to calculate fluxes in Y dir
109    C  nipass               :: number of passes to make in multi-dimensional method
110    C  ipass                :: number of the current pass being made
111        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
112        INTEGER iMin,iMax,jMin,jMax        INTEGER iMin,iMax,jMin,jMax
113        INTEGER i,j,k,kup,kDown,kp1        INTEGER i,j,k,kup,kDown,kp1
# Line 45  C     == Local variables Line 121  C     == Local variables
121        _RL localTij(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL localTij(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
122        _RL localTijk(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL localTijk(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
123        _RL kp1Msk        _RL kp1Msk
124          LOGICAL calc_fluxes_X,calc_fluxes_Y
125          INTEGER nipass,ipass
126    CEOP
127    
128    #ifdef ALLOW_AUTODIFF_TAMC
129              act1 = bi - myBxLo(myThid)
130              max1 = myBxHi(myThid) - myBxLo(myThid) + 1
131              act2 = bj - myByLo(myThid)
132              max2 = myByHi(myThid) - myByLo(myThid) + 1
133              act3 = myThid - 1
134              max3 = nTx*nTy
135              act4 = ikey_dynamics - 1
136              ikey = (act1 + 1) + act2*max1
137         &                      + act3*max1*max2
138         &                      + act4*max1*max2*max3
139    #endif /* ALLOW_AUTODIFF_TAMC */
140    
141  C--   Set up work arrays with valid (i.e. not NaN) values  C--   Set up work arrays with valid (i.e. not NaN) values
142  C     These inital values do not alter the numerical results. They  C     These inital values do not alter the numerical results. They
# Line 70  C     uninitialised but inert locations. Line 162  C     uninitialised but inert locations.
162    
163  C--   Start of k loop for horizontal fluxes  C--   Start of k loop for horizontal fluxes
164        DO k=1,Nr        DO k=1,Nr
165    #ifdef ALLOW_AUTODIFF_TAMC
166             kkey = (ikey-1)*Nr + k
167    CADJ STORE tracer(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
168    #endif /* ALLOW_AUTODIFF_TAMC */
169    
170  C--   Get temporary terms used by tendency routines  C--   Get temporary terms used by tendency routines
171        CALL CALC_COMMON_FACTORS (        CALL CALC_COMMON_FACTORS (
# Line 84  C--   Make local copy of tracer array Line 180  C--   Make local copy of tracer array
180         ENDDO         ENDDO
181        ENDDO        ENDDO
182    
183          IF (useCubedSphereExchange) THEN
184           nipass=3
185          ELSE
186           nipass=1
187          ENDIF
188    cph       nipass=1
189    
190    C--   Multiple passes for different directions on different tiles
191          DO ipass=1,nipass
192    #ifdef ALLOW_AUTODIFF_TAMC
193             passkey = ipass + (k-1)   *maxpass
194         &                   + (ikey-1)*maxpass*Nr
195             IF (nipass .GT. maxpass) THEN
196              STOP 'GAD_ADVECTION: nipass > maxpass. check tamc.h'
197             ENDIF
198    #endif /* ALLOW_AUTODIFF_TAMC */
199    
200          IF (nipass.EQ.3) THEN
201           calc_fluxes_X=.FALSE.
202           calc_fluxes_Y=.FALSE.
203           IF (ipass.EQ.1 .AND. (bi.EQ.1 .OR. bi.EQ.2) ) THEN
204            calc_fluxes_X=.TRUE.
205           ELSEIF (ipass.EQ.1 .AND. (bi.EQ.4 .OR. bi.EQ.5) ) THEN
206            calc_fluxes_Y=.TRUE.
207           ELSEIF (ipass.EQ.2 .AND. (bi.EQ.1 .OR. bi.EQ.6) ) THEN
208            calc_fluxes_Y=.TRUE.
209           ELSEIF (ipass.EQ.2 .AND. (bi.EQ.3 .OR. bi.EQ.4) ) THEN
210            calc_fluxes_X=.TRUE.
211           ELSEIF (ipass.EQ.3 .AND. (bi.EQ.2 .OR. bi.EQ.3) ) THEN
212            calc_fluxes_Y=.TRUE.
213           ELSEIF (ipass.EQ.3 .AND. (bi.EQ.5 .OR. bi.EQ.6) ) THEN
214            calc_fluxes_X=.TRUE.
215           ENDIF
216          ELSE
217           calc_fluxes_X=.TRUE.
218           calc_fluxes_Y=.TRUE.
219          ENDIF
220    
221    C--   X direction
222          IF (calc_fluxes_X) THEN
223    
224    C--   Internal exchange for calculations in X
225          IF (useCubedSphereExchange) THEN
226           DO j=1,Oly
227            DO i=1,Olx
228             localTij( 1-i , 1-j )=localTij( 1-j ,    i    )
229             localTij( 1-i ,sNy+j)=localTij( 1-j , sNy+1-i )
230             localTij(sNx+i, 1-j )=localTij(sNx+j,    i    )
231             localTij(sNx+i,sNy+j)=localTij(sNx+j, sNy+1-i )
232            ENDDO
233           ENDDO
234          ENDIF
235    
236  C-    Advective flux in X  C-    Advective flux in X
237        DO j=1-Oly,sNy+Oly        DO j=1-Oly,sNy+Oly
238         DO i=1-Olx,sNx+Olx         DO i=1-Olx,sNx+Olx
239          af(i,j) = 0.          af(i,j) = 0.
240         ENDDO         ENDDO
241        ENDDO        ENDDO
242    
243    #ifdef ALLOW_AUTODIFF_TAMC
244    #ifndef DISABLE_MULTIDIM_ADVECTION
245    CADJ STORE localTij(:,:)  = comlev1_bibj_pass, key=passkey, byte=isbyte
246    #endif
247    #endif /* ALLOW_AUTODIFF_TAMC */
248    
249        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
250         CALL GAD_FLUXLIMIT_ADV_X(         CALL GAD_FLUXLIMIT_ADV_X(
251       &      bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)       &      bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
# Line 100  C-    Advective flux in X Line 256  C-    Advective flux in X
256         CALL GAD_DST3FL_ADV_X(         CALL GAD_DST3FL_ADV_X(
257       &       bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)       &       bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
258        ELSE        ELSE
259         STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'         write(0,*) advectionScheme
260           STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'
261        ENDIF        ENDIF
262    
263        DO j=1-Oly,sNy+Oly        DO j=1-Oly,sNy+Oly
264         DO i=1-Olx,sNx+Olx-1         DO i=1-Olx,sNx+Olx-1
265          localTij(i,j)=localTij(i,j)-deltaTtracer*          localTij(i,j)=localTij(i,j)-deltaTtracer*
# Line 124  C--   Apply open boundary conditions Line 282  C--   Apply open boundary conditions
282        END IF        END IF
283  #endif /* ALLOW_OBCS */  #endif /* ALLOW_OBCS */
284    
285    C--   End of X direction
286          ENDIF
287    
288    C--   Y direction
289          IF (calc_fluxes_Y) THEN
290    
291    C--   Internal exchange for calculations in Y
292          IF (useCubedSphereExchange) THEN
293           DO j=1,Oly
294            DO i=1,Olx
295             localTij( 1-i , 1-j )=localTij(   j   , 1-i )
296             localTij( 1-i ,sNy+j)=localTij(   j   ,sNy+i)
297             localTij(sNx+i, 1-j )=localTij(sNx+1-j, 1-i )
298             localTij(sNx+i,sNy+j)=localTij(sNx+1-j,sNy+i)
299            ENDDO
300           ENDDO
301          ENDIF
302    
303  C-    Advective flux in Y  C-    Advective flux in Y
304        DO j=1-Oly,sNy+Oly        DO j=1-Oly,sNy+Oly
305         DO i=1-Olx,sNx+Olx         DO i=1-Olx,sNx+Olx
306          af(i,j) = 0.          af(i,j) = 0.
307         ENDDO         ENDDO
308        ENDDO        ENDDO
309    
310    #ifdef ALLOW_AUTODIFF_TAMC
311    #ifndef DISABLE_MULTIDIM_ADVECTION
312    CADJ STORE localTij(:,:)  = comlev1_bibj_pass, key=passkey, byte=isbyte
313    #endif
314    #endif /* ALLOW_AUTODIFF_TAMC */
315    
316        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
317         CALL GAD_FLUXLIMIT_ADV_Y(         CALL GAD_FLUXLIMIT_ADV_Y(
318       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)
# Line 142  C-    Advective flux in Y Line 325  C-    Advective flux in Y
325        ELSE        ELSE
326         STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'         STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
327        ENDIF        ENDIF
328    
329        DO j=1-Oly,sNy+Oly-1        DO j=1-Oly,sNy+Oly-1
330         DO i=1-Olx,sNx+Olx         DO i=1-Olx,sNx+Olx
331          localTij(i,j)=localTij(i,j)-deltaTtracer*          localTij(i,j)=localTij(i,j)-deltaTtracer*
# Line 152  C-    Advective flux in Y Line 336  C-    Advective flux in Y
336       &     )       &     )
337         ENDDO         ENDDO
338        ENDDO        ENDDO
339    
340  #ifdef ALLOW_OBCS  #ifdef ALLOW_OBCS
341  C--   Apply open boundary conditions  C--   Apply open boundary conditions
342        IF (useOBCS) THEN        IF (useOBCS) THEN
# Line 162  C--   Apply open boundary conditions Line 347  C--   Apply open boundary conditions
347         END IF         END IF
348        END IF        END IF
349  #endif /* ALLOW_OBCS */  #endif /* ALLOW_OBCS */
350        DO j=1-Oly,sNy+Oly-1  
351    C--   End of Y direction
352          ENDIF
353    
354          DO j=1-Oly,sNy+Oly
355         DO i=1-Olx,sNx+Olx         DO i=1-Olx,sNx+Olx
356          localTijk(i,j,k)=localTij(i,j)          localTijk(i,j,k)=localTij(i,j)
357         ENDDO         ENDDO
358        ENDDO        ENDDO
359    
360    C--   End of ipass loop
361          ENDDO
362    
363  C--   End of K loop for horizontal fluxes  C--   End of K loop for horizontal fluxes
364        ENDDO        ENDDO
365    
366  C--   Start of k loop for vertical flux  C--   Start of k loop for vertical flux
367        DO k=Nr,1,-1        DO k=Nr,1,-1
368    #ifdef ALLOW_AUTODIFF_TAMC
369             kkey = (ikey-1)*Nr + k
370    #endif /* ALLOW_AUTODIFF_TAMC */
371    
372  C--   kup    Cycles through 1,2 to point to w-layer above  C--   kup    Cycles through 1,2 to point to w-layer above
373  C--   kDown  Cycles through 2,1 to point to w-layer below  C--   kDown  Cycles through 2,1 to point to w-layer below
# Line 193  C-    Advective flux in R Line 387  C-    Advective flux in R
387         ENDDO         ENDDO
388        ENDDO        ENDDO
389    
390    #ifdef ALLOW_AUTODIFF_TAMC
391    CADJ STORE localTijk(:,:,k)  
392    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
393    #endif /* ALLOW_AUTODIFF_TAMC */
394    
395  C     Note: wVel needs to be masked  C     Note: wVel needs to be masked
396        IF (K.GE.2) THEN        IF (K.GE.2) THEN
397  C-    Compute vertical advective flux in the interior:  C-    Compute vertical advective flux in the interior:
# Line 200  C-    Compute vertical advective flux in Line 399  C-    Compute vertical advective flux in
399          CALL GAD_FLUXLIMIT_ADV_R(          CALL GAD_FLUXLIMIT_ADV_R(
400       &       bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)       &       bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
401         ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN         ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
402  c       CALL GAD_DST3_ADV_R(          CALL GAD_DST3_ADV_R(
403  c    &       bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)       &       bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
         STOP 'GAD_ADVECTION: adv. scheme not avail. yet'  
404         ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN         ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
405  c       CALL GAD_DST3FL_ADV_R(          CALL GAD_DST3FL_ADV_R(
406  c    &       bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)       &       bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
         STOP 'GAD_ADVECTION: adv. scheme not avail. yet'  
407         ELSE         ELSE
408          STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'          STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
409         ENDIF         ENDIF
# Line 215  C-    Surface "correction" term at k>1 : Line 412  C-    Surface "correction" term at k>1 :
412          DO i=1-Olx,sNx+Olx          DO i=1-Olx,sNx+Olx
413           af(i,j) = af(i,j)           af(i,j) = af(i,j)
414       &           + (maskC(i,j,k,bi,bj)-maskC(i,j,k-1,bi,bj))*       &           + (maskC(i,j,k,bi,bj)-maskC(i,j,k-1,bi,bj))*
415       &             rTrans(i,j)*localTijk(i,j,k)       &             rTrans(i,j)*tracer(i,j,k,bi,bj)
416    c    &             rTrans(i,j)*localTijk(i,j,k)
417          ENDDO          ENDDO
418         ENDDO         ENDDO
419        ELSE        ELSE
420  C-    Surface "correction" term at k=1 :  C-    Surface "correction" term at k=1 :
421         DO j=1-Oly,sNy+Oly         DO j=1-Oly,sNy+Oly
422          DO i=1-Olx,sNx+Olx          DO i=1-Olx,sNx+Olx
423           af(i,j) = rTrans(i,j)*localTijk(i,j,k)           af(i,j) = rTrans(i,j)*tracer(i,j,k,bi,bj)
424    c        af(i,j) = rTrans(i,j)*localTijk(i,j,k)
425          ENDDO          ENDDO
426         ENDDO         ENDDO
427        ENDIF        ENDIF

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.10

  ViewVC Help
Powered by ViewVC 1.1.22