diff --git a/Common/read_snapshot.f90 b/Common/read_snapshot.f90
index cfd0858166a7dc6b2648a24eaed9b979013766b0..d4fcbd3d5897298bed8fa63bd1bd80091d8576cd 100644
--- a/Common/read_snapshot.f90
+++ b/Common/read_snapshot.f90
@@ -4,7 +4,7 @@ module read_snapshot_m
 
 contains
 
-  subroutine read_snapshot(s, k, hshp, corner, step, nlon, nlat, copy, k1, &
+  subroutine read_snapshot(s, k, hshp, corner, step, nlon, nlat, copy, d_init, &
        ishape_last)
 
     ! Note: read_field_indices must have been called before read_snapshot.
@@ -29,7 +29,7 @@ contains
     ! size of ssh array in input NetCDF, assuming no repeated point if
     ! the grid is global
 
-    integer, intent(in):: copy, k1, ishape_last(:)
+    integer, intent(in):: copy, d_init, ishape_last(:)
 
     ! Local:
     integer ishape, ishape_first
@@ -39,17 +39,17 @@ contains
 
     !---------------------------------------------------------------------
 
-    if (k == k1) then
+    if (k == d_init) then
        ishape_first = 0
     else
-       ! {k > k1}
-       ishape_first = ishape_last(k - k1) + 1
+       ! {k > d_init}
+       ishape_first = ishape_last(k - d_init) + 1
     end if
 
-    s%number_vis_extr = ishape_last(k - k1 + 1) - ishape_first + 1
+    s%number_vis_extr = ishape_last(k - d_init + 1) - ishape_first + 1
     allocate(s%list_vis(s%number_vis_extr))
 
-    do ishape = ishape_first, ishape_last(k - k1 + 1)
+    do ishape = ishape_first, ishape_last(k - d_init + 1)
        call read_eddy(e, k2, i, hshp, ishape)
 
        ! Check that all the eddies have the same date index:
diff --git a/Inst_eddies/Tests/test_nearby_extr.f90 b/Inst_eddies/Tests/test_nearby_extr.f90
index 11f00354b23bc0b9ba7c8fadf403b3e948d558bb..b69228adadbedd4224556f7467c399df59544c49 100644
--- a/Inst_eddies/Tests/test_nearby_extr.f90
+++ b/Inst_eddies/Tests/test_nearby_extr.f90
@@ -17,7 +17,7 @@ program test_nearby_extr
   character(len = :), allocatable:: shpc_dir
   type(snapshot) s
   TYPE(shpc) hshp
-  integer k1, unit, ishape_last, l
+  integer d_init, unit, ishape_last, l
 
   real corner_deg(2)
   ! longitude and latitude of the corner of the whole grid in input
@@ -51,9 +51,9 @@ program test_nearby_extr
   close(unit)
 
   call shpc_open(hshp, trim(shpc_dir), rank = 0)
-  call dbf_read_attribute_03(k1, hshp%extremum, hshp%extr_date, ishape = 0)
-  call read_snapshot(s, k1, hshp, corner_deg * deg_to_rad, &
-       step_deg * deg_to_rad, nlon, nlat, copy = 0, k1 = k1, &
+  call dbf_read_attribute_03(d_init, hshp%extremum, hshp%extr_date, ishape = 0)
+  call read_snapshot(s, d_init, hshp, corner_deg * deg_to_rad, &
+       step_deg * deg_to_rad, nlon, nlat, copy = 0, d_init = d_init, &
        ishape_last = [ishape_last])
   CALL shpc_close(hshp)
 
diff --git a/Overlap/Tests/test_get_dispatch_snap.f90 b/Overlap/Tests/test_get_dispatch_snap.f90
index 9aebed2aedb4f1948b9ab1994ed65003b9009d99..cc11058037fca88f380db68e86b488ae4fc8dfe1 100644
--- a/Overlap/Tests/test_get_dispatch_snap.f90
+++ b/Overlap/Tests/test_get_dispatch_snap.f90
@@ -23,7 +23,7 @@ program test_get_dispatch_snap
   character(len = :), allocatable:: shpc_dir
   type(snapshot) s
   TYPE(shpc) hshp
-  integer k_begin, k1, copy, rank, n_proc, k_end, n_dates
+  integer k_begin, d_init, copy, rank, n_proc, k_end, n_dates
   integer unit_isolated, unit_number_eddies
 
   real:: corner(2) = [0.125, - 59.875]
@@ -96,19 +96,20 @@ program test_get_dispatch_snap
   if (rank /= 0) allocate(ishape_last(n_dates))
   call ezmpi_bcast(ishape_last, root = 0)
   call shpc_open(hshp, trim(shpc_dir), rank)
-  if (rank == 0) call dbf_read_attribute_03(k1, hshp%extremum, hshp%extr_date, &
-       ishape = 0)
-  call ezmpi_bcast(k1, root = 0)
-  k_begin = k1 + (rank * n_dates) / n_proc
+  if (rank == 0) call dbf_read_attribute_03(d_init, hshp%extremum, &
+       hshp%extr_date, ishape = 0)
+  call ezmpi_bcast(d_init, root = 0)
+  k_begin = d_init + (rank * n_dates) / n_proc
   
   if (rank < n_proc - 1) then
-     k_end = k1 + ((rank + 1) * n_dates) / n_proc
+     k_end = d_init + ((rank + 1) * n_dates) / n_proc
   else
-     k_end = k1 + n_dates - 1
+     k_end = d_init + n_dates - 1
   end if
   
   call get_snapshot(s, nlon, nlat, ishape_last, corner * deg_to_rad, &
-       step * deg_to_rad, copy, hshp, k1, k, k_end, rank, n_proc, max_delta = 1)
+       step * deg_to_rad, copy, hshp, d_init, k, k_end, rank, n_proc, &
+       max_delta = 1)
   CALL shpc_close(hshp)
   call dispatch_snapshot(s, unit_isolated, unit_number_eddies, rank, k_begin, &
        max_delta = 1, k = k)
diff --git a/Overlap/Tests/test_overlap.f90 b/Overlap/Tests/test_overlap.f90
index 4f0d412e2405383eefd7822da0e3426c97f921c3..9727a25df98d39269ebdfe2cb8facba4fd9b055b 100644
--- a/Overlap/Tests/test_overlap.f90
+++ b/Overlap/Tests/test_overlap.f90
@@ -21,7 +21,7 @@ program test_overlap
   implicit none
 
   character(len = :), allocatable:: shpc_dir
-  integer k1
+  integer d_init
   integer:: k_test_1 = 20454, k_test_2 = 20455
   integer unit, i, copy, rank, n_proc
   integer, allocatable:: ishape_last(:)
@@ -80,11 +80,11 @@ program test_overlap
   allocate(flow(max_delta + 1))
   call read_column(ishape_last, file = trim(shpc_dir) // "/ishape_last.txt")
   call shpc_open(hshp, trim(shpc_dir), rank = 0)
-  call dbf_read_attribute_03(k1, hshp%extremum, hshp%extr_date, ishape = 0)
+  call dbf_read_attribute_03(d_init, hshp%extremum, hshp%extr_date, ishape = 0)
   call read_snapshot(flow(1), k_test_1, hshp, corner, step, nlon, nlat, copy, &
-       k1, ishape_last)
+       d_init, ishape_last)
   call read_snapshot(flow(max_delta + 1), k_test_2, hshp, corner, step, nlon, &
-       nlat, copy, k1, ishape_last)
+       nlat, copy, d_init, ishape_last)
   CALL shpc_close(hshp)
   print *, "Enter flow(1)%list_vis%delta_out (array with ", &
        flow(1)%number_vis_extr, " values):"
diff --git a/Overlap/Tests/test_read_snapshot.f90 b/Overlap/Tests/test_read_snapshot.f90
index 81aac67ff782efbc21651d4d00445d6d915c54b8..07c653ddddc0ba4b3aa3a696cc8ebed5da2e89eb 100644
--- a/Overlap/Tests/test_read_snapshot.f90
+++ b/Overlap/Tests/test_read_snapshot.f90
@@ -19,7 +19,7 @@ program test_read_snapshot
   character(len = :), allocatable:: shpc_dir
   type(snapshot) s
   TYPE(shpc) hshp
-  integer k1, copy, unit, ishape_last
+  integer d_init, copy, unit, ishape_last
 
   real:: corner_deg(2) = [0.125, - 59.875]
   ! longitude and latitude of the corner of the whole grid in input
@@ -69,12 +69,12 @@ program test_read_snapshot
   close(unit)
 
   call shpc_open(hshp, trim(shpc_dir), rank = 0)
-  call dbf_read_attribute_03(k1, hshp%extremum, hshp%extr_date, ishape = 0)
-  call read_snapshot(s, k1, hshp, corner_deg * deg_to_rad, &
-       step_deg * deg_to_rad, nlon, nlat, copy, k1, [ishape_last])
+  call dbf_read_attribute_03(d_init, hshp%extremum, hshp%extr_date, ishape = 0)
+  call read_snapshot(s, d_init, hshp, corner_deg * deg_to_rad, &
+       step_deg * deg_to_rad, nlon, nlat, copy, d_init, [ishape_last])
   CALL shpc_close(hshp)
 
-  call write_snapshot(s, corner_deg, step_deg, nlon, nlat, copy, k1)
+  call write_snapshot(s, corner_deg, step_deg, nlon, nlat, copy, d_init)
   call mpi_finalize
 
 end program test_read_snapshot
diff --git a/Overlap/Tests/test_send_recv.f90 b/Overlap/Tests/test_send_recv.f90
index a7a4f0be4bacce5e332c1032c5180ec19f7c9bd2..f19ec4033706b89fadccf4c81c120929e63b4a40 100644
--- a/Overlap/Tests/test_send_recv.f90
+++ b/Overlap/Tests/test_send_recv.f90
@@ -24,7 +24,7 @@ program test_send_recv
 
   character(len = :), allocatable:: shpc_dir
   type(snapshot) s
-  integer rank, n_proc, k1, copy, n_dates, unit
+  integer rank, n_proc, d_init, copy, n_dates, unit
   logical flag
   INTEGER(KIND=MPI_ADDRESS_KIND) attribute_val
 
@@ -99,22 +99,22 @@ program test_send_recv
   call ezmpi_bcast(ishape_last, root = 0)
 
   call shpc_open(hshp, trim(shpc_dir), rank)
-  if (rank == 0) call dbf_read_attribute_03(k1, hshp%extremum, hshp%extr_date, &
-       ishape = 0)
-  call ezmpi_bcast(k1, root = 0)
-  if (rank == 1) call read_snapshot(s, k1, hshp, corner_deg * deg_to_rad, &
-       step_deg * deg_to_rad, nlon, nlat, copy, k1, ishape_last)
+  if (rank == 0) call dbf_read_attribute_03(d_init, hshp%extremum, &
+       hshp%extr_date, ishape = 0)
+  call ezmpi_bcast(d_init, root = 0)
+  if (rank == 1) call read_snapshot(s, d_init, hshp, corner_deg * deg_to_rad, &
+       step_deg * deg_to_rad, nlon, nlat, copy, d_init, ishape_last)
   CALL shpc_close(hshp)
 
   if (rank == 1) then
-     call send_snapshot(s, dest = 0, tag = k1)
+     call send_snapshot(s, dest = 0, tag = d_init)
   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 = k1)
-     call write_snapshot(s, corner_deg, step_deg, nlon, nlat, copy, k1)
+     call recv_snapshot(s, nlon, nlat, copy, source = 1, tag = d_init)
+     call write_snapshot(s, corner_deg, step_deg, nlon, nlat, copy, d_init)
   end if
 
   call mpi_finalize
diff --git a/Overlap/eddy_graph.f90 b/Overlap/eddy_graph.f90
index 014ea25d4610c9a0c4436bf893e18b7a3c5455ba..49c29c78dca8200a20d666aaf551d779c057c0a2 100644
--- a/Overlap/eddy_graph.f90
+++ b/Overlap/eddy_graph.f90
@@ -24,7 +24,7 @@ program eddy_graph
 
   integer rank, n_proc, copy, delta, j
   integer:: n_dates = huge(0) ! number of dates to read
-  integer k1, k_begin, k_end, k, k_end_main_loop
+  integer d_init, k_begin, k_end, k, k_end_main_loop
   character(len = :), allocatable:: shpc_dir
   integer:: max_delta = 1
   
@@ -116,9 +116,9 @@ program eddy_graph
   call ezmpi_bcast(ishape_last, root = 0)
 
   call shpc_open(hshp, trim(shpc_dir), rank)
-  if (rank == 0) call dbf_read_attribute_03(k1, hshp%extremum, hshp%extr_date, &
-       ishape = 0)
-  call ezmpi_bcast(k1, root = 0)
+  if (rank == 0) call dbf_read_attribute_03(d_init, hshp%extremum, &
+       hshp%extr_date, ishape = 0)
+  call ezmpi_bcast(d_init, root = 0)
 
   ! Open output files:
   
@@ -138,13 +138,13 @@ program eddy_graph
   call shpc_create(hshp_interp, shpc_dir = trim(file), cyclone = hshp%cyclone)
   call init_interpolated_eddy
 
-  k_begin = k1 + (rank * n_dates) / n_proc
+  k_begin = d_init + (rank * n_dates) / n_proc
 
   if (rank < n_proc - 1) then
-     k_end = k1 + ((rank + 1) * n_dates) / n_proc + max_delta - 1
+     k_end = d_init + ((rank + 1) * n_dates) / n_proc + max_delta - 1
      k_end_main_loop = k_end - max_delta + 1
   else
-     k_end = k1 + n_dates - 1
+     k_end = d_init + n_dates - 1
      k_end_main_loop = k_end
   end if
 
@@ -154,7 +154,7 @@ program eddy_graph
 
   do k = k_begin, k_begin + max_delta
      call get_snapshot(flow(k - k_begin + 1), nlon, nlat, ishape_last, corner, &
-          step, copy, hshp, k1, k, k_end, rank, n_proc, max_delta) ! (read)
+          step, copy, hshp, d_init, k, k_end, rank, n_proc, max_delta) ! (read)
   end do
 
   do delta = 1, max_delta
@@ -171,7 +171,7 @@ program eddy_graph
           k_begin, max_delta, k = k - max_delta - 1)
      flow(:max_delta) = flow(2:)
      call get_snapshot(flow(max_delta + 1), nlon, nlat, ishape_last, corner, &
-          step, copy, hshp, k1, k, k_end, rank, n_proc, max_delta)
+          step, copy, hshp, d_init, k, k_end, rank, n_proc, max_delta)
 
      do delta = 1, max_delta
         call overlap(flow, nlon, nlat, periodic, dist_lim, hshp_interp, k, &
@@ -187,7 +187,8 @@ program eddy_graph
           k_begin, max_delta, k = k - max_delta - 1)
      flow(:max_delta) = flow(2:)
      call get_snapshot(flow(max_delta + 1), nlon, nlat, ishape_last, corner, &
-          step, copy, hshp, k1, k, k_end, rank, n_proc, max_delta) ! reception
+          step, copy, hshp, d_init, k, k_end, rank, n_proc, max_delta)
+     ! (reception)
 
      ! Stitching:
      do delta = k - k_end + max_delta, max_delta
diff --git a/Overlap/get_snapshot.f90 b/Overlap/get_snapshot.f90
index fc04c173eb492a436e049740ac691450f82de0ee..30431c0fb1e4adf7a6e76b01e35ac54fa6720702 100644
--- a/Overlap/get_snapshot.f90
+++ b/Overlap/get_snapshot.f90
@@ -5,7 +5,7 @@ module get_snapshot_m
 contains
 
   subroutine get_snapshot(s, nlon, nlat, ishape_last, corner, step, copy, &
-       hshp, k1, k, k_end, rank, n_proc, max_delta)
+       hshp, d_init, k, k_end, rank, n_proc, max_delta)
 
     use derived_types, only: snapshot, shpc
     use read_snapshot_m, only: read_snapshot
@@ -24,7 +24,10 @@ contains
     real, intent(in):: step(:) ! (2) longitude and latitude steps, in rad
     integer, intent(in):: copy
     TYPE(shpc), intent(in):: hshp
-    integer, intent(in):: k1 ! first date index in the collection of shapefiles
+
+    integer, intent(in):: d_init
+    ! first date index in the collection of shapefiles
+
     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
@@ -37,7 +40,7 @@ contains
     !--------------------------------------------------------------
 
     if (rank == n_proc - 1 .or. k <= k_end - max_delta) then
-       call read_snapshot(s, k, hshp, corner, step, nlon, nlat, copy, k1, &
+       call read_snapshot(s, k, hshp, corner, step, nlon, nlat, copy, d_init, &
             ishape_last)
     else
        call recv_snapshot(s, nlon, nlat, copy, source = rank + 1, tag = k)