<p><b>dwj07@fsu.edu</b> 2012-01-06 13:04:31 -0700 (Fri, 06 Jan 2012)</p><p><br>
        -- TRUNK COMMIT --<br>
<br>
        Merging rayleigh forcing branch to trunk.<br>
</p><hr noshade><pre><font color="gray">Modified: trunk/mpas/namelist.input.ocean
===================================================================
--- trunk/mpas/namelist.input.ocean        2012-01-06 19:47:50 UTC (rev 1312)
+++ trunk/mpas/namelist.input.ocean        2012-01-06 20:04:31 UTC (rev 1313)
@@ -48,8 +48,6 @@
    config_visc_vorticity_term = .true.
    config_h_tracer_eddy_diff2 = 1.0e4
    config_h_tracer_eddy_diff4 = 0.0
-   config_mom_decay      = .false.
-   config_mom_decay_time = 3600.0
 /
 &amp;vmix
    config_vert_visc_type  = 'rich'


Property changes on: trunk/mpas/src
___________________________________________________________________
Added: svn:mergeinfo
   + /branches/ocean_projects/rayleigh/src:1298-1311


Property changes on: trunk/mpas/src/core_ocean
___________________________________________________________________
Modified: svn:mergeinfo
   - /branches/cam_mpas_nh/src/core_ocean:1260-1270
/branches/ocean_projects/imp_vert_mix_mrp/src/core_ocean:754-986
/branches/ocean_projects/split_explicit_mrp/src/core_ocean:1134-1138
/branches/ocean_projects/split_explicit_timestepping/src/core_ocean:1044-1097
/branches/ocean_projects/time_averaging/src/core_ocean:1271-1305
/branches/ocean_projects/vert_adv_mrp/src/core_ocean:704-745
/branches/source_renaming/src/core_ocean:1082-1113
/branches/time_manager/src/core_ocean:924-962
   + /branches/cam_mpas_nh/src/core_ocean:1260-1270
/branches/ocean_projects/imp_vert_mix_mrp/src/core_ocean:754-986
/branches/ocean_projects/rayleigh/src/core_ocean:1298-1311
/branches/ocean_projects/split_explicit_mrp/src/core_ocean:1134-1138
/branches/ocean_projects/split_explicit_timestepping/src/core_ocean:1044-1097
/branches/ocean_projects/time_averaging/src/core_ocean:1271-1305
/branches/ocean_projects/vert_adv_mrp/src/core_ocean:704-745
/branches/source_renaming/src/core_ocean:1082-1113
/branches/time_manager/src/core_ocean:924-962

Modified: trunk/mpas/src/core_ocean/Makefile
===================================================================
--- trunk/mpas/src/core_ocean/Makefile        2012-01-06 19:47:50 UTC (rev 1312)
+++ trunk/mpas/src/core_ocean/Makefile        2012-01-06 20:04:31 UTC (rev 1313)
@@ -13,6 +13,7 @@
            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_pressure_grad.o \
            mpas_ocn_tracer_vadv.o \
            mpas_ocn_tracer_vadv_spline.o \
@@ -44,7 +45,6 @@
        mpas_ocn_global_diagnostics.o \
            mpas_ocn_time_average.o
 
-
 all: core_hyd
 
 core_hyd: $(OBJS)
@@ -80,12 +80,14 @@
 
 mpas_ocn_vel_hmix_del4.o:
 
-mpas_ocn_vel_forcing.o: mpas_ocn_vel_forcing_windstress.o mpas_ocn_vel_forcing_bottomdrag.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:
 
-mpas_ocn_velforcing_bottomdrag.o:
+mpas_ocn_vel_forcing_bottomdrag.o:
 
+mpas_ocn_vel_forcing_rayleigh.o:
+
 mpas_ocn_vel_coriolis.o:
 
 mpas_ocn_tracer_hadv.o:  mpas_ocn_tracer_hadv2.o  mpas_ocn_tracer_hadv3.o  mpas_ocn_tracer_hadv4.o

Modified: trunk/mpas/src/core_ocean/Registry
===================================================================
--- trunk/mpas/src/core_ocean/Registry        2012-01-06 19:47:50 UTC (rev 1312)
+++ trunk/mpas/src/core_ocean/Registry        2012-01-06 20:04:31 UTC (rev 1313)
@@ -38,7 +38,7 @@
 namelist real      split_explicit_ts config_btr_gam2_SSHWt1  1.0
 namelist real      split_explicit_ts config_btr_gam3_uWt2    1.0
 namelist logical   split_explicit_ts config_btr_solve_SSH2   false
-namelist logical   sw_model config_h_ScaleWithMesh     false
+namelist logical   hmix     config_h_ScaleWithMesh     false
 namelist real      hmix     config_h_mom_eddy_visc2     0.0
 namelist real      hmix     config_h_mom_eddy_visc4     0.0
 namelist logical   hmix     config_visc_vorticity_term true
@@ -48,8 +48,8 @@
 namelist real      hmix     config_h_tracer_eddy_diff2  0.0
 namelist real      hmix     config_h_tracer_eddy_diff4  0.0
 namelist real      hmix     config_apvm_upwinding       0.5
-namelist logical   hmix     config_mom_decay            false 
-namelist real      hmix     config_mom_decay_time       3600.0
+namelist logical   hmix     config_rayleigh_friction    false
+namelist real      hmix     config_rayleigh_damping_coeff 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.

Modified: trunk/mpas/src/core_ocean/mpas_ocn_time_integration_rk4.F
===================================================================
--- trunk/mpas/src/core_ocean/mpas_ocn_time_integration_rk4.F        2012-01-06 19:47:50 UTC (rev 1312)
+++ trunk/mpas/src/core_ocean/mpas_ocn_time_integration_rk4.F        2012-01-06 20:04:31 UTC (rev 1313)
@@ -320,29 +320,6 @@
             call mpas_timer_stop(&quot;RK4-implicit vert mix&quot;)
          end if
 
-         ! mrp 110725 momentum decay term
-         if (config_mom_decay) then
-             call mpas_timer_start(&quot;RK4-momentum decay&quot;)
-
-            !
-            !  Implicit solve for momentum decay
-            !
-            !  Add term to RHS of momentum equation: -1/gamma u
-            !
-            !  This changes the solve to:
-            !  u^{n+1} = u_provis^{n+1}/(1+dt/gamma)
-            !
-            coef = 1.0/(1.0 + dt/config_mom_decay_time)
-            do iEdge=1,block % mesh % nEdges
-               do k=1,maxLevelEdgeTop(iEdge)
-                  u(k,iEdge) = coef*u(k,iEdge) 
-               end do
-            end do
-
-            call mpas_timer_stop(&quot;RK4-momentum decay&quot;)
-         end if
-
-
          if (config_test_case == 1) then    ! For case 1, wind field should be fixed
             block % state % time_levs(2) % state % u % array(:,:) = block % state % time_levs(1) % state % u % array(:,:)
          end if

Modified: trunk/mpas/src/core_ocean/mpas_ocn_time_integration_split.F
===================================================================
--- trunk/mpas/src/core_ocean/mpas_ocn_time_integration_split.F        2012-01-06 19:47:50 UTC (rev 1312)
+++ trunk/mpas/src/core_ocean/mpas_ocn_time_integration_split.F        2012-01-06 20:04:31 UTC (rev 1313)
@@ -1217,26 +1217,6 @@
             call ocn_tracer_vmix_tend_implicit(block % mesh, dt, vertdifftopofcell, h, tracers, err)
          end if
 
-         ! mrp 110725 adding momentum decay term
-         if (config_mom_decay) then
-
-            !
-            !  Implicit solve for momentum decay
-            !
-            !  Add term to RHS of momentum equation: -1/gamma u
-            !
-            !  This changes the solve to:
-            !  u^{n+1} = u_provis^{n+1}/(1+dt/gamma)
-            !
-            coef = 1.0/(1.0 + dt/config_mom_decay_time)
-            do iEdge=1,block % mesh % nEdges
-               do k=1,maxLevelEdgeTop(iEdge)
-                  u(k,iEdge) = coef*u(k,iEdge) 
-               end do
-            end do
-
-         end if
-
          if (config_test_case == 1) then    ! For case 1, wind field should be fixed
             block % state % time_levs(2) % state % u % array(:,:) = block % state % time_levs(1) % state % u % array(:,:)
          end if

Modified: trunk/mpas/src/core_ocean/mpas_ocn_vel_forcing.F
===================================================================
--- trunk/mpas/src/core_ocean/mpas_ocn_vel_forcing.F        2012-01-06 19:47:50 UTC (rev 1312)
+++ trunk/mpas/src/core_ocean/mpas_ocn_vel_forcing.F        2012-01-06 20:04:31 UTC (rev 1313)
@@ -19,6 +19,7 @@
 
    use ocn_vel_forcing_windstress
    use ocn_vel_forcing_bottomdrag
+   use ocn_vel_forcing_rayleigh
 
    implicit none
    private
@@ -114,7 +115,7 @@
       !
       !-----------------------------------------------------------------
 
-      integer :: err1, err2
+      integer :: err1, err2, err3
 
       !-----------------------------------------------------------------
       !
@@ -126,8 +127,10 @@
 
       call ocn_vel_forcing_windstress_tend(grid, u_src, h_edge, tend, err1)
       call ocn_vel_forcing_bottomdrag_tend(grid, u, ke_edge, h_edge, tend, err2)
+      call ocn_vel_forcing_rayleigh_tend(grid, u, tend, err3)
 
       err = ior(err1, err2)
+      err = ior(err, err3)
 
    !--------------------------------------------------------------------
 
@@ -161,12 +164,14 @@
 
       integer, intent(out) :: err !&lt; Output: error flag
 
-      integer :: err1, err2
+      integer :: err1, err2, err3
 
       call ocn_vel_forcing_windstress_init(err1)
       call ocn_vel_forcing_bottomdrag_init(err2)
+      call ocn_vel_forcing_rayleigh_init(err3)
 
       err = ior(err1, err2)
+      err = ior(err, err3)
 
    !--------------------------------------------------------------------
 

Copied: trunk/mpas/src/core_ocean/mpas_ocn_vel_forcing_rayleigh.F (from rev 1311, branches/ocean_projects/rayleigh/src/core_ocean/mpas_ocn_vel_forcing_rayleigh.F)
===================================================================
--- trunk/mpas/src/core_ocean/mpas_ocn_vel_forcing_rayleigh.F                                (rev 0)
+++ trunk/mpas/src/core_ocean/mpas_ocn_vel_forcing_rayleigh.F        2012-01-06 20:04:31 UTC (rev 1313)
@@ -0,0 +1,180 @@
+!|||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
+!
+!  ocn_vel_forcing_rayleigh
+!
+!&gt; \brief MPAS ocean Rayleigh Friction (to be used to smooth &quot;shocks&quot; from cold starts)
+!&gt; \author Todd Ringler
+!&gt; \date   5 January 2012
+!&gt; \version SVN:$Id:$
+!&gt; \details
+!&gt;  This module contains the routine for computing 
+!&gt;  tendencies based on linear Rayleigh friction.
+!
+!-----------------------------------------------------------------------
+
+module ocn_vel_forcing_rayleigh
+
+   use mpas_grid_types
+   use mpas_configure
+
+   implicit none
+   private
+   save
+
+   !--------------------------------------------------------------------
+   !
+   ! Public parameters
+   !
+   !--------------------------------------------------------------------
+
+   !--------------------------------------------------------------------
+   !
+   ! Public member functions
+   !
+   !--------------------------------------------------------------------
+
+   public :: ocn_vel_forcing_rayleigh_tend, &amp;
+             ocn_vel_forcing_rayleigh_init
+
+   !--------------------------------------------------------------------
+   !
+   ! Private module variables
+   !
+   !--------------------------------------------------------------------
+
+   logical :: rayleighFrictionOn
+   real (kind=RKIND) :: rayleighDampingCoef
+
+
+!***********************************************************************
+
+contains
+
+!***********************************************************************
+!
+!  ocn_vel_forcing_rayleigh_tend
+!
+!&gt; \brief   Computes tendency term from Rayleigh friction
+!&gt; \author  Todd Ringler
+!&gt; \date    5 January 2012
+!&gt; \version SVN:$Id$
+!&gt; \details 
+!&gt;  This routine computes the Rayleigh friction tendency for momentum
+!&gt;  based on current state.
+!
+!-----------------------------------------------------------------------
+
+   subroutine ocn_vel_forcing_rayleigh_tend(grid, u, tend, err)!{{{
+
+      !-----------------------------------------------------------------
+      !
+      ! input variables
+      !
+      !-----------------------------------------------------------------
+
+      real (kind=RKIND), dimension(:,:), intent(in) :: &amp;
+         u    !&lt; Input: velocity 
+
+      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 :: iEdge, nEdgesSolve, k
+      integer, dimension(:), pointer :: maxLevelEdgeTop
+
+      !-----------------------------------------------------------------
+      !
+      ! 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.rayleighFrictionOn) return
+
+      nEdgesSolve = grid % nEdgesSolve
+      maxLevelEdgeTop =&gt; grid % maxLevelEdgeTop % array
+
+      do iEdge=1,nEdgesSolve
+        do k=1,maxLevelEdgeTop(iEdge)
+
+           tend(k,iEdge) = tend(k,iEdge) - rayleighDampingCoef * u(k,iEdge)
+
+        enddo
+      enddo
+
+
+   !--------------------------------------------------------------------
+
+   end subroutine ocn_vel_forcing_rayleigh_tend!}}}
+
+!***********************************************************************
+!
+!  ocn_vel_forcing_rayleigh_init
+!
+!&gt; \brief   Initializes ocean Rayleigh friction
+!&gt; \author  Todd Ringler
+!&gt; \date    5 January 2012
+!&gt; \version SVN:$Id$
+!&gt; \details 
+!&gt;  This routine initializes quantities related to 
+!&gt;  in the ocean. 
+!
+!-----------------------------------------------------------------------
+
+   subroutine ocn_vel_forcing_rayleigh_init(err)!{{{
+
+   !--------------------------------------------------------------------
+
+      !-----------------------------------------------------------------
+      !
+      ! call individual init routines for each parameterization
+      !
+      !-----------------------------------------------------------------
+
+      integer, intent(out) :: err !&lt; Output: error flag
+
+
+      err = 0
+
+      rayleighDampingCoef = 0.0
+
+      if (config_rayleigh_friction) then
+          rayleighFrictionOn = .true.
+          rayleighDampingCoef = config_rayleigh_damping_coeff
+      endif
+
+   !--------------------------------------------------------------------
+
+   end subroutine ocn_vel_forcing_rayleigh_init!}}}
+
+!***********************************************************************
+
+end module ocn_vel_forcing_rayleigh
+
+!|||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
+! vim: foldmethod=marker

</font>
</pre>