diff --git a/Common/derived_types.f90 b/Common/derived_types.f90
index 87655a4531a0d7d4ee6b4e639df93a46ae900a0c..6337886f2b9bde8227c2f0c4d0aace8a03e58d72 100644
--- a/Common/derived_types.f90
+++ b/Common/derived_types.f90
@@ -82,12 +82,16 @@ module derived_types
           max_speed_eddy_index
 
      character(len = :), allocatable:: dir ! directory
+  end type Shpc_Slice_Handler
+
+  type shpc_slice_meta
+     ! Some metadata of a slice of SHPC
      integer d0 ! first date
 
      integer, allocatable:: ishape_last(:) ! (d0:)
      ! shape index (0-based) in the collection of shapefiles of the last
      ! shape at a given date index
-  end type Shpc_Slice_Handler
+  end type shpc_slice_meta
 
   private shpfileobject
 
diff --git a/Common/read_snapshot.f90 b/Common/read_snapshot.f90
index 0ed139330c8a99c4934f829b35293b5b50cd1743..602ea108c1f6fb37ab28cee47ccdad331977dd32 100644
--- a/Common/read_snapshot.f90
+++ b/Common/read_snapshot.f90
@@ -4,18 +4,19 @@ module read_snapshot_m
 
 contains
 
-  subroutine read_snapshot(s, hshpc, nlon, nlat, k, corner, step, copy)
+  subroutine read_snapshot(s, hshpc, ssm, nlon, nlat, k, corner, step, copy)
 
     ! Libraries:
     use contour_531, only: convert_to_ind 
     use jumble, only: assert
     use numer_rec_95, only: hunt
 
-    use derived_types, only: snapshot, eddy, shpc_slice_handler
+    use derived_types, only: snapshot, eddy, shpc_slice_handler, shpc_slice_meta
     use read_eddy_m, only: read_eddy
 
     type(snapshot), intent(out):: s ! completely defined
     TYPE(shpc_slice_handler), intent(in):: hshpc(:)
+    type(shpc_slice_meta), intent(in):: ssm(:)
 
     integer, intent(in):: nlon, nlat
     ! size of ssh array in input NetCDF, assuming no repeated point if
@@ -42,20 +43,20 @@ contains
     if (size(hshpc) == 1) then
        i_shpc = 1
     else
-       call hunt([hshpc%d0, huge(0)], k, i_shpc)
+       call hunt([ssm%d0, huge(0)], k, i_shpc)
     end if
 
-    if (k == hshpc(i_shpc)%d0) then
+    if (k == ssm(i_shpc)%d0) then
        ishape_first = 0
     else
-       ! {k > hshpc(i_shpc)%d0}
-       ishape_first = hshpc(i_shpc)%ishape_last(k - 1) + 1
+       ! {k > ssm(i_shpc)%d0}
+       ishape_first = ssm(i_shpc)%ishape_last(k - 1) + 1
     end if
 
-    s%number_extr = hshpc(i_shpc)%ishape_last(k) - ishape_first + 1
+    s%number_extr = ssm(i_shpc)%ishape_last(k) - ishape_first + 1
     allocate(s%list(s%number_extr))
 
-    do ishape = ishape_first, hshpc(i_shpc)%ishape_last(k)
+    do ishape = ishape_first, ssm(i_shpc)%ishape_last(k)
        call read_eddy(e, date_read, eddy_i, hshpc(i_shpc), ishape)
 
        ! Check that all the eddies have the same date index:
diff --git a/Common/shpc_close.f90 b/Common/shpc_close.f90
index 7fb38edee80894e21850f462bedf782c95569e90..e57ac792a62e5ea45a4d88e44acbc243e9d73c7c 100644
--- a/Common/shpc_close.f90
+++ b/Common/shpc_close.f90
@@ -20,7 +20,6 @@ contains
     CALL shpclose(hshp%max_speed)
     close(hshp%unit)
     deallocate(hshp%dir)
-    if (allocated(hshp%ishape_last)) deallocate(hshp%ishape_last)
 
   end subroutine shpc_close
   
diff --git a/Common/shpc_create.f90 b/Common/shpc_create.f90
index b3e7df61d929d6fddca59c19581cfc4ab881a1ce..c637d17c8e7377174060e60231036b48f027b9fb 100644
--- a/Common/shpc_create.f90
+++ b/Common/shpc_create.f90
@@ -14,8 +14,6 @@ contains
     use derived_types, only: shpc_slice_handler
 
     TYPE(shpc_slice_handler), intent(out):: hshp
-    ! fields d0 and ishape_last are not defined in this procedure
-
     character(len = *), intent(in):: shpc_dir
     logical, intent(in):: cyclone
 
diff --git a/Inst_eddies/Tests/test_nearby_extr.f90 b/Inst_eddies/Tests/test_nearby_extr.f90
index 63d95eb2bbcf387c01fd26990d1ad9c48039de35..b8022813ac7ade783b2cc0bdd43912d1ea1a63c4 100644
--- a/Inst_eddies/Tests/test_nearby_extr.f90
+++ b/Inst_eddies/Tests/test_nearby_extr.f90
@@ -5,7 +5,7 @@ program test_nearby_extr
   use jumble, only: deg_to_rad, rad_to_deg
   use shapelib_03, only: dbf_read_attribute_03
 
-  use derived_types, only: snapshot, shpc_slice_handler
+  use derived_types, only: snapshot, shpc_slice_handler, shpc_slice_meta
   use nearby_extr_m, only: nearby_extr
   use read_snapshot_m, only: read_snapshot
   use shpc_close_m, only: shpc_close
@@ -17,6 +17,7 @@ program test_nearby_extr
   type(snapshot) s
   TYPE(shpc_slice_handler) hshp
   integer unit, l
+  type(shpc_slice_meta) ssm
 
   real corner_deg(2)
   ! longitude and latitude of the corner of the whole grid in input
@@ -44,9 +45,9 @@ program test_nearby_extr
   close(unit)
 
   call shpc_open(hshp, trim(shpc_dir), pszaccess = "rb")
-  call dbf_read_attribute_03(hshp%d0, hshp%extremum, hshp%extr_date, ishape = 0)
-  call read_opcol(hshp%ishape_last, hshp%unit, my_lbound = hshp%d0)
-  call read_snapshot(s, [hshp], nlon, nlat, k = hshp%d0, &
+  call dbf_read_attribute_03(ssm%d0, hshp%extremum, hshp%extr_date, ishape = 0)
+  call read_opcol(ssm%ishape_last, hshp%unit, my_lbound = ssm%d0)
+  call read_snapshot(s, [hshp], [ssm], nlon, nlat, k = ssm%d0, &
        corner = corner_deg * deg_to_rad, step = step_deg * deg_to_rad, &
        copy = 0)
   CALL shpc_close(hshp)
diff --git a/Overlap/Tests/test_get_dispatch_snap.f90 b/Overlap/Tests/test_get_dispatch_snap.f90
index 9a6b245f53438233da0f704694185de6a575f8ba..b1aa7f87ee91ee94a3d3e46308490d7901cd211c 100644
--- a/Overlap/Tests/test_get_dispatch_snap.f90
+++ b/Overlap/Tests/test_get_dispatch_snap.f90
@@ -10,7 +10,7 @@ program test_get_dispatch_snap
        MPI_Comm_size, mpi_abort
   use shapelib_03, only: dbf_read_attribute_03
 
-  use derived_types, only: snapshot, shpc_slice_handler
+  use derived_types, only: snapshot, shpc_slice_handler, shpc_slice_meta
   use dispatch_snapshot_m, only: dispatch_snapshot
   use get_snapshot_m, only: get_snapshot
   use send_snapshot_m, only: send_snapshot
@@ -23,6 +23,7 @@ program test_get_dispatch_snap
   character(len = :), allocatable:: shpc_dir
   type(snapshot) s
   TYPE(shpc_slice_handler) hshp
+  type(shpc_slice_meta) ssm
   integer k_begin, copy, rank, n_proc, k_end, n_dates
   integer unit_isolated
 
@@ -73,11 +74,11 @@ program test_get_dispatch_snap
   end if
 
   call shpc_open(hshp, trim(shpc_dir), pszaccess = "rb")
-  call dbf_read_attribute_03(hshp%d0, hshp%extremum, hshp%extr_date, ishape = 0)
-  call read_opcol(hshp%ishape_last, hshp%unit, my_lbound = hshp%d0)
+  call dbf_read_attribute_03(ssm%d0, hshp%extremum, hshp%extr_date, ishape = 0)
+  call read_opcol(ssm%ishape_last, hshp%unit, my_lbound = ssm%d0)
 
   if (rank == 0) then
-     n_dates = size(hshp%ishape_last)
+     n_dates = size(ssm%ishape_last)
      call new_unit(unit_isolated)
      open(unit_isolated, file = "isolated_nodes.txt", status = "replace", &
           action = "write")
@@ -90,16 +91,16 @@ program test_get_dispatch_snap
   call ezmpi_bcast(k, root = 0)
   call ezmpi_bcast(copy, root = 0)
   call ezmpi_bcast(n_dates, root = 0)
-  k_begin = hshp%d0 + (rank * n_dates) / n_proc
+  k_begin = ssm%d0 + (rank * n_dates) / n_proc
   
   if (rank < n_proc - 1) then
-     k_end = hshp%d0 + ((rank + 1) * n_dates) / n_proc
+     k_end = ssm%d0 + ((rank + 1) * n_dates) / n_proc
   else
-     k_end = hshp%d0 + n_dates - 1
+     k_end = ssm%d0 + n_dates - 1
   end if
   
   call get_snapshot(s, nlon, nlat, corner * deg_to_rad, step * deg_to_rad, &
-       copy, [hshp], k, k_end, rank, n_proc, max_delta = 1)
+       copy, [hshp], [ssm], k, k_end, rank, n_proc, max_delta = 1)
   CALL shpc_close(hshp)
   call dispatch_snapshot(s, unit_isolated, rank, k_begin, max_delta = 1, k = k)
 
diff --git a/Overlap/Tests/test_overlap.f90 b/Overlap/Tests/test_overlap.f90
index fe92043addd25aafe3f66344aeb909117cf632c2..09eae3c16f7dd658e3912675ca8579714817d712 100644
--- a/Overlap/Tests/test_overlap.f90
+++ b/Overlap/Tests/test_overlap.f90
@@ -7,7 +7,7 @@ program test_overlap
   use jumble, only: deg_to_rad, assert
   use shapelib_03, only: dbf_read_attribute_03
 
-  use derived_types, only: snapshot, shpc_slice_handler
+  use derived_types, only: snapshot, shpc_slice_handler, shpc_slice_meta
   use overlap_m, only: overlap
   use read_snapshot_m, only: read_snapshot
   use shpc_close_m, only: shpc_close
@@ -21,6 +21,7 @@ program test_overlap
   integer unit, i, copy, n_dates
   type(snapshot), allocatable:: flow(:) ! (max_delta + 1)
   TYPE(shpc_slice_handler) hshp
+  type(shpc_slice_meta) ssm
 
   real:: corner_deg(2) = [huge(0.), huge(0.)], corner(2)
   ! longitude and latitude of the corner of the whole grid, in degrees
@@ -65,19 +66,18 @@ program test_overlap
   step = step_deg * deg_to_rad
   allocate(flow(max_delta + 1))
   call shpc_open(hshp, trim(shpc_dir), pszaccess = "rb")
-  call dbf_read_attribute_03(hshp%d0, hshp%extremum, hshp%extr_date, &
-       ishape = 0)
-  call read_opcol(hshp%ishape_last, hshp%unit, my_lbound = hshp%d0)
-  n_dates = size(hshp%ishape_last)
-  call assert(hshp%d0 <= [k_test_1, k_test_2] .and. [k_test_1, k_test_2] &
-       < hshp%d0 + n_dates, "test_overlap k_test_1, k_test_2")
-  e_overestim = maxval([hshp%ishape_last(hshp%d0) + 1, &
-       ediff1d(hshp%ishape_last)])
+  call dbf_read_attribute_03(ssm%d0, hshp%extremum, hshp%extr_date, ishape = 0)
+  call read_opcol(ssm%ishape_last, hshp%unit, my_lbound = ssm%d0)
+  n_dates = size(ssm%ishape_last)
+  call assert(ssm%d0 <= [k_test_1, k_test_2] .and. [k_test_1, k_test_2] &
+       < ssm%d0 + n_dates, "test_overlap k_test_1, k_test_2")
+  e_overestim = maxval([ssm%ishape_last(ssm%d0) + 1, ediff1d(ssm%ishape_last)])
   open(unit, file = "e_overestim.txt", status = "replace", action = "write")
   write(unit, fmt = *) e_overestim
   close(unit)
-  call read_snapshot(flow(1), [hshp], nlon, nlat, k_test_1, corner, step, copy)
-  call read_snapshot(flow(max_delta + 1), [hshp], nlon, nlat, k_test_2, &
+  call read_snapshot(flow(1), [hshp], [ssm], nlon, nlat, k_test_1, corner, &
+       step, copy)
+  call read_snapshot(flow(max_delta + 1), [hshp], [ssm], nlon, nlat, k_test_2, &
        corner, step, copy)
   CALL shpc_close(hshp)
   print *, "Enter flow(1)%list%delta_out (array with ", &
diff --git a/Overlap/Tests/test_read_eddy.f90 b/Overlap/Tests/test_read_eddy.f90
index a59d554d22b61112732b2018de2f10866b407ca0..70c6cb5dd5d75c685e7c224d27567c3783a4363c 100644
--- a/Overlap/Tests/test_read_eddy.f90
+++ b/Overlap/Tests/test_read_eddy.f90
@@ -1,8 +1,7 @@
 program test_read_eddy
 
   ! Library:
-  use jumble, only: get_command_arg_dyn, read_opcol
-  use shapelib_03, only: dbf_read_attribute_03
+  use jumble, only: get_command_arg_dyn
 
   use derived_types, only: eddy, shpc_slice_handler
   use read_eddy_m, only: read_eddy
@@ -26,8 +25,6 @@ program test_read_eddy
   print *, "Enter namelist main_nml."
   read(unit = *, nml = main_nml)
   call shpc_open(hshp, shpc_dir, pszaccess = "rb")
-  call dbf_read_attribute_03(hshp%d0, hshp%extremum, hshp%extr_date, ishape = 0)
-  call read_opcol(hshp%ishape_last, hshp%unit, my_lbound = hshp%d0)
   call read_eddy(e, k, eddy_i, hshp, ishape)
   CALL shpc_close(hshp)
 
diff --git a/Overlap/Tests/test_read_snapshot.f90 b/Overlap/Tests/test_read_snapshot.f90
index b6a9783a81ce1b595f15767c118e60d4497291e4..6fbd08d0e3268a3285734fa34110d7cf13b293f0 100644
--- a/Overlap/Tests/test_read_snapshot.f90
+++ b/Overlap/Tests/test_read_snapshot.f90
@@ -7,7 +7,7 @@ program test_read_snapshot
        read_opcol
   use shapelib_03, only: dbf_read_attribute_03
 
-  use derived_types, only: snapshot, shpc_slice_handler
+  use derived_types, only: snapshot, shpc_slice_handler, shpc_slice_meta
   use read_snapshot_m, only: read_snapshot
   use shpc_close_m, only: shpc_close
   use shpc_open_m, only: shpc_open
@@ -18,6 +18,7 @@ program test_read_snapshot
   character(len = :), allocatable:: shpc_dir
   type(snapshot) s
   TYPE(shpc_slice_handler), allocatable:: hshp(:) ! (n_shpc)
+  type(shpc_slice_meta), allocatable:: ssm(:) ! (n_shpc)
   integer copy, unit, k, i
   integer n_shpc ! number of input SHPC directories
 
@@ -44,14 +45,14 @@ program test_read_snapshot
   n_shpc = COMMAND_ARGUMENT_COUNT()
   call assert(n_shpc /= 0, &
        "Required arguments: SHPC-directory [SHPC-directory] ...")
-  allocate(hshp(n_shpc))
+  allocate(hshp(n_shpc), ssm(n_shpc))
 
   do i = 1, n_shpc
      call get_command_arg_dyn(i, shpc_dir)
      call shpc_open(hshp(i), trim(shpc_dir), pszaccess = "rb")
-     call dbf_read_attribute_03(hshp(i)%d0, hshp(i)%extremum, &
+     call dbf_read_attribute_03(ssm(i)%d0, hshp(i)%extremum, &
           hshp(i)%extr_date, ishape = 0)
-     call read_opcol(hshp(i)%ishape_last, hshp(i)%unit, my_lbound = hshp(i)%d0)
+     call read_opcol(ssm(i)%ishape_last, hshp(i)%unit, my_lbound = ssm(i)%d0)
   end do
 
   ! Assuming grid_nml.txt is the same in all input SHPC:
@@ -70,13 +71,13 @@ program test_read_snapshot
   copy = merge(dist_lim, 0, periodic)
 
   ! main_nml:
-  k = hshp(1)%d0
+  k = ssm(1)%d0
   write(unit = error_unit, nml = main_nml)
   write(unit = error_unit, fmt = *) "Enter namelist main_nml."
   read(unit = *, nml = main_nml)
   write(unit = *, nml = main_nml)
 
-  call read_snapshot(s, hshp, nlon, nlat, k, &
+  call read_snapshot(s, hshp, ssm, nlon, nlat, k, &
        corner = corner_deg * deg_to_rad, step = step_deg * deg_to_rad, &
        copy = copy)
 
diff --git a/Overlap/Tests/test_send_recv.f90 b/Overlap/Tests/test_send_recv.f90
index a522354841f1c1f63a435235915d1479c29a3e70..860beeb600d472992bb713f6bc7da5ede669a58b 100644
--- a/Overlap/Tests/test_send_recv.f90
+++ b/Overlap/Tests/test_send_recv.f90
@@ -11,7 +11,7 @@ program test_send_recv
   use jumble, only: deg_to_rad, assert
   use shapelib_03, only: dbf_read_attribute_03
 
-  use derived_types, only: snapshot, shpc_slice_handler
+  use derived_types, only: snapshot, shpc_slice_handler, shpc_slice_meta
   use read_snapshot_m, only: read_snapshot
   use recv_snapshot_m, only: recv_snapshot
   use send_snapshot_m, only: send_snapshot
@@ -42,6 +42,7 @@ program test_send_recv
   namelist /grid_nml/ corner_deg, step_deg, nlon, nlat
   logical periodic ! grid is periodic in longitude
   TYPE(shpc_slice_handler) hshp
+  type(shpc_slice_meta) ssm
 
   !---------------------------------------------------------------------
 
@@ -83,11 +84,11 @@ program test_send_recv
   end if
 
   call shpc_open(hshp, trim(shpc_dir), pszaccess = "rb")
-  call dbf_read_attribute_03(hshp%d0, hshp%extremum, hshp%extr_date, ishape = 0)
-  call read_opcol(hshp%ishape_last, hshp%unit, my_lbound = hshp%d0)
+  call dbf_read_attribute_03(ssm%d0, hshp%extremum, hshp%extr_date, ishape = 0)
+  call read_opcol(ssm%ishape_last, hshp%unit, my_lbound = ssm%d0)
 
   if (rank == 0) then
-     n_dates = size(hshp%ishape_last)
+     n_dates = size(ssm%ishape_last)
   end if
 
   call ezmpi_bcast(corner_deg, root = 0)
@@ -97,20 +98,20 @@ program test_send_recv
   call ezmpi_bcast(copy, root = 0)
   call ezmpi_bcast(n_dates, root = 0)
 
-  if (rank == 1) call read_snapshot(s, [hshp], nlon, nlat, k = hshp%d0, &
+  if (rank == 1) call read_snapshot(s, [hshp], [ssm], nlon, nlat, k = ssm%d0, &
        corner = corner_deg * deg_to_rad, step = step_deg * deg_to_rad, &
        copy = copy)
   CALL shpc_close(hshp)
 
   if (rank == 1) then
-     call send_snapshot(s, dest = 0, tag = hshp%d0)
+     call send_snapshot(s, dest = 0, tag = ssm%d0)
   else
      ! rank == 0
      call MPI_Comm_get_attr(MPI_Comm_world, MPI_TAG_UB, attribute_val, flag)
      call assert(flag, "test_send_recv MPI_Comm_get_attr MPI_TAG_UB")
      print *, "MPI_TAG_UB = ", attribute_val
-     call recv_snapshot(s, nlon, nlat, copy, source = 1, tag = hshp%d0)
-     call write_snapshot(s, corner_deg, step_deg, nlon, nlat, copy, hshp%d0)
+     call recv_snapshot(s, nlon, nlat, copy, source = 1, tag = ssm%d0)
+     call write_snapshot(s, corner_deg, step_deg, nlon, nlat, copy, ssm%d0)
   end if
 
   call mpi_finalize
diff --git a/Overlap/eddy_graph.f90 b/Overlap/eddy_graph.f90
index e0e1a432075eae3c50b0e8163abbbbebf31a1f6d..c837280f7c7bfda9317e937a0666ca236b5bb49b 100644
--- a/Overlap/eddy_graph.f90
+++ b/Overlap/eddy_graph.f90
@@ -10,7 +10,7 @@ program eddy_graph
        MPI_Comm_size
   use shapelib_03, only: dbf_read_attribute_03
 
-  use derived_types, only: snapshot, shpc_slice_handler
+  use derived_types, only: snapshot, shpc_slice_handler, shpc_slice_meta
   use dispatch_snapshot_m, only: dispatch_snapshot
   use get_snapshot_m, only: get_snapshot
   use overlap_m, only: overlap
@@ -53,6 +53,7 @@ program eddy_graph
   integer n_shpc ! number of input SHPC directories
   integer e_overestim ! over-estimation of the number of eddies at each date
   TYPE(shpc_slice_handler), allocatable:: hshpc(:) ! (n_shpc)
+  type(shpc_slice_meta), allocatable:: ssm(:) ! (n_shpc)
   type(snapshot), allocatable:: flow(:) ! (max_delta + 1)
   character(len = 30) file
 
@@ -74,15 +75,15 @@ program eddy_graph
   end if
 
   call ezmpi_bcast(n_shpc, root = 0)
-  allocate(hshpc(n_shpc))
+  allocate(hshpc(n_shpc), ssm(n_shpc))
 
   do i = 1, n_shpc
      call get_command_arg_dyn(i, shpc_dir)
      call shpc_open(hshpc(i), trim(shpc_dir), pszaccess = "rb")
-     call dbf_read_attribute_03(hshpc(i)%d0, hshpc(i)%extremum, &
+     call dbf_read_attribute_03(ssm(i)%d0, hshpc(i)%extremum, &
           hshpc(i)%extr_date, ishape = 0)
-     call read_opcol(hshpc(i)%ishape_last, hshpc(i)%unit, &
-          my_lbound = hshpc(i)%d0)
+     call read_opcol(ssm(i)%ishape_last, hshpc(i)%unit, &
+          my_lbound = ssm(i)%d0)
   end do
 
   if (rank == 0) then
@@ -110,14 +111,14 @@ program eddy_graph
      copy = merge(dist_lim, 0, periodic)
 
      if (n_dates == huge(0)) &
-          n_dates = sum([(size(hshpc(i)%ishape_last), i = 1, n_shpc)])
+          n_dates = sum([(size(ssm(i)%ishape_last), i = 1, n_shpc)])
      print *, "n_dates = ", n_dates
      call assert(n_dates >= max_delta + 1, &
           "eddy_graph: n_dates should be >= max_delta + 1")
      call assert(n_proc <= n_dates / (max_delta + 1), &
           "eddy_graph: n_proc should be <= n_dates / (max_delta + 1)")
-     e_overestim = maxval([(hshpc(i)%ishape_last(hshpc(i)%d0) + 1, &
-          ediff1d(hshpc(i)%ishape_last), i = 1, n_shpc)])
+     e_overestim = maxval([(ssm(i)%ishape_last(ssm(i)%d0) + 1, &
+          ediff1d(ssm(i)%ishape_last), i = 1, n_shpc)])
      open(unit, file = "e_overestim.txt", status = "replace", action = "write")
      write(unit, fmt = *) e_overestim
      close(unit)
@@ -146,13 +147,13 @@ program eddy_graph
   ! Note: no title line, because we want the edgelist to be easily
   ! readable by various graph software.
 
-  k_begin = hshpc(1)%d0 + (rank * n_dates) / n_proc
+  k_begin = ssm(1)%d0 + (rank * n_dates) / n_proc
 
   if (rank < n_proc - 1) then
-     k_end = hshpc(1)%d0 + ((rank + 1) * n_dates) / n_proc + max_delta - 1
+     k_end = ssm(1)%d0 + ((rank + 1) * n_dates) / n_proc + max_delta - 1
      k_end_main_loop = k_end - max_delta + 1
   else
-     k_end = hshpc(1)%d0 + n_dates - 1
+     k_end = ssm(1)%d0 + n_dates - 1
      k_end_main_loop = k_end
   end if
 
@@ -162,7 +163,7 @@ program eddy_graph
 
   do k = k_begin, k_begin + max_delta
      call get_snapshot(flow(k - k_begin + 1), nlon, nlat, corner, step, copy, &
-          hshpc, k, k_end, rank, n_proc, max_delta) ! (read)
+          hshpc, ssm, k, k_end, rank, n_proc, max_delta) ! (read)
   end do
 
   do delta = 1, max_delta
@@ -179,7 +180,7 @@ program eddy_graph
           k = k - max_delta - 1)
      flow(:max_delta) = flow(2:)
      call get_snapshot(flow(max_delta + 1), nlon, nlat, corner, step, copy, &
-          hshpc, k, k_end, rank, n_proc, max_delta)
+          hshpc, ssm, k, k_end, rank, n_proc, max_delta)
      
      do delta = 1, max_delta
         call overlap(flow, nlon, nlat, periodic, dist_lim, e_overestim, k, &
@@ -195,7 +196,7 @@ program eddy_graph
           k = k - max_delta - 1)
      flow(:max_delta) = flow(2:)
      call get_snapshot(flow(max_delta + 1), nlon, nlat, corner, step, copy, &
-          hshpc, k, k_end, rank, n_proc, max_delta)
+          hshpc, ssm, k, k_end, rank, n_proc, max_delta)
      ! (reception)
 
      ! Stitching:
diff --git a/Overlap/get_snapshot.f90 b/Overlap/get_snapshot.f90
index 504c8a656d6eba466fd2a5691e059302df8817bc..7aa1e38307a50f92882318732e581ac3b5995b5b 100644
--- a/Overlap/get_snapshot.f90
+++ b/Overlap/get_snapshot.f90
@@ -4,10 +4,10 @@ module get_snapshot_m
 
 contains
 
-  subroutine get_snapshot(s, nlon, nlat, corner, step, copy, hshp, k, k_end, &
-       rank, n_proc, max_delta)
+  subroutine get_snapshot(s, nlon, nlat, corner, step, copy, hshp, ssm, k, &
+       k_end, rank, n_proc, max_delta)
 
-    use derived_types, only: snapshot, shpc_slice_handler
+    use derived_types, only: snapshot, shpc_slice_handler, shpc_slice_meta
     use read_snapshot_m, only: read_snapshot
     use recv_snapshot_m, only: recv_snapshot
 
@@ -20,6 +20,7 @@ contains
     real, intent(in):: step(:) ! (2) longitude and latitude steps, in rad
     integer, intent(in):: copy
     TYPE(shpc_slice_handler), intent(in):: hshp(:)
+    type(shpc_slice_meta), intent(in):: ssm(:)
     integer, intent(in):: k ! date index
     integer, intent(in):: k_end ! last date index analyzed by this MPI process
     integer, intent(in):: rank ! of MPI process
@@ -32,7 +33,7 @@ contains
     !--------------------------------------------------------------
 
     if (rank == n_proc - 1 .or. k <= k_end - max_delta) then
-       call read_snapshot(s, hshp, nlon, nlat, k, corner, step, copy)
+       call read_snapshot(s, hshp, ssm, nlon, nlat, k, corner, step, copy)
     else
        call recv_snapshot(s, nlon, nlat, copy, source = rank + 1, tag = k)
     end if