/[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.14 by heimbach, Tue Nov 12 20:42:24 2002 UTC revision 1.23 by jmc, Sat Jun 26 02:38:54 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, vertAdvecScheme,
13       I                         myTime,myIter,myThid)       I     tracerIdentity,
14         I     uVel, vVel, wVel, tracer,
15         O     gTracer,
16         I     bi,bj, myTime,myIter,myThid)
17    
18  C !DESCRIPTION:  C !DESCRIPTION:
19  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 39  C !USES: ===============================
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  #ifdef ALLOW_AUTODIFF_TAMC
# Line 71  C !USES: =============================== Line 47  C !USES: ===============================
47  #endif  #endif
48    
49  C !INPUT PARAMETERS: ===================================================  C !INPUT PARAMETERS: ===================================================
50  C  bi,bj                :: tile indices  C  implicitAdvection :: implicit vertical advection (later on)
51  C  advectionScheme      :: advection scheme to use  C  advectionScheme   :: advection scheme to use (Horizontal plane)
52  C  tracerIdentity       :: identifier for the tracer (required only for OBCS)  C  vertAdvecScheme   :: advection scheme to use (vertical direction)
53  C  Tracer               :: tracer field  C  tracerIdentity    :: tracer identifier (required only for OBCS)
54  C  myTime               :: current time  C  uVel              :: velocity, zonal component
55  C  myIter               :: iteration number  C  vVel              :: velocity, meridional component
56  C  myThid               :: thread number  C  wVel              :: velocity, vertical component
57        INTEGER bi,bj  C  tracer            :: tracer field
58        INTEGER advectionScheme  C  bi,bj             :: tile indices
59    C  myTime            :: current time
60    C  myIter            :: iteration number
61    C  myThid            :: thread number
62          LOGICAL implicitAdvection
63          INTEGER advectionScheme, vertAdvecScheme
64        INTEGER tracerIdentity        INTEGER tracerIdentity
65        _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)
66          _RL vVel  (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
67          _RL wVel  (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
68          _RL tracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
69          INTEGER bi,bj
70        _RL myTime        _RL myTime
71        INTEGER myIter        INTEGER myIter
72        INTEGER myThid        INTEGER myThid
73    
74  C !OUTPUT PARAMETERS: ==================================================  C !OUTPUT PARAMETERS: ==================================================
75  C  gTracer              :: tendancy array  C  gTracer           :: tendancy array
76        _RL gTracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)        _RL gTracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
77    
78  C !LOCAL VARIABLES: ====================================================  C !LOCAL VARIABLES: ====================================================
79  C  maskUp               :: 2-D array for mask at W points  C  maskUp        :: 2-D array for mask at W points
80  C  iMin,iMax,jMin,jMax  :: loop range for called routines  C  iMin,iMax,    :: loop range for called routines
81  C  i,j,k                :: loop indices  C  jMin,jMax     :: loop range for called routines
82  C  kup                  :: index into 2 1/2D array, toggles between 1 and 2  C  i,j,k         :: loop indices
83  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
84  C  kp1                  :: =k+1 for k<Nr, =Nr for k=Nr  C  kdown         :: index into 2 1/2D array, toggles between 2 and 1
85  C  xA,yA                :: areas of X and Y face of tracer cells  C  kp1           :: =k+1 for k<Nr, =Nr for k=Nr
86  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
87  C  rTransKp1            :: vertical volume transport at interface k+1  C  uTrans,vTrans :: 2-D arrays of volume transports at U,V points
88  C  af                   :: 2-D array for horizontal advective flux  C  rTrans        :: 2-D arrays of volume transports at W points
89  C  fVerT                :: 2 1/2D arrays for vertical advective flux  C  rTransKp1     :: vertical volume transport at interface k+1
90  C  localTij             :: 2-D array used as temporary local copy of tracer fld  C  af            :: 2-D array for horizontal advective flux
91  C  localTijk            :: 3-D array used as temporary local copy of tracer fld  C  fVerT         :: 2 1/2D arrays for vertical advective flux
92  C  kp1Msk               :: flag (0,1) to act as over-riding mask for W levels  C  localTij      :: 2-D array, temporary local copy of tracer fld
93  C  calc_fluxes_X        :: logical to indicate to calculate fluxes in X dir  C  localTijk     :: 3-D array, temporary local copy of tracer fld
94  C  calc_fluxes_Y        :: logical to indicate to calculate fluxes in Y dir  C  kp1Msk        :: flag (0,1) for over-riding mask for W levels
95  C  nipass               :: number of passes to make in multi-dimensional method  C  calc_fluxes_X :: logical to indicate to calculate fluxes in X dir
96  C  ipass                :: number of the current pass being made  C  calc_fluxes_Y :: logical to indicate to calculate fluxes in Y dir
97    C  nipass        :: number of passes in multi-dimensional method
98    C  ipass         :: number of the current pass being made
99        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
100        INTEGER iMin,iMax,jMin,jMax        INTEGER iMin,iMax,jMin,jMax
101        INTEGER i,j,k,kup,kDown        INTEGER i,j,k,kup,kDown
# Line 142  CEOP Line 129  CEOP
129       &                      + act2*max0*max1       &                      + act2*max0*max1
130       &                      + act3*max0*max1*max2       &                      + act3*max0*max1*max2
131       &                      + act4*max0*max1*max2*max3       &                      + act4*max0*max1*max2*max3
132            if (tracerIdentity.GT.maxpass)            if (tracerIdentity.GT.maxpass) then
133       &         STOP 'maxpass seems smaller than tracerIdentity'               print *, 'ph-pass gad_advection ', maxpass, tracerIdentity
134                 STOP 'maxpass seems smaller than tracerIdentity'
135              endif
136  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
137    
138  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 373  C--   Apply open boundary conditions Line 362  C--   Apply open boundary conditions
362  C--   End of Y direction  C--   End of Y direction
363        ENDIF        ENDIF
364    
       DO j=1-Oly,sNy+Oly  
        DO i=1-Olx,sNx+Olx  
         localTijk(i,j,k)=localTij(i,j)  
        ENDDO  
       ENDDO  
   
365  C--   End of ipass loop  C--   End of ipass loop
366        ENDDO        ENDDO
367    
368          IF ( implicitAdvection ) THEN
369    C-    explicit advection is done ; store tendency in gTracer:
370            DO j=1-Oly,sNy+Oly
371             DO i=1-Olx,sNx+Olx
372              gTracer(i,j,k,bi,bj)=
373         &     (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer
374             ENDDO
375            ENDDO
376          ELSE
377    C-    horizontal advection done; store intermediate result in 3D array:
378           DO j=1-Oly,sNy+Oly
379            DO i=1-Olx,sNx+Olx
380             localTijk(i,j,k)=localTij(i,j)
381            ENDDO
382           ENDDO
383          ENDIF
384    
385  C--   End of K loop for horizontal fluxes  C--   End of K loop for horizontal fluxes
386        ENDDO        ENDDO
387    
388          IF ( .NOT.implicitAdvection ) THEN
389  C--   Start of k loop for vertical flux  C--   Start of k loop for vertical flux
390        DO k=Nr,1,-1         DO k=Nr,1,-1
391  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
392           kkey = (ikey-1)*Nr + k           kkey = (igadkey-1)*Nr + k
393  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
   
394  C--   kup    Cycles through 1,2 to point to w-layer above  C--   kup    Cycles through 1,2 to point to w-layer above
395  C--   kDown  Cycles through 2,1 to point to w-layer below  C--   kDown  Cycles through 2,1 to point to w-layer below
396        kup  = 1+MOD(k+1,2)          kup  = 1+MOD(k+1,2)
397        kDown= 1+MOD(k,2)          kDown= 1+MOD(k,2)
398  c     kp1=min(Nr,k+1)  c       kp1=min(Nr,k+1)
399        kp1Msk=1.          kp1Msk=1.
400        if (k.EQ.Nr) kp1Msk=0.          if (k.EQ.Nr) kp1Msk=0.
   
 #ifdef ALLOW_AUTODIFF_TAMC  
 CADJ STORE localTijk(:,:,k)    
 CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte  
 CADJ STORE rTrans(:,:)    
 CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte  
 #endif /* ALLOW_AUTODIFF_TAMC */  
401    
402  C-- Compute Vertical transport  C-- Compute Vertical transport
403  C     Note: wVel needs to be masked  #ifdef ALLOW_AIM
404    C- a hack to prevent Water-Vapor vert.transport into the stratospheric level Nr
405            IF ( k.EQ.1 .OR.
406         &     (useAIM .AND. tracerIdentity.EQ.GAD_SALINITY .AND. k.EQ.Nr)
407         &              ) THEN
408    #else
409            IF ( k.EQ.1 ) THEN
410    #endif
411    
       IF (k.EQ.1) THEN  
412  C- Surface interface :  C- Surface interface :
413             DO j=1-Oly,sNy+Oly
414              DO i=1-Olx,sNx+Olx
415               rTransKp1(i,j) = kp1Msk*rTrans(i,j)
416               rTrans(i,j) = 0.
417               fVerT(i,j,kUp) = 0.
418               af(i,j) = 0.
419              ENDDO
420             ENDDO
421    
422         DO j=1-Oly,sNy+Oly          ELSE
         DO i=1-Olx,sNx+Olx  
          rTransKp1(i,j) = rTrans(i,j)  
          rTrans(i,j) = 0.  
          fVerT(i,j,kUp) = 0.  
         ENDDO  
        ENDDO  
   
       ELSE  
423  C- Interior interface :  C- Interior interface :
424         DO j=1-Oly,sNy+Oly  
425          DO i=1-Olx,sNx+Olx           DO j=1-Oly,sNy+Oly
426           rTransKp1(i,j) = kp1Msk*rTrans(i,j)            DO i=1-Olx,sNx+Olx
427           rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)             rTransKp1(i,j) = kp1Msk*rTrans(i,j)
428       &               *maskC(i,j,k-1,bi,bj)             rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)
429           af(i,j) = 0.       &                 *maskC(i,j,k-1,bi,bj)
430          ENDDO             af(i,j) = 0.
431         ENDDO            ENDDO
432             ENDDO
433    
434  #ifdef ALLOW_GMREDI  #ifdef ALLOW_GMREDI
435  C--   Residual transp = Bolus transp + Eulerian transp  C--   Residual transp = Bolus transp + Eulerian transp
436         IF (useGMRedi)           IF (useGMRedi)
437       &   CALL GMREDI_CALC_WFLOW(       &   CALL GMREDI_CALC_WFLOW(
438       &                    rTrans, bi, bj, k, myThid)       &                    rTrans, bi, bj, k, myThid)
439  #endif /* ALLOW_GMREDI */  #endif /* ALLOW_GMREDI */
440    
441    #ifdef ALLOW_AUTODIFF_TAMC
442    CADJ STORE localTijk(:,:,k)  
443    CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
444    CADJ STORE rTrans(:,:)  
445    CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
446    #endif /* ALLOW_AUTODIFF_TAMC */
447    
448  C-    Compute vertical advective flux in the interior:  C-    Compute vertical advective flux in the interior:
449         IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN           IF (vertAdvecScheme.EQ.ENUM_FLUX_LIMIT) THEN
450          CALL GAD_FLUXLIMIT_ADV_R(            CALL GAD_FLUXLIMIT_ADV_R(
451       &       bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
452         ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3 ) THEN
453          CALL GAD_DST3_ADV_R(            CALL GAD_DST3_ADV_R(
454       &       bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
455         ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
456          CALL GAD_DST3FL_ADV_R(            CALL GAD_DST3FL_ADV_R(
457       &       bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
458         ELSE           ELSE
459          STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'            STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
460         ENDIF           ENDIF
461  C-    add the advective flux to fVerT  C-    add the advective flux to fVerT
462         DO j=1-Oly,sNy+Oly           DO j=1-Oly,sNy+Oly
463          DO i=1-Olx,sNx+Olx            DO i=1-Olx,sNx+Olx
464           fVerT(i,j,kUp) = af(i,j)             fVerT(i,j,kUp) = af(i,j)
465          ENDDO            ENDDO
466         ENDDO           ENDDO
467    
468  C- end Surface/Interior if bloc  C- end Surface/Interior if bloc
469        ENDIF          ENDIF
470    
471  C--   Divergence of fluxes  #ifdef ALLOW_AUTODIFF_TAMC
472        DO j=1-Oly,sNy+Oly  CADJ STORE rTrans(:,:)  
473         DO i=1-Olx,sNx+Olx  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
474          localTij(i,j)=localTijk(i,j,k)-deltaTtracer*  CADJ STORE rTranskp1(:,:)  
475       &    _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
476       &    *recip_rA(i,j,bi,bj)  #endif /* ALLOW_AUTODIFF_TAMC */
477       &    *( fVerT(i,j,kUp)-fVerT(i,j,kDown)  
478       &      -tracer(i,j,k,bi,bj)*(rTrans(i,j)-rTransKp1(i,j))  C--   Divergence of vertical fluxes
479       &     )*rkFac          DO j=1-Oly,sNy+Oly
480          gTracer(i,j,k,bi,bj)=           DO i=1-Olx,sNx+Olx
481       &   (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer            localTij(i,j)=localTijk(i,j,k)-deltaTtracer*
482         ENDDO       &     _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
483        ENDDO       &     *recip_rA(i,j,bi,bj)
484         &     *( fVerT(i,j,kUp)-fVerT(i,j,kDown)
485         &       -tracer(i,j,k,bi,bj)*(rTrans(i,j)-rTransKp1(i,j))
486         &      )*rkFac
487              gTracer(i,j,k,bi,bj)=
488         &     (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer
489             ENDDO
490            ENDDO
491    
492  C--   End of K loop for vertical flux  C--   End of K loop for vertical flux
493        ENDDO         ENDDO
494    C--   end of if not.implicitAdvection block
495          ENDIF
496    
497        RETURN        RETURN
498        END        END

Legend:
Removed from v.1.14  
changed lines
  Added in v.1.23

  ViewVC Help
Powered by ViewVC 1.1.22