<p><b>dwj07@fsu.edu</b> 2012-05-02 08:40:23 -0600 (Wed, 02 May 2012)</p><p><br>
        -- BRANCH COMMIT --<br>
<br>
        Adding a routine to determine halo indices for cells.<br>
        Currently it should be able to handle an arbitrary number of halos, but has only been tested with 2 so far.<br>
</p><hr noshade><pre><font color="gray">Modified: branches/omp_blocks/multiple_blocks/src/framework/mpas_block_decomp.F
===================================================================
--- branches/omp_blocks/multiple_blocks/src/framework/mpas_block_decomp.F        2012-05-01 20:14:08 UTC (rev 1854)
+++ branches/omp_blocks/multiple_blocks/src/framework/mpas_block_decomp.F        2012-05-02 14:40:23 UTC (rev 1855)
@@ -543,15 +543,17 @@
      deallocate(block_local_id_list)
    end subroutine mpas_finish_block_proc_list!}}}
 
-   subroutine mpas_get_exchange_lists(dminfo, ownedListField, ownedDecomposed, neededListField, neededDecomposed)!{{{
+   subroutine mpas_get_exchange_lists(dminfo, ownedListField, ownedDecomposed, neededListField, neededDecomposed, offSetField)!{{{
      type (dm_info), intent(in) :: dminfo !&lt; Input: Domain information
      type (field1dInteger), pointer :: ownedListField !&lt; Input/Output: pointer to the field which contains owned elements for exchange list.
      logical, intent(in) :: ownedDecomposed !&lt; Input: logical flag determining if the ownedList is decomposed using block_decomp or not.
      type (field1dInteger), pointer :: neededListField !&lt; Input/Output: pointer to a field which contains needed elements for exchange list.
      logical, intent(in) :: neededDecomposed !&lt; Input: logical flag determining if the neededList is decomposed using block_decomp or not.
+     type (field0dInteger), pointer, optional :: offSetField
 
      type (field2dInteger), pointer :: ownedListSorted, sorted_field_ptr
 
+     type (field0dInteger), pointer :: offset_ptr
      type (field1dInteger), pointer :: field_ptr
      type (exchange_list), pointer :: exchListPtr, exchListPtr2
 
@@ -564,7 +566,7 @@
      integer :: recvNeighbor, sendNeighbor
      integer :: current_proc, nMesgRecv, nMesgSend
      integer :: localBlockID, globalBlockID, owningProc
-     integer :: currentProc
+     integer :: currentProc, offSet
 
      integer :: mpi_ierr, mpi_rreq, mpi_sreq
 
@@ -722,6 +724,14 @@
            end if
          end do ! j loop over nMesgRecv
 
+!        write(6,*) 'numToSend'
+!        write(6,*) numToSend
+
+!        write(6,*) 'elementRecipients'
+!        do iElement = 1, nOwnedElements
+!          write(6,*) elementRecipients(:,iElement)
+!        end do
+
          ! Find end of send list
          exchListPtr =&gt; field_ptr % sendList(1) 
          exchListPtr2 =&gt; field_ptr % sendList(1) % next
@@ -741,6 +751,7 @@
              exchListPtr % nlist = numToSend(j)
 
              allocate(exchListPtr % list(numToSend(j)))
+             exchListPtr % list = -1
 
              do iElement = 1, nOwnedElements
                if(elementRecipients(1,iElement) == j-1) then
@@ -773,6 +784,19 @@
 
      field_ptr =&gt; neededListField
      do while(associated(field_ptr))
+       offSet = 0
+       if(present(offSetField)) then
+         offSet_ptr =&gt; offSetfield
+         do while(associated(offSet_ptr))
+           if(offSet_ptr % block % blockID == field_ptr % block % blockID) then
+             exit
+           end if
+           offSet_ptr =&gt; offSet_ptr % next
+         end do
+
+         offSet = offSet_ptr % scalar
+       end if
+
        numToRecv = 0
        do i = 1, nMesgRecv
          if(ownerBlockListIn(i) == field_ptr % block % blockID) then
@@ -820,7 +844,7 @@
              if(ownerBlockListIn(i) == field_ptr % block % blockID .and. abs(ownerListIn(i)) == iBlock-1) then
                iElement = iElement + 1
 
-               exchListPtr % list(iElement) = iElementInBlock
+               exchListPtr % list(iElement) = iElementInBlock + offSet
              end if
            end do
          end if
@@ -1071,4 +1095,354 @@
 
    end subroutine mpas_link_exchange_list_field3d_real!}}}
 
+!***********************************************************************
+!
+!  routine mpas_get_halo_cells_and_exchange_lists
+!
+!&gt; \brief   Determines cell indices for each halo layer, and builds exchange lists
+!&gt; \author  Doug Jacobsen
+!&gt; \date    04/30/12
+!&gt; \version SVN:$Id$
+!&gt; \details 
+!&gt;  This routine builds the field indexToCellID_nHalos, which is an array of nHalos linked lists.
+!&gt;  Each index in indexToCellID_nHalos represnts a linked list of cells in a given halo.
+!&gt;  It creates the exchange lists for cells, and places them in the block structure.
+!&gt;  In order to call this routine, there are some assumptions made.
+!&gt;  The first assumption is that the 1 index of each array is setup correctly, 
+!&gt;      ie block pointers are valid, dimSizes are valid, next pointers are valid, ets
+!&gt;  The second assumption is that the arrays in each field are allocated and full with their appropriate information.
+!&gt;  These assumptions lead to the conclusion that the 0 halo has to be properly setup prior to calling this routine.
+!
+!-----------------------------------------------------------------------
+
+   subroutine mpas_get_halo_cells_and_exchange_lists(dminfo, nHalos, indexToCellID_0Halo, nEdgesOnCell_0Halo, cellsOnCell_0Halo, indexToCellID_nHalos, nEdgesOnCell_nHalos, cellsOnCell_nHalos)!{{{
+
+       type (dm_info), intent(in) :: dminfo
+       integer, intent(in) :: nHalos
+       type (field1dInteger), pointer :: indexToCellID_0Halo
+       type (field1dInteger), pointer :: nEdgesOnCell_0Halo
+       type (field2dInteger), pointer :: cellsOnCell_0Halo
+
+       type (field1dInteger), dimension(:), pointer :: indexToCellID_nHalos
+       type (field1dInteger), dimension(:), pointer :: nEdgesOnCell_nHalos
+       type (field2dInteger), dimension(:), pointer :: cellsOnCell_nHalos
+
+       type (field1dInteger), pointer :: indexToCellID_ptr, indexToCellID_Halo_ptr
+       type (field1dInteger), pointer :: nEdgesOnCell_ptr, nEdgesOnCell_Halo_ptr
+       type (field2dInteger), pointer :: cellsOnCell_ptr, cellsOnCell_Halo_ptr
+
+       type (field0dInteger), pointer :: offSetField
+       type (field0dInteger), pointer :: offSet_ptr
+
+       type (block_type), pointer :: block_ptr
+
+       type (exchange_list), pointer :: recvListPtr, copyListPtr
+       type (graph) :: block_graph, block_graph_with_halo
+
+       integer :: nCellsInBlock, nCellsInHalo, maxEdges
+       integer :: indexShift, exchListOffSet
+       integer :: haloStart, haloEnd
+       integer :: iHalo, i, j, k
+
+       maxEdges = cellsOnCell_0Halo % dimSizes(1)
+       allocate(indexToCellID_nHalos(nHalos))
+       allocate(nEdgesOnCell_nHalos(nHalos))
+       allocate(cellsOnCell_nHalos(nHalos))
+       allocate(offSetField)
+
+       block_ptr =&gt; indexToCellID_0Halo % block
+       offSet_ptr =&gt; offSetField
+
+       do while(associated(block_ptr))
+         allocate(block_ptr % parinfo)
+         allocate(block_ptr % parinfo % cellsToSend(nHalos))
+         allocate(block_ptr % parinfo % cellsToRecv(nHalos))
+         allocate(block_ptr % parinfo % cellsToCopy(nHalos))
+         offSet_ptr % block =&gt; block_ptr
+         block_ptr =&gt; block_ptr % next
+         if(associated(block_ptr)) then
+           allocate(offSet_ptr % next)
+           offSet_ptr =&gt; offSet_ptr % next
+         end if
+         nullify(offSet_ptr % next)
+       end do
+
+       do iHalo = 1, nHalos
+         ! Setup block pointers for the next halo
+         indexToCellID_ptr =&gt; indexToCellID_0Halo
+         nEdgesOnCell_ptr =&gt; nEdgesOnCell_0Halo
+         cellsOnCell_ptr =&gt; cellsOnCell_0Halo
+
+         indexToCellID_Halo_ptr =&gt; indexToCellID_nHalos(iHalo)
+         nEdgesOnCell_Halo_ptr =&gt; nEdgesOnCell_nHalos(iHalo)
+         cellsOnCell_Halo_ptr =&gt; cellsOnCell_nHalos(iHalo)
+         do while (associated(indexToCellID_ptr))
+
+           indexToCellID_Halo_ptr % block =&gt; indexToCellID_ptr % block
+           nEdgesOnCell_Halo_ptr % block =&gt; nEdgesOnCell_ptr % block
+           cellsOnCell_Halo_ptr % block =&gt; cellsOnCell_ptr % block
+
+           indexToCellID_ptr =&gt; indexToCellID_ptr % next
+           nEdgesOnCell_ptr =&gt; nEdgesOnCell_ptr % next
+           cellsOnCell_ptr =&gt; cellsOnCell_ptr % next
+           if(associated(indexToCellID_ptr)) then
+             allocate(indexToCellID_Halo_ptr % next)
+             allocate(nEdgesOnCell_Halo_ptr % next)
+             allocate(cellsOnCell_Halo_ptr % next)
+             indexToCellID_Halo_ptr =&gt; indexToCellID_Halo_ptr % next
+             nEdgesOnCell_Halo_ptr =&gt; nEdgesOnCell_Halo_ptr % next
+             cellsOnCell_Halo_ptr =&gt; cellsOnCell_Halo_ptr % next
+           end if
+
+           nullify(indexTocellID_Halo_ptr % next)
+           nullify(nEdgesOnCell_Halo_ptr % next)
+           nullify(cellsOnCell_Halo_ptr % next)
+         end do
+
+         indexToCellID_ptr =&gt; indexToCellID_0Halo
+         nEdgesOnCell_ptr =&gt; nEdgesOnCell_0Halo
+         cellsOnCell_ptr =&gt; cellsOnCell_0Halo
+         offSet_ptr =&gt; offSetField
+         do while (associated(indexToCellID_ptr))
+           nCellsInBlock = indexToCellID_ptr % dimSizes(1)
+
+           ! Determine number of total cells in block and halos
+           do k = 1, iHalo-1
+             indexToCellID_Halo_ptr =&gt; indexToCellID_nHalos(k)
+             do while(associated(indexToCellID_Halo_ptr))
+               if(indexToCellID_Halo_ptr % block % blockID == indexToCellID_ptr % block % blockID) exit
+               indexToCellID_Halo_ptr =&gt; indexToCellID_Halo_ptr % next
+             end do
+             nCellsInBlock = nCellsInBlock + indexToCellID_Halo_ptr % dimSizes(1)
+           end do
+
+           ! Setup block graph, using owned and halo cells
+           offSet_ptr % scalar = nCellsInBlock
+           block_graph % nVertices = nCellsInBlock
+           block_graph % nVerticesTotal = nCellsInBlock
+           block_graph % maxDegree = maxEdges
+           block_graph % ghostStart = nCellsInBlock + 1
+
+           allocate(block_graph % vertexID(nCellsInBlock))
+           allocate(block_graph % nAdjacent(nCellsInBlock))
+           allocate(block_graph % adjacencyList(maxEdges, nCellsInBlock))
+
+           ! Add all owned cells to graph
+           indexShift = 0
+           block_graph % vertexID(indexShift+1:indexToCellID_ptr % dimSizes(1)) = indexToCellID_ptr % array(:)
+           block_graph % nAdjacent(indexShift+1:nEdgesOnCell_ptr % dimSizes(1)) = nEdgesOnCell_ptr % array(:)
+           block_graph % adjacencyList(:,indexShift+1:cellsOnCell_ptr % dimSizes(2)) = cellsOnCell_ptr % array(:,:)
+
+           ! Add all halo cells to graph
+           indexShift = indexShift + indexToCellID_ptr % dimSizes(1)
+           do k = 1, iHalo-1
+             indexToCellID_Halo_ptr =&gt; indexToCellID_nHalos(k)
+             nEdgesOnCell_Halo_ptr =&gt; nEdgesOnCell_nHalos(k)
+             cellsOnCell_Halo_ptr =&gt; cellsOnCell_nHalos(k)
+             do while(associated(indexToCellID_Halo_ptr))
+               if(indexToCellID_Halo_ptr % block % blockID == indexToCellID_ptr % block % blockID) exit
+               indexToCellID_Halo_ptr =&gt; indexToCellID_Halo_ptr % next
+               nEdgesOnCell_Halo_ptr =&gt; nEdgesOnCell_Halo_ptr % next
+               cellsOnCell_Halo_ptr =&gt; cellsOnCell_Halo_ptr % next
+             end do
+
+             block_graph % vertexID(indexShift+1:indexShift+indexToCellID_Halo_ptr % dimSizes(1)) = indexToCellID_Halo_ptr % array(:)
+             block_graph % nAdjacent(indexShift+1:indexShift+nEdgesOnCell_Halo_ptr % dimSizes(1)) = nEdgesOnCell_Halo_ptr % array(:)
+             block_graph % adjacencyList(:,indexShift+1:indexShift+cellsOnCell_Halo_ptr % dimSizes(2)) = cellsOnCell_Halo_ptr % array(:,:)
+             indexShift = indexShift + indexToCellID_Halo_ptr % dimSizes(1)
+           end do
+
+           ! Get a new block graph with the next halo layer added.
+           call mpas_block_decomp_add_halo(dminfo, block_graph, block_graph_with_halo)
+  
+           indexToCellID_Halo_ptr =&gt; indexToCellID_nHalos(iHalo)
+           nEdgesOnCell_Halo_ptr =&gt; nEdgesOnCell_nHalos(iHalo)
+           cellsOnCell_Halo_ptr =&gt; cellsOnCell_nHalos(iHalo)
+  
+           do while(associated(indexToCellID_Halo_ptr))
+  
+             if(indexToCellID_Halo_ptr % block % blockID == indexToCellID_ptr % block % blockID) exit
+  
+             indexToCellID_Halo_ptr =&gt; indexToCellID_Halo_ptr % next
+             nEdgesOnCell_Halo_ptr =&gt; nEdgesOnCell_Halo_ptr % next
+             cellsOnCell_Halo_ptr =&gt; cellsOnCell_Halo_ptr % next
+           end do
+
+           haloStart = block_graph_with_halo % nVertices
+           haloEnd = block_graph_with_halo % nVerticesTotal
+           nCellsInHalo = haloEnd - haloStart
+
+           indexToCellID_Halo_ptr % dimSizes(1) = nCellsInHalo
+           nEdgesOnCell_Halo_ptr % dimSizes(1) = nCellsInHalo
+           cellsOnCell_Halo_ptr % dimSizes(1) = maxEdges
+           cellsOnCell_Halo_ptr % dimSizes(2) = nCellsInHalo
+
+           allocate(indexToCellID_Halo_ptr % array(nCellsInHalo))
+           allocate(nEdgesOnCell_Halo_ptr % array(nCellsInHalo))
+           allocate(cellsOnCell_Halo_ptr % array(maxEdges, nCellsInHalo))
+
+           indexToCellID_Halo_ptr % array(:) = block_graph_with_halo % vertexID(haloStart+1:haloEnd)
+
+           deallocate(block_graph % vertexID)
+           deallocate(block_graph % nAdjacent)
+           deallocate(block_graph % adjacencyList)
+           deallocate(block_graph_with_halo % vertexID)
+           deallocate(block_graph_with_halo % nAdjacent)
+           deallocate(block_graph_with_halo % adjacencyList)
+           indexToCellID_ptr =&gt; indexToCellID_ptr % next
+           nEdgesOnCell_ptr =&gt; nEdgesOnCell_ptr % next
+           cellsOnCell_ptr =&gt; cellsOnCell_ptr % next
+           offSet_ptr =&gt; offSet_ptr % next
+         end do
+
+         indexToCellID_Halo_ptr =&gt; indexToCellID_nHalos(iHalo)
+         nEdgesOnCell_Halo_ptr =&gt; nEdgesOnCell_nHalos(iHalo)
+         cellsOnCell_Halo_ptr =&gt; cellsOnCell_nHalos(iHalo)
+
+         call mpas_get_exchange_lists(dminfo, indexToCellID_0Halo, .true., indexToCellID_Halo_ptr, .true.)
+
+         call mpas_link_exchange_list_field(indexToCellID_0Halo, indexToCellID_Halo_ptr, nEdgesOnCell_0Halo, nEdgesOnCell_Halo_ptr)
+         call mpas_link_exchange_list_field(indexToCellID_0Halo, indexToCellID_Halo_ptr, cellsOnCell_0Halo, cellsOnCell_Halo_ptr)
+
+         call mpas_dmpar_alltoall_field(dminfo, indexToCellID_0Halo, indexToCellID_Halo_ptr)
+         call mpas_dmpar_alltoall_field(dminfo, nEdgesOnCell_0Halo, nEdgesOnCell_Halo_ptr)
+         call mpas_dmpar_alltoall_field(dminfo, cellsOnCell_0Halo, cellsOnCell_Halo_ptr)
+
+         indexToCellID_ptr =&gt; indexToCellID_0Halo
+         indexToCellID_Halo_ptr =&gt; indextoCellID_nHalos(iHalo)
+         offSet_ptr =&gt; offSetField
+         do while(associated(indexToCellID_ptr))
+           indexToCellID_ptr % block % parinfo % cellsToSend(iHalo) = indexToCellID_ptr % sendList(1)
+           indexToCellID_ptr % block % parinfo % cellsToRecv(iHalo) = indexToCellID_Halo_ptr % recvList(1)
+           indexToCellID_ptr % block % parinfo % cellsToCopy(iHalo) = indexToCellID_Halo_ptr % copyList(1)
+
+           recvListPtr =&gt; indexToCellID_ptr % block % parinfo % cellsToRecv(iHalo) % next
+           do while(associated(recvListPtr))
+             recvListPtr % list = recvListPtr % list + offSet_ptr % scalar
+             recvListPtr =&gt; recvListPtr % next
+           end do
+
+           copyListPtr =&gt; indexToCellID_ptr % block % parinfo % cellsToCopy(iHalo) % next
+           do while(associated(copyListPtr))
+             copyListPtr % list = copyListPtr % list + offSet_ptr % scalar
+             copyListPtr =&gt; copyListPtr % next
+           end do
+
+           deallocate(indexToCellID_ptr % sendList)
+           deallocate(indexToCellID_Halo_ptr % recvList)
+           deallocate(indexToCellID_Halo_ptr % copyList)
+
+           indexToCellID_ptr =&gt; indexToCellID_ptr % next
+           indextoCellID_Halo_ptr =&gt; indexToCellID_Halo_ptr % next
+           offSet_ptr =&gt; offSet_ptr % next
+         end do
+
+       end do ! iHalo loop over nHalos
+
+   end subroutine mpas_get_halo_cells_and_exchange_lists  !}}}
+
+!***********************************************************************
+!
+!  routine mpas_get_vertex_ids_and_exchange_lists
+!
+!&gt; \brief   Determines vertex indices for each halo layer, and builds exchange lists
+!&gt; \author  Doug Jacobsen
+!&gt; \date    05/01/12
+!&gt; \version SVN:$Id$
+!&gt; \details 
+!&gt;  This routine fills in the arrays for the indexToVertexID_0Halo, and indexToVertexID_nHalos
+!&gt;  indexToVertexID_0Halo represents all vertices in the 0 halo, while indexToVertexID_nHalos represnts
+!&gt;  the vertex id's for all vertices in all other halos. It is an array of linked lists where each
+!&gt;  index represents the linked list of vertex ids at that halo layer.
+!&gt;  It creates the exchange lists for vertices, and places them in the block structure.
+!&gt;  In order to call this routine, there are some assumptions made.
+!&gt;  The first assumption is that the 1 index of each array is setup correctly, 
+!&gt;      ie block pointers are valid, dimSizes are valid, next pointers are valid, ets
+!&gt;  The second assumption is that the arrays in each field are allocated and full with their appropriate information.
+!&gt;  These assumptions lead to the conclusion that the 0 halo has to be properly setup prior to calling this routine.
+!
+!-----------------------------------------------------------------------
+
+   subroutine mpas_get_vertex_ids_and_exchange_lists(dminfo, nHalos, maxEdges, vertexDegree, indexToCellID_0Halo, nEdgesOnCell_0Halo, verticesOnCell_0Halo, cellsOnVertex_0Halo, indexToCellID_nHalos, indexToVertexID_0Halo, indexToVertexID_nHalos)!{{{
+       type (dm_info), intent(in) :: dminfo
+       integer, intent(in) :: nHalos
+       integer, intent(in) :: maxEdges
+       integer, intent(in) :: vertexDegree
+
+       type(field1dInteger), pointer :: indexToCellID_0Halo
+       type(field1dInteger), pointer :: nEdgesOnCell_0Halo
+       type(field1dInteger), pointer :: verticesOnCell_0Halo
+       type(field1dInteger), pointer :: cellsOnVertex_0Halo
+       type(field1dInteger), dimension(:), pointer :: indexToCellID_nHalos
+
+       type(field1dInteger), pointer :: indexToVertexID_0Halo
+       type(field1dInteger), dimension(:), pointer :: indexToVertexID_nHalos
+
+       type(field1dInteger), dimension(:), pointer :: cellsOnVertex_nHalos
+       type(field1dInteger), dimension(:), pointer :: nEdgesOnCell_nHalos
+
+       type(field1dInteger), pointer :: indexToCellID_ptr, nEdgesOnCell_ptr, verticesOnCell_ptr, cellsOnVertex_ptr, indexToVertexID_ptr
+       type(field1dInteger), pointer :: indexToCellID_Halo_ptr, indexToVertexID_Halo_ptr
+
+       integer, dimension(:), pointer :: all_vertices_in_block
+       integer :: nCellsInBlock
+       integer :: nVerticesInBlock
+       integer :: nVerticesInHalo, haloStart, haloEnd
+
+       type (graph) :: block_graph, block_graph_with_halo
+
+       integer :: iCell, iVertex
+       integer :: i, j, k, iHalo
+
+       allocate(indexToVertexID_0Halo)
+       allocate(indexToVertexID_nHalos(nHalos+1)) ! 1 more halo than cells
+       allocate(cellsOnVertex_nHalos(nHalos+1)) ! 1 more halo than cells
+       allocate(nEdgesOnCell_nHalos(nHalos))
+
+       ! Build the 0 and 1 halos
+       indexToCellID_ptr =&gt; indexToCellID_0Halo
+       nEdgesOnCell_ptr =&gt; nEdgesOnCell_0Halo
+       verticesOnCell_ptr =&gt; verticesOnCell_0Halo
+       cellsOnVertex_ptr =&gt; cellsOnVertex_0Halo
+       indexToVertexID_ptr =&gt; indexToVertexID_0Halo
+       indexToVertexID_Halo_ptr =&gt; indexToVertexID_nHalos(1)
+       do while(associated(indexToCellID_ptr))
+         nCellsInBlock = indexToCellID_ptr % dimSizes(1)
+
+         call mpas_block_decomp_all_edges_in_block(maxEdges, nCellsInBlock, nEdgesOnCell_ptr % array, verticesOnCell_ptr % array, nVerticesInBlock, all_vertices_in_block)
+         call mpas_block_decomp_partitioned_edge_list(nCellsInBlock, indexToCellID_ptr % array, vertexDegree, nVerticesInBlock, cellsOnVertex_ptr % array, all_vertices_in_block, haloStart)
+
+!        call mpas_block_decomp_all_edges_in_block(maxEdges, block_graph_2Halo % nVerticesTotal, block_graph_2Halo % nAdjacent, &amp;
+!                                           verticesOnCell_2Halo, nlocal_vertices, local_vertex_list)
+
+!        call mpas_block_decomp_partitioned_edge_list(nOwnCells, &amp;
+!                                              block_graph_2Halo % vertexID(1:nOwnCells), &amp;
+!                                              vertexDegree, nlocal_vertices, cellsOnVertex_2Halo, local_vertex_list, ghostVertexStart)
+
+         indexToVertexID_ptr % block =&gt; indexToCellID_ptr % block
+         indexToVertexID_ptr % dimSizes(1) = haloStart
+         allocate(indexToVertexID_ptr % array(indexToVertexID_ptr % dimSizes(1)))
+
+         indexToVertexID_ptr % array(:) = all_vertices_in_block(1:haloStart)
+
+         indexToVertexID_Halo_ptr % block =&gt; indexToCellID_Halo_ptr % block
+         indexToVertexID_Halo_ptr % dimSizes(1) = nVerticesInBlock - haloStart
+         allocate(indexToVertexID_Halo_ptr % array(indexToVertexID_Halo_ptr % dimSizes(1)))
+
+         indexToVertexID_Halo_ptr % array(:) = all_vertices_in_block(haloStart+1:nVerticesInBlock)
+
+         indexToCellID_ptr =&gt; indexToCellID_ptr % next
+         verticesOnCell_ptr =&gt; verticesOnCell_ptr % next
+         cellsOnVertex_ptr =&gt; cellsOnVertex_ptr % next
+         if(associated(indexToCellID_ptr)) then
+           allocate(indexToVertexID_ptr % next)
+           indexToVertexID_ptr =&gt; indexToVertexID_ptr % next
+         end if
+
+         nullify(indexToVertexID_ptr % next)
+       end do
+
+   end subroutine mpas_get_vertex_ids_and_exchange_lists!}}}
+
+
 end module mpas_block_decomp

Modified: branches/omp_blocks/multiple_blocks/src/framework/mpas_io_input.F
===================================================================
--- branches/omp_blocks/multiple_blocks/src/framework/mpas_io_input.F        2012-05-01 20:14:08 UTC (rev 1854)
+++ branches/omp_blocks/multiple_blocks/src/framework/mpas_io_input.F        2012-05-02 14:40:23 UTC (rev 1855)
@@ -81,35 +81,41 @@
 
       type (field1DChar) :: xtime
 
+      type (field0DInteger), pointer :: int0d_ptr
       type (field1DInteger), pointer :: int1d_ptr
       type (field1DInteger), pointer :: int1d_ptr2
       type (field1DInteger), pointer :: int1d_ptr3
+      type (field1DInteger), pointer :: int1d_ptr4
+      type (field1DInteger), pointer :: int1d_ptr5
       type (field2DInteger), pointer :: int2d_ptr
+      type (field2DInteger), pointer :: int2d_ptr2
+      type (field2DInteger), pointer :: int2d_ptr3
 
+      type (field1dInteger), pointer :: nCellsSolveField
+
+      type (field1DInteger), dimension(:), pointer :: indexToCellID_Halos
+      type (field1DInteger), dimension(:), pointer :: nEdgesOnCell_Halos
+      type (field2DInteger), dimension(:), pointer :: cellsOnCell_Halos
+
+      type (field1dInteger), dimension(:), pointer :: indexToVertexID_Halos
+      type (field1dInteger), dimension(:), pointer :: indexToEdgesID_Halos
+
       type (field1DInteger), pointer :: indexToCellID_0Halo
       type (field1DInteger), pointer :: nEdgesOnCell_0Halo
       type (field2DInteger), pointer :: cellsOnCell_0Halo
+      type (field2DInteger), pointer :: verticesOnCell_0Halo
+      type (field2DInteger), pointer :: edgesOnCell_0Halo
 
-      type (field1DInteger), pointer :: indexToCellID_1Halo
-      type (field1DInteger), pointer :: nEdgesOnCell_1Halo
-      type (field2DInteger), pointer :: cellsOnCell_1Halo
-   
-!     integer, dimension(:),   pointer :: indexToCellID_0Halo
-!     integer, dimension(:),   pointer :: nEdgesOnCell_0Halo
-!     integer, dimension(:,:), pointer :: cellsOnCell_0Halo
+      type (field1DInteger), pointer :: indexToVertexID_0Halo
+      type (field2DInteger), pointer :: cellsOnVertex_0Halo
 
-      integer, dimension(:),   pointer :: nEdgesOnCell_2Halo
+      type (field1DInteger), pointer :: indexToVertexID_tList
+      type (field2DInteger), pointer :: cellsOnVertex_tList
 
-      integer, dimension(:,:), pointer :: edgesOnCell_2Halo
-      integer, dimension(:,:), pointer :: verticesOnCell_2Halo
+      type (field1DInteger), pointer :: indexToEdgeID_tList
 
-      integer, dimension(:,:), pointer :: cellsOnEdge_2Halo
-      integer, dimension(:,:), pointer :: cellsOnVertex_2Halo
+      type (field0dInteger), pointer :: offSetField
 
-      integer, dimension(:,:), pointer :: cellIDSorted
-      integer, dimension(:,:), pointer :: edgeIDSorted
-      integer, dimension(:,:), pointer :: vertexIDSorted
-
 #ifdef HAVE_ZOLTAN
 #ifdef _MPI 
       type (field1DReal), pointer :: xCell, yCell, zCell
@@ -128,7 +134,10 @@
       type (graph) :: block_graph_0Halo, block_graph_1Halo, block_graph_2Halo
       integer :: ghostEdgeStart, ghostVertexStart
 
-      integer :: nBlocksLocal, nBlocksMax, iBlock, nCellsInBlock, nCellsInHalo
+      integer :: nBlocksLocal, nBlocksMax, iBlock, haloStart
+      integer :: nCellsInBlock, nCellsInHalo
+      integer :: nVerticesInBlock
+      integer :: nEdgesInBlock
 
       type (MPAS_Time_type) :: startTime
       type (MPAS_Time_type) :: sliceTime
@@ -506,7 +515,7 @@
       cellsOnEdgeField % dimSizes(1) = 2
       cellsOnEdgeField % dimSizes(1) = nReadEdges
       cellsOnEdgeField % block =&gt; readingBlock
-      nullify(cellsOnEdgeField)
+      nullify(cellsOnEdgeField % next)
 
    
       ! Global indices of cells adjacent to each vertex
@@ -528,9 +537,9 @@
       call MPAS_io_set_var_indices(inputHandle, 'cellsOnVertex', readIndices, ierr=ierr)
       call mpas_io_get_var(inputHandle, 'cellsOnVertex', cellsOnVertexField % array, ierr)
       cellsOnVertexField % dimSizes(1) = vertexDegree
-      cellsOnVertexField % dimSizes(2) = nREadVertices
+      cellsOnVertexField % dimSizes(2) = nReadVertices
       cellsOnVertexField % block =&gt; readingBlock
-      nullify(cellsOnVertexField)
+      nullify(cellsOnVertexField % next)
       deallocate(readIndices)
    
    
@@ -570,6 +579,7 @@
       nBlocksLocal = size(block_id)
       call mpas_dmpar_max_int(domain % dminfo, nBlocksLocal, nBlocksMax)
 
+      allocate(offSetField)
       allocate(indexToCellID_0Halo)
       allocate(domain % blocklist)
 
@@ -577,6 +587,7 @@
 
       block_ptr =&gt; domain % blocklist
       int1d_ptr =&gt; indexToCellID_0Halo
+      int0d_ptr =&gt; offSetField
       do iBlock = 1, nBlocksLocal
         nCellsInBlock = block_count(iBlock)
 
@@ -585,52 +596,64 @@
 
         int1d_ptr % block =&gt; block_ptr
         int1d_ptr % dimSizes(1) = nCellsInBlock
+
+        int0d_ptr % block =&gt; block_ptr
+        int0d_ptr % scalar = nCellsInBlock
         allocate(int1d_ptr % array(nCellsInBlock))
         do i = 1, nCellsInBlock
           int1d_ptr % array(i) = local_cell_list(block_start(iBlock) + i)
         end do
 
         if(iBlock &lt; nBlocksLocal) then
-            allocate(block_ptr % next)
-            allocate(int1d_ptr % next)
-            block_ptr % next % prev =&gt; block_ptr
-            block_ptr =&gt; block_ptr % next
-            int1d_ptr =&gt; int1d_ptr % next
-        else
-            nullify(block_ptr % next)
-            nullify(int1d_ptr % next)
+          allocate(block_ptr % next)
+          allocate(int1d_ptr % next)
+          block_ptr % next % prev =&gt; block_ptr
+          block_ptr =&gt; block_ptr % next
+          int1d_ptr =&gt; int1d_ptr % next
         end if
+
+        nullify(block_ptr % next)
+        nullify(int1d_ptr % next)
       end do
 
       allocate(nEdgesOnCell_0Halo)
       allocate(cellsOnCell_0Halo)
+      allocate(verticesOnCell_0Halo)
 
       block_ptr =&gt; domain % blocklist
       int1d_ptr =&gt; nEdgesOnCell_0Halo
       int2d_ptr =&gt; cellsOnCell_0Halo
+      int2d_ptr2 =&gt; verticesOnCell_0Halo
 
       do while(associated(block_ptr))
-        nullify(int1d_ptr % next)
-        nullify(int2d_ptr % next)
-
         nCellsInBlock = block_count(block_ptr %  localBlockID + 1)
 
         allocate(int1d_ptr % array(nCellsInBlock))
         allocate(int2d_ptr % array(maxEdges, nCellsInBlock))
+        allocate(int2d_ptr2 % array(maxEdges, nCellsInBlock))
 
         int1d_ptr % block =&gt; block_ptr
         int2d_ptr % block =&gt; block_ptr
+        int2d_ptr2 % block =&gt; block_ptr
         int1d_ptr % dimSizes(1) = nCellsInBlock
         int2d_ptr % dimSizes(1) = maxEdges
         int2d_ptr % dimSizes(2) = nCellsInBlock
+        int2d_ptr2 % dimSizes(1) = maxEdges
+        int2d_ptr2 % dimSizes(2) = nCellsInBlock
 
         block_ptr =&gt; block_ptr % next
         if(associated(block_ptr)) then
           allocate(int1d_ptr % next)
           allocate(int2d_ptr % next)
+          allocate(int2d_ptr2 % next)
           int1d_ptr =&gt; int1d_ptr % next
           int2d_ptr =&gt; int2d_ptr % next
+          int2d_ptr2 =&gt; int2d_ptr2 % next
         end if
+
+        nullify(int1d_ptr % next)
+        nullify(int2d_ptr % next)
+        nullify(int2d_ptr2 % next)
       end do
 
       !
@@ -646,6 +669,8 @@
       call mpas_link_exchange_list_field(indexToCellIDField, indexToCellID_0Halo, nEdgesOnCellField, nEdgesOnCell_0Halo)
       write(6,*) 'link 0 halo exchange lists 2'
       call mpas_link_exchange_list_field(indexToCellIDField, indexToCellID_0Halo, cellsOnCellField, cellsOnCell_0Halo)
+      write(6,*) 'link 0 halo exchange lists 3'
+      call mpas_link_exchange_list_field(indexToCellIDField, indexToCellID_0Halo, verticesOnCellField, verticesOnCell_0Halo)
 
       write(6,*) '0 halo all to all 1'
       call mpas_dmpar_alltoall_field(domain % dminfo, indexToCellIDField, indexToCellID_0Halo)
@@ -653,8 +678,107 @@
       call mpas_dmpar_alltoall_field(domain % dminfo, nEdgesOnCellField, nEdgesOnCell_0Halo)
       write(6,*) '0 halo all to all 3'
       call mpas_dmpar_alltoall_field(domain % dminfo, cellsOnCellField, cellsOnCell_0Halo)
+      write(6,*) '0 halo all to all 4'
+      call mpas_dmpar_alltoall_field(domain % dminfo, verticesOnCellField, verticesOnCell_0Halo)
 
       write(6,*) 'Done with 0 halo'
+
+!      write(6,*) 'Building temporary indexToVertexID list. Containing 0 and 1 halo vertices'
+!      allocate(indexToVertexID_tList)
+!      int1d_ptr =&gt; nEdgesOnCell_0Halo
+!      int1d_ptr2 =&gt; indexToVertexID_tList
+!      int2d_ptr =&gt; verticesOnCell_0Halo
+!      int2d_ptr2 =&gt; cellsOnVertex_tList
+!      do while(associated(int1d_ptr))
+!        call mpas_block_decomp_all_edges_in_block(maxEdges, int1d_ptr % dimSizes(1), int1d_ptr % array, &amp;
+!                                                  int2d_ptr % array, nVerticesInBlock, int1d_ptr2 % array)
+!
+!        int1d_ptr2 % block =&gt; int1d_ptr % block
+!        int2d_ptr2 % block =&gt; int1d_ptr % block
+!
+!        int1d_ptr2 % dimSizes(1) = nVerticesInBlock
+!        int2d_ptr2 % dimSizes(1) = vertexDegree
+!        int2d_ptr2 % dimSizes(2) = nVerticesInBlock
+!
+!        allocate(int2d_ptr2 % array(vertexDegree, nVerticesInBlock))
+!
+!        int1d_ptr =&gt; int1d_ptr % next
+!        int2d_ptr =&gt; int2d_ptr % next
+!
+!        if(associated(int1d_ptr)) then
+!          allocate(int1d_ptr2 % next)
+!          allocate(int2d_ptr2 % next)
+!          int1d_ptr2 =&gt; int1d_ptr2 % next
+!          int2d_ptr2 =&gt; int2d_ptr2 % next
+!        end if
+!        nullify(int1d_ptr2 % next)
+!        nullify(int2d_ptr2 % next)
+!      end do
+!
+!      write(6,*) 'Making vertex exchange lists'
+!
+!      call mpas_get_exchange_lists(domain % dminfo, indexToVertexIDField, .false., indexToVertexID_tList, .true.)
+!
+!      write(6,*) 'SendLists'
+!      sendListPtr =&gt; indexToVertexIDField % sendList(1) % next
+!      do while(associated(sendListPtr))
+!        write(6,*) sendListPtr % procID, sendListPtr % blockID, sendListPtr % nList
+!        write(6,*) sendListPtr % list
+!        sendListPtr =&gt; sendListPtr % next
+!      end do
+!
+!      write(6,*) 'Linking vertex exchange lists'
+!      call mpas_link_exchange_list_field(indexToVertexIDField, indexToVertexID_tList, cellsOnVertexField, cellsOnVertex_tList)
+!      write(6,*) 'All to all on cellsOnVertex'
+!      call mpas_dmpar_alltoall_field(domain % dminfo, cellsOnVertexField, cellsOnVertex_tList)
+!
+!      write(6,*) 'Splitting vertices into 0 and 1 halos'
+!      allocate(indexToVertexID_0Halo)
+!      allocate(indexToVertexID_Halos(nHalos+1))
+!      int1d_ptr =&gt; indexToCellID_0Halo
+!      int1d_ptr2 =&gt; indexToVertexID_tList
+!      int1d_ptr3 =&gt; indexToVertexID_0Halo
+!      int1d_ptr4 =&gt; indexToVertexID_Halos(1)
+!      int2d_ptr =&gt; cellsOnVertex_tList
+!      int2d_ptr2 =&gt; cellsOnVertex_0Halo
+!
+!      do while(associated(int1d_ptr))
+!        call mpas_block_decomp_partitioned_edge_list(int1d_ptr % dimSizes(1), int1d_ptr % array, vertexDegree, int1d_ptr2 % dimSizes(1), int2d_ptr % array, int1d_ptr2 % array, haloStart)
+!
+!        int1d_ptr3 % block =&gt; int1d_ptr % block
+!        int1d_ptr3 % dimSizes(1) = haloStart
+!        allocate(int1d_ptr3 % array(haloStart))
+!        int1d_ptr3 % array(:) = int1d_ptr2 % array(1:haloStart)
+!
+!        int1d_ptr4 % block =&gt; int1d_ptr % block
+!        int1d_ptr4 % dimSizes(1) = int1d_ptr2 % dimSizes(1) - haloStart
+!        allocate(int1d_ptr4 % array(int1d_ptr4 % dimSizes(1)))
+!        int1d_ptr4 % array(:) = int1d_ptr2 % array(haloStart+1:int1d_ptr2 % dimSizes(1))
+!
+!        int2d_ptr2 % block =&gt; int2d_ptr2 % block
+!        int2d_ptr2 % dimSizes(1) = vertexDegree
+!        int2d_ptr2 % dimSizes(2) = haloStart
+!        allocate(int2d_ptr2 % array(vertexDegree, haloStart))
+!        int2d_ptr2 % array(:,:) = int2d_ptr % array(:, 1:haloStart)
+!
+!        int1d_ptr =&gt; int1d_ptr % next
+!        int1d_ptr2 =&gt; int1d_ptr2 % next
+!        int2d_ptr =&gt; int2d_ptr % next
+!        if(associated(int1d_ptr)) then
+!          allocate(int1d_ptr3 % next)
+!          allocate(int1d_ptr4 % next)
+!          allocate(int2d_ptr2 % next)
+!          int1d_ptr3 =&gt; int1d_ptr3 % next
+!          int1d_ptr4 =&gt; int1d_ptr4 % next
+!          int2d_ptr2 =&gt; int2d_ptr2 % next
+!        end if
+!        nullify(int1d_ptr3 % next)
+!        nullify(int1d_ptr4 % next)
+!        nullify(int2d_ptr3 % next)
+!      end do
+
+!     call mpas_deallocate_field(indexToVertexID_tList)
+!     call mpas_deallocate_field(cellsOnVertex_tList)
    
 #ifdef HAVE_ZOLTAN
 #ifdef _MPI 
@@ -681,129 +805,41 @@
 !     deallocate(recvCellList % list)
 !     deallocate(recvCellList)
 
-      write(6,*) 'Determining 1 halo cells'
+      write(6,*) 'Trying new halo routine'
+      call mpas_get_halo_cells_and_exchange_lists(domain % dminfo, nHalos, indexToCellID_0Halo, nEdgesOnCell_0Halo, cellsOnCell_0Halo, indexToCellID_Halos, nEdgesOnCell_Halos, cellsOnCell_Halos)
 
-      allocate(indexToCellID_1Halo)
+!     call mpas_get_vertex_ids_and_exchange_lists(domain % dminfo, nHalos, maxEdges, vertexDegree, indexToCellID_0Halo, nEdgesOnCell_0Halo
 
-      int1d_ptr =&gt; indexToCellID_0Halo
-      int1d_ptr2 =&gt; nEdgesOnCell_0Halo
-      int2d_ptr =&gt; cellsOnCell_0Halo
+!     block_ptr =&gt; domain % blocklist
+!     do while(associated(block_ptr))
+!       write(6,*) 'block id = ', block_ptr % blockID
+!       do i = 1, nHalos
+!         write(6,*) 'sendList on halo layer', i
+!         sendListPtr =&gt; block_ptr % parinfo % cellsToSend(i)
+!         do while(associated(sendListPtr))
+!           write(6,*) sendListPtr % procID, sendListPtr % blockID, sendListPtr % nList
+!           sendListPtr =&gt; sendListPtr % next
+!         end do
+!         write(6,*) 'recvList on halo layer', i
+!         recvListPtr =&gt; block_ptr % parinfo % cellsToRecv(i)
+!         do while(associated(recvListPtr))
+!           write(6,*) recvListPtr % procID, recvListPtr % blockID, recvListPtr % nList
+!           recvListPtr =&gt; recvListPtr % next
+!         end do
+!         write(6,*) 'copyList on halo layer', i
+!         copyListPtr =&gt; block_ptr % parinfo % cellsToCopy(i)
+!         do while(associated(copyListPtr))
+!           write(6,*) copyListPtr % procID, copyListPtr % blockID, copyListPtr % nList
+!           copyListPtr =&gt; copyListPtr % next
+!         end do
 
-      int1d_ptr3 =&gt; indexToCellID_1Halo
+!       end do
+!       block_ptr =&gt; block_ptr % next
+!     end do
 
-      do while(associated(int1d_ptr))
-        ! Build 0 halo graph. Describing all owned cells.
-        block_graph_0halo % nVerticesTotal = int1d_ptr % dimSizes(1)
-        block_graph_0halo % nVertices = int1d_ptr % dimSizes(1)
-        block_graph_0halo % maxDegree = maxEdges
-        block_graph_0halo % ghostStart = int1d_ptr % dimSizes(1)
-        allocate(block_graph_0Halo % vertexID(int1d_ptr % dimSizes(1)))
-        allocate(block_graph_0Halo % nAdjacent(int1d_ptr % dimSizes(1)))
-        allocate(block_graph_0Halo % adjacencyList(maxEdges, int1d_ptr % dimSizes(1)))
-
-        block_graph_0Halo % vertexID(:) = int1d_ptr % array(:)
-        block_graph_0Halo % nAdjacent(:) = int1d_ptr2 % array(:)
-        block_graph_0Halo % adjacencyList(:,:) = int2d_ptr % array(:,:)
-
-        ! Build 1 halo graph. Containing all owned cells and all cells in the 1 halo.
-        call mpas_block_decomp_add_halo(domain % dminfo, block_graph_0Halo, block_graph_1Halo)
-
-        ! Copy cells in the 1 halo to indexToCellID_1Halo field pointer.
-        nCellsInHalo = block_graph_1Halo % nVerticesTotal - block_graph_1Halo % nVertices
-
-        int1d_ptr3 % block =&gt; int1d_ptr % block
-        int1d_ptr3 % dimSizes(1) = nCellsInHalo
-        allocate(int1d_ptr3 % array(nCellsInHalo))
-        int1d_ptr3 % array(:) = block_graph_1halo % vertexID(block_graph_1Halo % ghostStart:block_graph_1Halo % nVerticesTotal)
-
-        int1d_ptr =&gt; int1d_ptr % next
-        int1d_ptr2 =&gt; int1d_ptr2 % next
-        int2d_ptr =&gt; int2d_ptr % next
-
-        if(associated(int1d_ptr)) then
-          deallocate(block_graph_0Halo % vertexID)
-          deallocate(block_graph_0Halo % nAdjacent)
-          deallocate(block_graph_0Halo % adjacencyList)
-
-          deallocate(block_graph_1Halo % vertexID)
-          deallocate(block_graph_1Halo % nAdjacent)
-          deallocate(block_graph_1Halo % adjacencyList)
-
-          allocate(int1d_ptr3 % next)
-          int1d_ptr3 =&gt; int1d_ptr3 % next
-          nullify(int1d_ptr3 % next)
-        end if
-      end do
-
-      write(6,*) 'Setting up the 1halo exchange lists'
-
-      !Build exchange lists for 0 halo to 1 halo, for allToAll communications
-      call mpas_get_exchange_lists(domain % dminfo, indexToCellID_0Halo, .true., indexToCellID_1Halo, .true.)
-
-      write(6,*) 'Setting up 1 halo fields'
-      ! setup 1 halo fields for allToAll communications
-      allocate(nEdgesOnCell_1Halo)
-      allocate(cellsOnCell_1Halo)
-
-      int1d_ptr =&gt; indexToCellID_1Halo
-      int1d_ptr2 =&gt; nEdgesOnCell_1Halo
-      int2d_ptr =&gt; cellsOnCell_1Halo
-
-      do while(associated(int1d_ptr))
-        int1d_ptr2 % block =&gt; int1d_ptr % block
-        int2d_ptr % block =&gt; int1d_ptr % block
-
-        int1d_ptr2 % dimSizes(1) = int1d_ptr % dimSizes(1)
-        int2d_ptr % dimSizes(1) = maxEdges
-        int2d_ptr % dimSizes(2) = int1d_ptr % dimSizes(1)
-
-        allocate(int1d_ptr2 % array(int1d_ptr2 % dimSizes(1)))
-        allocate(int2d_ptr % array(int2d_ptr % dimSizes(1), int2d_ptr % dimSizes(2)))
-        
-        int1d_ptr =&gt; int1d_ptr % next
-        if(associated(int1d_ptr)) then
-          allocate(int1d_ptr2 % next)
-          allocate(int2d_ptr % next)
-          int1d_ptr2 =&gt; int1d_ptr2 % next
-          int2d_ptr =&gt; int2d_ptr % next
-          nullify(int1d_ptr2 % next)
-          nullify(int2d_ptr % next)
-        end if
-      end do
-
-
-      write(6,*) 'All to all 1'
-      call mpas_dmpar_alltoall_field(domain % dminfo, indexToCellID_0Halo, indexToCellID_1Halo)
-
-      write(6,*) 'Linking 1 halo exchange lists 1' 
-      call mpas_link_exchange_list_field(indexToCellID_0Halo, indexToCellID_1Halo, nEdgesOnCell_0Halo, nEdgesOnCell_1Halo)
-
-      write(6,*) 'All to all 2'
-      call mpas_dmpar_alltoall_field(domain % dminfo, nEdgesOnCell_0Halo, nEdgesOnCell_1Halo)
-
-      write(6,*) 'Linking 1 halo exchange lists 2' 
-      call mpas_link_exchange_list_field(indexToCellID_0Halo, indexToCellID_1Halo, cellsOnCell_0Halo, cellsOnCell_1Halo)
-
-      write(6,*) 'All to all 3'
-      call mpas_dmpar_alltoall_field(domain % dminfo, cellsOnCell_0Halo, cellsOnCell_1Halo)
-
       write(6,*) 'Stopping'
       stop
  
-!      !
-!      ! Work out exchange lists for 2-halo and exchange cell information for 2-halo
-!      !
-!      block_graph_1Halo % nVertices = block_graph_1Halo % nVerticesTotal
-!      block_graph_1Halo % ghostStart = block_graph_1Halo % nVerticesTotal + 1
-!     
-!      ! Get back a graph describing the owned and 1-halo cells plus the cells in the 2-halo
-!      call mpas_block_decomp_add_halo(domain % dminfo, block_graph_1Halo, block_graph_2Halo)
-!   
-!      block_graph_2Halo % nVertices = block_graph_0Halo % nVertices
-!      block_graph_2Halo % ghostStart = block_graph_2Halo % nVertices + 1
-!
-!      nOwnCells = block_graph_2Halo % nVertices
-!
 !#ifdef HAVE_ZOLTAN
 !#ifdef _MPI 
 !      !! For now, only use Zoltan with MPI
@@ -815,26 +851,6 @@
 !#endif
 !#endif
 !
-!      call mpas_dmpar_get_owner_list(domain % dminfo, &amp;
-!                                block_graph_0Halo % nVertices, block_graph_2Halo % nVerticesTotal, &amp;
-!                                block_graph_0Halo % vertexID,  block_graph_2Halo % vertexID, &amp;
-!                                send2Halo, recv2Halo)
-!   
-!      call mpas_dmpar_alltoall_field(domain % dminfo, block_graph_0Halo % vertexID, block_graph_2Halo % vertexID, &amp;
-!                                block_graph_0Halo % nVertices, block_graph_2Halo % nVerticesTotal, &amp;
-!                                send2Halo, recv2Halo)
-!   
-!      call mpas_dmpar_alltoall_field(domain % dminfo, block_graph_0Halo % nAdjacent, block_graph_2Halo % nAdjacent, &amp;
-!                                block_graph_0Halo % nVertices, block_graph_2Halo % nVerticesTotal, &amp;
-!                                send2Halo, recv2Halo)
-!   
-!      call mpas_dmpar_alltoall_field(domain % dminfo, block_graph_0Halo % adjacencyList, block_graph_2Halo % adjacencyList, &amp;
-!                                block_graph_0Halo % maxDegree, block_graph_0Halo % nVertices, block_graph_2Halo % nVerticesTotal, &amp;
-!                                send2Halo, recv2Halo)
-!
-!
-!   
-!      !
 !      ! Knowing which cells are in block and the 2-halo, we can exchange lists of which edges are
 !      !   on each cell and which vertices are on each cell from the processes that read these
 !      !   fields for each cell to the processes that own the cells
@@ -1438,58 +1454,58 @@
 !         end do
 !      end do
 
-      deallocate(cellIDSorted)
-      deallocate(edgeIDSorted)
-      deallocate(vertexIDSorted)
-
-   
-      !
-      ! Deallocate fields, graphs, and other memory
-      !
-      deallocate(indexToCellIDField % ioinfo)
-      deallocate(indexToCellIDField % array)
-#ifdef HAVE_ZOLTAN
-#ifdef _MPI 
-      deallocate(xCellField % ioinfo)
-      deallocate(xCellField % array)
-      deallocate(yCellField % ioinfo)
-      deallocate(yCellField % array)
-      deallocate(zCellField % ioinfo)
-      deallocate(zCellField % array)
-#endif
-#endif
-      deallocate(indexToEdgeIDField % ioinfo)
-      deallocate(indexToEdgeIDField % array)
-      deallocate(indexToVertexIDField % ioinfo)
-      deallocate(indexToVertexIDField % array)
-      deallocate(cellsOnCellField % ioinfo)
-      deallocate(cellsOnCellField % array)
-      deallocate(edgesOnCellField % ioinfo)
-      deallocate(edgesOnCellField % array)
-      deallocate(verticesOnCellField % ioinfo)
-      deallocate(verticesOnCellField % array)
-      deallocate(cellsOnEdgeField % ioinfo)
-      deallocate(cellsOnEdgeField % array)
-      deallocate(cellsOnVertexField % ioinfo)
-      deallocate(cellsOnVertexField % array)
-      deallocate(cellsOnCell_0Halo)
-      deallocate(nEdgesOnCell_0Halo)
-      deallocate(indexToCellID_0Halo)
-      deallocate(cellsOnEdge_2Halo)
-      deallocate(cellsOnVertex_2Halo)
-      deallocate(nEdgesOnCell_2Halo)
-      deallocate(edgesOnCell_2Halo)
-      deallocate(verticesOnCell_2Halo)
-      deallocate(block_graph_0Halo % vertexID)
-      deallocate(block_graph_0Halo % nAdjacent)
-      deallocate(block_graph_0Halo % adjacencyList)
-#ifdef HAVE_ZOLTAN
-#ifdef _MPI
-      deallocate(xCell)
-      deallocate(yCell)
-      deallocate(zCell)
-#endif
-#endif
+!      deallocate(cellIDSorted)
+!      deallocate(edgeIDSorted)
+!      deallocate(vertexIDSorted)
+!
+!   
+!      !
+!      ! Deallocate fields, graphs, and other memory
+!      !
+!      deallocate(indexToCellIDField % ioinfo)
+!      deallocate(indexToCellIDField % array)
+!#ifdef HAVE_ZOLTAN
+!#ifdef _MPI 
+!      deallocate(xCellField % ioinfo)
+!      deallocate(xCellField % array)
+!      deallocate(yCellField % ioinfo)
+!      deallocate(yCellField % array)
+!      deallocate(zCellField % ioinfo)
+!      deallocate(zCellField % array)
+!#endif
+!#endif
+!      deallocate(indexToEdgeIDField % ioinfo)
+!      deallocate(indexToEdgeIDField % array)
+!      deallocate(indexToVertexIDField % ioinfo)
+!      deallocate(indexToVertexIDField % array)
+!      deallocate(cellsOnCellField % ioinfo)
+!      deallocate(cellsOnCellField % array)
+!      deallocate(edgesOnCellField % ioinfo)
+!      deallocate(edgesOnCellField % array)
+!      deallocate(verticesOnCellField % ioinfo)
+!      deallocate(verticesOnCellField % array)
+!      deallocate(cellsOnEdgeField % ioinfo)
+!      deallocate(cellsOnEdgeField % array)
+!      deallocate(cellsOnVertexField % ioinfo)
+!      deallocate(cellsOnVertexField % array)
+!      deallocate(cellsOnCell_0Halo)
+!      deallocate(nEdgesOnCell_0Halo)
+!      deallocate(indexToCellID_0Halo)
+!      deallocate(cellsOnEdge_2Halo)
+!      deallocate(cellsOnVertex_2Halo)
+!      deallocate(nEdgesOnCell_2Halo)
+!      deallocate(edgesOnCell_2Halo)
+!      deallocate(verticesOnCell_2Halo)
+!      deallocate(block_graph_0Halo % vertexID)
+!      deallocate(block_graph_0Halo % nAdjacent)
+!      deallocate(block_graph_0Halo % adjacencyList)
+!#ifdef HAVE_ZOLTAN
+!#ifdef _MPI
+!      deallocate(xCell)
+!      deallocate(yCell)
+!      deallocate(zCell)
+!#endif
+!#endif
    end subroutine mpas_input_state_for_domain!}}}
 
    !CR:TODO: an identical subroutine is found in module_io_output - merge

</font>
</pre>