<p><b>dwj07@fsu.edu</b> 2013-01-08 15:22:11 -0700 (Tue, 08 Jan 2013)</p><p><br>
        -- BRANCH COMMIT --<br>
<br>
        Fixing coupling interval stuff with CESM.<br>
        Adding seaLevelPressure to pressure field.<br>
</p><hr noshade><pre><font color="gray">Modified: branches/ocean_projects/generic_forcing/src/core_ocean/Registry
===================================================================
--- branches/ocean_projects/generic_forcing/src/core_ocean/Registry        2013-01-07 21:47:07 UTC (rev 2377)
+++ branches/ocean_projects/generic_forcing/src/core_ocean/Registry        2013-01-08 22:22:11 UTC (rev 2378)
@@ -288,6 +288,7 @@
 var persistent real    windSrressReconstructMeridional ( nVertLevels nCells Time ) 2 o windStressReconstructMeridional state - -
 var persistent real    MontPot ( nVertLevels nCells Time ) 2 - MontPot state - -
 var persistent real    pressure ( nVertLevels nCells Time ) 2 - pressure state - -
+var persistent real    seaLevelPressure ( nCells Time ) 2 - seaLevelPressure state - -
 var persistent real    wTop ( nVertLevelsP1 nCells Time ) 2 - wTop state - -
 var persistent real    rhoDisplaced ( nVertLevels nCells Time ) 2 - rhoDisplaced state - -
 var persistent real    viscosity ( nVertLevels nEdges Time ) 2 o viscosity state - -
@@ -351,7 +352,6 @@
 var persistent real    iceRunoffFlux ( nCells Time ) 2 - iceRunoffFlux state - -
 var persistent real    shortWaveHeatFlux ( nCells Time ) 2 - shortWaveHeatFlux state - -
 var persistent real    rainFlux ( nCells Time ) 2 - rainFlux state - -
-var persistent real    seaLevelPressure ( nCells Time ) 2 - seaLevelPressure state - -
 var persistent real    iceFraction ( nCells Time ) 2 - iceFraction state - -
 var persistent real    prognosticCO2 ( nCells Time ) 2 - prognosticCO2 state - -
 var persistent real    diagnosticCO2 ( nCells Time ) 2 - diagnosticCO2 state - -

Modified: branches/ocean_projects/generic_forcing/src/core_ocean/mpas_ocn_mpas_core.F
===================================================================
--- branches/ocean_projects/generic_forcing/src/core_ocean/mpas_ocn_mpas_core.F        2013-01-07 21:47:07 UTC (rev 2377)
+++ branches/ocean_projects/generic_forcing/src/core_ocean/mpas_ocn_mpas_core.F        2013-01-08 22:22:11 UTC (rev 2378)
@@ -46,6 +46,7 @@
    integer, parameter :: outputAlarmID = 1
    integer, parameter :: restartAlarmID = 2
    integer, parameter :: statsAlarmID = 3
+   integer, parameter :: coupleAlarmID = 4
 
    type (timer_node), pointer :: globalDiagTimer, timeIntTimer
    type (timer_node), pointer :: initDiagSolveTimer

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        2013-01-07 21:47:07 UTC (rev 2377)
+++ branches/ocean_projects/generic_forcing/src/core_ocean/mpas_ocn_tendency.F        2013-01-08 22:22:11 UTC (rev 2378)
@@ -438,9 +438,9 @@
       real (kind=RKIND), dimension(:), allocatable:: pTop
 
       real (kind=RKIND), dimension(:), pointer :: &amp;
-        bottomDepth, fVertex, dvEdge, dcEdge, areaCell, areaTriangle, ssh
+        bottomDepth, fVertex, dvEdge, dcEdge, areaCell, areaTriangle, ssh, seaLevelPressure
       real (kind=RKIND), dimension(:,:), pointer :: &amp;
-        weightsOnEdge, kiteAreasOnVertex, h_edge, h, u, v, pressure,&amp;
+        weightsOnEdge, kiteAreasOnVertex, h_edge, h, u, v, pressure, &amp;
         circulation, vorticity, ke, ke_edge, MontPot, wTop, zMid, &amp;
         Vor_edge, Vor_vertex, Vor_cell, gradVor_n, gradVor_t, divergence, &amp;
         rho, temperature, salinity, kev, kevc, uBolusGM, uTransport
@@ -469,6 +469,7 @@
       rho         =&gt; s % rho % array
       MontPot     =&gt; s % MontPot % array
       pressure    =&gt; s % pressure % array
+      seaLevelPressure    =&gt; s % seaLevelPressure % array
       zMid        =&gt; s % zMid % array
       ssh         =&gt; s % ssh % array
       tracers     =&gt; s % tracers % array
@@ -817,7 +818,7 @@
         do iCell=1,nCells
            ! pressure for generalized coordinates
            ! assume atmospheric pressure at the surface is zero for now.
-           pressure(1,iCell) = rho(1,iCell)*gravity &amp;
+           pressure(1,iCell) = seaLevelPressure(iCell) + rho(1,iCell)*gravity &amp;
               * 0.5*h(1,iCell)
 
            do k=2,maxLevelCell(iCell)

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        2013-01-07 21:47:07 UTC (rev 2377)
+++ branches/ocean_projects/generic_forcing/src/ocean_cesm_driver/ocn_comp_mct.F        2013-01-08 22:22:11 UTC (rev 2378)
@@ -68,8 +68,6 @@
       cpl_diag_transp,     &amp;! flag id for computing diagnostics
       my_task
 
-  real (kind=RKIND), dimension(:,:,:,:), allocatable ::  SBUFF_SUM           ! accumulated sum of send buffer quantities
-                                                                             ! for averaging before being sent
    real (kind=RKIND) :: tlast_coupled
 
    integer  :: nsend, nrecv
@@ -83,7 +81,7 @@
    type (dm_info), pointer :: dminfo
    type (domain_type), pointer :: domain
    type (io_output_object), save :: output_obj
-   integer :: output_frame
+   integer :: output_frame, itimestep
 !  type (MPAS_Clock_type) :: clock
 
 !=======================================================================
@@ -139,6 +137,9 @@
 
     integer :: lbnum
 
+    type (MPAS_Time_Type) :: alarmStartTime
+    type (MPAS_TimeInterval_Type) :: alarmTimeStep
+
 !-----------------------------------------------------------------------
 !
 !  set cdata pointers
@@ -290,17 +291,11 @@
     call seq_timemgr_EClockGetData(EClock, dtime=ocn_cpl_dt)
     call convert_seconds_to_timestamp(ocn_cpl_dt, coupleTimeStamp)
 
-!-----------------------------------------------------------------------
-!
-!  get intial state from driver
-!
-!-----------------------------------------------------------------------
+    ! set coupling alarm
+    call mpas_set_timeInterval(alarmTimeStep, timeString=coupleTimeStamp, ierr=ierr)
+    alarmStartTime = currTime
+    call mpas_add_clock_alarm(clock, coupleAlarmID, alarmStartTime, alarmTimeStep, ierr=ierr)
 
-   call ocn_import_mct(x2o_o, errorCode)  
-   if (errorCode /= 0) then
-      call mpas_dmpar_global_abort('ERROR in ocn_import_mct')
-   endif
-
 !-----------------------------------------------------------------------
 !
 !  send intial state to driver
@@ -322,6 +317,17 @@
 !  call seq_infodata_PutData( infodata, ocn_nx = nx_global , ocn_ny = ny_global)
    call seq_infodata_PutData( infodata, ocn_prognostic=.true., ocnrof_prognostic=.true.)
 
+!-----------------------------------------------------------------------
+!
+!  get intial state from driver
+!
+!-----------------------------------------------------------------------
+
+   call ocn_import_mct(x2o_o, errorCode)  
+   if (errorCode /= 0) then
+      call mpas_dmpar_global_abort('ERROR in ocn_import_mct')
+   endif
+
 !----------------------------------------------------------------------------
 !
 ! Reset shr logging to original values
@@ -368,6 +374,14 @@
          call mpas_output_state_init(output_obj, domain, &quot;OUTPUT&quot;)         
       end if
 
+      call mpas_advance_clock(clock)
+      currTime = mpas_get_clock_time(clock, MPAS_NOW, ierr)
+      call mpas_get_time(curr_time=currTime, dateTimeString=timeStamp, ierr=ierr)
+      write(0,*) 'Initial time ', trim(timeStamp)
+
+      call ocn_write_output_frame(output_obj, output_frame, domain)
+      itimestep = 0
+
 !-----------------------------------------------------------------------
 !EOC
 
@@ -439,7 +453,8 @@
 !
 !    integer :: lbnum
 
-      integer :: itimestep
+      integer :: ymd, tod, ihour, iminute, isecond
+      integer :: iyear, imonth, iday, curr_ymd, curr_tod
       real (kind=RKIND) :: dt
       type (block_type), pointer :: block_ptr
 
@@ -447,40 +462,34 @@
       type (MPAS_TimeInterval_Type) :: alarmTimeStep
       character(len=StrKIND) :: timeStamp
       integer :: ierr
-      integer, parameter :: couplingAlarmID = 4
 
       ! Eventually, dt should be domain specific
       dt = config_dt
 
       currTime = mpas_get_clock_time(clock, MPAS_NOW, ierr)
-      call mpas_get_time(curr_time=currTime, dateTimeString=timeStamp, ierr=ierr)
-      write(0,*) 'Initial time ', trim(timeStamp)
+!     call mpas_get_time(curr_time=currTime, dateTimeString=timeStamp, ierr=ierr)
+!     write(0,*) 'Initial time ', trim(timeStamp)
 
-      ! set coupling alarm
-      call mpas_set_timeInterval(alarmTimeStep, timeString=coupleTimeStamp, ierr=ierr)
-      alarmStartTime = currTime
-      call mpas_add_clock_alarm(clock, couplingAlarmID, alarmStartTime, alarmTimeStep, ierr=ierr)
+!     call ocn_write_output_frame(output_obj, output_frame, domain)
 
-      call ocn_write_output_frame(output_obj, output_frame, domain)
       block_ptr =&gt; domain % blocklist
-
       do while(associated(block_ptr))
         call ocn_time_average_init(block_ptr % state % time_levs(1) % state)
         block_ptr =&gt; block_ptr % next
       end do
 
+      call ocn_import_mct(x2o_o, ierr)
+
       ! During integration, time level 1 stores the model state at the beginning of the
       !   time step, and time level 2 stores the state advanced dt in time by timestep(...)
-      itimestep = 0
-      do while (.not. mpas_is_clock_stop_time(clock))
-
+      do while (.not. mpas_is_alarm_ringing(clock,coupleAlarmID, ierr=ierr))
          itimestep = itimestep + 1
          call mpas_advance_clock(clock)
 
          currTime = mpas_get_clock_time(clock, MPAS_NOW, ierr)
          call mpas_get_time(curr_time=currTime, dateTimeString=timeStamp, ierr=ierr)
          write(0,*) 'Doing timestep ', trim(timeStamp)
-   
+
          block_ptr =&gt; domain % blocklist
          do while(associated(block_ptr))
            call ocn_build_forcing_arrays(currTime, block_ptr % mesh, block_ptr % state % time_levs(2) % state, ierr)
@@ -497,12 +506,6 @@
             call mpas_shift_time_levels_state(block_ptr % state)
             block_ptr =&gt; block_ptr % next
          end do
-
-         if (mpas_is_alarm_ringing(clock, couplingAlarmID, ierr=ierr)) then
-            call mpas_reset_clock_alarm(clock, couplingAlarmID, ierr=ierr)
-            call ocn_import_mct(x2o_o, ierr)
-            call ocn_export_mct(o2x_o, ierr)
-         end if
       
          if (mpas_is_alarm_ringing(clock, outputAlarmID, ierr=ierr)) then
             call mpas_reset_clock_alarm(clock, outputAlarmID, ierr=ierr)
@@ -535,119 +538,27 @@
             call mpas_output_state_for_domain(restart_obj, domain, 1)
             call mpas_output_state_finalize(restart_obj, domain % dminfo)
          end if
+      end do
 
-      end do
-!
-!#if (defined _MEMTRACE)
-!    if(my_task == 0 ) then
-!       lbnum=1
-!       call memmon_dump_fort('memmon.out',SubName//':start::',lbnum) 
-!    endif
-!#endif
-!
-!!-----------------------------------------------------------------------
-!!
-!!  start up the main timer
-!!
-!!-----------------------------------------------------------------------
-!
-!   call mpas_timer_start('total time')
-!
-!
-!!-----------------------------------------------------------------------
-!!
-!! reset shr logging to my log file
-!!
-!!----------------------------------------------------------------------------
-!
-!    errorCode = POP_Success
-!
-!    call shr_file_getLogUnit (shrlogunit)
-!    call shr_file_getLogLevel(shrloglev)
-!    call shr_file_setLogUnit (stdout)
-!
-!    call seq_cdata_setptrs(cdata_o, infodata=infodata)
-!
-!!----------------------------------------------------------------------------
-!!
-!! restart flag (rstwr) will assume only an eod restart for now
-!!
-!!----------------------------------------------------------------------------
-!
-!    call seq_infodata_GetData( infodata, info_debug=info_debug)
-!    if (info_debug &gt;= 2) then
-!       ldiag_cpl = .true. 
-!    else
-!       ldiag_cpl = .false.
-!    endif
-!
-!    rstwr = seq_timemgr_RestartAlarmIsOn(EClock)
-!
-!!-----------------------------------------------------------------------
-!!
-!!  advance the model in time over coupling interval
-!!  write restart dumps and archiving
-!!
-!!-----------------------------------------------------------------------
-!
-!    ! Note that all ocean time flags are evaluated each timestep in time_manager
-!    ! ocn_import_mct is analogous to pop_unpack_fluxes_from_coupler in cpl6 
-!    ! ocn_export_mct is analogous to prepare_send_to_coupler in cpl6
-!    ! tlast_coupled is set to zero at the end of ocn_export_mct
-!
-!    itimestep = 0
-!    timestep: do
-!       ! obtain import state from driver
-!       if (check_time_flag(cpl_ts) .or. nsteps_run == 0) then
-!          call ocn_import_mct(x2o_o, errorCode)   
-!
-!          if (errorCode /= POP_Success) then
-!             call POP_ErrorPrint(errorCode)
-!             call exit_POP(sigAbort, 'ERROR in step')
-!          endif
-!
-!          !DWJ Need to write on mpas side
-!!         call pop_set_coupled_forcing 
-!       end if
-!
-!
-!    end do timestep
-!
-!    advance: do 
-!
-!       call step(errorCode)
-!
-!       if (errorCode /= POP_Success) then
-!          call POP_ErrorPrint(errorCode)
-!          call exit_POP(sigAbort, 'ERROR in step')
-!       endif
-!
-!       if (check_KE(100.0_r8)) then
-!          !*** exit if energy is blowing
-!          call output_driver
-!          call exit_POP(sigAbort,'ERROR: k.e. &gt; 100 ')
-!       endif
-!       call output_driver
-!       
-!       ! return export state to driver
-!       call pop_sum_buffer()  
-!       if (check_time_flag(cpl_ts)) then
-!          call ocn_export_mct(o2x_o, errorCode)
-!          if (errorCode /= POP_Success) then
-!             call POP_ErrorPrint(errorCode)
-!             call exit_POP(sigAbort, 'ERROR in ocn_export_mct')
-!          endif
-!
-!          exit advance
-!       end if
-!       
-!    enddo advance
-!
-!    if ( lsend_precip_fact ) then
-!       precadj = precip_fact * 1.0e6_r8  
-!       call seq_infodata_PutData( infodata, precip_fact=precadj )
-!    end if
-!    
+      if (mpas_is_alarm_ringing(clock, coupleAlarmID, ierr=ierr)) then
+         call ocn_export_mct(o2x_o, ierr)
+         call mpas_reset_clock_alarm(clock, coupleAlarmID, ierr=ierr)
+      end if
+
+      currTime = mpas_get_clock_time(clock, MPAS_NOW, ierr)
+      call mpas_get_time(curr_time=currTime, YYYY=iyear, MM=imonth, DD=iday, H=ihour, M=iminute, S=isecond, ierr=ierr)
+      call seq_timemgr_EClockGetData(EClock, curr_ymd=curr_ymd, curr_tod=curr_tod)

+      ymd = iyear * 10000 + imonth*100 + iday
+      tod = ihour * 3600 + iminute * 60 + isecond
+      if (.not. seq_timemgr_EClockDateInSync( EClock, ymd, tod)) then
+         write(0,*) 'MPAS ymd=',ymd,' MPAS tod=', tod
+         write(0,*) 'sync ymd=',curr_ymd,' sync tod=', curr_tod
+         write(0,*) 'Internal mpas clock not in sync with sync clock'
+      end if
+
+
+
 !!--------------------------------------------------------------------
 !!
 !! check that internal clock is in sync with master clock
@@ -666,24 +577,7 @@
 !          &quot;:: Internal pop2 clock not in sync with Sync Clock&quot;)
 !    end if
 !   
-!!----------------------------------------------------------------------------
-!!
-!! Reset shr logging to original values
-!!
-!!----------------------------------------------------------------------------
-!
-!   call shr_file_setLogUnit (shrlogunit)
-!   call shr_file_setLogLevel(shrloglev)
-!
-!   call mpas_timer_stop('total time')
-!
-!#if (defined _MEMTRACE)
-!    if(my_task == 0) then
-!       lbnum=1
-!       call memmon_dump_fort('memmon.out',SubName//':end::',lbnum) 
-!       call memmon_reset_addr()
-!    endif
-!#endif
+
 !-----------------------------------------------------------------------
 !EOC
 

</font>
</pre>