<p><b>dwj07@fsu.edu</b> 2012-01-17 12:22:35 -0700 (Tue, 17 Jan 2012)</p><p><br>
        -- BRANCH COMMIT --<br>
<br>
        Making some changes to allow the tracer advection modules to compile.<br>
<br>
        Changed the ddt diagnostic_type in ocean core to match other cores, as diag_type.<br>
<br>
        Currently the initialization routines are called for tracer_advectionwithin mpas_ocn_mpas_core.<br>
<br>
        Ocean core runs with these modifications. The actual advection routines are not called yet.<br>
</p><hr noshade><pre><font color="gray">Modified: branches/ocean_projects/advection_routines/src/core_ocean/Registry
===================================================================
--- branches/ocean_projects/advection_routines/src/core_ocean/Registry        2012-01-17 18:10:30 UTC (rev 1382)
+++ branches/ocean_projects/advection_routines/src/core_ocean/Registry        2012-01-17 19:22:35 UTC (rev 1383)
@@ -152,6 +152,11 @@
 % Space needed for advection
 var persistent real    deriv_two ( FIFTEEN TWO nEdges ) 0 - deriv_two mesh - -
 var persistent integer advCells ( TWENTYONE nCells ) 0 - advCells mesh - -
+% Added for monotonic advection scheme
+var persistent real    adv_coefs ( FIFTEEN nEdges ) 0 - adv_coefs mesh - -
+var persistent real    adv_coefs_3rd ( FIFTEEN nEdges ) 0 - adv_coefs_3rd mesh - -
+var persistent integer advCellsForEdge ( FIFTEEN nEdges ) 0 - advCellsForEdge mesh - -
+var persistent integer nAdvCellsForEdge ( nEdges ) 0 - nAdvCellsForEdge mesh - -
 
 % !! NOTE: the following arrays are needed to allow the use
 % !! of the module_advection.F w/o alteration
@@ -255,10 +260,10 @@
 var persistent real    CFLNumberGlobal ( Time ) 2 o CFLNumberGlobal state - -
 
 % Diagnostics fields, only one time level required
-var persistent real    RiTopOfCell ( nVertLevelsP1 nCells Time ) 1 - RiTopOfCell diagnostics - -
-var persistent real    RiTopOfEdge ( nVertLevelsP1 nEdges Time ) 1 - RiTopOfEdge diagnostics - -
-var persistent real    vertViscTopOfEdge ( nVertLevelsP1 nEdges Time ) 1 - vertViscTopOfEdge diagnostics - -
-var persistent real    vertDiffTopOfCell ( nVertLevelsP1 nCells Time ) 1 - vertDiffTopOfCell diagnostics - -
+var persistent real    RiTopOfCell ( nVertLevelsP1 nCells Time ) 1 - RiTopOfCell diag - -
+var persistent real    RiTopOfEdge ( nVertLevelsP1 nEdges Time ) 1 - RiTopOfEdge diag - -
+var persistent real    vertViscTopOfEdge ( nVertLevelsP1 nEdges Time ) 1 - vertViscTopOfEdge diag - -
+var persistent real    vertDiffTopOfCell ( nVertLevelsP1 nCells Time ) 1 - vertDiffTopOfCell diag - -
 
 var persistent real    nAccumulate ( Time ) 2 o nAccumulate state - -
 var persistent real    acc_ssh ( nCells Time ) 2 o acc_ssh state - -

Modified: branches/ocean_projects/advection_routines/src/core_ocean/mpas_ocn_mpas_core.F
===================================================================
--- branches/ocean_projects/advection_routines/src/core_ocean/mpas_ocn_mpas_core.F        2012-01-17 18:10:30 UTC (rev 1382)
+++ branches/ocean_projects/advection_routines/src/core_ocean/mpas_ocn_mpas_core.F        2012-01-17 19:22:35 UTC (rev 1383)
@@ -45,7 +45,9 @@
    subroutine mpas_core_init(domain, startTimeStamp)!{{{
 
       use mpas_grid_types
+      use mpas_tracer_advection
 
+
       implicit none
 
       type (domain_type), intent(inout) :: domain
@@ -88,6 +90,9 @@
       call ocn_tendency_init(err_tmp)
       err = ior(err,err_tmp)
 
+      call mpas_tracer_advection_init(err_tmp)
+      err = ior(err,err_tmp)
+
       call mpas_timer_init(domain)
 
       if(err.eq.1) then
@@ -209,6 +214,8 @@
       use mpas_grid_types
       use mpas_rbf_interpolation
       use mpas_vector_reconstruction
+      use mpas_tracer_advection
+
    
       implicit none
    
@@ -217,6 +224,7 @@
       real (kind=RKIND), intent(in) :: dt
       integer :: i, iEdge, iCell, k
    
+      call mpas_tracer_advection_coefficients(mesh)
       call ocn_time_average_init(block % state % time_levs(1) % state)
    
       call mpas_timer_start(&quot;diagnostic solve&quot;, .false., initDiagSolveTimer)

Modified: branches/ocean_projects/advection_routines/src/core_ocean/mpas_ocn_tendency.F
===================================================================
--- branches/ocean_projects/advection_routines/src/core_ocean/mpas_ocn_tendency.F        2012-01-17 18:10:30 UTC (rev 1382)
+++ branches/ocean_projects/advection_routines/src/core_ocean/mpas_ocn_tendency.F        2012-01-17 19:22:35 UTC (rev 1383)
@@ -111,7 +111,8 @@
 
       type (tend_type), intent(inout) :: tend
       type (state_type), intent(in) :: s
-      type (diagnostics_type), intent(in) :: d
+!     type (diagnostics_type), intent(in) :: d ! dwj: 01/17/12 change for cross core compatibility
+      type (diag_type), intent(in) :: d
       type (mesh_type), intent(in) :: grid
 
       real (kind=RKIND), dimension(:,:), pointer :: h_edge, u, wTop, tend_h
@@ -182,7 +183,8 @@
 
       type (tend_type), intent(inout) :: tend
       type (state_type), intent(in) :: s
-      type (diagnostics_type), intent(in) :: d
+!     type (diagnostics_type), intent(in) :: d ! dwj: 01/17/12 change for cross core compatibilty
+      type (diag_type), intent(in) :: d
       type (mesh_type), intent(in) :: grid
 
       real (kind=RKIND), dimension(:,:), pointer :: &amp;
@@ -302,7 +304,8 @@
 
       type (tend_type), intent(inout) :: tend
       type (state_type), intent(in) :: s
-      type (diagnostics_type), intent(in) :: d
+!     type (diagnostics_type), intent(in) :: d ! dwj: 01/17/12 change for cross core compatibilty
+      type (diag_type), intent(in) :: d
       type (mesh_type), intent(in) :: grid
 
       real (kind=RKIND), dimension(:,:), pointer :: &amp;

Modified: branches/ocean_projects/advection_routines/src/core_ocean/mpas_ocn_time_integration_rk4.F
===================================================================
--- branches/ocean_projects/advection_routines/src/core_ocean/mpas_ocn_time_integration_rk4.F        2012-01-17 18:10:30 UTC (rev 1382)
+++ branches/ocean_projects/advection_routines/src/core_ocean/mpas_ocn_time_integration_rk4.F        2012-01-17 19:22:35 UTC (rev 1383)
@@ -166,19 +166,20 @@
         call mpas_timer_start(&quot;RK4-tendency computations&quot;)
         block =&gt; domain % blocklist
         do while (associated(block))
+        ! dwj 01/17/12 changing from diagnostics to diag for cross core compatibility
            if (.not.config_implicit_vertical_mix) then
-              call ocn_vmix_coefs(block % mesh, provis, block % diagnostics, err)
+              call ocn_vmix_coefs(block % mesh, provis, block % diag, err)
            end if
-           call ocn_tend_h(block % tend, provis, block % diagnostics, block % mesh)
-           call ocn_tend_u(block % tend, provis, block % diagnostics, block % mesh)
+           call ocn_tend_h(block % tend, provis, block % diag, block % mesh)
+           call ocn_tend_u(block % tend, provis, block % diag, block % mesh)
 
            ! mrp 110718 filter btr mode out of u_tend
            ! still got h perturbations with just this alone.  Try to set uBtr=0 after full u computation
            if (config_rk_filter_btr_mode) then
-               call filter_btr_mode_tend_u(block % tend, provis, block % diagnostics, block % mesh)
+               call filter_btr_mode_tend_u(block % tend, provis, block % diag, block % mesh)
            endif
 
-           call ocn_tend_scalar(block % tend, provis, block % diagnostics, block % mesh)
+           call ocn_tend_scalar(block % tend, provis, block % diag, block % mesh)
            block =&gt; block % next
         end do
         call mpas_timer_stop(&quot;RK4-tendency computations&quot;)
@@ -272,14 +273,15 @@
       block =&gt; domain % blocklist
       do while (associated(block))
 
+      ! dwj 01/17/12 change from diagnostics to diag for cross core compatibilty
          u           =&gt; block % state % time_levs(2) % state % u % array
          tracers     =&gt; block % state % time_levs(2) % state % tracers % array
          h           =&gt; block % state % time_levs(2) % state % h % array
          h_edge      =&gt; block % state % time_levs(2) % state % h_edge % array
          ke_edge     =&gt; block % state % time_levs(2) % state % ke_edge % array
          num_tracers = block % state % time_levs(2) % state % num_tracers
-         vertViscTopOfEdge =&gt; block % diagnostics % vertViscTopOfEdge % array
-         vertDiffTopOfCell =&gt; block % diagnostics % vertDiffTopOfCell % array
+         vertViscTopOfEdge =&gt; block % diag % vertViscTopOfEdge % array
+         vertDiffTopOfCell =&gt; block % diag % vertDiffTopOfCell % array
          maxLevelCell    =&gt; block % mesh % maxLevelCell % array
          maxLevelEdgeTop =&gt; block % mesh % maxLevelEdgeTop % array
                   
@@ -296,7 +298,8 @@
          if (config_implicit_vertical_mix) then
             call mpas_timer_start(&quot;RK4-implicit vert mix&quot;)
 
-            call ocn_vmix_coefs(block % mesh, block % state % time_levs(2) % state, block % diagnostics, err)
+      ! dwj 01/17/12 change from diagnostics to diag for cross core compatibilty
+            call ocn_vmix_coefs(block % mesh, block % state % time_levs(2) % state, block % diag, err)
 
             !
             !  Implicit vertical solve for momentum
@@ -355,7 +358,8 @@
 
       type (tend_type), intent(inout) :: tend
       type (state_type), intent(in) :: s
-      type (diagnostics_type), intent(in) :: d
+!     type (diagnostics_type), intent(in) :: d ! dwj: 01/17/12 change for cross core compatibilty
+      type (diag_type), intent(in) :: d
       type (mesh_type), intent(in) :: grid
 
 ! mrp 110512 I just split compute_tend into compute_tend_u and compute_tend_h.

Modified: branches/ocean_projects/advection_routines/src/core_ocean/mpas_ocn_time_integration_split.F
===================================================================
--- branches/ocean_projects/advection_routines/src/core_ocean/mpas_ocn_time_integration_split.F        2012-01-17 18:10:30 UTC (rev 1382)
+++ branches/ocean_projects/advection_routines/src/core_ocean/mpas_ocn_time_integration_split.F        2012-01-17 19:22:35 UTC (rev 1383)
@@ -194,12 +194,13 @@
         ! compute velocity tendencies, T(u*,w*,p*)
         call mpas_timer_start(&quot;se bcl vel&quot;, .false., timer_bcl_vel)
 
+        ! dwj 01/17/12 changing from diagnostics to diag for cross core compatibility
         block =&gt; domain % blocklist
         do while (associated(block))
           if (.not.config_implicit_vertical_mix) then
-            call ocn_vmix_coefs(block % mesh, block % state % time_levs(2) % state, block % diagnostics, err)
+            call ocn_vmix_coefs(block % mesh, block % state % time_levs(2) % state, block % diag, err)
           end if
-          call ocn_tend_u(block % tend, block % state % time_levs(2) % state , block % diagnostics, block % mesh)
+          call ocn_tend_u(block % tend, block % state % time_levs(2) % state , block % diag, block % mesh)
           block =&gt; block % next
         end do
 
@@ -767,15 +768,16 @@
         !
         !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
 
+        ! dwj 01/17/12 changing from diagnostics to diag for cross core  compatibility
         block =&gt; domain % blocklist
         do while (associated(block))
           call ocn_wtop(block % state % time_levs(2) % state, block % mesh)
 
           if (trim(config_time_integration) == 'unsplit_explicit') then
-            call ocn_tend_h(block % tend, block % state % time_levs(2) % state , block % diagnostics, block % mesh)
+            call ocn_tend_h(block % tend, block % state % time_levs(2) % state , block % diag, block % mesh)
           endif
 
-          call ocn_tend_scalar(block % tend, block % state % time_levs(2) % state , block % diagnostics, block % mesh)
+          call ocn_tend_scalar(block % tend, block % state % time_levs(2) % state , block % diag, block % mesh)
 
           block =&gt; block % next
         end do
@@ -983,19 +985,21 @@
         !
         !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
 
+        ! dwj 01/17/12 changing from diagnostics to diag for cross core compatibilty
         u           =&gt; block % state % time_levs(2) % state % u % array
         tracers     =&gt; block % state % time_levs(2) % state % tracers % array
         h           =&gt; block % state % time_levs(2) % state % h % array
         h_edge      =&gt; block % state % time_levs(2) % state % h_edge % array
         ke_edge     =&gt; block % state % time_levs(2) % state % ke_edge % array
         num_tracers = block % state % time_levs(2) % state % num_tracers
-        vertViscTopOfEdge =&gt; block % diagnostics % vertViscTopOfEdge % array
-        vertDiffTopOfCell =&gt; block % diagnostics % vertDiffTopOfCell % array
+        vertViscTopOfEdge =&gt; block % diag % vertViscTopOfEdge % array
+        vertDiffTopOfCell =&gt; block % diag % vertDiffTopOfCell % array
         maxLevelCell    =&gt; block % mesh % maxLevelCell % array
         maxLevelEdgeTop =&gt; block % mesh % maxLevelEdgeTop % array
 
         if (config_implicit_vertical_mix) then
-          call ocn_vmix_coefs(block % mesh, block % state % time_levs(2) % state, block % diagnostics, err)
+        ! dwj 01/17/12 changing from diagnostics to diag for cross core compatibilty
+          call ocn_vmix_coefs(block % mesh, block % state % time_levs(2) % state, block % diag, err)
 
           !
           !  Implicit vertical solve for momentum
@@ -1043,7 +1047,8 @@
 
       type (tend_type), intent(inout) :: tend
       type (state_type), intent(in) :: s
-      type (diagnostics_type), intent(in) :: d
+!     type (diagnostics_type), intent(in) :: d ! dwj: 01/17/12 change for cross core compatibilty
+      type (diag_type), intent(in) :: d
       type (mesh_type), intent(in) :: grid
 
 ! mrp 110512 I just split compute_tend into compute_tend_u and compute_tend_h.

Modified: branches/ocean_projects/advection_routines/src/core_ocean/mpas_ocn_vmix.F
===================================================================
--- branches/ocean_projects/advection_routines/src/core_ocean/mpas_ocn_vmix.F        2012-01-17 18:10:30 UTC (rev 1382)
+++ branches/ocean_projects/advection_routines/src/core_ocean/mpas_ocn_vmix.F        2012-01-17 19:22:35 UTC (rev 1383)
@@ -95,7 +95,8 @@
       type (state_type), intent(inout) :: &amp;
          s             !&lt; Input/Output: state information
 
-      type (diagnostics_type), intent(inout) :: &amp;
+!     type (diagnostics_type), intent(inout) :: &amp; ! dwj: 01/17/12 change for cross core compatibility
+      type (diag_type), intent(inout) :: &amp;
          d             !&lt; Input/Output: diagnostic information
 
       !-----------------------------------------------------------------

Modified: branches/ocean_projects/advection_routines/src/core_ocean/mpas_ocn_vmix_coefs_const.F
===================================================================
--- branches/ocean_projects/advection_routines/src/core_ocean/mpas_ocn_vmix_coefs_const.F        2012-01-17 18:10:30 UTC (rev 1382)
+++ branches/ocean_projects/advection_routines/src/core_ocean/mpas_ocn_vmix_coefs_const.F        2012-01-17 19:22:35 UTC (rev 1383)
@@ -90,7 +90,8 @@
       type (state_type), intent(inout) :: &amp;
          s             !&lt; Input/Output: state information
 
-      type (diagnostics_type), intent(inout) :: &amp;
+!     type (diagnostics_type), intent(inout) :: &amp; ! dwj: 01/17/12 change for cross core compatility
+      type (diag_type), intent(inout) :: &amp;
          d             !&lt; Input/Output: diagnostic information
 
       !-----------------------------------------------------------------

Modified: branches/ocean_projects/advection_routines/src/core_ocean/mpas_ocn_vmix_coefs_rich.F
===================================================================
--- branches/ocean_projects/advection_routines/src/core_ocean/mpas_ocn_vmix_coefs_rich.F        2012-01-17 18:10:30 UTC (rev 1382)
+++ branches/ocean_projects/advection_routines/src/core_ocean/mpas_ocn_vmix_coefs_rich.F        2012-01-17 19:22:35 UTC (rev 1383)
@@ -89,7 +89,8 @@
       type (state_type), intent(inout) :: &amp;
          s             !&lt; Input/Output: state information
 
-      type (diagnostics_type), intent(inout) :: &amp;
+!     type (diagnostics_type), intent(inout) :: &amp; ! dwj: 01/17/12 change for cross core compatibilty
+      type (diag_type), intent(inout) :: &amp;
          d             !&lt; Input/Output: diagnostic information
 
       !-----------------------------------------------------------------

Modified: branches/ocean_projects/advection_routines/src/core_ocean/mpas_ocn_vmix_coefs_tanh.F
===================================================================
--- branches/ocean_projects/advection_routines/src/core_ocean/mpas_ocn_vmix_coefs_tanh.F        2012-01-17 18:10:30 UTC (rev 1382)
+++ branches/ocean_projects/advection_routines/src/core_ocean/mpas_ocn_vmix_coefs_tanh.F        2012-01-17 19:22:35 UTC (rev 1383)
@@ -84,7 +84,8 @@
       type (state_type), intent(inout) :: &amp;
          s             !&lt; Input/Output: state information
 
-      type (diagnostics_type), intent(inout) :: &amp;
+!     type (diagnostics_type), intent(inout) :: &amp; ! dwj: 01/17/12 change for cross core compatibilty
+      type (diag_type), intent(inout) :: &amp;
          d             !&lt; Input/Output: diagnostic information
 
       !-----------------------------------------------------------------

Modified: branches/ocean_projects/advection_routines/src/operators/Makefile
===================================================================
--- branches/ocean_projects/advection_routines/src/operators/Makefile        2012-01-17 18:10:30 UTC (rev 1382)
+++ branches/ocean_projects/advection_routines/src/operators/Makefile        2012-01-17 19:22:35 UTC (rev 1383)
@@ -1,6 +1,6 @@
 .SUFFIXES: .F .o
 
-OBJS = mpas_rbf_interpolation.o mpas_vector_reconstruction.o mpas_spline_interpolation.o
+OBJS = mpas_rbf_interpolation.o mpas_vector_reconstruction.o mpas_spline_interpolation.o mpas_tracer_advection.o
 
 all: operators
 
@@ -8,9 +8,13 @@
         ar -ru libops.a $(OBJS)
 
 mpas_vector_reconstruction.o: mpas_rbf_interpolation.o
+
 mpas_rbf_interpolation.o:
+
 mpas_spline_interpolation:
 
+mpas_tracer_advection.o:
+
 clean:
         $(RM) *.o *.mod *.f90 libops.a
 

Modified: branches/ocean_projects/advection_routines/src/operators/mpas_tracer_advection.F
===================================================================
--- branches/ocean_projects/advection_routines/src/operators/mpas_tracer_advection.F        2012-01-17 18:10:30 UTC (rev 1382)
+++ branches/ocean_projects/advection_routines/src/operators/mpas_tracer_advection.F        2012-01-17 19:22:35 UTC (rev 1383)
@@ -2,15 +2,9 @@
 
    use mpas_grid_types
    use mpas_configure
-   use mpas_constants
-   use mpas_dmpar
-   use mpas_vector_reconstruction
-   ! Added only clause to keep xlf90 from getting confused from the overloaded abs intrinsic in mpas_timekeeping
-   use mpas_mpas_timekeeping, only: MPAS_Time_type, MPAS_TimeInterval_type, &amp;
-                               MPAS_setTime, MPAS_setTimeInterval, MPAS_getTime, operator(+)
 
-   use mpas_tracer_advection_std
-   use mpas_tracer_advection_mono
+!  use mpas_tracer_advection_std
+!  use mpas_tracer_advection_mono
      
    implicit none
    private
@@ -173,7 +167,7 @@
         
       end do ! end loop over edges
 
-   end subroutine adv_coef_compression!}}}
+   end subroutine mpas_tracer_advection_coefficients!}}}
 
    subroutine mpas_tracer_advection_tend(tend, s_old, s_new, diag, grid, dt, dminfo, cellsToSend, cellsToRecv)!{{{
 
@@ -188,9 +182,9 @@
       type (exchange_list), pointer :: cellsToSend, cellsToRecv
 
       if(monotonicOn) then
-         call mpas_tracer_advection_mono( tend, s_old, s_new, diag, grid, dt, dminfo, cellsToSend, cellsToRecv)
+!        call mpas_tracer_advection_mono( tend, s_old, s_new, diag, grid, dt, dminfo, cellsToSend, cellsToRecv)
       else
-         call mpas_tracer_advection_std(tend, s_old, s_new, diag, grid, dt)
+!        call mpas_tracer_advection_std(tend, s_old, s_new, diag, grid, dt)
       endif
    end subroutine!}}}
 
@@ -208,5 +202,4 @@
 
    end subroutine mpas_tracer_advection_init!}}}
 
-
 end module mpas_tracer_advection

Modified: branches/ocean_projects/advection_routines/src/operators/mpas_tracer_advection_mono.F
===================================================================
--- branches/ocean_projects/advection_routines/src/operators/mpas_tracer_advection_mono.F        2012-01-17 18:10:30 UTC (rev 1382)
+++ branches/ocean_projects/advection_routines/src/operators/mpas_tracer_advection_mono.F        2012-01-17 19:22:35 UTC (rev 1383)
@@ -2,13 +2,12 @@
 
    use mpas_grid_types
    use mpas_configure
-   use mpas_constants
    use mpas_dmpar
-   use mpas_vector_reconstruction
-   ! Added only clause to keep xlf90 from getting confused from the overloaded abs intrinsic in mpas_timekeeping
-   use mpas_mpas_timekeeping, only: MPAS_Time_type, MPAS_TimeInterval_type, &amp;
-                               MPAS_setTime, MPAS_setTimeInterval, MPAS_getTime, operator(+)
 
+   implicit none
+   private
+   save 
+
    contains
 
    subroutine mpas_tracer_advection_mono_tend( tend, s_old, s_new, diag, grid, dt, dminfo, cellsToSend, cellsToRecv)!{{{
@@ -17,7 +16,7 @@
    ! Input: s - current model state
    !        grid - grid metadata
    !
-      implicit none
+   !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 
 
       type (tend_type), intent(in) :: tend
       type (state_type), intent(in) :: s_old

Modified: branches/ocean_projects/advection_routines/src/operators/mpas_tracer_advection_std.F
===================================================================
--- branches/ocean_projects/advection_routines/src/operators/mpas_tracer_advection_std.F        2012-01-17 18:10:30 UTC (rev 1382)
+++ branches/ocean_projects/advection_routines/src/operators/mpas_tracer_advection_std.F        2012-01-17 19:22:35 UTC (rev 1383)
@@ -2,13 +2,12 @@
 
    use mpas_grid_types
    use mpas_configure
-   use mpas_constants
    use mpas_dmpar
-   use mpas_vector_reconstruction
-   ! Added only clause to keep xlf90 from getting confused from the overloaded abs intrinsic in mpas_timekeeping
-   use mpas_mpas_timekeeping, only: MPAS_Time_type, MPAS_TimeInterval_type, &amp;
-                               MPAS_setTime, MPAS_setTimeInterval, MPAS_getTime, operator(+)
 
+   implicit none
+   private
+   save
+
    contains
 
    subroutine mpas_tracer_advection_std_tend( tend, s_old, s_new, diag, grid, dt)!{{{
@@ -20,8 +19,6 @@
    ! Output: tend - computed scalar tendencies
    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 
 
-      implicit none
-
       type (tend_type), intent(in) :: tend
       type (state_type), intent(in) :: s_old
       type (state_type), intent(inout) :: s_new

</font>
</pre>