@@ -2532,6 +2532,159 @@ defmodule Enum do
25322532 end
25332533 end
25342534
2535+ @ doc """
2536+ Slides a single or multiple elements given by `range_or_single_index` from `enumerable`
2537+ to `insertion_index`.
2538+
2539+ The semantics of the range to be moved match the semantics of `Enum.slice/2`.
2540+ Specifically, that means:
2541+
2542+ * Indices are normalized, meaning that negative indexes will be counted from the end
2543+ (for example, -1 means the last element of the enumerable). This will result in *two*
2544+ traversals of your enumerable on types like lists that don't provide a constant-time count.
2545+
2546+ * If the normalized index range's `last` is out of bounds, the range is truncated to the last element.
2547+
2548+ * If the normalized index range's `first` is out of bounds, the selected range for sliding
2549+ will be empty, so you'll get back your input list.
2550+
2551+ * Decreasing ranges (such as `5..0//1`) also select an empty range to be moved,
2552+ so you'll get back your input list.
2553+
2554+ * Ranges with any step but 1 will raise an error.
2555+
2556+ ## Examples
2557+
2558+ # Slide a single element
2559+ iex> Enum.slide([:a, :b, :c, :d, :e, :f, :g], 5, 1)
2560+ [:a, :f, :b, :c, :d, :e, :g]
2561+
2562+ # Slide a range of elements backward
2563+ iex> Enum.slide([:a, :b, :c, :d, :e, :f, :g], 3..5, 1)
2564+ [:a, :d, :e, :f, :b, :c, :g]
2565+
2566+ # Slide a range of elements forward
2567+ iex> Enum.slide([:a, :b, :c, :d, :e, :f, :g], 1..3, 5)
2568+ [:a, :e, :f, :b, :c, :d, :g]
2569+
2570+ # Slide with negative indices (counting from the end)
2571+ iex> Enum.slide([:a, :b, :c, :d, :e, :f, :g], 3..-1//1, 2)
2572+ [:a, :b, :d, :e, :f, :g, :c]
2573+ iex> Enum.slide([:a, :b, :c, :d, :e, :f, :g], -4..-2, 1)
2574+ [:a, :d, :e, :f, :b, :c, :g]
2575+
2576+ """
2577+ def slide ( enumerable , range_or_single_index , insertion_index )
2578+
2579+ def slide ( enumerable , single_index , insertion_index ) when is_integer ( single_index ) do
2580+ slide ( enumerable , single_index .. single_index , insertion_index )
2581+ end
2582+
2583+ # This matches the behavior of Enum.slice/2
2584+ def slide ( _ , _ .. _ // step = index_range , _insertion_index ) when step != 1 do
2585+ raise ArgumentError ,
2586+ "Enum.slide/3 does not accept ranges with custom steps, got: #{ inspect ( index_range ) } "
2587+ end
2588+
2589+ # Normalize negative input ranges like Enum.slice/2
2590+ def slide ( enumerable , first .. last , insertion_index ) when first < 0 or last < 0 do
2591+ count = Enum . count ( enumerable )
2592+ normalized_first = if first >= 0 , do: first , else: first + count
2593+ normalized_last = if last >= 0 , do: last , else: last + count
2594+
2595+ if normalized_first >= 0 and normalized_first < count and normalized_first != insertion_index do
2596+ normalized_range = normalized_first .. normalized_last // 1
2597+ slide ( enumerable , normalized_range , insertion_index )
2598+ else
2599+ Enum . to_list ( enumerable )
2600+ end
2601+ end
2602+
2603+ def slide ( enumerable , insertion_index .. _ , insertion_index ) do
2604+ Enum . to_list ( enumerable )
2605+ end
2606+
2607+ def slide ( _ , first .. last , insertion_index )
2608+ when insertion_index > first and insertion_index < last do
2609+ raise "Insertion index for slide must be outside the range being moved " <>
2610+ "(tried to insert #{ first } ..#{ last } at #{ insertion_index } )"
2611+ end
2612+
2613+ # Guarantees at this point: step size == 1 and first <= last and (insertion_index < first or insertion_index > last)
2614+ def slide ( enumerable , first .. last , insertion_index ) do
2615+ impl = if is_list ( enumerable ) , do: & slide_list_start / 4 , else: & slide_any / 4
2616+
2617+ cond do
2618+ insertion_index <= first -> impl . ( enumerable , insertion_index , first , last )
2619+ insertion_index > last -> impl . ( enumerable , first , last + 1 , insertion_index )
2620+ end
2621+ end
2622+
2623+ # Takes the range from middle..last and moves it to be in front of index start
2624+ defp slide_any ( enumerable , start , middle , last ) do
2625+ # We're going to deal with 4 "chunks" of the enumerable:
2626+ # 0. "Head," before the start index
2627+ # 1. "Slide back," between start (inclusive) and middle (exclusive)
2628+ # 2. "Slide front," between middle (inclusive) and last (inclusive)
2629+ # 3. "Tail," after last
2630+ #
2631+ # But, we're going to accumulate these into only two lists: pre and post.
2632+ # We'll reverse-accumulate the head into our pre list, then "slide back" into post,
2633+ # then "slide front" into pre, then "tail" into post.
2634+ #
2635+ # Then at the end, we're going to reassemble and reverse them, and end up with the
2636+ # chunks in the correct order.
2637+ { _size , pre , post } =
2638+ Enum . reduce ( enumerable , { 0 , [ ] , [ ] } , fn item , { index , pre , post } ->
2639+ { pre , post } =
2640+ cond do
2641+ index < start -> { [ item | pre ] , post }
2642+ index >= start and index < middle -> { pre , [ item | post ] }
2643+ index >= middle and index <= last -> { [ item | pre ] , post }
2644+ true -> { pre , [ item | post ] }
2645+ end
2646+
2647+ { index + 1 , pre , post }
2648+ end )
2649+
2650+ :lists . reverse ( pre , :lists . reverse ( post ) )
2651+ end
2652+
2653+ # Like slide_any/4 above, this optimized implementation of slide for lists depends
2654+ # on the indices being sorted such that we're moving middle..last to be in front of start.
2655+ defp slide_list_start ( [ h | t ] , start , middle , last )
2656+ when start > 0 and start <= middle and middle <= last do
2657+ [ h | slide_list_start ( t , start - 1 , middle - 1 , last - 1 ) ]
2658+ end
2659+
2660+ defp slide_list_start ( list , 0 , middle , last ) , do: slide_list_middle ( list , middle , last , [ ] )
2661+
2662+ defp slide_list_middle ( [ h | t ] , middle , last , acc ) when middle > 0 do
2663+ slide_list_middle ( t , middle - 1 , last - 1 , [ h | acc ] )
2664+ end
2665+
2666+ defp slide_list_middle ( list , 0 , last , start_to_middle ) do
2667+ { slid_range , tail } = slide_list_last ( list , last + 1 , [ ] )
2668+ slid_range ++ :lists . reverse ( start_to_middle , tail )
2669+ end
2670+
2671+ # You asked for a middle index off the end of the list... you get what we've got
2672+ defp slide_list_middle ( [ ] , _ , _ , acc ) do
2673+ :lists . reverse ( acc )
2674+ end
2675+
2676+ defp slide_list_last ( [ h | t ] , last , acc ) when last > 0 do
2677+ slide_list_last ( t , last - 1 , [ h | acc ] )
2678+ end
2679+
2680+ defp slide_list_last ( rest , 0 , acc ) do
2681+ { :lists . reverse ( acc ) , rest }
2682+ end
2683+
2684+ defp slide_list_last ( [ ] , _ , acc ) do
2685+ { :lists . reverse ( acc ) , [ ] }
2686+ end
2687+
25352688 @ doc """
25362689 Applies the given function to each element in the `enumerable`,
25372690 storing the result in a list and passing it as the accumulator
0 commit comments