<p><b>dwj07@fsu.edu</b> 2012-09-12 10:19:17 -0600 (Wed, 12 Sep 2012)</p><p><br>
        -- BRANCH COMMIT --<br>
<br>
        Fixing some issues with CESM build.<br>
<br>
        Adding an optional namelist filename variable for reading namelist from CESM.<br>
</p><hr noshade><pre><font color="gray">Modified: branches/ocean_projects/cesm_coupling/src/framework/mpas_configure.F
===================================================================
--- branches/ocean_projects/cesm_coupling/src/framework/mpas_configure.F        2012-09-12 15:18:13 UTC (rev 2156)
+++ branches/ocean_projects/cesm_coupling/src/framework/mpas_configure.F        2012-09-12 16:19:17 UTC (rev 2157)
@@ -7,14 +7,23 @@
    contains
 
 
-   subroutine mpas_read_namelist(dminfo)
+   subroutine mpas_read_namelist(dminfo, nml_filename)
 
       implicit none
 
       type (dm_info), intent(in) :: dminfo
+      character (len=StrKIND), optional :: nml_filename
 
+      character (len=StrKIND) :: filename
+
       integer :: funit, ierr
 
+      if(present(nml_filename)) then
+          filename = nml_filename
+      else
+          filename = &quot;namelist.input&quot;
+      end if
+
 #include &quot;config_namelist_defs.inc&quot;
 
       funit = 21
@@ -24,7 +33,7 @@
 
       if (dminfo % my_proc_id == IO_NODE) then
          write(0,*) 'Reading namelist.input'
-         open(funit,file='namelist.input',status='old',form='formatted')
+         open(funit,file=filename,status='old',form='formatted')
 
 #include &quot;config_namelist_reads.inc&quot;
          close(funit)

Modified: branches/ocean_projects/cesm_coupling/src/framework/mpas_framework.F
===================================================================
--- branches/ocean_projects/cesm_coupling/src/framework/mpas_framework.F        2012-09-12 15:18:13 UTC (rev 2156)
+++ branches/ocean_projects/cesm_coupling/src/framework/mpas_framework.F        2012-09-12 16:19:17 UTC (rev 2157)
@@ -13,7 +13,7 @@
    contains
 
    
-   subroutine mpas_framework_init(dminfo, domain, mpi_comm)
+   subroutine mpas_framework_init(dminfo, domain, mpi_comm, nml_filename)
 
       implicit none
 
@@ -21,13 +21,19 @@
       type (domain_type), pointer :: domain
       integer, intent(in), optional :: mpi_comm
 
+      character (len=StrKIND), optional :: nml_filename
+
       integer :: pio_num_iotasks
       integer :: pio_stride
 
       allocate(dminfo)
       call mpas_dmpar_init(dminfo, mpi_comm)
 
-      call mpas_read_namelist(dminfo)
+      if(present(nml_filename)) then
+         call mpas_read_namelist(dminfo, nml_filename)
+      else
+         call mpas_read_namelist(dminfo)
+      end if
 
       call mpas_allocate_domain(domain, dminfo)
       

Modified: branches/ocean_projects/cesm_coupling/src/ocean_cesm_driver/Makefile
===================================================================
--- branches/ocean_projects/cesm_coupling/src/ocean_cesm_driver/Makefile        2012-09-12 15:18:13 UTC (rev 2156)
+++ branches/ocean_projects/cesm_coupling/src/ocean_cesm_driver/Makefile        2012-09-12 16:19:17 UTC (rev 2157)
@@ -2,16 +2,19 @@
 
 OBJS = ocn_comp_mct.o \
        ocn_communicator.o \
-       MPASO_CplIndices.o
+       MPASO_CplIndices.o \
+           mpaso_mct_vars.o
 
 all: $(OBJS)
 
-ocn_comp_mct.o: ocn_communicator.o MPASO_CplIndices.o
+ocn_comp_mct.o: ocn_communicator.o MPASO_CplIndices.o mpaso_mct_vars.o
 
 ocn_communicator.o:
 
 MPASO_CplIndices.o:
 
+mpaso_mct_vars.o:
+
 clean:
         $(RM) *.o *.mod *.f90
 

Added: branches/ocean_projects/cesm_coupling/src/ocean_cesm_driver/mpaso_mct_vars.F
===================================================================
--- branches/ocean_projects/cesm_coupling/src/ocean_cesm_driver/mpaso_mct_vars.F                                (rev 0)
+++ branches/ocean_projects/cesm_coupling/src/ocean_cesm_driver/mpaso_mct_vars.F        2012-09-12 16:19:17 UTC (rev 2157)
@@ -0,0 +1,15 @@
+module mpaso_mct_vars
+  
+  use seq_flds_mod
+  use mct_mod
+
+  implicit none
+
+  save
+  public                               ! By default make data private
+
+  integer :: MPASO_MCT_OCNID
+  type(mct_gsMap), pointer :: MPASO_MCT_gsMap_o
+  type(mct_gGrid), pointer :: MPASO_MCT_dom_o

+end module mpaso_mct_vars

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-09-12 15:18:13 UTC (rev 2156)
+++ branches/ocean_projects/cesm_coupling/src/ocean_cesm_driver/ocn_comp_mct.F        2012-09-12 16:19:17 UTC (rev 2157)
@@ -26,6 +26,7 @@
    use ocn_communicator,  only: mpi_communicator_ocn
 
    use MPASO_CplIndices
+   use mpaso_mct_vars
 
    use mpas_framework
    use mpas_core
@@ -54,8 +55,7 @@
 !
 ! !PRIVATE MODULE VARIABLES
 
-  logical ::   &amp;
-       ldiag_cpl = .false.
+  logical :: ldiag_cpl = .false.
 
   integer, private ::   &amp;
       cpl_write_restart,   &amp;! flag id for write restart
@@ -64,21 +64,15 @@
       cpl_diag_global,     &amp;! flag id for computing diagnostics
       cpl_diag_transp       ! flag id for computing diagnostics
 
-  real (kind=RKIND),   &amp;
-      dimension(:,:,:,:), allocatable ::  &amp;
-      SBUFF_SUM           ! accumulated sum of send buffer quantities
-                          ! for averaging before being sent
-   real (kind=RKIND) ::  &amp;
-     tlast_coupled
+  real (kind=RKIND), dimension(:,:,:,:), allocatable ::  SBUFF_SUM           ! accumulated sum of send buffer quantities
+                                                                             ! for averaging before being sent
+   real (kind=RKIND) :: tlast_coupled
 
-   integer  ::   &amp;
-      nsend, nrecv
+   integer  :: nsend, nrecv
 
-   character(len=StrKIND) :: &amp;
-      runtype         
+   character(len=StrKIND) :: runtype         
 
-   type(seq_infodata_type), pointer :: &amp;
-      infodata   
+   type(seq_infodata_type), pointer :: infodata   
 
    !! MPAS-O Datatypes
    type (dm_info), pointer :: dminfo
@@ -96,17 +90,17 @@
 ! !IROUTINE: ocn_init_mct
 !
 ! !INTERFACE:
-  subroutine ocn_init_mct( EClock, cdata_o, x2o_o, o2x_o, NLFilename )
+  subroutine ocn_init_mct( EClock, cdata_o, x2o_o, o2x_o, NLFilename )!{{{
 !
 ! !DESCRIPTION:
 ! Initialize POP 
 !
 ! !INPUT/OUTPUT PARAMETERS:
 
-    type(ESMF_Clock)            , intent(in)    :: EClock
-    type(seq_cdata)             , intent(inout) :: cdata_o
-    type(mct_aVect)             , intent(inout) :: x2o_o, o2x_o
-    character(len=*), optional  , intent(in)    :: NLFilename ! Namelist filename
+    type(ESMF_Clock), intent(in) :: EClock
+    type(seq_cdata), intent(inout) :: cdata_o
+    type(mct_aVect), intent(inout) :: x2o_o, o2x_o
+    character(len=*), optional, intent(in) :: NLFilename ! Namelist filename
 !
 ! !REVISION HISTORY:
 ! Author: Mariana Vertenstein
@@ -117,39 +111,22 @@
 !
 !-----------------------------------------------------------------------
 
-    integer ::  &amp;
-       OCNID,       &amp;
-       mpicom_o,    &amp;
-       lsize,       &amp;
-       start_ymd,   &amp;
-       start_tod,   &amp;
-       start_year,  &amp;
-       start_day,   &amp;
-       start_month, &amp;
-       start_hour,  &amp;
-       iyear,       &amp;
-       ocn_cpl_dt,  &amp;
-       mpas_o_cpl_dt,  &amp;
-       shrlogunit,  &amp;  ! old values
-       shrloglev       ! old values
+    integer :: OCNID, mpicom_o, lsize, start_ymd, start_tod, start_year, start_day,   &amp;
+       start_month, start_hour, iyear, ocn_cpl_dt, mpas_o_cpl_dt, shrlogunit, shrloglev  
 
-    type(mct_gsMap), pointer :: &amp;
-       gsMap_o
+    type(mct_gsMap), pointer :: gsMap_o
 
-    type(mct_gGrid), pointer :: &amp;
-       dom_o
+    type(mct_gGrid), pointer :: dom_o
 
-    integer :: &amp;
-       errorCode         ! error code
+    integer :: errorCode  ! error code
 
-    integer :: &amp;
-       nThreads
+    integer :: nThreads
 
-    real (kind=RKIND) ::  &amp;
-       precadj
+    real (kind=RKIND) :: precadj
 
     integer :: iam,ierr 
     character(len=StrKIND)  :: starttype          ! infodata start type
+    character(len=StrKIND)  :: timeStamp
 
     integer :: lbnum
 
@@ -164,9 +141,9 @@
    call seq_cdata_setptrs(cdata_o, ID=OCNID, mpicom=mpicom_o, &amp;
         gsMap=gsMap_o, dom=dom_o, infodata=infodata)
 
-!  MPASO_MCT_OCNID =  OCNID
-!  MPASO_MCT_gsMap_o =&gt; gsMap_o
-!  MPASO_MCT_dom_o   =&gt; dom_o
+   MPASO_MCT_OCNID =  OCNID
+   MPASO_MCT_gsMap_o =&gt; gsMap_o
+   MPASO_MCT_dom_o   =&gt; dom_o
 
 #if (defined _MEMTRACE)
     call MPI_comm_rank(mpicom_o,iam,ierr)
@@ -191,7 +168,6 @@
     call MPASO_CplIndicesSet()
 
 !   call seq_infodata_GetData( infodata, case_name=runid )
-   
     call seq_infodata_GetData( infodata, start_type=starttype)
 
 
@@ -224,32 +200,11 @@
 !  inst_suffix = seq_comm_suffix(OCNID)
 
    call t_startf('mpas-o_init')
-   call mpas_framework_init(dminfo, domain)
+   call mpas_framework_init(dminfo, domain, mpi_communicator_ocn)
 
-!-----------------------------------------------------------------------
-!
-!  register non-standard incoming fields
-!
-!-----------------------------------------------------------------------
-
-!  if (index_x2o_Sa_co2prog &gt; 0) then
-!     call named_field_register('ATM_CO2_PROG', ATM_CO2_PROG_nf_ind)
-!  endif
-!  if (index_x2o_Sa_co2diag &gt; 0) then
-!     call named_field_register('ATM_CO2_DIAG', ATM_CO2_DIAG_nf_ind)
-!  endif
-!  call register_string('mpas-o_init_coupled')
-!  call flushm (stdout)
-
-!-----------------------------------------------------------------------
-!
-!  second initialization phase of mpas-o
-!
-!-----------------------------------------------------------------------
-
    call mpas_input_state_for_domain(domain)
 
-!  call mpas_core_init(domain, timeStamp)
+   call mpas_core_init(domain, timeStamp)
 
 !-----------------------------------------------------------------------
 !
@@ -257,8 +212,6 @@
 !
 !-----------------------------------------------------------------------
 
-!  call ccsm_char_date_and_time
-
    call t_stopf ('mpas-o_init')
 
 !----------------------------------------------------------------------------
@@ -277,10 +230,10 @@
 !
 !-----------------------------------------------------------------------
 
-   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
+!     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 (iyear0 /= start_year) then
 !        call mpas_dmpar_global_abort(' iyear0 does not match start_year')
@@ -295,7 +248,7 @@
 !         call exit_POP(sigAbort,' sec0 does not start_tod')
 !      end if
 !#endif
-   end if
+!  end if
 
 !-----------------------------------------------------------------------
 !
@@ -322,28 +275,9 @@
    
    nsend = mct_avect_nRattr(o2x_o)
    nrecv = mct_avect_nRattr(x2o_o)
-!  allocate (SBUFF_SUM(nx_block,ny_block,max_blocks_clinic,nsend))
 
 !-----------------------------------------------------------------------
 !
-!  Initialize flags and shortwave absorption profile
-!  Note that these cpl_write_xxx flags have no freqency options
-!  set; therefore, they will retain a default value of .false.
-!  unless they are explicitly set .true.  at the appropriate times
-!
-!-----------------------------------------------------------------------
-
-!  call init_time_flag('cpl_write_restart',cpl_write_restart, owner = 'ocn_init_mct')
-!  call init_time_flag('cpl_write_history',cpl_write_history, owner = 'ocn_init_mct')
-!  call init_time_flag('cpl_write_tavg'   ,cpl_write_tavg,    owner = 'ocn_init_mct')
-!  call init_time_flag('cpl_diag_global'  ,cpl_diag_global,   owner = 'ocn_init_mct')
-!  call init_time_flag('cpl_diag_transp'  ,cpl_diag_transp,   owner = 'ocn_init_mct')
-
-!  lsmft_avail = .true.
-!  tlast_coupled = c0
-
-!-----------------------------------------------------------------------
-!
 !   initialize necessary  coupling info
 !
 !-----------------------------------------------------------------------
@@ -397,28 +331,6 @@
 
 !-----------------------------------------------------------------------
 !
-!  document orbital parameters
-!
-!-----------------------------------------------------------------------
-
-!  if (registry_match('qsw_distrb_iopt_cosz')) then
-!  call seq_infodata_GetData(infodata, &amp;
-!     orb_eccen=orb_eccen, orb_mvelpp=orb_mvelpp, orb_lambm0=orb_lambm0, orb_obliqr=orb_obliqr)
-
-!    write(stdout,*) ' '
-!   endif
-
-!-----------------------------------------------------------------------
-!
-!  Now document all time flags, because this is the last step of pop2 
-!    initialization
-!
-!-----------------------------------------------------------------------
-
-!  call document_time_flags
-
-!-----------------------------------------------------------------------
-!
 !  output delimiter to log file
 !
 !-----------------------------------------------------------------------
@@ -438,7 +350,7 @@
 !-----------------------------------------------------------------------
 !EOC
 
- end subroutine ocn_init_mct
+ end subroutine ocn_init_mct!}}}
 
 !***********************************************************************
 !BOP
@@ -446,7 +358,7 @@
 ! !IROUTINE: ocn_run_mct
 !
 ! !INTERFACE:
-  subroutine ocn_run_mct( EClock, cdata_o, x2o_o, o2x_o)
+  subroutine ocn_run_mct( EClock, cdata_o, x2o_o, o2x_o)!{{{
 
     use mpas_kind_types
     use mpas_grid_types
@@ -655,7 +567,7 @@
 !-----------------------------------------------------------------------
 !EOC
 
-  end subroutine ocn_run_mct
+  end subroutine ocn_run_mct!}}}
 
 !***********************************************************************
 !BOP
@@ -663,7 +575,7 @@
 ! !IROUTINE: ocn_final_mct
 !
 ! !INTERFACE:
-  subroutine ocn_final_mct( EClock, cdata_o, x2o_o, o2x_o)
+  subroutine ocn_final_mct( EClock, cdata_o, x2o_o, o2x_o)!{{{
 !
 ! !DESCRIPTION:
 ! Finalize POP
@@ -695,14 +607,14 @@
     call mpas_core_finalize(domain)
     call mpas_framework_finalize(dminfo, domain)
 
-  end subroutine ocn_final_mct
+  end subroutine ocn_final_mct!}}}
 
 !***********************************************************************
 !BOP
 !IROUTINE: ocn_SetGSMap_mct
 ! !INTERFACE:
 
- subroutine ocn_SetGSMap_mct( mpicom_ocn, OCNID, gsMap_ocn )
+ subroutine ocn_SetGSMap_mct( mpicom_ocn, OCNID, gsMap_ocn )!{{{
 
    use mpas_dmpar
 
@@ -771,14 +683,14 @@
 !-----------------------------------------------------------------------
 !EOC
 
-  end subroutine ocn_SetGSMap_mct
+  end subroutine ocn_SetGSMap_mct!}}}
 
 !***********************************************************************
 !BOP
 ! !IROUTINE: ocn_domain_mct
 ! !INTERFACE:
 
- subroutine ocn_domain_mct( lsize, gsMap_o, dom_o )
+ subroutine ocn_domain_mct( lsize, gsMap_o, dom_o )!{{{
 
 ! !DESCRIPTION:
 !  This routine mct global seg maps for the pop decomposition
@@ -900,7 +812,7 @@
 !-----------------------------------------------------------------------
 !EOC
 
-  end subroutine ocn_domain_mct
+  end subroutine ocn_domain_mct!}}}
 
 
 !***********************************************************************
@@ -908,7 +820,7 @@
 ! !IROUTINE: ocn_import_mct
 ! !INTERFACE:
 
- subroutine ocn_import_mct(x2o_o, errorCode)
+ subroutine ocn_import_mct(x2o_o, errorCode)!{{{
 
 ! !DESCRIPTION:
 !-----------------------------------------------------------------------
@@ -1221,13 +1133,13 @@
 !-----------------------------------------------------------------------
 !EOC
 
- end subroutine ocn_import_mct
+ end subroutine ocn_import_mct!}}}
 !***********************************************************************
 !BOP
 ! !IROUTINE: ocn_export_mct
 ! !INTERFACE:
 
- subroutine ocn_export_mct(o2x_o, errorCode)   
+ subroutine ocn_export_mct(o2x_o, errorCode)   !{{{
 
 ! !DESCRIPTION:
 !  This routine calls the routines necessary to send pop fields to
@@ -1469,7 +1381,7 @@
 !-----------------------------------------------------------------------
 !EOC
 
- end subroutine ocn_export_mct
+ end subroutine ocn_export_mct!}}}
 
 !***********************************************************************
 
@@ -1477,7 +1389,7 @@
 ! !IROUTINE: pop_sum_buffer
 ! !INTERFACE:
 
- subroutine pop_sum_buffer
+ subroutine pop_sum_buffer!{{{
 
 ! !DESCRIPTION:
 !  This routine accumulates sums for averaging fields to
@@ -1607,7 +1519,7 @@
 !-----------------------------------------------------------------------
 !EOC
 
- end subroutine pop_sum_buffer
+ end subroutine pop_sum_buffer!}}}
  
 !***********************************************************************
 

</font>
</pre>