<p><b>ringler@lanl.gov</b> 2012-03-22 16:53:57 -0600 (Thu, 22 Mar 2012)</p><p><br>
a branch for prototyping and testing various turbulence closures<br>
</p><hr noshade><pre><font color="gray">Modified: branches/ocean_projects/closure/src/core_ocean/Makefile
===================================================================
--- trunk/mpas/src/core_ocean/Makefile        2012-03-22 20:55:04 UTC (rev 1696)
+++ branches/ocean_projects/closure/src/core_ocean/Makefile        2012-03-22 22:53:57 UTC (rev 1697)
@@ -10,6 +10,7 @@
            mpas_ocn_vel_hmix.o \
            mpas_ocn_vel_hmix_del2.o \
            mpas_ocn_vel_hmix_del4.o \
+           mpas_ocn_vel_hmix_leith.o \
            mpas_ocn_vel_forcing.o \
            mpas_ocn_vel_forcing_windstress.o \
            mpas_ocn_vel_forcing_bottomdrag.o \
@@ -83,12 +84,14 @@
 
 mpas_ocn_vel_vadv.o:
 
-mpas_ocn_vel_hmix.o: mpas_ocn_vel_hmix_del2.o mpas_ocn_vel_hmix_del4.o
+mpas_ocn_vel_hmix.o: mpas_ocn_vel_hmix_del2.o mpas_ocn_vel_hmix_del4.o mpas_ocn_vel_hmix_leith.o
 
 mpas_ocn_vel_hmix_del2.o:
 
 mpas_ocn_vel_hmix_del4.o:
 
+mpas_ocn_vel_hmix_leith.o:
+
 mpas_ocn_vel_forcing.o: mpas_ocn_vel_forcing_windstress.o mpas_ocn_vel_forcing_bottomdrag.o mpas_ocn_vel_forcing_rayleigh.o
 
 mpas_ocn_vel_forcing_windstress.o:
@@ -173,6 +176,7 @@
                                           mpas_ocn_vel_hmix.o \
                                           mpas_ocn_vel_hmix_del2.o \
                                           mpas_ocn_vel_hmix_del4.o \
+                                          mpas_ocn_vel_hmix_leith.o \
                                           mpas_ocn_vel_forcing.o \
                                           mpas_ocn_vel_forcing_windstress.o \
                                           mpas_ocn_vel_forcing_bottomdrag.o \

Modified: branches/ocean_projects/closure/src/core_ocean/Registry
===================================================================
--- trunk/mpas/src/core_ocean/Registry        2012-03-22 20:55:04 UTC (rev 1696)
+++ branches/ocean_projects/closure/src/core_ocean/Registry        2012-03-22 22:53:57 UTC (rev 1697)
@@ -49,6 +49,8 @@
 namelist logical   hmix     config_rayleigh_friction    false
 namelist real      hmix     config_rayleigh_damping_coeff 0.0
 namelist real      hmix     config_apvm_scale_factor      0.0
+namelist real      hmix     config_leith_parameter        0.0
+namelist real      hmix     config_leith_dx               0.0
 namelist character vmix     config_vert_visc_type       const
 namelist character vmix     config_vert_diff_type       const
 namelist logical   vmix     config_implicit_vertical_mix  .true.
@@ -124,6 +126,7 @@
 var persistent real    meshDensity ( nCells ) 0 iro meshDensity mesh - -
 var persistent real    meshScalingDel2 ( nEdges ) 0 ro meshScalingDel2 mesh - -
 var persistent real    meshScalingDel4 ( nEdges ) 0 ro meshScalingDel4 mesh - -
+var persistent real    meshScaling ( nEdges ) 0 ro meshScaling mesh - -
 
 var persistent integer cellsOnEdge ( TWO nEdges ) 0 iro cellsOnEdge mesh - -
 var persistent integer nEdgesOnCell ( nCells ) 0 iro nEdgesOnCell mesh - -

Modified: branches/ocean_projects/closure/src/core_ocean/mpas_ocn_mpas_core.F
===================================================================
--- trunk/mpas/src/core_ocean/mpas_ocn_mpas_core.F        2012-03-22 20:55:04 UTC (rev 1696)
+++ branches/ocean_projects/closure/src/core_ocean/mpas_ocn_mpas_core.F        2012-03-22 22:53:57 UTC (rev 1697)
@@ -776,23 +776,26 @@
       type (mesh_type), intent(inout) :: mesh
 
       integer :: iEdge, cell1, cell2
-      real (kind=RKIND), dimension(:), pointer :: meshDensity, meshScalingDel2, meshScalingDel4
+      real (kind=RKIND), dimension(:), pointer :: meshDensity, meshScalingDel2, meshScalingDel4, meshScaling
 
       meshDensity =&gt; mesh % meshDensity % array
       meshScalingDel2 =&gt; mesh % meshScalingDel2 % array
       meshScalingDel4 =&gt; mesh % meshScalingDel4 % array
+      meshScaling =&gt; mesh % meshScaling % array
 
       !
       ! Compute the scaling factors to be used in the del2 and del4 dissipation
       !
       meshScalingDel2(:) = 1.0
       meshScalingDel4(:) = 1.0
+      meshScaling(:) = 1.0
       if (config_h_ScaleWithMesh) then
          do iEdge=1,mesh%nEdges
             cell1 = mesh % cellsOnEdge % array(1,iEdge)
             cell2 = mesh % cellsOnEdge % array(2,iEdge)
             meshScalingDel2(iEdge) = 1.0 / ( (meshDensity(cell1) + meshDensity(cell2) )/2.0)**(5.0/12.0)
             meshScalingDel4(iEdge) = 1.0 / ( (meshDensity(cell1) + meshDensity(cell2) )/2.0)**(5.0/6.0)
+            meshScaling(iEdge)     = 1.0 / ( (meshDensity(cell1) + meshDensity(cell2) )/2.0)**(1.0/4.0)
          end do
       end if
 

Modified: branches/ocean_projects/closure/src/core_ocean/mpas_ocn_vel_hmix.F
===================================================================
--- trunk/mpas/src/core_ocean/mpas_ocn_vel_hmix.F        2012-03-22 20:55:04 UTC (rev 1696)
+++ branches/ocean_projects/closure/src/core_ocean/mpas_ocn_vel_hmix.F        2012-03-22 22:53:57 UTC (rev 1697)
@@ -21,6 +21,7 @@
    use mpas_timer
    use ocn_vel_hmix_del2
    use ocn_vel_hmix_del4
+   use ocn_vel_hmix_leith
 
    implicit none
    private
@@ -47,7 +48,7 @@
    !
    !--------------------------------------------------------------------
 
-   type (timer_node), pointer :: del2Timer, del4Timer
+   type (timer_node), pointer :: del2Timer, del4Timer, leithTimer
 
 
 !***********************************************************************
@@ -112,7 +113,7 @@
       !
       !-----------------------------------------------------------------
 
-      integer :: err1, err2
+      integer :: err1, err2, err3
 
       !-----------------------------------------------------------------
       !
@@ -128,8 +129,12 @@
       call mpas_timer_start(&quot;del4&quot;, .false., del4Timer)
       call ocn_vel_hmix_del4_tend(grid, divergence, vorticity, tend, err2)
       call mpas_timer_stop(&quot;del4&quot;, del4Timer)
+      call mpas_timer_start(&quot;leith&quot;, .false., leithTimer)
+      call ocn_vel_hmix_leith_tend(grid, vorticity, tend, err3)
+      call mpas_timer_stop(&quot;leith&quot;, leithTimer)
 
       err = ior(err1, err2)
+      err = ior(err, err3)
 
    !--------------------------------------------------------------------
 
@@ -163,12 +168,14 @@
 
       integer, intent(out) :: err !&lt; Output: error flag
 
-      integer :: err1, err2
+      integer :: err1, err2, err3
 
       call ocn_vel_hmix_del2_init(err1)
       call ocn_vel_hmix_del4_init(err2)
+      call ocn_vel_hmix_leith_init(err3)
 
       err = ior(err1, err2)
+      err = ior(err,  err3)
 
    !--------------------------------------------------------------------
 

Added: branches/ocean_projects/closure/src/core_ocean/mpas_ocn_vel_hmix_leith.F
===================================================================
--- branches/ocean_projects/closure/src/core_ocean/mpas_ocn_vel_hmix_leith.F                                (rev 0)
+++ branches/ocean_projects/closure/src/core_ocean/mpas_ocn_vel_hmix_leith.F        2012-03-22 22:53:57 UTC (rev 1697)
@@ -0,0 +1,204 @@
+!|||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
+!
+!  ocn_vel_hmix_leith
+!
+!&gt; \brief Ocean horizontal mixing - Laplacian parameterization 
+!&gt; \author Phil Jones, Doug Jacobsen
+!&gt; \date   15 September 2011
+!&gt; \version SVN:$Id:$
+!&gt; \details
+!&gt;  This module contains routines for computing horizontal mixing 
+!&gt;  tendencies using a Laplacian formulation.
+!
+!-----------------------------------------------------------------------
+
+module ocn_vel_hmix_leith
+
+   use mpas_grid_types
+   use mpas_configure
+
+   implicit none
+   private
+   save
+
+   !--------------------------------------------------------------------
+   !
+   ! Public parameters
+   !
+   !--------------------------------------------------------------------
+
+   !--------------------------------------------------------------------
+   !
+   ! Public member functions
+   !
+   !--------------------------------------------------------------------
+
+   public :: ocn_vel_hmix_leith_tend, &amp;
+             ocn_vel_hmix_leith_init
+
+   !-------------------------------------------------------------------
+   !
+   ! Private module variables
+   !
+   !--------------------------------------------------------------------
+
+   logical ::  hmixLeithOn  !&lt; integer flag to determine whether Leith chosen
+
+   real (kind=RKIND) :: &amp;
+      leith_parameter,         &amp;!&lt; nondimensional Leith parameter
+      leith_dx                  !&lt; length scale of finest mesh resolution
+
+!***********************************************************************
+
+contains
+
+!***********************************************************************
+!
+!  routine ocn_vel_hmix_leith_tend
+!
+!&gt; \brief   Computes velocity tendency term based on Leith turblence closure
+!&gt; \author  Todd Ringler
+!&gt; \date    2 March 2012
+!&gt; \version SVN:$Id$
+!&gt; \details 
+!&gt;  This routine computes a velocity tendency consistent with the Leith turbulence
+!&gt;  closure for an enstrophy cascade.
+!
+!-----------------------------------------------------------------------
+
+   subroutine ocn_vel_hmix_leith_tend(grid, vorticity, tend, err)!{{{
+
+      !-----------------------------------------------------------------
+      !
+      ! input variables
+      !
+      !-----------------------------------------------------------------
+
+      real (kind=RKIND), dimension(:,:), intent(in) :: &amp;
+         vorticity       !&lt; Input: vorticity
+
+      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 !&lt; Output: error flag
+
+      !-----------------------------------------------------------------
+      !
+      ! local variables
+      !
+      !-----------------------------------------------------------------
+
+      integer :: k, iEdge, nEdgesSolve, vertex1, vertex2
+      integer, dimension(:), pointer :: maxLevelEdgeTop
+      integer, dimension(:,:), pointer :: verticesOnEdge, edgeMask
+
+      real (kind=RKIND) :: u_diffusion, invLength2, leithVisc, pii
+      real (kind=RKIND), dimension(:), pointer :: meshScaling, dvEdge
+
+      !-----------------------------------------------------------------
+      !
+      ! exit if this mixing is not selected
+      !
+      !-----------------------------------------------------------------
+
+      err = 0
+
+      if(.not.hmixLeithOn) return
+
+      nEdgesSolve = grid % nEdgesSolve
+      maxLevelEdgeTop =&gt; grid % maxLevelEdgeTop % array
+      verticesOnEdge =&gt; grid % verticesOnEdge % array
+      meshScaling =&gt; grid % meshScaling % array
+      edgeMask =&gt; grid % edgeMask % array
+      dvEdge =&gt; grid % dvEdge % array
+      pii = 2.*asin(1.0)
+
+      !write(0,*) ' min/max before Leith : ', minval(tend), maxval(tend)
+
+      do iEdge=1,nEdgesSolve
+         vertex1 = verticesOnEdge(1,iEdge)
+         vertex2 = verticesOnEdge(2,iEdge)
+
+         invLength2 = 1.0 / dvEdge(iEdge)
+
+         do k=1,maxLevelEdgeTop(iEdge)
+
+            leithVisc = ( leith_parameter * leith_dx * meshScaling(iEdge) / pii)**3 &amp;
+                        * abs( vorticity(k,vertex2) - vorticity(k,vertex1) ) * invLength2
+
+            u_diffusion = -leithVisc * ( vorticity(k,vertex2) - vorticity(k,vertex1) ) * invLength2
+                         
+            tend(k,iEdge) = tend(k,iEdge) + edgeMask(k, iEdge) * u_diffusion
+
+         end do
+      end do
+
+      !write(0,*) ' min/max after  Leith : ', minval(tend), maxval(tend)
+      !write(0,*) leith_parameter, leith_dx
+      !write(0,*) minval(meshScaling), maxval(meshScaling)
+
+   !--------------------------------------------------------------------
+
+   end subroutine ocn_vel_hmix_leith_tend!}}}
+
+!***********************************************************************
+!
+!  routine ocn_vel_hmix_leith_init
+!
+!&gt; \brief   Initializes parameters related to the Leith turblence closure 
+!&gt; \author  Todd Ringler
+!&gt; \date    2 March 2012
+!&gt; \version SVN:$Id$
+!&gt; \details
+!&gt;  This routine initializes parameters related to the Leith turblence closure. 
+!-----------------------------------------------------------------------
+
+   subroutine ocn_vel_hmix_leith_init(err)!{{{
+
+
+   integer, intent(out) :: err !&lt; Output: error flag
+
+   !--------------------------------------------------------------------
+   !
+   ! set some local module variables based on input config choices
+   !
+   !--------------------------------------------------------------------
+
+   err = 0
+
+   hmixLeithOn = .false.
+
+   if ( config_leith_parameter &gt; 0.0 ) then
+      hmixLeithOn = .true.
+      leith_parameter = config_leith_parameter
+      leith_dx = config_leith_dx
+      write(0,*) ' Leith ', hmixLeithOn, leith_parameter, leith_dx
+   endif
+
+
+   !--------------------------------------------------------------------
+
+   end subroutine ocn_vel_hmix_leith_init!}}}
+
+!***********************************************************************
+
+end module ocn_vel_hmix_leith
+
+!|||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
+! vim: foldmethod=marker

</font>
</pre>