/[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.11 by jmc, Wed Mar 6 02:01:54 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  rTransKp1            :: vertical volume transport at interface k+1
103    C  af                   :: 2-D array for horizontal advective flux
104    C  fVerT                :: 2 1/2D arrays for vertical advective flux
105    C  localTij             :: 2-D array used as temporary local copy of tracer fld
106    C  localTijk            :: 3-D array used as temporary local copy of tracer fld
107    C  kp1Msk               :: flag (0,1) to act as over-riding mask for W levels
108    C  calc_fluxes_X        :: logical to indicate to calculate fluxes in X dir
109    C  calc_fluxes_Y        :: logical to indicate to calculate fluxes in Y dir
110    C  nipass               :: number of passes to make in multi-dimensional method
111    C  ipass                :: number of the current pass being made
112        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
113        INTEGER iMin,iMax,jMin,jMax        INTEGER iMin,iMax,jMin,jMax
114        INTEGER i,j,k,kup,kDown,kp1        INTEGER i,j,k,kup,kDown
115        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
116        _RS yA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS yA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
117        _RL uTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
118        _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
119        _RL rTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
120          _RL rTransKp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
121        _RL af      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL af      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
122        _RL fVerT   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerT   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
123        _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 125  C     == Local variables
125        _RL kp1Msk        _RL kp1Msk
126        LOGICAL calc_fluxes_X,calc_fluxes_Y        LOGICAL calc_fluxes_X,calc_fluxes_Y
127        INTEGER nipass,ipass        INTEGER nipass,ipass
128    CEOP
129    
130    #ifdef ALLOW_AUTODIFF_TAMC
131              act1 = bi - myBxLo(myThid)
132              max1 = myBxHi(myThid) - myBxLo(myThid) + 1
133              act2 = bj - myByLo(myThid)
134              max2 = myByHi(myThid) - myByLo(myThid) + 1
135              act3 = myThid - 1
136              max3 = nTx*nTy
137              act4 = ikey_dynamics - 1
138              ikey = (act1 + 1) + act2*max1
139         &                      + act3*max1*max2
140         &                      + act4*max1*max2*max3
141    #endif /* ALLOW_AUTODIFF_TAMC */
142    
143  C--   Set up work arrays with valid (i.e. not NaN) values  C--   Set up work arrays with valid (i.e. not NaN) values
144  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 154  C     uninitialised but inert locations.
154          rTrans(i,j)  = 0. _d 0          rTrans(i,j)  = 0. _d 0
155          fVerT(i,j,1) = 0. _d 0          fVerT(i,j,1) = 0. _d 0
156          fVerT(i,j,2) = 0. _d 0          fVerT(i,j,2) = 0. _d 0
157            rTransKp1(i,j)= 0. _d 0
158         ENDDO         ENDDO
159        ENDDO        ENDDO
160    
# Line 72  C     uninitialised but inert locations. Line 165  C     uninitialised but inert locations.
165    
166  C--   Start of k loop for horizontal fluxes  C--   Start of k loop for horizontal fluxes
167        DO k=1,Nr        DO k=1,Nr
168    #ifdef ALLOW_AUTODIFF_TAMC
169             kkey = (ikey-1)*Nr + k
170    CADJ STORE tracer(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
171    #endif /* ALLOW_AUTODIFF_TAMC */
172    
173  C--   Get temporary terms used by tendency routines  C--   Get temporary terms used by tendency routines
174        CALL CALC_COMMON_FACTORS (        CALL CALC_COMMON_FACTORS (
# Line 79  C--   Get temporary terms used by tenden Line 176  C--   Get temporary terms used by tenden
176       O         xA,yA,uTrans,vTrans,rTrans,maskUp,       O         xA,yA,uTrans,vTrans,rTrans,maskUp,
177       I         myThid)       I         myThid)
178    
179    #ifdef ALLOW_GMREDI
180    C--   Residual transp = Bolus transp + Eulerian transp
181           IF (useGMRedi)
182         &   CALL GMREDI_CALC_UVFLOW(
183         &            uTrans, vTrans, bi, bj, k, myThid)
184    #endif /* ALLOW_GMREDI */
185    
186  C--   Make local copy of tracer array  C--   Make local copy of tracer array
187        DO j=1-OLy,sNy+OLy        DO j=1-OLy,sNy+OLy
188         DO i=1-OLx,sNx+OLx         DO i=1-OLx,sNx+OLx
# Line 91  C--   Make local copy of tracer array Line 195  C--   Make local copy of tracer array
195        ELSE        ELSE
196         nipass=1         nipass=1
197        ENDIF        ENDIF
198         nipass=1  cph       nipass=1
199    
200  C--   Multiple passes for different directions on different tiles  C--   Multiple passes for different directions on different tiles
201        DO ipass=1,nipass        DO ipass=1,nipass
202    #ifdef ALLOW_AUTODIFF_TAMC
203             passkey = ipass + (k-1)   *maxpass
204         &                   + (ikey-1)*maxpass*Nr
205             IF (nipass .GT. maxpass) THEN
206              STOP 'GAD_ADVECTION: nipass > maxpass. check tamc.h'
207             ENDIF
208    #endif /* ALLOW_AUTODIFF_TAMC */
209    
210        IF (nipass.EQ.3) THEN        IF (nipass.EQ.3) THEN
211         calc_fluxes_X=.FALSE.         calc_fluxes_X=.FALSE.
# Line 138  C-    Advective flux in X Line 249  C-    Advective flux in X
249          af(i,j) = 0.          af(i,j) = 0.
250         ENDDO         ENDDO
251        ENDDO        ENDDO
252    
253    #ifdef ALLOW_AUTODIFF_TAMC
254    #ifndef DISABLE_MULTIDIM_ADVECTION
255    CADJ STORE localTij(:,:)  = comlev1_bibj_pass, key=passkey, byte=isbyte
256    #endif
257    #endif /* ALLOW_AUTODIFF_TAMC */
258    
259        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
260         CALL GAD_FLUXLIMIT_ADV_X(         CALL GAD_FLUXLIMIT_ADV_X(
261       &      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 266  C-    Advective flux in X
266         CALL GAD_DST3FL_ADV_X(         CALL GAD_DST3FL_ADV_X(
267       &       bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)       &       bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
268        ELSE        ELSE
269         STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'         write(0,*) advectionScheme
270           STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'
271        ENDIF        ENDIF
272    
273        DO j=1-Oly,sNy+Oly        DO j=1-Oly,sNy+Oly
274         DO i=1-Olx,sNx+Olx-1         DO i=1-Olx,sNx+Olx-1
275          localTij(i,j)=localTij(i,j)-deltaTtracer*          localTij(i,j)=localTij(i,j)-deltaTtracer*
# Line 196  C-    Advective flux in Y Line 316  C-    Advective flux in Y
316          af(i,j) = 0.          af(i,j) = 0.
317         ENDDO         ENDDO
318        ENDDO        ENDDO
319    
320    #ifdef ALLOW_AUTODIFF_TAMC
321    #ifndef DISABLE_MULTIDIM_ADVECTION
322    CADJ STORE localTij(:,:)  = comlev1_bibj_pass, key=passkey, byte=isbyte
323    #endif
324    #endif /* ALLOW_AUTODIFF_TAMC */
325    
326        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
327         CALL GAD_FLUXLIMIT_ADV_Y(         CALL GAD_FLUXLIMIT_ADV_Y(
328       &       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 335  C-    Advective flux in Y
335        ELSE        ELSE
336         STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'         STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
337        ENDIF        ENDIF
338    
339        DO j=1-Oly,sNy+Oly-1        DO j=1-Oly,sNy+Oly-1
340         DO i=1-Olx,sNx+Olx         DO i=1-Olx,sNx+Olx
341          localTij(i,j)=localTij(i,j)-deltaTtracer*          localTij(i,j)=localTij(i,j)-deltaTtracer*
# Line 247  C--   End of K loop for horizontal fluxe Line 375  C--   End of K loop for horizontal fluxe
375    
376  C--   Start of k loop for vertical flux  C--   Start of k loop for vertical flux
377        DO k=Nr,1,-1        DO k=Nr,1,-1
378    #ifdef ALLOW_AUTODIFF_TAMC
379             kkey = (ikey-1)*Nr + k
380    #endif /* ALLOW_AUTODIFF_TAMC */
381    
382  C--   kup    Cycles through 1,2 to point to w-layer above  C--   kup    Cycles through 1,2 to point to w-layer above
383  C--   kDown  Cycles through 2,1 to point to w-layer below  C--   kDown  Cycles through 2,1 to point to w-layer below
384        kup  = 1+MOD(k+1,2)        kup  = 1+MOD(k+1,2)
385        kDown= 1+MOD(k,2)        kDown= 1+MOD(k,2)
386    c     kp1=min(Nr,k+1)
387          kp1Msk=1.
388          if (k.EQ.Nr) kp1Msk=0.
389    
390  C--   Get temporary terms used by tendency routines  #ifdef ALLOW_AUTODIFF_TAMC
391        CALL CALC_COMMON_FACTORS (  CADJ STORE localTijk(:,:,k)  
392       I         bi,bj,iMin,iMax,jMin,jMax,k,  CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
393       O         xA,yA,uTrans,vTrans,rTrans,maskUp,  #endif /* ALLOW_AUTODIFF_TAMC */
      I         myThid)  
394    
395  C-    Advective flux in R  C-- Compute Vertical transport
396        DO j=1-Oly,sNy+Oly  C     Note: wVel needs to be masked
397         DO i=1-Olx,sNx+Olx  
398          af(i,j) = 0.        IF (k.EQ.1) THEN
399    C- Surface interface :
400    
401           DO j=1-Oly,sNy+Oly
402            DO i=1-Olx,sNx+Olx
403             rTransKp1(i,j) = rTrans(i,j)
404             rTrans(i,j) = 0.
405             fVerT(i,j,kUp) = 0.
406            ENDDO
407         ENDDO         ENDDO
       ENDDO  
408    
409  C     Note: wVel needs to be masked        ELSE
410        IF (K.GE.2) THEN  C- Interior interface :
411           DO j=1-Oly,sNy+Oly
412            DO i=1-Olx,sNx+Olx
413             rTransKp1(i,j) = kp1Msk*rTrans(i,j)
414             rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)
415         &               *maskC(i,j,k-1,bi,bj)
416             af(i,j) = 0.
417            ENDDO
418           ENDDO
419    
420    #ifdef ALLOW_GMREDI
421    C--   Residual transp = Bolus transp + Eulerian transp
422           IF (useGMRedi)
423         &   CALL GMREDI_CALC_WFLOW(
424         &                    rTrans, bi, bj, k, myThid)
425    #endif /* ALLOW_GMREDI */
426    
427  C-    Compute vertical advective flux in the interior:  C-    Compute vertical advective flux in the interior:
428         IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN         IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
429          CALL GAD_FLUXLIMIT_ADV_R(          CALL GAD_FLUXLIMIT_ADV_R(
# Line 281  C-    Compute vertical advective flux in Line 437  C-    Compute vertical advective flux in
437         ELSE         ELSE
438          STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'          STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
439         ENDIF         ENDIF
440  C-    Surface "correction" term at k>1 :  C-    add the advective flux to fVerT
        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 :  
441         DO j=1-Oly,sNy+Oly         DO j=1-Oly,sNy+Oly
442          DO i=1-Olx,sNx+Olx          DO i=1-Olx,sNx+Olx
443           af(i,j) = rTrans(i,j)*localTijk(i,j,k)           fVerT(i,j,kUp) = af(i,j)
444          ENDDO          ENDDO
        ENDDO  
       ENDIF  
 C-    add the advective flux to fVerT  
       DO j=1-Oly,sNy+Oly  
        DO i=1-Olx,sNx+Olx  
         fVerT(i,j,kUp) = af(i,j)  
445         ENDDO         ENDDO
446        ENDDO  
447    C- end Surface/Interior if bloc
448          ENDIF
449    
450  C--   Divergence of fluxes  C--   Divergence of fluxes
       kp1=min(Nr,k+1)  
       kp1Msk=1.  
       if (k.EQ.Nr) kp1Msk=0.  
451        DO j=1-Oly,sNy+Oly        DO j=1-Oly,sNy+Oly
452         DO i=1-Olx,sNx+Olx         DO i=1-Olx,sNx+Olx
453          localTij(i,j)=localTijk(i,j,k)-deltaTtracer*          localTij(i,j)=localTijk(i,j,k)-deltaTtracer*
454       &    _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &    _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
455       &    *recip_rA(i,j,bi,bj)       &    *recip_rA(i,j,bi,bj)
456       &    *( fVerT(i,j,kUp)-fVerT(i,j,kDown)       &    *( fVerT(i,j,kUp)-fVerT(i,j,kDown)
457       &      -tracer(i,j,k,bi,bj)*rA(i,j,bi,bj)*       &      -tracer(i,j,k,bi,bj)*(rTrans(i,j)-rTransKp1(i,j))
      &        (wVel(i,j,k,bi,bj)-kp1Msk*wVel(i,j,kp1,bi,bj))  
458       &     )*rkFac       &     )*rkFac
459          gTracer(i,j,k,bi,bj)=          gTracer(i,j,k,bi,bj)=
460       &   (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer       &   (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer

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

  ViewVC Help
Powered by ViewVC 1.1.22