<p><b>dwj07@fsu.edu</b> 2012-11-14 11:06:45 -0700 (Wed, 14 Nov 2012)</p><p><br>
 -- BRANCH COMMIT --<br>
<br>
 Updating CESM coupling branch.<br>
<br>
 MPAS-O Can now run in standalone mode (no forcing) within the CESM.<br>
</p><hr noshade><pre><font color="gray">Modified: branches/ocean_projects/cesm_coupling/src/core_ocean/Registry
===================================================================
--- branches/ocean_projects/cesm_coupling/src/core_ocean/Registry        2012-11-13 18:31:40 UTC (rev 2303)
+++ branches/ocean_projects/cesm_coupling/src/core_ocean/Registry        2012-11-14 18:06:45 UTC (rev 2304)
@@ -14,6 +14,7 @@
 namelist logical   sw_model config_prescribe_velocity  false
 namelist logical   sw_model config_prescribe_thickness false
 namelist integer   sw_model config_num_halos           3
+namelist integer   sw_model config_ncouple_per_day     1
 namelist character io       config_input_name          grid.nc
 namelist character io       config_output_name         output.nc
 namelist character io       config_restart_name        restart.nc
@@ -104,7 +105,7 @@
 dim vertexDegree vertexDegree
 dim nVertLevels nVertLevels
 dim nVertLevelsP1 nVertLevels+1
-dim nMonths nMonths
+%dim nMonths 1
 
 %
 % var persistence type  name_in_file  ( dims )  time_levs iro-  name_in_code struct super-array array_class
@@ -200,7 +201,7 @@
 % Boundary conditions: read from input, saved in restart and written to output
 var persistent integer boundaryEdge ( nVertLevels nEdges ) 0 iro boundaryEdge mesh - -
 var persistent integer boundaryVertex ( nVertLevels nVertices ) 0 iro boundaryVertex mesh - -
-var persistent integer boundaryCell ( nVertLevels nCells ) 0 iro boundaryCell mesh - -
+var persistent integer boundaryCell ( nVertLevels nCells ) 0 - boundaryCell mesh - -
 var persistent integer edgeMask ( nVertLevels nEdges ) 0 o edgeMask mesh - -
 var persistent integer vertexMask ( nVertLevels nVertices ) 0 o vertexMask mesh - -
 var persistent integer cellMask ( nVertLevels nCells ) 0 o cellMask mesh - -
@@ -209,9 +210,9 @@
 var persistent real    salinityRestore ( nCells ) 0 iro salinityRestore mesh - -
 
 % mrp trying to figure out why these do not appear
-var persistent real    windStressMonthly ( nMonths nEdges ) 0 iro windStressMonthly mesh - -
-var persistent real    temperatureRestoreMonthly ( nMonths nCells ) 0 iro temperatureRestoreMonthly mesh - -
-var persistent real    salinityRestoreMonthly ( nMonths nCells ) 0 iro salinityRestoreMonthly mesh - -
+%var persistent real    windStressMonthly ( nMonths nEdges ) 0 - windStressMonthly mesh - -
+%var persistent real    temperatureRestoreMonthly ( nMonths nCells ) 0 - temperatureRestoreMonthly mesh - -
+%var persistent real    salinityRestoreMonthly ( nMonths nCells ) 0 - salinityRestoreMonthly mesh - -
 
 % Prognostic variables: read from input, saved in restart, and written to output
 var persistent real    u ( nVertLevels nEdges Time ) 2 ir u state - -
@@ -239,7 +240,7 @@
 var persistent real   uBcl ( nVertLevels nEdges Time )  2 - uBcl state - - 
 
 % Diagnostic fields: only written to output
-var persistent real    zMid ( nVertLevels nCells Time ) 2 io zMid state - -
+var persistent real    zMid ( nVertLevels nCells Time ) 2 - zMid state - -
 var persistent real    v ( nVertLevels nEdges Time ) 2 - v state - -
 var persistent real    uTransport ( nVertLevels nEdges Time ) 2 - uTransport state - -
 var persistent real    uBolusGM ( nVertLevels nEdges Time ) 2 - uBolusGM state - -

Modified: branches/ocean_projects/cesm_coupling/src/core_ocean/mpas_ocn_monthly_forcing.F
===================================================================
--- branches/ocean_projects/cesm_coupling/src/core_ocean/mpas_ocn_monthly_forcing.F        2012-11-13 18:31:40 UTC (rev 2303)
+++ branches/ocean_projects/cesm_coupling/src/core_ocean/mpas_ocn_monthly_forcing.F        2012-11-14 18:06:45 UTC (rev 2304)
@@ -113,41 +113,41 @@
 
       nCells = grid % nCells
       nEdges = grid % nEdges
-      nMonths = grid % nMonths
+!     nMonths = grid % nMonths
 
       temperatureRestore =&gt; grid % temperatureRestore % array
       salinityRestore =&gt; grid % salinityRestore % array
       u_src =&gt; grid % u_src % array
 
-      temperatureRestoreMonthly =&gt; grid % temperatureRestoreMonthly % array
-      salinityRestoreMonthly =&gt; grid % salinityRestoreMonthly % array
-      windStressMonthly =&gt; grid % windStressMonthly % array
+!     temperatureRestoreMonthly =&gt; grid % temperatureRestoreMonthly % array
+!     salinityRestoreMonthly =&gt; grid % salinityRestoreMonthly % array
+!     windStressMonthly =&gt; grid % windStressMonthly % array
 
       call mpas_get_time(timeStamp, MM = iMonth, DD = iDayInMonth, ierr = ierr)
 
       err = ierr
 
-      iMonthP1 = mod(iMonth, nMonths) + 1
+!     iMonthP1 = mod(iMonth, nMonths) + 1
 
       weight = 1.0 - (iDayInMonth-1) / 30.0
       weightP1 = 1.0 - weight
 
-      do iCell=1,nCells
-        ! Interpolate between iMonth and iMonthP1 records, using iDayInMonth
-        data = temperatureRestoreMonthly(iMonth,iCell)
-        dataP1 = temperatureRestoreMonthly(iMonthP1,iCell)
-        temperatureRestore(iCell) = data * weight + dataP1 * weightP1
-        data = salinityRestoreMonthly(iMonth,iCell)
-        dataP1 = salinityRestoreMonthly(iMonthP1,iCell)
-        salinityRestore(iCell) = data * weight + dataP1 * weightP1
-      end do
+!     do iCell=1,nCells
+!       ! Interpolate between iMonth and iMonthP1 records, using iDayInMonth
+!       data = temperatureRestoreMonthly(iMonth,iCell)
+!       dataP1 = temperatureRestoreMonthly(iMonthP1,iCell)
+!       temperatureRestore(iCell) = data * weight + dataP1 * weightP1
+!       data = salinityRestoreMonthly(iMonth,iCell)
+!       dataP1 = salinityRestoreMonthly(iMonthP1,iCell)
+!       salinityRestore(iCell) = data * weight + dataP1 * weightP1
+!     end do
 
-      do iEdge=1,nEdges
-        ! Interpolate between iMonth and iMonthP1 records, using iDayInMonth
-        data = windStressMonthly(iMonth,iEdge)
-        dataP1 = windStressMonthly(iMonthP1,iEdge)
-        u_src(1,iEdge) = data * weight + dataP1 * weightP1
-      end do
+!     do iEdge=1,nEdges
+!       ! Interpolate between iMonth and iMonthP1 records, using iDayInMonth
+!       data = windStressMonthly(iMonth,iEdge)
+!       dataP1 = windStressMonthly(iMonthP1,iEdge)
+!       u_src(1,iEdge) = data * weight + dataP1 * weightP1
+!     end do
 
    !--------------------------------------------------------------------
 

Modified: branches/ocean_projects/cesm_coupling/src/framework/mpas_dmpar.F
===================================================================
--- branches/ocean_projects/cesm_coupling/src/framework/mpas_dmpar.F        2012-11-13 18:31:40 UTC (rev 2303)
+++ branches/ocean_projects/cesm_coupling/src/framework/mpas_dmpar.F        2012-11-14 18:06:45 UTC (rev 2304)
@@ -83,7 +83,9 @@
          dminfo % comm = mpi_comm
          dminfo % using_external_comm = .true.
       else
+#ifndef MPAS_CESM
          call MPI_Init(mpi_ierr)
+#endif
          dminfo % comm = MPI_COMM_WORLD
          dminfo % using_external_comm = .false.
       end if
@@ -98,7 +100,7 @@
       write(0,'(a,i5,a,i5,a)') 'task ', mpi_rank, ' of ', mpi_size, &amp;
         ' is running'
 
-      call open_streams(dminfo % my_proc_id)
+!     call open_streams(dminfo % my_proc_id)
 
       dminfo % info = MPI_INFO_NULL
 #else
@@ -119,10 +121,12 @@
 #ifdef _MPI
       integer :: mpi_ierr
 
+#ifndef MPAS_CESM
       if (.not. dminfo % using_external_comm) then
          call MPI_Finalize(mpi_ierr)
       end if
 #endif
+#endif
 
    end subroutine mpas_dmpar_finalize!}}}
 

Modified: branches/ocean_projects/cesm_coupling/src/framework/mpas_io.F
===================================================================
--- branches/ocean_projects/cesm_coupling/src/framework/mpas_io.F        2012-11-13 18:31:40 UTC (rev 2303)
+++ branches/ocean_projects/cesm_coupling/src/framework/mpas_io.F        2012-11-14 18:06:45 UTC (rev 2304)
@@ -518,6 +518,7 @@
       logical :: found
       integer :: pio_ierr
 
+          write(0,*) 'Inq var ', trim(fieldname)
       if (present(ierr)) ierr = MPAS_IO_NOERR
 
       ! Sanity checks

Modified: branches/ocean_projects/cesm_coupling/src/ocean_cesm_driver/ocn_comp_mct.F
===================================================================
--- branches/ocean_projects/cesm_coupling/src/ocean_cesm_driver/ocn_comp_mct.F        2012-11-13 18:31:40 UTC (rev 2303)
+++ branches/ocean_projects/cesm_coupling/src/ocean_cesm_driver/ocn_comp_mct.F        2012-11-14 18:06:45 UTC (rev 2304)
@@ -82,6 +82,7 @@
    type (domain_type), pointer :: domain
    type (io_output_object), save :: output_obj
    integer :: output_frame
+!  type (MPAS_Clock_type) :: clock
 
 !=======================================================================
 
@@ -127,7 +128,9 @@
 
     real (kind=RKIND) :: precadj
 
+    type (MPAS_Time_Type) :: currTime
     integer :: iam,ierr 
+    integer :: iyear0, imonth0
     character(len=StrKIND)  :: starttype          ! infodata start type
     character(len=StrKIND)  :: timeStamp
     character(len=StrKIND)  :: nml_filename
@@ -178,7 +181,6 @@
     call seq_infodata_GetData( infodata, start_type=starttype)
 
 
-    !!!DWJ CHECK RUN TYPES
     if (     trim(starttype) == trim(seq_infodata_start_type_start)) then
        runtype = &quot;initial&quot;
     else if (trim(starttype) == trim(seq_infodata_start_type_cont) ) then
@@ -188,10 +190,6 @@
     else
        call mpas_dmpar_global_abort(' ocn_comp_mct ERROR: unknown starttype')
     end if
-    !!!DWJ CHECK RUN TYPES
-
-
-    !TODO: check for consistency of pop runid and runtype with seq_infodata
    
 !-----------------------------------------------------------------------
 !
@@ -209,24 +207,17 @@
    call t_startf('mpas-o_init')
    nml_filename = &quot;mpaso.in&quot;
 
-   write(6,*) 'Getting iosys pointer'
    io_system =&gt; shr_pio_getiosys(ocnid)
-   write(6,*) 'Setting iosys pointer'
    call mpas_io_set_iosys(io_system)
 
-
-   write(6,*) 'Init framework'
    call mpas_framework_init(dminfo, domain, mpi_communicator_ocn, nml_filename)
 
    my_task = dminfo % my_proc_id
+   call mpas_timer_start(&quot;total time&quot;)
 
-
-   write(6,*) 'Input state'
    call mpas_input_state_for_domain(domain)
 
-   write(6,*) 'Init core'
    call mpas_core_init(domain, timeStamp)
-   write(6,*) 'Init complete'
 
 !-----------------------------------------------------------------------
 !
@@ -242,9 +233,9 @@
 !
 !----------------------------------------------------------------------------
 
-    call shr_file_getLogUnit (shrlogunit)
-    call shr_file_getLogLevel(shrloglev)
-!   call shr_file_setLogUnit (stdout)
+   call shr_file_getLogUnit (shrlogunit)
+   call shr_file_getLogLevel(shrloglev)
+!  call shr_file_setLogUnit (stdout)
    
 !-----------------------------------------------------------------------
 !
@@ -252,25 +243,19 @@
 !
 !-----------------------------------------------------------------------
 
-!  if (runtype == 'initial') then
-!     call seq_timemgr_EClockGetData(EClock, &amp;
-!          start_ymd=start_ymd, start_tod=start_tod)
-!     call shr_cal_date2ymd(start_ymd,start_year,start_month,start_day)
+  if (runtype == 'initial') then
+     currTime = mpas_get_clock_time(clock, MPAS_NOW, ierr)
+     call mpas_get_time(curr_time=currTime, YYYY=iyear0, MM=imonth0, ierr=ierr)
+     call seq_timemgr_EClockGetData(EClock, start_ymd=start_ymd, start_tod=start_tod)
+     call shr_cal_date2ymd(start_ymd,start_year,start_month,start_day)
 
-!     if (iyear0 /= start_year) then
-!        call mpas_dmpar_global_abort(' iyear0 does not match start_year')
-!     end if
-!     if (imonth0 /= start_month) then
-!        call mpas_dmpar_global_abort(' imonth0 does not match start_year')
-!     end if
-!#ifndef _HIRES 
-!      if (seconds_this_day /= start_tod) then
-!         call document ('ocn_init_mct', 'sec0     ', seconds_this_day)
-!         call document ('ocn_init_mct', 'start_tod ', start_tod)
-!         call exit_POP(sigAbort,' sec0 does not start_tod')
-!      end if
-!#endif
-!  end if
+     if (iyear0 /= start_year) then
+        call mpas_dmpar_global_abort(' iyear0 does not match start_year')
+     end if
+     if (imonth0 /= start_month) then
+        call mpas_dmpar_global_abort(' imonth0 does not match start_year')
+     end if
+  end if
 
 !-----------------------------------------------------------------------
 !
@@ -305,12 +290,12 @@
 !-----------------------------------------------------------------------
 
     call seq_timemgr_EClockGetData(EClock, dtime=ocn_cpl_dt)
-!   mpas_o_cpl_dt = seconds_in_day / ncouple_per_day
-!   if (mpas_o_cpl_dt /= ocn_cpl_dt) then
-!      write(stdout,*)'mpas-o_cpl_dt= ',mpas_o_cpl_dt, &amp;
-!                    ' ocn_cpl_dt= ',ocn_cpl_dt   
-!      call mpas_dmpar_global_abort('ERROR mpas-o_cpl_dt and ocn_cpl_dt must be identical')
-!   end if
+    mpas_o_cpl_dt = 86400 / config_ncouple_per_day
+    if (mpas_o_cpl_dt /= ocn_cpl_dt) then
+       write(0,*)'mpas-o_cpl_dt= ',mpas_o_cpl_dt, &amp;
+                     ' ocn_cpl_dt= ',ocn_cpl_dt   
+       call mpas_dmpar_global_abort('ERROR mpas-o_cpl_dt and ocn_cpl_dt must be identical')
+    end if
 
 !-----------------------------------------------------------------------
 !
@@ -344,7 +329,6 @@
 
 #if (defined _MEMTRACE)
     if(iam  == 0) then
-!        write(6,*) 'ocn_init_mct:end::'
         lbnum=1
         call memmon_dump_fort('memmon.out','ocn_init_mct:end::',lbnum) 
         call memmon_reset_addr()
@@ -369,6 +353,17 @@
 #endif
 !  endif
 
+      !
+      ! Set up output streams to be written to by the MPAS core
+      !
+      output_frame = 1
+
+      if(config_frames_per_outfile &gt; 0) then
+         call mpas_output_state_init(output_obj, domain, &quot;OUTPUT&quot;, trim(timeStamp))
+      else
+         call mpas_output_state_init(output_obj, domain, &quot;OUTPUT&quot;)         
+      end if
+
 !-----------------------------------------------------------------------
 !EOC
 
@@ -439,6 +434,92 @@
 !    integer(int_kind) :: info_debug
 !
 !    integer :: lbnum
+
+      integer :: itimestep
+      real (kind=RKIND) :: dt
+      type (block_type), pointer :: block_ptr
+
+      type (MPAS_Time_Type) :: currTime
+      character(len=StrKIND) :: timeStamp
+      integer :: ierr
+   
+      ! 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 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
+
+      ! 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))
+
+         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, ierr)
+           block_ptr =&gt; block_ptr % next
+         end do
+
+         call mpas_timer_start(&quot;time integration&quot;, .false., timeIntTimer)
+         call mpas_timestep(domain, itimestep, dt, timeStamp)
+         call mpas_timer_stop(&quot;time integration&quot;, timeIntTimer)
+   
+         ! Move time level 2 fields back into time level 1 for next time step
+         block_ptr =&gt; domain % blocklist
+         do while(associated(block_ptr))
+            call mpas_shift_time_levels_state(block_ptr % state)
+            block_ptr =&gt; block_ptr % next
+         end do
+      
+         if (mpas_is_alarm_ringing(clock, outputAlarmID, ierr=ierr)) then
+            call mpas_reset_clock_alarm(clock, outputAlarmID, ierr=ierr)
+            ! output_frame will always be &gt; 1 here unless it was reset after the maximum number of frames per outfile was reached
+            if(output_frame == 1) then
+               call mpas_output_state_finalize(output_obj, domain % dminfo)
+               call mpas_output_state_init(output_obj, domain, &quot;OUTPUT&quot;, trim(timeStamp))
+            end if
+
+            block_ptr =&gt; domain % blocklist
+            do while (associated(block_ptr))
+                call ocn_time_average_normalize(block_ptr % state % time_levs(1) % state)
+                block_ptr =&gt; block_ptr % next
+            end do
+
+            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
+         end if
+
+         if (mpas_is_alarm_ringing(clock, restartAlarmID, ierr=ierr)) then
+            call mpas_reset_clock_alarm(clock, restartAlarmID, ierr=ierr)
+
+            ! Write one restart time per file
+            call mpas_output_state_init(restart_obj, domain, &quot;RESTART&quot;, trim(timeStamp))
+            call mpas_output_state_for_domain(restart_obj, domain, 1)
+            call mpas_output_state_finalize(restart_obj, domain % dminfo)
+         end if
+
+      end do
 !
 !#if (defined _MEMTRACE)
 !    if(my_task == 0 ) then
@@ -624,7 +705,10 @@
 
 !-----------------------------------------------------------------------
 
+
+
     call mpas_output_state_finalize(output_obj, domain % dminfo)
+    call mpas_timer_stop(&quot;total time&quot;)
     call mpas_timer_write()
     call mpas_core_finalize(domain)
     call mpas_framework_finalize(dminfo, domain)

</font>
</pre>