<p><b>dwj07@fsu.edu</b> 2012-12-18 12:23:35 -0700 (Tue, 18 Dec 2012)</p><p><br>
        -- BRANCH COMMIT --<br>
<br>
        Adding first cut of short wave absorption.<br>
</p><hr noshade><pre><font color="gray">Modified: branches/ocean_projects/generic_forcing/namelist.input.ocean
===================================================================
--- branches/ocean_projects/generic_forcing/namelist.input.ocean        2012-12-18 02:14:46 UTC (rev 2355)
+++ branches/ocean_projects/generic_forcing/namelist.input.ocean        2012-12-18 19:23:35 UTC (rev 2356)
@@ -108,3 +108,13 @@
    config_restoreT_timescale = 90.0
    config_restoreS_timescale = 90.0
 /
+&amp;forcing
+   config_use_monthly_forcing = .false.
+   config_use_coupled_forcing = .false.
+   config_use_virtual_salinity_flux = .false.
+/
+&amp;forcing_sw
+   config_sw_absorption_type = 'jerlov'
+   config_jerlov_water_type = 5
+   config_fixed_jerlov_weights = .true.
+/

Modified: branches/ocean_projects/generic_forcing/src/core_ocean/Makefile
===================================================================
--- branches/ocean_projects/generic_forcing/src/core_ocean/Makefile        2012-12-18 02:14:46 UTC (rev 2355)
+++ branches/ocean_projects/generic_forcing/src/core_ocean/Makefile        2012-12-18 19:23:35 UTC (rev 2356)
@@ -49,6 +49,8 @@
            mpas_ocn_tracer_advection_std_vadv4.o \
            mpas_ocn_tracer_advection_mono.o \
            mpas_ocn_tracer_advection_helpers.o \
+           mpas_ocn_tracer_short_wave_absorption.o \
+           mpas_ocn_tracer_short_wave_absorption_jerlov.o \
        mpas_ocn_time_integration.o \
        mpas_ocn_time_integration_rk4.o \
        mpas_ocn_time_integration_split.o \
@@ -57,6 +59,7 @@
            mpas_ocn_equation_of_state_linear.o \
        mpas_ocn_global_diagnostics.o \
            mpas_ocn_time_average.o \
+           mpas_ocn_forcing_coupled.o \
            mpas_ocn_forcing_monthly.o \
            mpas_ocn_forcing.o \
            mpas_ocn_constants.o
@@ -162,6 +165,10 @@
 
 mpas_ocn_tracer_advection_helpers.o:
 
+mpas_ocn_tracer_short_wave_absorption.o: mpas_ocn_tracer_short_wave_absorption_jerlov.o
+
+mpas_ocn_tracer_short_wave_absorption_jerlov.o:
+
 mpas_ocn_restoring.o:
 
 mpas_ocn_vmix.o: mpas_ocn_vmix_coefs_const.o mpas_ocn_vmix_coefs_rich.o mpas_ocn_vmix_coefs_tanh.o
@@ -178,10 +185,12 @@
 
 mpas_ocn_equation_of_state_linear.o:
 
-mpas_ocn_forcing.o: mpas_ocn_forcing_monthly.o
+mpas_ocn_forcing.o: mpas_ocn_forcing_monthly.o mpas_ocn_forcing_coupled.o
 
 mpas_ocn_forcing_monthly.o:
 
+mpas_ocn_forcing_coupled.o: mpas_ocn_constants.o
+
 mpas_ocn_constants.o:
 
 mpas_ocn_mpas_core.o: mpas_ocn_test_cases.o \
@@ -217,6 +226,8 @@
                                           mpas_ocn_tracer_hmix_del2.o \
                                           mpas_ocn_tracer_hmix_del4.o \
                                           mpas_ocn_tracer_surface_flux.o \
+                                          mpas_ocn_tracer_short_wave_absorption.o \
+                                          mpas_ocn_tracer_short_wave_absorption_jerlov.o \
                                           mpas_ocn_vmix.o \
                                           mpas_ocn_vmix_coefs_const.o \
                                           mpas_ocn_vmix_coefs_rich.o \
@@ -242,6 +253,7 @@
                                           mpas_ocn_time_average.o \
                                           mpas_ocn_forcing.o \
                                           mpas_ocn_forcing_monthly.o \
+                                          mpas_ocn_forcing_coupled.o \
                                           mpas_ocn_constants.o
 
 clean:

Modified: branches/ocean_projects/generic_forcing/src/core_ocean/Registry
===================================================================
--- branches/ocean_projects/generic_forcing/src/core_ocean/Registry        2012-12-18 02:14:46 UTC (rev 2355)
+++ branches/ocean_projects/generic_forcing/src/core_ocean/Registry        2012-12-18 19:23:35 UTC (rev 2356)
@@ -96,7 +96,12 @@
 namelist logical   restore   config_restoreTS           false
 namelist real      restore   config_restoreT_timescale  90.0
 namelist real      restore   config_restoreS_timescale  90.0
-namelist logical   restore   config_use_monthly_forcing false
+namelist logical   forcing   config_use_monthly_forcing false
+namelist logical   forcing   config_use_coupled_forcing false
+namelist logical   forcing   config_use_virtual_salinity_flux false
+namelist character forcing_sw config_sw_absorption_type 'jerlov'
+namelist integer   forcing_sw config_jerlov_water_type  5
+namelist logical   forcing_sw config_fixed_jerlov_weights  .false.
 
 %
 % dim  type  name_in_file  name_in_code

Modified: branches/ocean_projects/generic_forcing/src/core_ocean/mpas_ocn_tendency.F
===================================================================
--- branches/ocean_projects/generic_forcing/src/core_ocean/mpas_ocn_tendency.F        2012-12-18 02:14:46 UTC (rev 2355)
+++ branches/ocean_projects/generic_forcing/src/core_ocean/mpas_ocn_tendency.F        2012-12-18 19:23:35 UTC (rev 2356)
@@ -292,6 +292,7 @@
       type (mesh_type), intent(in) :: grid !&lt; Input: Grid information
       real (kind=RKIND), intent(in) :: dt !&lt; Input: Time step
 
+      real (kind=RKIND), dimension(:), pointer :: shortWaveHeatFlux
       real (kind=RKIND), dimension(:,:), pointer :: surfaceTracerFlux
       real (kind=RKIND), dimension(:,:), pointer :: &amp;
         uTransport, h,wTop, h_edge, vertDiffTopOfCell, tend_h, uh
@@ -310,6 +311,9 @@
       vertDiffTopOfCell =&gt; d % vertDiffTopOfCell % array
 
       surfaceTracerFlux =&gt; grid % surfaceTracerFlux % array
+#ifdef MPAS_CESM
+      shortWaveHeatFlux =&gt; grid % shortWaveHeatFlux % array
+#endif 
 
       tend_tr     =&gt; tend % tracers % array
       tend_h      =&gt; tend % h % array
@@ -383,6 +387,12 @@
       call ocn_tracer_surface_flux_tend(grid, surfaceTracerFlux, tend_tr, err)
       call mpas_timer_stop(&quot;surfaceTracerFlux&quot;)
 
+#ifdef MPAS_CESM
+      call mpas_timer_start(&quot;short wave&quot;, .false.)
+      call ocn_tracer_short_wave_absorption_tend(grid, tend_tr % index_temperature, h, shortWaveHeatFlux, tend_tr, err)
+      call mpas_timer_stop(&quot;short wave&quot;)
+#endif
+
  10   format(2i8,10e20.10)
       call mpas_timer_stop(&quot;ocn_tend_scalar&quot;)
 

Added: branches/ocean_projects/generic_forcing/src/core_ocean/mpas_ocn_tracer_short_wave_absorption.F
===================================================================
--- branches/ocean_projects/generic_forcing/src/core_ocean/mpas_ocn_tracer_short_wave_absorption.F                                (rev 0)
+++ branches/ocean_projects/generic_forcing/src/core_ocean/mpas_ocn_tracer_short_wave_absorption.F        2012-12-18 19:23:35 UTC (rev 2356)
@@ -0,0 +1,156 @@
+!|||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
+!
+!  ocn_tracer_short_wave_absorption
+!
+!&gt; \brief MPAS ocean tracer short wave
+!&gt; \author Doug Jacobsen
+!&gt; \date   12/17/12
+!&gt; \version SVN:$Id:$
+!&gt; \details
+!&gt;  This module contains the routine for computing 
+!&gt;  short wave tendencies
+!
+!-----------------------------------------------------------------------
+
+module ocn_tracer_short_wave_absorption
+
+   use mpas_grid_types
+   use mpas_configure
+   use ocn_tracer_short_wave_absorption_jerlov
+
+   implicit none
+   private
+   save
+
+   !--------------------------------------------------------------------
+   !
+   ! Public parameters
+   !
+   !--------------------------------------------------------------------
+
+   !--------------------------------------------------------------------
+   !
+   ! Public member functions
+   !
+   !--------------------------------------------------------------------
+
+   public :: ocn_tracer_short_wave_absorption_tend, &amp;
+             ocn_tracer_short_wave_absorption_init
+
+   !--------------------------------------------------------------------
+   !
+   ! Private module variables
+   !
+   !--------------------------------------------------------------------
+
+   logical :: useJerlov
+
+!***********************************************************************
+
+contains
+
+!***********************************************************************
+!
+!  routine ocn_tracer_short_wave_absorption_tend
+!
+!&gt; \brief   Computes tendency term for surface fluxes
+!&gt; \author  Doug Jacobsen
+!&gt; \date    12/17/12
+!&gt; \version SVN:$Id$
+!&gt; \details 
+!&gt;  This routine computes the tendency for tracers based on surface fluxes.
+!
+!-----------------------------------------------------------------------
+
+   subroutine ocn_tracer_short_wave_absorption_tend(grid, index_temperature, h, shortWaveHeatFlux, tend, err)!{{{
+
+      !-----------------------------------------------------------------
+      !
+      ! input variables
+      !
+      !-----------------------------------------------------------------
+
+      type (mesh_type), intent(in) :: &amp;
+         grid          !&lt; Input: grid information
+
+      real (kind=RKIND), dimension(:,:), intent(in) :: &amp;
+        shortWaveHeatFlux !&lt; Input: short wave heat flux
+
+      real (kind=RKIND), dimension(:,:), intent(in) :: h !&lt; Input: Layer thicknesses
+
+      integer, intent(in) :: index_temperature
+
+      !-----------------------------------------------------------------
+      !
+      ! 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
+      !
+      !-----------------------------------------------------------------
+
+      err = 0
+
+      if(useJerlov) then
+         call mpas_ocn_tracer_short_wave_absorption_jerlov_tend(grid, index_temperature, h, shortWaveHeatFlux, tend, err)
+      end if
+
+   !--------------------------------------------------------------------
+
+   end subroutine ocn_tracer_short_wave_absorption_tend!}}}
+
+!***********************************************************************
+!
+!  routine ocn_tracer_short_wave_absorption_init
+!
+!&gt; \brief   Initializes ocean tracer surface flux quantities
+!&gt; \author  Doug Jacobsen
+!&gt; \date    12/17/12
+!&gt; \version SVN:$Id$
+!&gt; \details 
+!&gt;  This routine initializes quantities related to surface fluxes in the ocean.
+!
+!-----------------------------------------------------------------------
+
+   subroutine ocn_tracer_short_wave_absorption_init(err)!{{{
+
+   !--------------------------------------------------------------------
+
+      integer, intent(out) :: err !&lt; Output: error flag
+
+      err = 0
+
+      useJerlov = .false.
+
+      if(trim(config_sw_absorption_type) .ne. 'jerlov') then
+        write(0,*) 'Incorrect option for config_sw_absorption_type. Options are: jerlov'
+        err = 1
+        return
+      else if(trim(config_sw_absorption_type) == 'jerlov') then
+        useJerlov = .true.
+        call mpas_ocn_tracer_short_wave_absorption_jerlov_init(err)
+      end if
+
+
+   end subroutine ocn_tracer_short_wave_absorption_init!}}}
+
+!***********************************************************************
+
+end module ocn_tracer_short_wave_absorption
+
+!|||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
+! vim: foldmethod=marker

Added: branches/ocean_projects/generic_forcing/src/core_ocean/mpas_ocn_tracer_short_wave_absorption_jerlov.F
===================================================================
--- branches/ocean_projects/generic_forcing/src/core_ocean/mpas_ocn_tracer_short_wave_absorption_jerlov.F                                (rev 0)
+++ branches/ocean_projects/generic_forcing/src/core_ocean/mpas_ocn_tracer_short_wave_absorption_jerlov.F        2012-12-18 19:23:35 UTC (rev 2356)
@@ -0,0 +1,252 @@
+!|||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
+!
+!  ocn_tracer_short_wave_absorption_jerlov
+!
+!&gt; \brief MPAS ocean tracer short wave
+!&gt; \author Doug Jacobsen
+!&gt; \date   12/17/12
+!&gt; \version SVN:$Id:$
+!&gt; \details
+!&gt;  This module contains the routine for computing 
+!&gt;  short wave tendencies using Jerlov
+!
+!-----------------------------------------------------------------------
+
+module ocn_tracer_short_wave_absorption_jerlov
+
+   use mpas_grid_types
+   use mpas_configure
+
+   implicit none
+   private
+   save
+
+   !--------------------------------------------------------------------
+   !
+   ! Public parameters
+   !
+   !--------------------------------------------------------------------
+
+   !--------------------------------------------------------------------
+   !
+   ! Public member functions
+   !
+   !--------------------------------------------------------------------
+
+   public :: ocn_tracer_short_wave_absorption_jerlov_tend, &amp;
+             ocn_tracer_short_wave_absorption_jerlov_init
+
+   !--------------------------------------------------------------------
+   !
+   ! Private module variables
+   !
+   !--------------------------------------------------------------------
+
+
+   integer, parameter :: num_water_types = 5
+
+   !-----------------------------------------------------------------------
+   !
+   !   define Jerlov water properties with rfac, depth1, depth2
+   !     Jerlov water type :  I       IA      IB      II      III
+   !     jerlov_water_type :  1       2       3       4       5
+   !
+   !-----------------------------------------------------------------------
+
+   real (kind=RKIND), dimension(num_water_types) ::                       &amp;
+      rfac   = (/ 0.58_RKIND, 0.62_RKIND, 0.67_RKIND, 0.77_RKIND, 0.78_RKIND /), &amp;
+      depth1 = (/ 0.35_RKIND, 0.60_RKIND, 1.00_RKIND, 1.50_RKIND, 1.40_RKIND /), &amp;
+      depth2 = (/ 23.0_RKIND, 20.0_RKIND, 17.0_RKIND, 14.0_RKIND, 7.90_RKIND /)
+
+!***********************************************************************
+
+contains
+
+!***********************************************************************
+!
+!  routine ocn_tracer_short_wave_absorption_jerlov_tend
+!
+!&gt; \brief   Computes tendency term for surface fluxes
+!&gt; \author  Doug Jacobsen
+!&gt; \date    12/17/12
+!&gt; \version SVN:$Id$
+!&gt; \details 
+!&gt;  This routine computes the tendency for tracers based on surface fluxes.
+!
+!-----------------------------------------------------------------------
+
+   subroutine ocn_tracer_short_wave_absorption_jerlov_tend(grid, index_temperature, h, shortWaveHeatFlux, tend, err)!{{{
+
+      !-----------------------------------------------------------------
+      !
+      ! input variables
+      !
+      !-----------------------------------------------------------------
+
+      type (mesh_type), intent(in) :: &amp;
+         grid          !&lt; Input: grid information
+
+      real (kind=RKIND), dimension(:), intent(in) :: &amp;
+        shortWaveHeatFlux !&lt; Input: short wave heat flux
+
+      real (kind=RKIND), dimension(:,:), intent(in) :: h !&lt; Input: Layer thicknesses
+
+      integer, intent(in) :: index_temperature
+
+      !-----------------------------------------------------------------
+      !
+      ! 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 :: iCell, nCells, k, nVertLevels
+
+      integer, dimension(:), pointer :: maxLevelCell
+
+      real (kind=RKIND) :: depth
+      real (kind=RKIND), dimension(:), pointer :: hZLevel
+      real (kind=RKIND), dimension(:), allocatable :: weights
+
+      err = 0
+
+      nCells = grid % nCells
+      nVertLevels = grid % nVertLevels
+
+      maxLevelCell =&gt; grid % maxLevelCell % array
+      hZLevel =&gt; grid % hZLevel % array
+
+      allocate(weights(nVertLevels+1))
+      weights = 0.0_RKIND
+      weights(1) = 1.0_RKIND
+
+      if(config_fixed_jerlov_weights) then
+         do iCell = 1, nCells
+           depth = 0.0_RKIND
+           do k =1, maxLevelCell(iCell)
+             depth = depth + hZLevel(k)
+
+             call ocn_get_jerlov_fraction(depth, weights(k))
+             tend(index_temperature, k, iCell) = tend(index_temperature, k, iCell) + shortWaveHeatFlux(iCell)*(weights(k) - weights(k+1)) / h(k, iCell)
+           end do
+         end do
+      else
+         do iCell = 1, nCells
+           depth = 0.0_RKIND
+           do k =1, maxLevelCell(iCell)
+             depth = depth + h(k, iCell)
+
+             call ocn_get_jerlov_fraction(depth, weights(k))
+             tend(index_temperature, k, iCell) = tend(index_temperature, k, iCell) + shortWaveHeatFlux(iCell)*(weights(k) - weights(k+1)) / h(k, iCell)
+           end do
+         end do
+      end if
+
+      deallocate(weights)
+
+   !--------------------------------------------------------------------
+
+   end subroutine ocn_tracer_short_wave_absorption_jerlov_tend!}}}
+
+!***********************************************************************
+!
+!  routine ocn_tracer_short_wave_absorption_jerlov_init
+!
+!&gt; \brief   Initializes ocean tracer surface flux quantities
+!&gt; \author  Doug Jacobsen
+!&gt; \date    12/17/12
+!&gt; \version SVN:$Id$
+!&gt; \details 
+!&gt;  This routine initializes quantities related to surface fluxes in the ocean.
+!
+!-----------------------------------------------------------------------
+
+   subroutine ocn_tracer_short_wave_absorption_jerlov_init(grid, err)!{{{
+
+   !--------------------------------------------------------------------
+
+      type (mesh_type), intent(in) :: &amp;
+         grid          !&lt; Input: grid information
+
+      integer, intent(out) :: err !&lt; Output: error flag
+
+      err = 0
+
+      if(trim(config_sw_absorption_type) .ne. 'jerlov') then
+        write(0,*) 'Incorrect option for config_sw_absorption_type. Options are: jerlov'
+        err = 1
+        return
+      end if
+
+   end subroutine ocn_tracer_short_wave_absorption_jerlov_init!}}}
+
+!***********************************************************************
+
+!***********************************************************************
+!
+!  routine ocn_init_jerlov_fractions
+!
+!&gt; \brief   Initializes short wave absorption fractions
+!&gt; \author  Doug Jacobsen
+!&gt; \date    12/17/12
+!&gt; \version SVN:$Id$
+!&gt; \details 
+!&gt;  Computes fraction of solar short-wave flux penetrating to
+!&gt;  specified depth due to exponential decay in Jerlov water type.
+!&gt;  Reference : two band solar absorption model of Simpson and
+!&gt;     Paulson (1977)
+!
+!-----------------------------------------------------------------------
+   subroutine ocn_get_jerlov_fraction(depth, weight)!{{{
+!  Note: below 200m the solar penetration gets set to zero,
+!     otherwise the limit for the exponent ($+/- 5678$) needs to be 
+!     taken care of.
+
+      real (kind=RKIND), intent(in) :: depth !&lt; Input: Depth of bottom of cell
+      real (kind=RKIND), intent(out) :: weight !&lt; Output: Weight for Jerlov absorption
+
+!-----------------------------------------------------------------------
+!
+!  local variables
+!
+!-----------------------------------------------------------------------
+
+      integer :: k, nVertLevels
+      integer,  parameter :: num_water_types = 5  ! max number of different water types
+   
+      real (kind=RKIND), parameter :: depth_cutoff = -200.0_RKIND
+   
+!-----------------------------------------------------------------------
+!
+!  compute absorption fraction
+!
+!-----------------------------------------------------------------------
+
+      if (-depth &lt; depth_cutoff) then
+         weight = 0.0_RKIND
+      else
+         weight = rfac(config_jerlov_water_type) * exp(-depth/depth1(config_jerlov_water_type)) &amp;
+                  + (1.0_RKIND - rfac(config_jerlov_water_type)) * exp(-depth/depth2(config_jerlov_water_type))
+      endif
+   end subroutine ocn_get_jerlov_fraction!}}}
+
+end module ocn_tracer_short_wave_absorption_jerlov
+
+!|||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||||
+! vim: foldmethod=marker

Modified: branches/ocean_projects/generic_forcing/src/ocean_cesm_driver/ocn_comp_mct.F
===================================================================
--- branches/ocean_projects/generic_forcing/src/ocean_cesm_driver/ocn_comp_mct.F        2012-12-18 02:14:46 UTC (rev 2355)
+++ branches/ocean_projects/generic_forcing/src/ocean_cesm_driver/ocn_comp_mct.F        2012-12-18 19:23:35 UTC (rev 2356)
@@ -1024,7 +1024,7 @@
         block_ptr % mesh % riverRunoffFlux % array(n) = x2o_o % rAttr(index_x2o_Forr_roff, n)
         block_ptr % mesh % iceRunoffFlux % array(n) = x2o_o % rAttr(index_x2o_Forr_ioff, n)
 
-        block_ptr % mesh % shortWaveHeatFlux % array(n) = x2o_o % rAttr(index_x2o_Foxx_swnet, n)
+        block_ptr % mesh % shortWaveHeatFlux % array(n) = max(x2o_o % rAttr(index_x2o_Foxx_swnet, n), 0.0_RKIND)
 
         block_ptr % mesh % rainFlux % array(n) = x2o_o % rAttr(index_x2o_Faxa_rain, n)
         block_ptr % mesh % seaLevelPressure % array(n) = x2o_o % rAttr(index_x2o_Sa_pslv, n)

</font>
</pre>