<p><b>dwj07@fsu.edu</b> 2011-09-16 15:57:58 -0600 (Fri, 16 Sep 2011)</p><p><br>
        -- BRANCH COMMIT --<br>
<br>
        Adding modules for vertical advection.<br>
<br>
        Include submodules for spline and stencil as well as<br>
        subsubmodules for each order of accuracy.<br>
</p><hr noshade><pre><font color="gray">Modified: branches/ocean_projects/performance/src/core_ocean/Makefile
===================================================================
--- branches/ocean_projects/performance/src/core_ocean/Makefile        2011-09-16 19:27:37 UTC (rev 1006)
+++ branches/ocean_projects/performance/src/core_ocean/Makefile        2011-09-16 21:57:58 UTC (rev 1007)
@@ -14,6 +14,18 @@
            module_OcnVelForcingWindStress.o \
            module_OcnVelForcingBottomDrag.o \
            module_OcnVelPressureGrad.o \
+           module_OcnTracerVadv.o \
+           module_OcnTracerVadvSpline.o \
+           module_OcnTracerVadvSpline2.o \
+           module_OcnTracerVadvSpline3.o \
+           module_OcnTracerVadvStencil.o \
+           module_OcnTracerVadvStencil2.o \
+           module_OcnTracerVadvStencil3.o \
+           module_OcnTracerVadvStencil4.o \
+           module_OcnTracerHadv.o \
+           module_OcnTracerHadv2.o \
+           module_OcnTracerHadv3.o \
+           module_OcnTracerHadv4.o \
        module_time_integration.o \
        module_global_diagnostics.o
 
@@ -52,6 +64,30 @@
 
 module_OcnVelCoriolis.o:
 
+module_OcnTracerHadv.o:  module_OcnTracerHadv2.o  module_OcnTracerHadv3.o  module_OcnTracerHadv4.o
+
+module_OcnTracerHadv2.o:
+
+module_OcnTracerHadv3.o:
+
+module_OcnTracerHadv4.o:
+
+module_OcnTracerVadv.o: module_OcnTracerVadvSpline.o module_OcnTracerVadvStencil.o
+
+module_OcnTracerVadvSpline.o: module_OcnTracerVadvSpline2.o  module_OcnTracerVadvSpline3.o
+
+module_OcnTracerVadvSpline2.o:
+
+module_OcnTracerVadvSpline3.o:
+
+module_OcnTracerVadvStencil.o: module_OcnTracerVadvStencil2.o module_OcnTracerVadvStencil3.o  module_OcnTracerVadvStencil4.o 
+
+module_OcnTracerVadvStencil2.o:
+
+module_OcnTracerVadvStencil3.o:
+
+module_OcnTracerVadvStencil4.o:
+
 module_mpas_core.o: module_advection.o \
                                         module_OcnThickHadv.o \
                                         module_OcnThickVadv.o \
@@ -66,6 +102,18 @@
                                         module_OcnVelForcingWindStress.o \
                                         module_OcnVelForcingBottomDrag.o \
                                         module_OcnVelPressureGrad.o \
+                                        module_OcnTracerHadv.o \
+                                        module_OcnTracerHadv2.o \
+                                        module_OcnTracerHadv3.o \
+                                        module_OcnTracerHadv4.o \
+                                        module_OcnTracerVadv.o \
+                                        module_OcnTracerVadvSpline.o \
+                                        module_OcnTracerVadvSpline2.o \
+                                        module_OcnTracerVadvSpline3.o \
+                                        module_OcnTracerVadvStencil.o \
+                                        module_OcnTracerVadvStencil2.o \
+                                        module_OcnTracerVadvStencil3.o \
+                                        module_OcnTracerVadvStencil4.o \
                                         module_time_integration.o
 
 clean:

Added: branches/ocean_projects/performance/src/core_ocean/module_OcnTracerVadv.F
===================================================================
--- branches/ocean_projects/performance/src/core_ocean/module_OcnTracerVadv.F                                (rev 0)
+++ branches/ocean_projects/performance/src/core_ocean/module_OcnTracerVadv.F        2011-09-16 21:57:58 UTC (rev 1007)
@@ -0,0 +1,185 @@
+!|||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
+!
+!  OcnTracerVadv
+!
+!&gt; \brief MPAS ocean vertical tracer advection driver
+!&gt; \author Doug Jacobsen
+!&gt; \date   16 September 2011
+!&gt; \version SVN:$Id:$
+!&gt; \details
+!&gt;  This module contains the main driver routine for computing 
+!&gt;  vertical advection tendencies.  
+!
+!-----------------------------------------------------------------------
+
+module OcnTracerVadv
+
+   use grid_types
+   use configure
+
+   use OcnTracerVadvStencil
+   use OcnTracerVadvSpline
+
+   implicit none
+   private
+   save
+
+   !--------------------------------------------------------------------
+   !
+   ! Public parameters
+   !
+   !--------------------------------------------------------------------
+
+   !--------------------------------------------------------------------
+   !
+   ! Public member functions
+   !
+   !--------------------------------------------------------------------
+
+   public :: OcnTracerVadvTend, &amp;
+             OcnTracerVadvInit
+
+   !--------------------------------------------------------------------
+   !
+   ! Private module variables
+   !
+   !--------------------------------------------------------------------
+
+   logical :: vadvOn
+
+
+!***********************************************************************
+
+contains
+
+!***********************************************************************
+!
+!  routine OcnTracerVadvTend
+!
+!&gt; \brief   Computes tendency term for vertical tracer advection
+!&gt; \author  Phil Jones, Doug Jacobsen
+!&gt; \date    15 September 2011
+!&gt; \version SVN:$Id$
+!&gt; \details 
+!&gt;  This routine computes the vertical advection tendency for tracer
+!&gt;  based on current state and user choices of advection parameterization.
+!&gt;  Multiple parameterizations may be chosen and added together.  These
+!&gt;  tendencies are generally computed by calling the specific routine
+!&gt;  for the chosen parameterization, so this routine is primarily a
+!&gt;  driver for managing these choices.
+!
+!-----------------------------------------------------------------------
+
+   subroutine OcnTracerVadvTend(grid, wTop, tracers, tend, err)
+
+      !-----------------------------------------------------------------
+      !
+      ! input variables
+      !
+      !-----------------------------------------------------------------
+
+      real (kind=RKIND), dimension(:,:), intent(in) :: &amp;
+         wTop    !&lt; Input: vertical velocity in top layer
+
+      real (kind=RKIND), dimension(:,:,:), intent(in) :: &amp;
+         tracers     !&lt; Input: tracers
+
+      type (mesh_type), intent(in) :: &amp;
+         grid          !&lt; Input: grid information
+
+      !-----------------------------------------------------------------
+      !
+      ! input/output variables
+      !
+      !-----------------------------------------------------------------
+
+      real (kind=RKIND), dimension(:,:,:), intent(inout) :: &amp;
+         tend          !&lt; Input/Output: velocity tendency
+
+      !-----------------------------------------------------------------
+      !
+      ! output variables
+      !
+      !-----------------------------------------------------------------
+
+      integer, intent(out) :: err
+
+      !-----------------------------------------------------------------
+      !
+      ! local variables
+      !
+      !-----------------------------------------------------------------
+
+      integer :: err1, err2
+
+      !-----------------------------------------------------------------
+      !
+      ! call relevant routines for computing tendencies
+      ! note that the user can choose multiple options and the 
+      !   tendencies will be added together
+      !
+      !-----------------------------------------------------------------
+
+      err = 0
+
+      if(.not.vadvOn) return
+
+      call OcnTracerVadvStencilTend(grid, wTop, tracers, tend, err1)
+      call OcnTracerVadvSplineTend(grid, wTop, tracers, tend, err2)
+
+      err = err1 .or. err2
+
+   !--------------------------------------------------------------------
+
+   end subroutine OcnTracerVadvTend
+
+!***********************************************************************
+!
+!  routine OcnTracerVadvInit
+!
+!&gt; \brief   Initializes ocean tracer vertical advection quantities
+!&gt; \author  Phil Jones, Doug Jacobsen
+!&gt; \date    15 September 2011
+!&gt; \version SVN:$Id$
+!&gt; \details 
+!&gt;  This routine initializes a variety of quantities related to 
+!&gt;  vertical velocity advection in the ocean. Since a variety of 
+!&gt;  parameterizations are available, this routine primarily calls the
+!&gt;  individual init routines for each parameterization. 
+!
+!-----------------------------------------------------------------------
+
+
+   subroutine OcnTracerVadvInit(err)
+
+   !--------------------------------------------------------------------
+
+      !-----------------------------------------------------------------
+      !
+      ! call individual init routines for each parameterization
+      !
+      !-----------------------------------------------------------------
+
+      integer, intent(out) :: err
+
+      integer :: err1, err2
+
+      vadvOn = .false.
+
+      if (config_vert_grid_type.eq.'zlevel') then
+          vadvOn = .true.
+          call OcnTracerVadvStencilInit(err1)
+          call OcnTracerVadvSplineInit(err2)
+
+          err = err1 .or. err2
+      endif
+
+   !--------------------------------------------------------------------
+
+   end subroutine OcnTracerVadvInit
+
+!***********************************************************************
+
+end module OcnTracerVadv
+
+!|||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||

Added: branches/ocean_projects/performance/src/core_ocean/module_OcnTracerVadvSpline.F
===================================================================
--- branches/ocean_projects/performance/src/core_ocean/module_OcnTracerVadvSpline.F                                (rev 0)
+++ branches/ocean_projects/performance/src/core_ocean/module_OcnTracerVadvSpline.F        2011-09-16 21:57:58 UTC (rev 1007)
@@ -0,0 +1,186 @@
+!|||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
+!
+!  OcnTracerVadvSpline
+!
+!&gt; \brief MPAS ocean vertical tracer advection driver
+!&gt; \author Doug Jacobsen
+!&gt; \date   16 September 2011
+!&gt; \version SVN:$Id:$
+!&gt; \details
+!&gt;  This module contains the main driver routine for computing 
+!&gt;  vertical advection tendencies.  
+!
+!-----------------------------------------------------------------------
+
+module OcnTracerVadvSpline
+
+   use grid_types
+   use configure
+
+   use OcnTracerVadvSpline2
+   use OcnTracerVadvSpline3
+
+   implicit none
+   private
+   save
+
+   !--------------------------------------------------------------------
+   !
+   ! Public parameters
+   !
+   !--------------------------------------------------------------------
+
+   !--------------------------------------------------------------------
+   !
+   ! Public member functions
+   !
+   !--------------------------------------------------------------------
+
+   public :: OcnTracerVadvSplineTend, &amp;
+             OcnTracerVadvSplineInit
+
+   !--------------------------------------------------------------------
+   !
+   ! Private module variables
+   !
+   !--------------------------------------------------------------------
+
+   logical :: splineOn
+
+
+!***********************************************************************
+
+contains
+
+!***********************************************************************
+!
+!  routine OcnTracerVadvSplineTend
+!
+!&gt; \brief   Computes tendency term for vertical tracer advection
+!&gt; \author  Doug Jacobsen
+!&gt; \date    16 September 2011
+!&gt; \version SVN:$Id$
+!&gt; \details 
+!&gt;  This routine computes the vertical advection tendency for tracer
+!&gt;  based on current state and user choices of advection parameterization.
+!&gt;  Multiple parameterizations may be chosen and added together.  These
+!&gt;  tendencies are generally computed by calling the specific routine
+!&gt;  for the chosen parameterization, so this routine is primarily a
+!&gt;  driver for managing these choices.
+!
+!-----------------------------------------------------------------------
+
+   subroutine OcnTracerVadvSplineTend(grid, wTop, tracers, tend, err)
+
+      !-----------------------------------------------------------------
+      !
+      ! input variables
+      !
+      !-----------------------------------------------------------------
+
+      real (kind=RKIND), dimension(:,:), intent(in) :: &amp;
+         wTop    !&lt; Input: vertical velocity in top layer
+
+      real (kind=RKIND), dimension(:,:,:), intent(in) :: &amp;
+         tracers     !&lt; Input: tracers
+
+      type (mesh_type), intent(in) :: &amp;
+         grid          !&lt; Input: grid information
+
+      !-----------------------------------------------------------------
+      !
+      ! input/output variables
+      !
+      !-----------------------------------------------------------------
+
+      real (kind=RKIND), dimension(:,:,:), intent(inout) :: &amp;
+         tend          !&lt; Input/Output: velocity tendency
+
+      !-----------------------------------------------------------------
+      !
+      ! output variables
+      !
+      !-----------------------------------------------------------------
+
+      integer, intent(out) :: err
+
+      !-----------------------------------------------------------------
+      !
+      ! local variables
+      !
+      !-----------------------------------------------------------------
+
+      integer :: err1, err2
+
+      !-----------------------------------------------------------------
+      !
+      ! call relevant routines for computing tendencies
+      ! note that the user can choose multiple options and the 
+      !   tendencies will be added together
+      !
+      !-----------------------------------------------------------------
+
+      err = 0
+
+      if(.not.splineOn) return
+
+      call OcnTracerVadvSpline2Tend(grid, wTop, tracers, tend, err1)
+      call OcnTracerVadvSpline3Tend(grid, wTop, tracers, tend, err2)
+
+      err = err1 .or. err2
+
+   !--------------------------------------------------------------------
+
+   end subroutine OcnTracerVadvSplineTend
+
+!***********************************************************************
+!
+!  routine OcnTracerVadvSplineInit
+!
+!&gt; \brief   Initializes ocean tracer vertical advection quantities
+!&gt; \author  Doug Jacobsen
+!&gt; \date    16 September 2011
+!&gt; \version SVN:$Id$
+!&gt; \details 
+!&gt;  This routine initializes a variety of quantities related to 
+!&gt;  vertical velocity advection in the ocean. Since a variety of 
+!&gt;  parameterizations are available, this routine primarily calls the
+!&gt;  individual init routines for each parameterization. 
+!
+!-----------------------------------------------------------------------
+
+
+   subroutine OcnTracerVadvSplineInit(err)
+
+   !--------------------------------------------------------------------
+
+      !-----------------------------------------------------------------
+      !
+      ! call individual init routines for each parameterization
+      !
+      !-----------------------------------------------------------------
+
+      integer, intent(out) :: err
+
+      integer :: err1, err2
+
+      splineOn = .false.
+
+      if(config_vert_tracer_adv.eq.'spline') then
+         splineOn = .true.
+
+         call OcnTracerVadvSpline2Init(err2)
+         call OcnTracerVadvSpline3Init(err2)
+
+         err = err1 .or. err2
+      endif
+
+   !--------------------------------------------------------------------
+
+   end subroutine OcnTracerVadvSplineInit
+
+!***********************************************************************
+
+end module OcnTracerVadvSpline
+
+!|||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||

Added: branches/ocean_projects/performance/src/core_ocean/module_OcnTracerVadvSpline2.F
===================================================================
--- branches/ocean_projects/performance/src/core_ocean/module_OcnTracerVadvSpline2.F                                (rev 0)
+++ branches/ocean_projects/performance/src/core_ocean/module_OcnTracerVadvSpline2.F        2011-09-16 21:57:58 UTC (rev 1007)
@@ -0,0 +1,220 @@
+!|||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
+!
+!  OcnTracerVadvSpline2
+!
+!&gt; \brief MPAS ocean vertical tracer advection driver
+!&gt; \author Doug Jacobsen
+!&gt; \date   16 September 2011
+!&gt; \version SVN:$Id:$
+!&gt; \details
+!&gt;  This module contains the main driver routine for computing 
+!&gt;  vertical advection tendencies.  
+!
+!-----------------------------------------------------------------------
+
+module OcnTracerVadvSpline2
+
+   use grid_types
+   use configure
+   use timer
+
+   implicit none
+   private
+   save
+
+   !--------------------------------------------------------------------
+   !
+   ! Public parameters
+   !
+   !--------------------------------------------------------------------
+
+   !--------------------------------------------------------------------
+   !
+   ! Public member functions
+   !
+   !--------------------------------------------------------------------
+
+   public :: OcnTracerVadvSpline2Tend, &amp;
+             OcnTracerVadvSpline2Init
+
+   !--------------------------------------------------------------------
+   !
+   ! Private module variables
+   !
+   !--------------------------------------------------------------------
+
+   logical :: spline2On
+
+
+!***********************************************************************
+
+contains
+
+!***********************************************************************
+!
+!  routine OcnTracerVadvSpline2Tend
+!
+!&gt; \brief   Computes tendency term for vertical tracer advection
+!&gt; \author  Doug Jacobsen
+!&gt; \date    16 September 2011
+!&gt; \version SVN:$Id$
+!&gt; \details 
+!&gt;  This routine computes the vertical advection tendency for tracer
+!&gt;  based on current state and user choices of advection parameterization.
+!&gt;  Multiple parameterizations may be chosen and added together.  These
+!&gt;  tendencies are generally computed by calling the specific routine
+!&gt;  for the chosen parameterization, so this routine is primarily a
+!&gt;  driver for managing these choices.
+!
+!-----------------------------------------------------------------------
+
+   subroutine OcnTracerVadvSpline2Tend(grid, wTop, tracers, tend, err)
+
+      !-----------------------------------------------------------------
+      !
+      ! input variables
+      !
+      !-----------------------------------------------------------------
+
+      real (kind=RKIND), dimension(:,:), intent(in) :: &amp;
+         wTop    !&lt; Input: vertical velocity in top layer
+
+      real (kind=RKIND), dimension(:,:,:), intent(in) :: &amp;
+         tracers     !&lt; Input: tracers
+
+      type (mesh_type), intent(in) :: &amp;
+         grid          !&lt; Input: grid information
+
+      !-----------------------------------------------------------------
+      !
+      ! input/output variables
+      !
+      !-----------------------------------------------------------------
+
+      real (kind=RKIND), dimension(:,:,:), intent(inout) :: &amp;
+         tend          !&lt; Input/Output: velocity tendency
+
+      !-----------------------------------------------------------------
+      !
+      ! output variables
+      !
+      !-----------------------------------------------------------------
+
+      integer, intent(out) :: err
+
+      !-----------------------------------------------------------------
+      !
+      ! local variables
+      !
+      !-----------------------------------------------------------------
+
+      integer :: iCell, nCells, nCellsSolve, k, iTracer, num_tracers, nVertLevels
+
+      integer, dimension(:), pointer :: maxLevelCell
+
+      real (kind=RKIND), dimension(:), pointer :: hRatioZLevelK, hRatioZLevelKm1
+
+      real (kind=RKIND), dimension(:,:,:), allocatable :: tracerTop
+
+      !-----------------------------------------------------------------
+      !
+      ! call relevant routines for computing tendencies
+      ! note that the user can choose multiple options and the 
+      !   tendencies will be added together
+      !
+      !-----------------------------------------------------------------
+
+      err = 0
+
+      if(.not.spline2On) return
+      ! Compute tracerTop using linear interpolation.
+
+      call timer_start(&quot;compute_scalar_tend-vert adv spline 2&quot;)
+
+      nCells = grid % nCells
+      nCellsSolve = grid % nCellsSolve
+      nVertLevels = grid % nVertLevels
+      num_tracers = size(tracers, 1)
+      maxLevelCell =&gt; grid % maxLevelCell % array
+
+      hRatioZLevelK =&gt; grid % hRatioZLevelK % array
+      hRatioZLevelKm1 =&gt; grid % hRatioZLevelKm1 % array
+
+      allocate(tracerTop(num_tracers,nVertLevels+1,nCells))
+
+      do iCell=1,nCellsSolve 
+         do k=2,maxLevelCell(iCell)
+            do iTracer=1,num_tracers
+               ! Note hRatio on the k side is multiplied by tracer at k-1
+               ! and hRatio on the Km1 (k-1) side is mult. by tracer at k.
+               tracerTop(iTracer,k,iCell) = &amp;
+                    hRatioZLevelK(k)  *tracers(iTracer,k-1,iCell) &amp;
+                  + hRatioZLevelKm1(k)*tracers(iTracer,k  ,iCell)
+            end do
+         end do
+      end do
+
+      do iCell=1,nCellsSolve 
+         do k=1,maxLevelCell(iCell)  
+            do iTracer=1,num_tracers
+               tend(iTracer,k,iCell) = tend(iTracer,k,iCell) &amp;
+                  - (   wTop(k  ,iCell)*tracerTop(iTracer,k  ,iCell) &amp;
+                      - wTop(k+1,iCell)*tracerTop(iTracer,k+1,iCell))
+            end do
+         end do
+      end do
+
+      deallocate(tracerTop)
+
+      call timer_stop(&quot;compute_scalar_tend-vert adv spline 2&quot;)
+   !--------------------------------------------------------------------
+
+   end subroutine OcnTracerVadvSpline2Tend
+
+!***********************************************************************
+!
+!  routine OcnTracerVadvSpline2Init
+!
+!&gt; \brief   Initializes ocean tracer vertical advection quantities
+!&gt; \author  Doug Jacobsen
+!&gt; \date    16 September 2011
+!&gt; \version SVN:$Id$
+!&gt; \details 
+!&gt;  This routine initializes a variety of quantities related to 
+!&gt;  vertical velocity advection in the ocean. Since a variety of 
+!&gt;  parameterizations are available, this routine primarily calls the
+!&gt;  individual init routines for each parameterization. 
+!
+!-----------------------------------------------------------------------
+
+
+   subroutine OcnTracerVadvSpline2Init(err)
+
+   !--------------------------------------------------------------------
+
+      !-----------------------------------------------------------------
+      !
+      ! call individual init routines for each parameterization
+      !
+      !-----------------------------------------------------------------
+
+      integer, intent(out) :: err
+
+      err = 0
+
+      spline2On = .false.
+
+      if(config_vert_tracer_adv_order.eq.2) then
+        spline2On = .true.
+      endif
+
+
+   !--------------------------------------------------------------------
+
+   end subroutine OcnTracerVadvSpline2Init
+
+!***********************************************************************
+
+end module OcnTracerVadvSpline2
+
+!|||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||

Added: branches/ocean_projects/performance/src/core_ocean/module_OcnTracerVadvSpline3.F
===================================================================
--- branches/ocean_projects/performance/src/core_ocean/module_OcnTracerVadvSpline3.F                                (rev 0)
+++ branches/ocean_projects/performance/src/core_ocean/module_OcnTracerVadvSpline3.F        2011-09-16 21:57:58 UTC (rev 1007)
@@ -0,0 +1,249 @@
+!|||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
+!
+!  OcnTracerVadvSpline3
+!
+!&gt; \brief MPAS ocean vertical tracer advection driver
+!&gt; \author Doug Jacobsen
+!&gt; \date   16 September 2011
+!&gt; \version SVN:$Id:$
+!&gt; \details
+!&gt;  This module contains the main driver routine for computing 
+!&gt;  vertical advection tendencies.  
+!
+!-----------------------------------------------------------------------
+
+module OcnTracerVadvSpline3
+
+   use grid_types
+   use configure
+   use timer
+   use spline_interpolation
+
+   implicit none
+   private
+   save
+
+   !--------------------------------------------------------------------
+   !
+   ! Public parameters
+   !
+   !--------------------------------------------------------------------
+
+   !--------------------------------------------------------------------
+   !
+   ! Public member functions
+   !
+   !--------------------------------------------------------------------
+
+   public :: OcnTracerVadvSpline3Tend, &amp;
+             OcnTracerVadvSpline3Init
+
+   !--------------------------------------------------------------------
+   !
+   ! Private module variables
+   !
+   !--------------------------------------------------------------------
+
+   logical :: spline3On
+
+
+!***********************************************************************
+
+contains
+
+!***********************************************************************
+!
+!  routine OcnTracerVadvSpline3Tend
+!
+!&gt; \brief   Computes tendency term for vertical tracer advection
+!&gt; \author  Doug Jacobsen
+!&gt; \date    16 September 2011
+!&gt; \version SVN:$Id$
+!&gt; \details 
+!&gt;  This routine computes the vertical advection tendency for tracer
+!&gt;  based on current state and user choices of advection parameterization.
+!&gt;  Multiple parameterizations may be chosen and added together.  These
+!&gt;  tendencies are generally computed by calling the specific routine
+!&gt;  for the chosen parameterization, so this routine is primarily a
+!&gt;  driver for managing these choices.
+!
+!-----------------------------------------------------------------------
+
+   subroutine OcnTracerVadvSpline3Tend(grid, wTop, tracers, tend, err)
+
+      !-----------------------------------------------------------------
+      !
+      ! input variables
+      !
+      !-----------------------------------------------------------------
+
+      real (kind=RKIND), dimension(:,:), intent(in) :: &amp;
+         wTop    !&lt; Input: vertical velocity in top layer
+
+      real (kind=RKIND), dimension(:,:,:), intent(in) :: &amp;
+         tracers     !&lt; Input: tracers
+
+      type (mesh_type), intent(in) :: &amp;
+         grid          !&lt; Input: grid information
+
+      !-----------------------------------------------------------------
+      !
+      ! input/output variables
+      !
+      !-----------------------------------------------------------------
+
+      real (kind=RKIND), dimension(:,:,:), intent(inout) :: &amp;
+         tend          !&lt; Input/Output: velocity tendency
+
+      !-----------------------------------------------------------------
+      !
+      ! output variables
+      !
+      !-----------------------------------------------------------------
+
+      integer, intent(out) :: err
+
+      !-----------------------------------------------------------------
+      !
+      ! local variables
+      !
+      !-----------------------------------------------------------------
+
+      integer :: iCell, nCells, nCellsSolve, k, iTracer, num_tracers, nVertLevels
+
+      integer, dimension(:), pointer :: maxLevelCell
+
+      real (kind=RKIND), dimension(:), pointer :: hRatioZLevelK, &amp;
+            hRatioZLevelKm1, zTopZLevel, zMidZLevel
+
+      real (kind=RKIND), dimension(:), allocatable :: tracer2ndDer,  &amp;
+            tracersIn, tracersOut, posZMidZLevel, posZTopZLevel
+      real (kind=RKIND), dimension(:,:,:), allocatable :: tracerTop
+
+      !-----------------------------------------------------------------
+      !
+      ! call relevant routines for computing tendencies
+      ! note that the user can choose multiple options and the 
+      !   tendencies will be added together
+      !
+      !-----------------------------------------------------------------
+
+      err = 0
+
+      if(.not.spline3On) return
+      ! Compute tracerTop using linear interpolation.
+
+      call timer_start(&quot;compute_scalar_tend-vert adv spline 3&quot;)
+
+      nCells = grid % nCells
+      nCellsSolve = grid % nCellsSolve
+      nVertLevels = grid % nVertLevels
+      num_tracers = size(tracers, 1)
+      maxLevelCell =&gt; grid % maxLevelCell % array
+
+      hRatioZLevelK =&gt; grid % hRatioZLevelK % array
+      hRatioZLevelKm1 =&gt; grid % hRatioZLevelKm1 % array
+      zMidZLevel =&gt; grid % zMidZLevel % array
+      zTopZLevel =&gt; grid % zTopZLevel % array
+
+      allocate(tracerTop(num_tracers,nVertLevels+1,nCells))
+
+      ! Compute tracerTop using cubic spline interpolation.
+
+      allocate(tracer2ndDer(nVertLevels))
+      allocate(tracersIn(nVertLevels),tracersOut(nVertLevels), &amp;
+            posZMidZLevel(nVertLevels), posZTopZLevel(nVertLevels-1))
+
+      ! For the ocean, zlevel coordinates are negative and decreasing, 
+      ! but spline functions assume increasing, so flip to positive.
+
+      posZMidZLevel = -zMidZLevel(1:nVertLevels)
+      posZTopZLevel = -zTopZLevel(2:nVertLevels)
+
+      do iCell=1,nCellsSolve 
+         ! mrp 110201 efficiency note: push tracer loop down
+         ! into spline subroutines to improve efficiency
+         do iTracer=1,num_tracers
+
+            ! Place data in arrays to avoid creating new temporary arrays for every 
+            ! subroutine call.  
+            tracersIn(1:maxLevelCell(iCell))=tracers(iTracer,1:maxLevelCell(iCell),iCell)
+
+            call CubicSplineCoefficients(posZMidZLevel, &amp;
+               tracersIn, maxLevelCell(iCell), tracer2ndDer)
+
+            call InterpolateCubicSpline( &amp;
+               posZMidZLevel, tracersIn, tracer2ndDer, maxLevelCell(iCell), &amp;
+               posZTopZLevel, tracersOut, maxLevelCell(iCell)-1 )
+
+            tracerTop(iTracer,2:maxLevelCell(iCell),iCell) = tracersOut(1:maxLevelCell(iCell)-1)
+
+         end do
+      end do
+
+      do iCell=1,nCellsSolve 
+         do k=1,maxLevelCell(iCell)  
+            do iTracer=1,num_tracers
+               tend(iTracer,k,iCell) = tend(iTracer,k,iCell) &amp;
+                  - (   wTop(k  ,iCell)*tracerTop(iTracer,k  ,iCell) &amp;
+                      - wTop(k+1,iCell)*tracerTop(iTracer,k+1,iCell))
+            end do
+         end do
+      end do
+
+      deallocate(tracer2ndDer)
+      deallocate(tracersIn,tracersOut, posZMidZLevel, posZTopZLevel)
+      deallocate(tracerTop)
+
+      call timer_stop(&quot;compute_scalar_tend-vert adv spline 3&quot;)
+   !--------------------------------------------------------------------
+
+   end subroutine OcnTracerVadvSpline3Tend
+
+!***********************************************************************
+!
+!  routine OcnTracerVadvSpline3Init
+!
+!&gt; \brief   Initializes ocean tracer vertical advection quantities
+!&gt; \author  Doug Jacobsen
+!&gt; \date    16 September 2011
+!&gt; \version SVN:$Id$
+!&gt; \details 
+!&gt;  This routine initializes a variety of quantities related to 
+!&gt;  vertical velocity advection in the ocean. Since a variety of 
+!&gt;  parameterizations are available, this routine primarily calls the
+!&gt;  individual init routines for each parameterization. 
+!
+!-----------------------------------------------------------------------
+
+
+   subroutine OcnTracerVadvSpline3Init(err)
+
+   !--------------------------------------------------------------------
+
+      !-----------------------------------------------------------------
+      !
+      ! call individual init routines for each parameterization
+      !
+      !-----------------------------------------------------------------
+
+      integer, intent(out) :: err
+
+      err = 0
+
+      spline3On = .false.
+
+      if(config_vert_tracer_adv_order.eq.3) then
+        spline3On = .true.
+      endif
+
+
+   !--------------------------------------------------------------------
+
+   end subroutine OcnTracerVadvSpline3Init
+
+!***********************************************************************
+
+end module OcnTracerVadvSpline3
+
+!|||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||

Added: branches/ocean_projects/performance/src/core_ocean/module_OcnTracerVadvStencil.F
===================================================================
--- branches/ocean_projects/performance/src/core_ocean/module_OcnTracerVadvStencil.F                                (rev 0)
+++ branches/ocean_projects/performance/src/core_ocean/module_OcnTracerVadvStencil.F        2011-09-16 21:57:58 UTC (rev 1007)
@@ -0,0 +1,191 @@
+!|||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
+!
+!  OcnTracerVadvStencil
+!
+!&gt; \brief MPAS ocean vertical tracer advection driver
+!&gt; \author Doug Jacobsen
+!&gt; \date   16 September 2011
+!&gt; \version SVN:$Id:$
+!&gt; \details
+!&gt;  This module contains the main driver routine for computing 
+!&gt;  vertical advection tendencies.  
+!
+!-----------------------------------------------------------------------
+
+module OcnTracerVadvStencil
+
+   use grid_types
+   use configure
+
+   use OcnTracerVadvStencil2
+   use OcnTracerVadvStencil3
+   use OcnTracerVadvStencil4
+
+   implicit none
+   private
+   save
+
+   !--------------------------------------------------------------------
+   !
+   ! Public parameters
+   !
+   !--------------------------------------------------------------------
+
+   !--------------------------------------------------------------------
+   !
+   ! Public member functions
+   !
+   !--------------------------------------------------------------------
+
+   public :: OcnTracerVadvStencilTend, &amp;
+             OcnTracerVadvStencilInit
+
+   !--------------------------------------------------------------------
+   !
+   ! Private module variables
+   !
+   !--------------------------------------------------------------------
+
+   logical :: stencilOn
+
+
+!***********************************************************************
+
+contains
+
+!***********************************************************************
+!
+!  routine OcnTracerVadvStencilTend
+!
+!&gt; \brief   Computes tendency term for vertical tracer advection
+!&gt; \author  Phil Jones, Doug Jacobsen
+!&gt; \date    15 September 2011
+!&gt; \version SVN:$Id$
+!&gt; \details 
+!&gt;  This routine computes the vertical advection tendency for tracer
+!&gt;  based on current state and user choices of advection parameterization.
+!&gt;  Multiple parameterizations may be chosen and added together.  These
+!&gt;  tendencies are generally computed by calling the specific routine
+!&gt;  for the chosen parameterization, so this routine is primarily a
+!&gt;  driver for managing these choices.
+!
+!-----------------------------------------------------------------------
+
+   subroutine OcnTracerVadvStencilTend(grid, wTop, tracers, tend, err)
+
+      !-----------------------------------------------------------------
+      !
+      ! input variables
+      !
+      !-----------------------------------------------------------------
+
+      real (kind=RKIND), dimension(:,:), intent(in) :: &amp;
+         wTop    !&lt; Input: vertical velocity in top layer
+
+      real (kind=RKIND), dimension(:,:,:), intent(in) :: &amp;
+         tracers     !&lt; Input: tracers
+
+      type (mesh_type), intent(in) :: &amp;
+         grid          !&lt; Input: grid information
+
+      !-----------------------------------------------------------------
+      !
+      ! input/output variables
+      !
+      !-----------------------------------------------------------------
+
+      real (kind=RKIND), dimension(:,:,:), intent(inout) :: &amp;
+         tend          !&lt; Input/Output: velocity tendency
+
+      !-----------------------------------------------------------------
+      !
+      ! output variables
+      !
+      !-----------------------------------------------------------------
+
+      integer, intent(out) :: err
+
+      !-----------------------------------------------------------------
+      !
+      ! local variables
+      !
+      !-----------------------------------------------------------------
+
+      integer :: err1, err2, err3
+
+      !-----------------------------------------------------------------
+      !
+      ! call relevant routines for computing tendencies
+      ! note that the user can choose multiple options and the 
+      !   tendencies will be added together
+      !
+      !-----------------------------------------------------------------
+
+      err = 0
+
+      if(.not. stencilOn) return
+
+      call OcnTracerVadvStencil2Tend(grid, wTop, tracers, tend, err1)
+      call OcnTracerVadvStencil3Tend(grid, wTop, tracers, tend, err1)
+      call OcnTracerVadvStencil4Tend(grid, wTop, tracers, tend, err1)
+
+      err = err1 .or. err2 .or. err3
+
+   !--------------------------------------------------------------------
+
+   end subroutine OcnTracerVadvStencilTend
+
+!***********************************************************************
+!
+!  routine OcnTracerVadvStencilInit
+!
+!&gt; \brief   Initializes ocean tracer vertical advection quantities
+!&gt; \author  Phil Jones, Doug Jacobsen
+!&gt; \date    15 September 2011
+!&gt; \version SVN:$Id$
+!&gt; \details 
+!&gt;  This routine initializes a variety of quantities related to 
+!&gt;  vertical velocity advection in the ocean. Since a variety of 
+!&gt;  parameterizations are available, this routine primarily calls the
+!&gt;  individual init routines for each parameterization. 
+!
+!-----------------------------------------------------------------------
+
+
+   subroutine OcnTracerVadvStencilInit(err)
+
+   !--------------------------------------------------------------------
+
+      !-----------------------------------------------------------------
+      !
+      ! call individual init routines for each parameterization
+      !
+      !-----------------------------------------------------------------
+
+      integer, intent(out) :: err
+
+      integer :: err1, err2, err3
+
+      err = 0
+
+      stencilOn = .false.
+
+      if (config_vert_tracer_adv.eq.'stencil') then
+         stencilOn = .true.
+
+         call OcnTracerVadvStencil2Init(err1)
+         call OcnTracerVadvStencil3Init(err2)
+         call OcnTracerVadvStencil4Init(err3)
+
+         err = err1 .or. err2 .or. err3
+      endif
+
+   !--------------------------------------------------------------------
+
+   end subroutine OcnTracerVadvStencilInit
+
+!***********************************************************************
+
+end module OcnTracerVadvStencil
+
+!|||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||

Added: branches/ocean_projects/performance/src/core_ocean/module_OcnTracerVadvStencil2.F
===================================================================
--- branches/ocean_projects/performance/src/core_ocean/module_OcnTracerVadvStencil2.F                                (rev 0)
+++ branches/ocean_projects/performance/src/core_ocean/module_OcnTracerVadvStencil2.F        2011-09-16 21:57:58 UTC (rev 1007)
@@ -0,0 +1,218 @@
+!|||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
+!
+!  OcnTracerVadvStencil2
+!
+!&gt; \brief MPAS ocean vertical tracer advection driver
+!&gt; \author Doug Jacobsen
+!&gt; \date   16 September 2011
+!&gt; \version SVN:$Id:$
+!&gt; \details
+!&gt;  This module contains the main driver routine for computing 
+!&gt;  vertical advection tendencies.  
+!
+!-----------------------------------------------------------------------
+
+module OcnTracerVadvStencil2
+
+   use grid_types
+   use configure
+   use timer
+
+   implicit none
+   private
+   save
+
+   !--------------------------------------------------------------------
+   !
+   ! Public parameters
+   !
+   !--------------------------------------------------------------------
+
+   !--------------------------------------------------------------------
+   !
+   ! Public member functions
+   !
+   !--------------------------------------------------------------------
+
+   public :: OcnTracerVadvStencil2Tend, &amp;
+             OcnTracerVadvStencil2Init
+
+   !--------------------------------------------------------------------
+   !
+   ! Private module variables
+   !
+   !--------------------------------------------------------------------
+
+   logical :: stencil2On
+
+
+!***********************************************************************
+
+contains
+
+!***********************************************************************
+!
+!  routine OcnTracerVadvStencil2Tend
+!
+!&gt; \brief   Computes tendency term for vertical tracer advection
+!&gt; \author  Phil Jones, Doug Jacobsen
+!&gt; \date    15 September 2011
+!&gt; \version SVN:$Id$
+!&gt; \details 
+!&gt;  This routine computes the vertical advection tendency for tracer
+!&gt;  based on current state and user choices of advection parameterization.
+!&gt;  Multiple parameterizations may be chosen and added together.  These
+!&gt;  tendencies are generally computed by calling the specific routine
+!&gt;  for the chosen parameterization, so this routine is primarily a
+!&gt;  driver for managing these choices.
+!
+!-----------------------------------------------------------------------
+
+   subroutine OcnTracerVadvStencil2Tend(grid, wTop, tracers, tend, err)
+
+      !-----------------------------------------------------------------
+      !
+      ! input variables
+      !
+      !-----------------------------------------------------------------
+
+      real (kind=RKIND), dimension(:,:), intent(in) :: &amp;
+         wTop    !&lt; Input: vertical velocity in top layer
+
+      real (kind=RKIND), dimension(:,:,:), intent(in) :: &amp;
+         tracers     !&lt; Input: tracers
+
+      type (mesh_type), intent(in) :: &amp;
+         grid          !&lt; Input: grid information
+
+      !-----------------------------------------------------------------
+      !
+      ! input/output variables
+      !
+      !-----------------------------------------------------------------
+
+      real (kind=RKIND), dimension(:,:,:), intent(inout) :: &amp;
+         tend          !&lt; Input/Output: velocity tendency
+
+      !-----------------------------------------------------------------
+      !
+      ! output variables
+      !
+      !-----------------------------------------------------------------
+
+      integer, intent(out) :: err
+
+      !-----------------------------------------------------------------
+      !
+      ! local variables
+      !
+      !-----------------------------------------------------------------
+
+      integer :: nCellsSolve, iCell, k, iTracer, num_tracers, nVertLevels
+      integer :: nCells
+
+      integer, dimension(:), pointer :: maxLevelCell
+
+      real (kind=RKIND), dimension(:,:,:), allocatable :: tracerTop
+
+
+      !-----------------------------------------------------------------
+      !
+      ! call relevant routines for computing tendencies
+      ! note that the user can choose multiple options and the 
+      !   tendencies will be added together
+      !
+      !-----------------------------------------------------------------
+
+      err = 0
+
+      if(.not. stencil2On) return
+
+
+      call timer_start(&quot;compute_scalar_tend-vert adv stencil 2&quot;)
+
+      nCells = grid % nCells
+      nCellsSolve = grid % nCellsSolve
+      num_tracers = size(tracers, 1)
+      nVertLevels = grid % nVertLevels
+      maxLevelCell =&gt; grid % maxLevelCell % array
+
+      allocate(tracerTop(num_tracers,nVertLevels+1,nCells))
+
+      ! Compute tracerTop using centered stencil, a simple average.
+
+      do iCell=1,nCellsSolve 
+         do k=2,maxLevelCell(iCell)
+            do iTracer=1,num_tracers
+               tracerTop(iTracer,k,iCell) = &amp;
+                  ( tracers(iTracer,k-1,iCell) &amp;
+                   +tracers(iTracer,k  ,iCell))/2.0
+            end do
+         end do
+      end do
+
+      do iCell=1,nCellsSolve 
+         do k=1,maxLevelCell(iCell)  
+            do iTracer=1,num_tracers
+               tend(iTracer,k,iCell) = tend(iTracer,k,iCell) &amp;
+                  - (   wTop(k  ,iCell)*tracerTop(iTracer,k  ,iCell) &amp;
+                      - wTop(k+1,iCell)*tracerTop(iTracer,k+1,iCell))
+            end do
+         end do
+      end do
+
+      deallocate(tracerTop)
+      call timer_stop(&quot;compute_scalar_tend-vert adv stencil 2&quot;)
+
+   !--------------------------------------------------------------------
+
+   end subroutine OcnTracerVadvStencil2Tend
+
+!***********************************************************************
+!
+!  routine OcnTracerVadvStencil2Init
+!
+!&gt; \brief   Initializes ocean tracer vertical advection quantities
+!&gt; \author  Phil Jones, Doug Jacobsen
+!&gt; \date    15 September 2011
+!&gt; \version SVN:$Id$
+!&gt; \details 
+!&gt;  This routine initializes a variety of quantities related to 
+!&gt;  vertical velocity advection in the ocean. Since a variety of 
+!&gt;  parameterizations are available, this routine primarily calls the
+!&gt;  individual init routines for each parameterization. 
+!
+!-----------------------------------------------------------------------
+
+
+   subroutine OcnTracerVadvStencil2Init(err)
+
+   !--------------------------------------------------------------------
+
+      !-----------------------------------------------------------------
+      !
+      ! call individual init routines for each parameterization
+      !
+      !-----------------------------------------------------------------
+
+      integer, intent(out) :: err
+
+      integer :: err1, err2, err3
+
+      err = 0
+      stencil2On = .false.
+
+      if(config_vert_tracer_adv_order.eq.2) then
+          stencil2On = .true.
+      endif
+
+
+   !--------------------------------------------------------------------
+
+   end subroutine OcnTracerVadvStencil2Init
+
+!***********************************************************************
+
+end module OcnTracerVadvStencil2
+
+!|||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||

Added: branches/ocean_projects/performance/src/core_ocean/module_OcnTracerVadvStencil3.F
===================================================================
--- branches/ocean_projects/performance/src/core_ocean/module_OcnTracerVadvStencil3.F                                (rev 0)
+++ branches/ocean_projects/performance/src/core_ocean/module_OcnTracerVadvStencil3.F        2011-09-16 21:57:58 UTC (rev 1007)
@@ -0,0 +1,239 @@
+!|||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
+!
+!  OcnTracerVadvStencil3
+!
+!&gt; \brief MPAS ocean vertical tracer advection driver
+!&gt; \author Doug Jacobsen
+!&gt; \date   16 September 2011
+!&gt; \version SVN:$Id:$
+!&gt; \details
+!&gt;  This module contains the main driver routine for computing 
+!&gt;  vertical advection tendencies.  
+!
+!-----------------------------------------------------------------------
+
+module OcnTracerVadvStencil3
+
+   use grid_types
+   use configure
+   use timer
+
+   implicit none
+   private
+   save
+
+   !--------------------------------------------------------------------
+   !
+   ! Public parameters
+   !
+   !--------------------------------------------------------------------
+
+   !--------------------------------------------------------------------
+   !
+   ! Public member functions
+   !
+   !--------------------------------------------------------------------
+
+   public :: OcnTracerVadvStencil3Tend, &amp;
+             OcnTracerVadvStencil3Init
+
+   !--------------------------------------------------------------------
+   !
+   ! Private module variables
+   !
+   !--------------------------------------------------------------------
+
+   logical :: stencil3On
+
+
+!***********************************************************************
+
+contains
+
+!***********************************************************************
+!
+!  routine OcnTracerVadvStencil3Tend
+!
+!&gt; \brief   Computes tendency term for vertical tracer advection
+!&gt; \author  Phil Jones, Doug Jacobsen
+!&gt; \date    15 September 2011
+!&gt; \version SVN:$Id$
+!&gt; \details 
+!&gt;  This routine computes the vertical advection tendency for tracer
+!&gt;  based on current state and user choices of advection parameterization.
+!&gt;  Multiple parameterizations may be chosen and added together.  These
+!&gt;  tendencies are generally computed by calling the specific routine
+!&gt;  for the chosen parameterization, so this routine is primarily a
+!&gt;  driver for managing these choices.
+!
+!-----------------------------------------------------------------------
+
+   subroutine OcnTracerVadvStencil3Tend(grid, wTop, tracers, tend, err)
+
+      !-----------------------------------------------------------------
+      !
+      ! input variables
+      !
+      !-----------------------------------------------------------------
+
+      real (kind=RKIND), dimension(:,:), intent(in) :: &amp;
+         wTop    !&lt; Input: vertical velocity in top layer
+
+      real (kind=RKIND), dimension(:,:,:), intent(in) :: &amp;
+         tracers     !&lt; Input: tracers
+
+      type (mesh_type), intent(in) :: &amp;
+         grid          !&lt; Input: grid information
+
+      !-----------------------------------------------------------------
+      !
+      ! input/output variables
+      !
+      !-----------------------------------------------------------------
+
+      real (kind=RKIND), dimension(:,:,:), intent(inout) :: &amp;
+         tend          !&lt; Input/Output: velocity tendency
+
+      !-----------------------------------------------------------------
+      !
+      ! output variables
+      !
+      !-----------------------------------------------------------------
+
+      integer, intent(out) :: err
+
+      !-----------------------------------------------------------------
+      !
+      ! local variables
+      !
+      !-----------------------------------------------------------------
+
+      integer :: nCellsSolve, iCell, k, iTracer, num_tracers, nVertLevels
+      integer :: nCells
+
+      integer, dimension(:), pointer :: maxLevelCell
+
+      real (kind=RKIND) :: cSignWTop, flux3Coef
+      real (kind=RKIND), dimension(:), pointer :: hRatioZLevelK, hRatioZLevelKm1
+      real (kind=RKIND), dimension(:,:,:), allocatable :: tracerTop
+
+
+      !-----------------------------------------------------------------
+      !
+      ! call relevant routines for computing tendencies
+      ! note that the user can choose multiple options and the 
+      !   tendencies will be added together
+      !
+      !-----------------------------------------------------------------
+
+      err = 0
+
+      if(.not. stencil3On) return
+
+      nCells = grid % nCells
+      nCellsSolve = grid % nCellsSolve
+      num_tracers = size(tracers, 1)
+      nVertLevels = grid % nVertLevels
+      maxLevelCell =&gt; grid % maxLevelCell % array
+      hRatioZLevelK =&gt; grid % hRatioZLevelK % array
+      hRatioZLevelKm1 =&gt; grid % hRatioZLevelKm1 % array
+
+      call timer_start(&quot;compute_scalar_tend-vert adv stencil 3&quot;)
+
+      allocate(tracerTop(num_tracers,nVertLevels+1,nCells))
+
+      ! Compute tracerTop using 3rd order stencil.  This is the same
+      ! as 4th order, but includes upwinding.
+
+      ! Hardwire flux3Coeff at 1.0 for now.  Could add this to the 
+      ! namelist, if desired.
+      flux3Coef = 1.0
+      do iCell=1,nCellsSolve 
+         k=2
+         do iTracer=1,num_tracers
+           tracerTop(iTracer,k,iCell) = &amp;
+                hRatioZLevelK(k)  *tracers(iTracer,k-1,iCell) &amp;
+              + hRatioZLevelKm1(k)*tracers(iTracer,k  ,iCell)
+         end do
+         do k=3,maxLevelCell(iCell)-1
+            cSignWTop = sign(flux3Coef,wTop(k,iCell))
+            do iTracer=1,num_tracers
+               tracerTop(iTracer,k,iCell) = &amp;
+                  ( (-1.+   cSignWTop)*tracers(iTracer,k-2,iCell) &amp;
+                   +( 7.-3.*cSignWTop)*tracers(iTracer,k-1,iCell) &amp;
+                   +( 7.+3.*cSignWTop)*tracers(iTracer,k  ,iCell) &amp;
+                   +(-1.-   cSignWTop)*tracers(iTracer,k+1,iCell) &amp;
+                  )/12.
+            end do
+         end do
+         k=maxLevelCell(iCell)
+            do iTracer=1,num_tracers
+              tracerTop(iTracer,k,iCell) = &amp;
+                   hRatioZLevelK(k)  *tracers(iTracer,k-1,iCell) &amp;
+                 + hRatioZLevelKm1(k)*tracers(iTracer,k  ,iCell)
+            end do
+      end do
+
+      do iCell=1,nCellsSolve 
+         do k=1,maxLevelCell(iCell)  
+            do iTracer=1,num_tracers
+               tend(iTracer,k,iCell) = tend(iTracer,k,iCell) &amp;
+                  - (   wTop(k  ,iCell)*tracerTop(iTracer,k  ,iCell) &amp;
+                      - wTop(k+1,iCell)*tracerTop(iTracer,k+1,iCell))
+            end do
+         end do
+      end do
+
+      deallocate(tracerTop)
+      call timer_stop(&quot;compute_scalar_tend-vert adv stencil 3&quot;)
+
+   !--------------------------------------------------------------------
+
+   end subroutine OcnTracerVadvStencil3Tend
+
+!***********************************************************************
+!
+!  routine OcnTracerVadvStencil3Init
+!
+!&gt; \brief   Initializes ocean tracer vertical advection quantities
+!&gt; \author  Phil Jones, Doug Jacobsen
+!&gt; \date    15 September 2011
+!&gt; \version SVN:$Id$
+!&gt; \details 
+!&gt;  This routine initializes a variety of quantities related to 
+!&gt;  vertical velocity advection in the ocean. Since a variety of 
+!&gt;  parameterizations are available, this routine primarily calls the
+!&gt;  individual init routines for each parameterization. 
+!
+!-----------------------------------------------------------------------
+
+
+   subroutine OcnTracerVadvStencil3Init(err)
+
+   !--------------------------------------------------------------------
+
+      !-----------------------------------------------------------------
+      !
+      ! call individual init routines for each parameterization
+      !
+      !-----------------------------------------------------------------
+
+      integer, intent(out) :: err
+
+      err = 0
+      stencil3On = .false.
+
+      if(config_vert_tracer_adv_order.eq.3) then
+          stencil3On = .true.
+      endif
+
+
+   !--------------------------------------------------------------------
+
+   end subroutine OcnTracerVadvStencil3Init
+
+!***********************************************************************
+
+end module OcnTracerVadvStencil3
+
+!|||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||

Added: branches/ocean_projects/performance/src/core_ocean/module_OcnTracerVadvStencil4.F
===================================================================
--- branches/ocean_projects/performance/src/core_ocean/module_OcnTracerVadvStencil4.F                                (rev 0)
+++ branches/ocean_projects/performance/src/core_ocean/module_OcnTracerVadvStencil4.F        2011-09-16 21:57:58 UTC (rev 1007)
@@ -0,0 +1,234 @@
+!|||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
+!
+!  OcnTracerVadvStencil4
+!
+!&gt; \brief MPAS ocean vertical tracer advection driver
+!&gt; \author Doug Jacobsen
+!&gt; \date   16 September 2011
+!&gt; \version SVN:$Id:$
+!&gt; \details
+!&gt;  This module contains the main driver routine for computing 
+!&gt;  vertical advection tendencies.  
+!
+!-----------------------------------------------------------------------
+
+module OcnTracerVadvStencil4
+
+   use grid_types
+   use configure
+   use timer
+
+   implicit none
+   private
+   save
+
+   !--------------------------------------------------------------------
+   !
+   ! Public parameters
+   !
+   !--------------------------------------------------------------------
+
+   !--------------------------------------------------------------------
+   !
+   ! Public member functions
+   !
+   !--------------------------------------------------------------------
+
+   public :: OcnTracerVadvStencil4Tend, &amp;
+             OcnTracerVadvStencil4Init
+
+   !--------------------------------------------------------------------
+   !
+   ! Private module variables
+   !
+   !--------------------------------------------------------------------
+
+   logical :: stencil4On
+
+
+!***********************************************************************
+
+contains
+
+!***********************************************************************
+!
+!  routine OcnTracerVadvStencil4Tend
+!
+!&gt; \brief   Computes tendency term for vertical tracer advection
+!&gt; \author  Phil Jones, Doug Jacobsen
+!&gt; \date    15 September 2011
+!&gt; \version SVN:$Id$
+!&gt; \details 
+!&gt;  This routine computes the vertical advection tendency for tracer
+!&gt;  based on current state and user choices of advection parameterization.
+!&gt;  Multiple parameterizations may be chosen and added together.  These
+!&gt;  tendencies are generally computed by calling the specific routine
+!&gt;  for the chosen parameterization, so this routine is primarily a
+!&gt;  driver for managing these choices.
+!
+!-----------------------------------------------------------------------
+
+   subroutine OcnTracerVadvStencil4Tend(grid, wTop, tracers, tend, err)
+
+      !-----------------------------------------------------------------
+      !
+      ! input variables
+      !
+      !-----------------------------------------------------------------
+
+      real (kind=RKIND), dimension(:,:), intent(in) :: &amp;
+         wTop    !&lt; Input: vertical velocity in top layer
+
+      real (kind=RKIND), dimension(:,:,:), intent(in) :: &amp;
+         tracers     !&lt; Input: tracers
+
+      type (mesh_type), intent(in) :: &amp;
+         grid          !&lt; Input: grid information
+
+      !-----------------------------------------------------------------
+      !
+      ! input/output variables
+      !
+      !-----------------------------------------------------------------
+
+      real (kind=RKIND), dimension(:,:,:), intent(inout) :: &amp;
+         tend          !&lt; Input/Output: velocity tendency
+
+      !-----------------------------------------------------------------
+      !
+      ! output variables
+      !
+      !-----------------------------------------------------------------
+
+      integer, intent(out) :: err
+
+      !-----------------------------------------------------------------
+      !
+      ! local variables
+      !
+      !-----------------------------------------------------------------
+
+      integer :: nCellsSolve, iCell, k, iTracer, num_tracers, nVertLevels
+      integer :: nCells
+
+      integer, dimension(:), pointer :: maxLevelCell
+
+      real (kind=RKIND) :: cSingWTop, flux3Coef
+      real (kind=RKIND), dimension(:), pointer :: hRatioZLevelK, hRatioZLevelKm1
+      real (kind=RKIND), dimension(:,:,:), allocatable :: tracerTop
+
+
+      !-----------------------------------------------------------------
+      !
+      ! call relevant routines for computing tendencies
+      ! note that the user can choose multiple options and the 
+      !   tendencies will be added together
+      !
+      !-----------------------------------------------------------------
+
+      err = 0
+
+      if(.not. Stencil4On) return
+
+      call timer_start(&quot;compute_scalar_tend-vert adv stencil 4&quot;)
+
+      nCells = grid % nCells
+      nCellsSolve = grid % nCellsSolve
+      num_tracers = size(tracers, 1)
+      nVertLevels = grid % nVertLevels
+      maxLevelCell =&gt; grid % maxLevelCell % array
+      hRatioZLevelK =&gt; grid % hRatioZLevelK % array
+      hRatioZLevelKm1 =&gt; grid % hRatioZLevelKm1 % array
+
+      allocate(tracerTop(num_tracers,nVertLevels+1,nCells))
+
+      ! Compute tracerTop using 4rd order stencil [-1 7 7 -1]
+
+      do iCell=1,nCellsSolve 
+         k=2
+            do iTracer=1,num_tracers
+              tracerTop(iTracer,k,iCell) = &amp;
+                   hRatioZLevelK(k)  *tracers(iTracer,k-1,iCell) &amp;
+                 + hRatioZLevelKm1(k)*tracers(iTracer,k  ,iCell)
+            end do
+         do k=3,maxLevelCell(iCell)-1
+            do iTracer=1,num_tracers
+               tracerTop(iTracer,k,iCell) = &amp;
+                  (-   tracers(iTracer,k-2,iCell) &amp;
+                   +7.*tracers(iTracer,k-1,iCell) &amp;
+                   +7.*tracers(iTracer,k  ,iCell) &amp;
+                   -   tracers(iTracer,k+1,iCell) &amp;
+                  )/12.
+            end do
+         end do
+         k=maxLevelCell(iCell)
+            do iTracer=1,num_tracers
+              tracerTop(iTracer,k,iCell) = &amp;
+                   hRatioZLevelK(k)  *tracers(iTracer,k-1,iCell) &amp;
+                 + hRatioZLevelKm1(k)*tracers(iTracer,k  ,iCell)
+            end do
+      end do
+
+      do iCell=1,nCellsSolve 
+         do k=1,maxLevelCell(iCell)  
+            do iTracer=1,num_tracers
+               tend(iTracer,k,iCell) = tend(iTracer,k,iCell) &amp;
+                      - (   wTop(k  ,iCell)*tracerTop(iTracer,k  ,iCell) &amp;
+                      - wTop(k+1,iCell)*tracerTop(iTracer,k+1,iCell))
+            end do
+         end do
+      end do
+
+      deallocate(tracerTop)
+      call timer_stop(&quot;compute_scalar_tend-vert adv stencil 4&quot;)
+
+   !--------------------------------------------------------------------
+
+   end subroutine OcnTracerVadvStencil4Tend
+
+!***********************************************************************
+!
+!  routine OcnTracerVadvStencil4Init
+!
+!&gt; \brief   Initializes ocean tracer vertical advection quantities
+!&gt; \author  Phil Jones, Doug Jacobsen
+!&gt; \date    15 September 2011
+!&gt; \version SVN:$Id$
+!&gt; \details 
+!&gt;  This routine initializes a variety of quantities related to 
+!&gt;  vertical velocity advection in the ocean. Since a variety of 
+!&gt;  parameterizations are available, this routine primarily calls the
+!&gt;  individual init routines for each parameterization. 
+!
+!-----------------------------------------------------------------------
+
+
+   subroutine OcnTracerVadvStencil4Init(err)
+
+   !--------------------------------------------------------------------
+
+      !-----------------------------------------------------------------
+      !
+      ! call individual init routines for each parameterization
+      !
+      !-----------------------------------------------------------------
+
+      integer, intent(out) :: err
+
+      err = 0
+      stencil4On = .false.
+
+      if(config_vert_tracer_adv_order.eq.4) then
+          stencil4On = .true.
+      endif
+
+
+   !--------------------------------------------------------------------
+
+   end subroutine OcnTracerVadvStencil4Init
+
+!***********************************************************************
+
+end module OcnTracerVadvStencil4
+
+!|||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||

Modified: branches/ocean_projects/performance/src/core_ocean/module_mpas_core.F
===================================================================
--- branches/ocean_projects/performance/src/core_ocean/module_mpas_core.F        2011-09-16 19:27:37 UTC (rev 1006)
+++ branches/ocean_projects/performance/src/core_ocean/module_mpas_core.F        2011-09-16 21:57:58 UTC (rev 1007)
@@ -10,6 +10,9 @@
    use OcnVelHmix
    use OcnVelForcing
 
+   use OcnTracerHadv
+   use OcnTracerVadv
+
    type (io_output_object) :: restart_obj
    integer :: restart_frame
 
@@ -81,6 +84,9 @@
       call OcnVelHmixInit(err)
       call OcnVelForcingInit(err)
 
+      call OcnTracerHadvInit(err)
+      call OcnTracerVadvInit(err)
+
    ! mrp 100316 In order for this to work, we need to pass domain % dminfo as an 
    ! input arguement into mpas_init.  Ask about that later.  For now, there will be
    ! no initial statistics write.

Modified: branches/ocean_projects/performance/src/core_ocean/module_time_integration.F
===================================================================
--- branches/ocean_projects/performance/src/core_ocean/module_time_integration.F        2011-09-16 19:27:37 UTC (rev 1006)
+++ branches/ocean_projects/performance/src/core_ocean/module_time_integration.F        2011-09-16 21:57:58 UTC (rev 1007)
@@ -17,6 +17,9 @@
    use OcnVelHmix
    use OcnVelForcing
 
+   use OcnTracerHadv
+   use OcnTracerVadv
+
    contains
 
    subroutine timestep(domain, dt, timeStamp)!{{{
@@ -2256,7 +2259,7 @@
       type (mesh_type), intent(in) :: grid
 
       integer :: i, k, iCell, iEdge, iTracer, cell1, cell2, upwindCell,&amp;
-        nEdges, nCells, nCellsSolve, nVertLevels, num_tracers
+        nEdges, nCells, nCellsSolve, nVertLevels, num_tracers, err
       real (kind=RKIND) :: invAreaCell1, invAreaCell2, tracer_turb_flux
       real (kind=RKIND) :: flux, tracer_edge, r
       real (kind=RKIND), dimension(:), pointer :: &amp;
@@ -2344,129 +2347,9 @@
       ! tracer_edge at the boundary will also need to be defined for flux boundaries.
 
       call timer_start(&quot;compute_scalar_tend-horiz adv&quot;)
-      coef_3rd_order = 0.
-      if (config_tracer_adv_order == 3) coef_3rd_order = 1.0
-      if (config_tracer_adv_order == 3 .and. config_monotonic) coef_3rd_order = 0.25
 
-      if (config_tracer_adv_order == 2) then
-          call timer_start(&quot;compute_scalar_tend-horiz adv 2&quot;)
+      call OcnTracerHadvTend(grid, u, h_edge, tracers, tend_tr, err)
 
-         do iEdge=1,nEdges
-            cell1 = cellsOnEdge(1,iEdge)
-            cell2 = cellsOnEdge(2,iEdge)
-            do k=1,maxLevelEdgeTop(iEdge)
-               do iTracer=1,num_tracers
-                  tracer_edge = 0.5 * (tracers(iTracer,k,cell1) + tracers(iTracer,k,cell2))
-                  flux = u(k,iEdge) * dvEdge(iEdge) * h_edge(k,iEdge) * tracer_edge
-                  tend_tr(iTracer,k,cell1) = tend_tr(iTracer,k,cell1) - flux/areaCell(cell1)
-                  tend_tr(iTracer,k,cell2) = tend_tr(iTracer,k,cell2) + flux/areaCell(cell2)
-               end do
-            end do
-         end do
-
-          call timer_stop(&quot;compute_scalar_tend-horiz adv 2&quot;)
-      else if (config_tracer_adv_order == 3) then
-          call timer_start(&quot;compute_scalar_tend-horiz adv 3&quot;)
-         do iEdge=1,nEdges
-            cell1 = cellsOnEdge(1,iEdge)
-            cell2 = cellsOnEdge(2,iEdge)
-
-            do k=1,maxLevelEdgeTop(iEdge)
-
-               d2fdx2_cell1 = 0.0
-               d2fdx2_cell2 = 0.0
-
-               do iTracer=1,num_tracers
-
-                  !-- if not a boundary cell
-                  if(boundaryCell(k,cell1).eq.0.and.boundaryCell(k,cell2).eq.0) then
-
-                     d2fdx2_cell1 = deriv_two(1,1,iEdge) * tracers(iTracer,k,cell1)
-                     d2fdx2_cell2 = deriv_two(1,2,iEdge) * tracers(iTracer,k,cell2)
-
-                     !-- all edges of cell 1
-                     do i=1, grid % nEdgesOnCell % array (cell1)
-                        d2fdx2_cell1 = d2fdx2_cell1 + &amp;
-                        deriv_two(i+1,1,iEdge) * tracers(iTracer,k,grid % CellsOnCell % array (i,cell1))
-                     end do
-
-                     !-- all edges of cell 2
-                     do i=1, grid % nEdgesOnCell % array (cell2)
-                        d2fdx2_cell2 = d2fdx2_cell2 + &amp;
-                        deriv_two(i+1,2,iEdge) * tracers(iTracer,k,grid % CellsOnCell % array (i,cell2))
-                     end do
-
-                  endif
-
-                  !-- if u &gt; 0:
-                  if (u(k,iEdge) &gt; 0) then
-                     flux = dvEdge(iEdge) * u(k,iEdge) * h_edge(k,iEdge) * (          &amp;
-                          0.5*(tracers(iTracer,k,cell1) + tracers(iTracer,k,cell2))      &amp;
-                          -(dcEdge(iEdge) **2) * (d2fdx2_cell1 + d2fdx2_cell2) / 12.          &amp;
-                          -(dcEdge(iEdge) **2) * coef_3rd_order*(d2fdx2_cell1 - d2fdx2_cell2) / 12. )
-                  !-- else u &lt;= 0:
-                  else
-                     flux = dvEdge(iEdge) *  u(k,iEdge) * h_edge(k,iEdge) * (          &amp;
-                          0.5*(tracers(iTracer,k,cell1) + tracers(iTracer,k,cell2))      &amp;
-                          -(dcEdge(iEdge) **2) * (d2fdx2_cell1 + d2fdx2_cell2) / 12.          &amp;
-                          +(dcEdge(iEdge) **2) * coef_3rd_order*(d2fdx2_cell1 - d2fdx2_cell2) / 12. )
-                  end if
-
-                  !-- update tendency
-                  tend_tr(iTracer,k,cell1) = tend_tr(iTracer,k,cell1) - flux/areaCell(cell1)
-                  tend_tr(iTracer,k,cell2) = tend_tr(iTracer,k,cell2) + flux/areaCell(cell2)
-               enddo
-            end do
-         end do
-          call timer_stop(&quot;compute_scalar_tend-horiz adv 3&quot;)
-
-      else if (config_tracer_adv_order == 4) then
-          call timer_start(&quot;compute_scalar_tend-horiz adv 4&quot;)
-
-         do iEdge=1,nEdges
-            cell1 = cellsOnEdge(1,iEdge)
-            cell2 = cellsOnEdge(2,iEdge)
-
-            do k=1,maxLevelEdgeTop(iEdge)
-
-               d2fdx2_cell1 = 0.0
-               d2fdx2_cell2 = 0.0
-
-               do iTracer=1,num_tracers
-
-                  !-- if not a boundary cell
-                  if(boundaryCell(k,cell1).eq.0.and.boundaryCell(k,cell2).eq.0) then
-
-                     d2fdx2_cell1 = deriv_two(1,1,iEdge) * tracers(iTracer,k,cell1)
-                     d2fdx2_cell2 = deriv_two(1,2,iEdge) * tracers(iTracer,k,cell2)
-
-                     !-- all edges of cell 1
-                     do i=1, grid % nEdgesOnCell % array (cell1)
-                        d2fdx2_cell1 = d2fdx2_cell1 + &amp;
-                        deriv_two(i+1,1,iEdge) * tracers(iTracer,k,grid % CellsOnCell % array (i,cell1))
-                     end do
-
-                     !-- all edges of cell 2
-                     do i=1, grid % nEdgesOnCell % array (cell2)
-                         d2fdx2_cell2 = d2fdx2_cell2 + &amp;
-                         deriv_two(i+1,2,iEdge) * tracers(iTracer,k,grid % CellsOnCell % array (i,cell2))
-                     end do
-
-                  endif
-
-                  flux = dvEdge(iEdge) *  u(k,iEdge) * h_edge(k,iEdge) * (          &amp;
-                       0.5*(tracers(iTracer,k,cell1) + tracers(iTracer,k,cell2))      &amp;
-                          -(dcEdge(iEdge) **2) * (d2fdx2_cell1 + d2fdx2_cell2) / 12. )
-
-                  !-- update tendency
-                  tend_tr(iTracer,k,cell1) = tend_tr(iTracer,k,cell1) - flux/areaCell(cell1)
-                  tend_tr(iTracer,k,cell2) = tend_tr(iTracer,k,cell2) + flux/areaCell(cell2)
-               enddo
-            end do
-         end do
-          call timer_stop(&quot;compute_scalar_tend-horiz adv 4&quot;)
-
-      endif   ! if (config_tracer_adv_order == 2 )
       call timer_stop(&quot;compute_scalar_tend-horiz adv&quot;)
 
 
@@ -2475,189 +2358,9 @@
       !
 
       call timer_start(&quot;compute_scalar_tend-vert adv&quot;)
-      if (config_vert_grid_type.eq.'zlevel') then
 
-         allocate(tracerTop(num_tracers,nVertLevels+1,nCells))
+      call OcnTracerVadvTend(grid, wTop, tracers, tend_tr, err)
 
-         ! Tracers at the top and bottom boundary are assigned nearest 
-         ! cell-centered value, regardless of tracer interpolation method.
-         ! wTop=0 at top and bottom sets the boundary condition.
-         do iCell=1,nCellsSolve 
-            do iTracer=1,num_tracers
-               tracerTop(iTracer,1,iCell) = tracers(iTracer,1,iCell)
-               tracerTop(iTracer,maxLevelCell(iCell)+1,iCell) = &amp;
-               tracers(iTracer,maxLevelCell(iCell),iCell)
-            end do
-         end do
-
-         if (config_vert_tracer_adv.eq.'stencil'.and. &amp;
-             config_vert_tracer_adv_order.eq.2) then
-             call timer_start(&quot;compute_scalar_tend-vert adv stencil 2&quot;)
-
-            ! Compute tracerTop using centered stencil, a simple average.
-
-            do iCell=1,nCellsSolve 
-               do k=2,maxLevelCell(iCell)
-                  do iTracer=1,num_tracers
-                     tracerTop(iTracer,k,iCell) = &amp;
-                        ( tracers(iTracer,k-1,iCell) &amp;
-                         +tracers(iTracer,k  ,iCell))/2.0
-                  end do
-               end do
-            end do
-         
-             call timer_stop(&quot;compute_scalar_tend-vert adv stencil 2&quot;)
-         elseif (config_vert_tracer_adv.eq.'stencil'.and. &amp;
-             config_vert_tracer_adv_order.eq.3) then
-             call timer_start(&quot;compute_scalar_tend-vert adv stencil 3&quot;)
-
-            ! Compute tracerTop using 3rd order stencil.  This is the same
-            ! as 4th order, but includes upwinding.
-
-            ! Hardwire flux3Coeff at 1.0 for now.  Could add this to the 
-            ! namelist, if desired.
-            flux3Coef = 1.0
-            do iCell=1,nCellsSolve 
-               k=2
-               do iTracer=1,num_tracers
-                 tracerTop(iTracer,k,iCell) = &amp;
-                      hRatioZLevelK(k)  *tracers(iTracer,k-1,iCell) &amp;
-                    + hRatioZLevelKm1(k)*tracers(iTracer,k  ,iCell)
-               end do
-               do k=3,maxLevelCell(iCell)-1
-                  cSignWTop = sign(flux3Coef,wTop(k,iCell))
-                  do iTracer=1,num_tracers
-                     tracerTop(iTracer,k,iCell) = &amp;
-                        ( (-1.+   cSignWTop)*tracers(iTracer,k-2,iCell) &amp;
-                         +( 7.-3.*cSignWTop)*tracers(iTracer,k-1,iCell) &amp;
-                         +( 7.+3.*cSignWTop)*tracers(iTracer,k  ,iCell) &amp;
-                         +(-1.-   cSignWTop)*tracers(iTracer,k+1,iCell) &amp;
-                        )/12.
-                  end do
-               end do
-               k=maxLevelCell(iCell)
-                  do iTracer=1,num_tracers
-                    tracerTop(iTracer,k,iCell) = &amp;
-                         hRatioZLevelK(k)  *tracers(iTracer,k-1,iCell) &amp;
-                       + hRatioZLevelKm1(k)*tracers(iTracer,k  ,iCell)
-                  end do
-            end do
-
-             call timer_stop(&quot;compute_scalar_tend-vert adv stencil 3&quot;)
-         elseif (config_vert_tracer_adv.eq.'stencil'.and. &amp;
-             config_vert_tracer_adv_order.eq.4) then
-             call timer_start(&quot;compute_scalar_tend-vert adv stencil 4&quot;)
-
-            ! Compute tracerTop using 4rd order stencil [-1 7 7 -1]
-
-            do iCell=1,nCellsSolve 
-               k=2
-                  do iTracer=1,num_tracers
-                    tracerTop(iTracer,k,iCell) = &amp;
-                         hRatioZLevelK(k)  *tracers(iTracer,k-1,iCell) &amp;
-                       + hRatioZLevelKm1(k)*tracers(iTracer,k  ,iCell)
-                  end do
-               do k=3,maxLevelCell(iCell)-1
-                  do iTracer=1,num_tracers
-                     tracerTop(iTracer,k,iCell) = &amp;
-                        (-   tracers(iTracer,k-2,iCell) &amp;
-                         +7.*tracers(iTracer,k-1,iCell) &amp;
-                         +7.*tracers(iTracer,k  ,iCell) &amp;
-                         -   tracers(iTracer,k+1,iCell) &amp;
-                        )/12.
-                  end do
-               end do
-               k=maxLevelCell(iCell)
-                  do iTracer=1,num_tracers
-                    tracerTop(iTracer,k,iCell) = &amp;
-                         hRatioZLevelK(k)  *tracers(iTracer,k-1,iCell) &amp;
-                       + hRatioZLevelKm1(k)*tracers(iTracer,k  ,iCell)
-                  end do
-            end do
-
-         elseif (config_vert_tracer_adv.eq.'spline'.and. &amp;
-             config_vert_tracer_adv_order.eq.2) then
-
-            ! Compute tracerTop using linear interpolation.
-
-            do iCell=1,nCellsSolve 
-               do k=2,maxLevelCell(iCell)
-                  do iTracer=1,num_tracers
-                     ! Note hRatio on the k side is multiplied by tracer at k-1
-                     ! and hRatio on the Km1 (k-1) side is mult. by tracer at k.
-                     tracerTop(iTracer,k,iCell) = &amp;
-                          hRatioZLevelK(k)  *tracers(iTracer,k-1,iCell) &amp;
-                        + hRatioZLevelKm1(k)*tracers(iTracer,k  ,iCell)
-                  end do
-               end do
-            end do
-         
-             call timer_stop(&quot;compute_scalar_tend-vert adv stencil 4&quot;)
-         elseif (config_vert_tracer_adv.eq.'spline'.and. &amp;
-             config_vert_tracer_adv_order.eq.3) then
-
-             call timer_start(&quot;compute_scalar_tend-vert adv spline 3&quot;)
-            ! Compute tracerTop using cubic spline interpolation.
-
-            allocate(tracer2ndDer(nVertLevels))
-            allocate(tracersIn(nVertLevels),tracersOut(nVertLevels), &amp;
-               posZMidZLevel(nVertLevels), posZTopZLevel(nVertLevels-1))
-
-            ! For the ocean, zlevel coordinates are negative and decreasing, 
-            ! but spline functions assume increasing, so flip to positive.
-
-            posZMidZLevel = -zMidZLevel(1:nVertLevels)
-            posZTopZLevel = -zTopZLevel(2:nVertLevels)
-
-            do iCell=1,nCellsSolve 
-               ! mrp 110201 efficiency note: push tracer loop down
-               ! into spline subroutines to improve efficiency
-               do iTracer=1,num_tracers
-
-                  ! Place data in arrays to avoid creating new temporary arrays for every 
-                  ! subroutine call.  
-                  tracersIn(1:maxLevelCell(iCell))=tracers(iTracer,1:maxLevelCell(iCell),iCell)
-
-                  call CubicSplineCoefficients(posZMidZLevel, &amp;
-                     tracersIn, maxLevelCell(iCell), tracer2ndDer)
-
-                  call InterpolateCubicSpline( &amp;
-                     posZMidZLevel, tracersIn, tracer2ndDer, maxLevelCell(iCell), &amp;
-                     posZTopZLevel, tracersOut, maxLevelCell(iCell)-1 )
-
-                  tracerTop(iTracer,2:maxLevelCell(iCell),iCell) = tracersOut(1:maxLevelCell(iCell)-1)
-
-               end do
-            end do
-
-            deallocate(tracer2ndDer)
-            deallocate(tracersIn,tracersOut, posZMidZLevel, posZTopZLevel)
-             call timer_stop(&quot;compute_scalar_tend-vert adv spline 3&quot;)
-
-        else
-
-            print *, 'Abort: Incorrect combination of ', &amp;
-              'config_vert_tracer_adv and config_vert_tracer_adv_order.'
-            print *, 'Use:'
-            print *, 'config_vert_tracer_adv=''stencil'' and config_vert_tracer_adv_order=2,3,4 or'
-            print *, 'config_vert_tracer_adv=''spline''  and config_vert_tracer_adv_order=2,3'
-            call dmpar_abort(dminfo)
-
-         endif ! vertical tracer advection method
-
-         do iCell=1,nCellsSolve 
-            do k=1,maxLevelCell(iCell)  
-               do iTracer=1,num_tracers
-                  tend_tr(iTracer,k,iCell) = tend_tr(iTracer,k,iCell) &amp;
-                     - (   wTop(k  ,iCell)*tracerTop(iTracer,k  ,iCell) &amp;
-                         - wTop(k+1,iCell)*tracerTop(iTracer,k+1,iCell))
-               end do
-            end do
-         end do
-
-         deallocate(tracerTop)
-
-      endif ! ZLevel
       call timer_stop(&quot;compute_scalar_tend-vert adv&quot;)
 
       !

</font>
</pre>