File 4481-Add-lists-enumerate-3.patch of Package erlang
From 54456030a9a1bea26786d8eb888061951111a413 Mon Sep 17 00:00:00 2001
From: Maria Scott <maria-12648430@hnc-agency.org>
Date: Wed, 1 Mar 2023 07:45:02 +0100
Subject: [PATCH] Add lists:enumerate/3
---
lib/stdlib/doc/src/lists.xml | 42 +++++++------------
lib/stdlib/src/lists.erl | 25 +++++++----
lib/stdlib/test/lists_SUITE.erl | 24 +++++++++++
lib/stdlib/test/lists_property_test_SUITE.erl | 4 ++
lib/stdlib/test/property_test/lists_prop.erl | 22 ++++++++++
5 files changed, 83 insertions(+), 34 deletions(-)
diff --git a/lib/stdlib/doc/src/lists.xml b/lib/stdlib/doc/src/lists.xml
index 00caf89d23..f6f329bf85 100644
--- a/lib/stdlib/doc/src/lists.xml
+++ b/lib/stdlib/doc/src/lists.xml
@@ -176,43 +176,33 @@
<func>
<name name="enumerate" arity="1" since="OTP 25.0"/>
+ <name name="enumerate" arity="2" since="OTP 25.0"/>
+ <name name="enumerate" arity="3" since="OTP 26.0"/>
<fsummary>Annotates elements with their index.</fsummary>
<desc>
<p>Returns <c><anno>List1</anno></c> with each element
- <c>H</c> replaced by a tuple of form <c>{I, H}</c> where
- <c>I</c> is the position of <c>H</c> in
- <c><anno>List1</anno></c>. The enumeration starts with 1 and
- increases by 1 in each step.</p>
- <p>That is, <c>enumerate/1</c> behaves as if it had been defined as follows:</p>
+ <c>H</c> replaced by a tuple of form <c>{I, H}</c> where
+ <c>I</c> is the position of <c>H</c> in
+ <c><anno>List1</anno></c>. The enumeration starts with
+ <c><anno>Index</anno></c> and increases by <c><anno>Step</anno></c>
+ in each step.</p>
+ <p>That is, <c>enumerate/3</c> behaves as if it had been defined as follows:</p>
<code type="erl">
-enumerate(List) ->
- {List1, _ } = lists:mapfoldl(fun(T, Acc) -> {{Acc, T}, Acc+1} end, 1, List),
+enumerate(I, S, List) ->
+ {List1, _ } = lists:mapfoldl(fun(T, Acc) -> {{Acc, T}, Acc+S} end, I, List),
List1.</code>
- <p><em>Example:</em></p>
+ <p>The default values for <c><anno>Index</anno></c> and
+ <c><anno>Step</anno></c> are both <c>1</c>.</p>
+ <p><em>Examples:</em></p>
<pre>
> <input>lists:enumerate([a,b,c]).</input>
[{1,a},{2,b},{3,c}]</pre>
- </desc>
- </func>
-
- <func>
- <name name="enumerate" arity="2" since="OTP 25.0"/>
- <fsummary>Annotates elements with their index.</fsummary>
- <desc>
- <p>Returns <c><anno>List1</anno></c> with each element
- <c>H</c> replaced by a tuple of form <c>{I, H}</c> where
- <c>I</c> is the position of <c>H</c> in
- <c><anno>List1</anno></c>. The enumeration starts with
- <c><anno>Index</anno></c> and increases by 1 in each step.</p>
- <p>That is, <c>enumerate/2</c> behaves as if it had been defined as follows:</p>
- <code type="erl">
-enumerate(I, List) ->
- {List1, _ } = lists:mapfoldl(fun(T, Acc) -> {{Acc, T}, Acc+1} end, I, List),
- List1.</code>
- <p><em>Example:</em></p>
<pre>
> <input>lists:enumerate(10, [a,b,c]).</input>
[{10,a},{11,b},{12,c}]</pre>
+ <pre>
+> <input>lists:enumerate(0, -2, [a,b,c]).</input>
+[{0,a},{-2,b},{-4,c}]</pre>
</desc>
</func>
diff --git a/lib/stdlib/src/lists.erl b/lib/stdlib/src/lists.erl
index b1be8e1c2d..15bed9e292 100644
--- a/lib/stdlib/src/lists.erl
+++ b/lib/stdlib/src/lists.erl
@@ -29,7 +29,7 @@
%% arguments. Please keep in alphabetical order.
-export([append/1, append/2, concat/1,
delete/2, droplast/1, duplicate/2,
- enumerate/1, enumerate/2,
+ enumerate/1, enumerate/2, enumerate/3,
flatlength/1, flatten/1, flatten/2,
join/2, last/1, min/1, max/1,
nth/2, nthtail/2,
@@ -1160,20 +1160,29 @@ keymap(Fun, Index, []) when is_integer(Index), Index >= 1,
List2 :: [{Index, T}],
Index :: integer(),
T :: term().
-enumerate(List1) when is_list(List1) ->
- enumerate_1(1, List1).
+enumerate(List1) ->
+ enumerate(1, 1, List1).
-spec enumerate(Index, List1) -> List2 when
List1 :: [T],
List2 :: [{Index, T}],
Index :: integer(),
T :: term().
-enumerate(Index, List1) when is_integer(Index), is_list(List1) ->
- enumerate_1(Index, List1).
+enumerate(Index, List1) ->
+ enumerate(Index, 1, List1).
-enumerate_1(Index, [H|T]) ->
- [{Index, H}|enumerate_1(Index + 1, T)];
-enumerate_1(_Index, []) ->
+-spec enumerate(Index, Step, List1) -> List2 when
+ List1 :: [T],
+ List2 :: [{Index, T}],
+ Index :: integer(),
+ Step :: integer(),
+ T :: term().
+enumerate(Index, Step, List1) when is_integer(Index), is_integer(Step) ->
+ enumerate_1(Index, Step, List1).
+
+enumerate_1(Index, Step, [H|T]) ->
+ [{Index, H}|enumerate_1(Index + Step, Step, T)];
+enumerate_1(_Index, _Step, []) ->
[].
%%% Suggestion from OTP-2948: sort and merge with Fun.
diff --git a/lib/stdlib/test/lists_SUITE.erl b/lib/stdlib/test/lists_SUITE.erl
index 792a94702a..1ab4458a5a 100644
--- a/lib/stdlib/test/lists_SUITE.erl
+++ b/lib/stdlib/test/lists_SUITE.erl
@@ -3198,15 +3198,39 @@ hof(Config) when is_list(Config) ->
enumerate(Config) when is_list(Config) ->
[] = lists:enumerate([]),
[] = lists:enumerate(10, []),
+ [] = lists:enumerate(-10, []),
+ [] = lists:enumerate(10, 2, []),
+ [] = lists:enumerate(10, -2, []),
+ [] = lists:enumerate(-10, 2, []),
+ [] = lists:enumerate(-10, -2, []),
[{1,a},{2,b},{3,c}] = lists:enumerate([a,b,c]),
[{10,a},{11,b},{12,c}] = lists:enumerate(10, [a,b,c]),
+ [{-10,a},{-9,b},{-8,c}] = lists:enumerate(-10, [a,b,c]),
+ [{10,a},{12,b},{14,c}] = lists:enumerate(10, 2, [a,b,c]),
+ [{10,a},{8,b},{6,c}] = lists:enumerate(10, -2, [a,b,c]),
+ [{-10,a},{-12,b},{-14,c}] = lists:enumerate(-10, -2, [a,b,c]),
{'EXIT', {function_clause, _}} = catch lists:enumerate(0),
{'EXIT', {function_clause, _}} = catch lists:enumerate(0, 10),
+ {'EXIT', {function_clause, _}} = catch lists:enumerate(0, 10, 20),
{'EXIT', {function_clause, _}} = catch lists:enumerate(1.0, []),
{'EXIT', {function_clause, _}} = catch lists:enumerate(1.0, [a,b,c]),
+ {'EXIT', {function_clause, _}} = catch lists:enumerate(1.0, 2, []),
+ {'EXIT', {function_clause, _}} = catch lists:enumerate(1.0, 2, [a,b,c]),
+ {'EXIT', {function_clause, _}} = catch lists:enumerate(1, 2.0, []),
+ {'EXIT', {function_clause, _}} = catch lists:enumerate(1, 2.0, [a,b,c]),
+ {'EXIT', {function_clause, _}} = catch lists:enumerate(1.0, 2.0, []),
+ {'EXIT', {function_clause, _}} = catch lists:enumerate(1.0, 2.0, [a,b,c]),
{'EXIT', {function_clause, _}} = catch lists:enumerate(<<1>>, []),
{'EXIT', {function_clause, _}} = catch lists:enumerate(<<1>>, [a,b,c]),
+ {'EXIT', {function_clause, _}} = catch lists:enumerate(<<1>>, 2, []),
+ {'EXIT', {function_clause, _}} = catch lists:enumerate(<<1>>, 2, [a,b,c]),
+ {'EXIT', {function_clause, _}} = catch lists:enumerate(1, <<2>>, []),
+ {'EXIT', {function_clause, _}} = catch lists:enumerate(1, <<2>>, [a,b,c]),
+ {'EXIT', {function_clause, _}} = catch lists:enumerate(<<1>>, <<2>>, []),
+ {'EXIT', {function_clause, _}} = catch lists:enumerate(<<1>>, <<2>>, [a,b,c]),
+ {'EXIT', {function_clause, _}} = catch lists:enumerate(<<1,2,3>>),
{'EXIT', {function_clause, _}} = catch lists:enumerate(1, <<1,2,3>>),
+ {'EXIT', {function_clause, _}} = catch lists:enumerate(1, 2, <<1,2,3>>),
ok.
diff --git a/lib/stdlib/test/lists_property_test_SUITE.erl b/lib/stdlib/test/lists_property_test_SUITE.erl
index 4b366d730a..ecbf14309e 100644
--- a/lib/stdlib/test/lists_property_test_SUITE.erl
+++ b/lib/stdlib/test/lists_property_test_SUITE.erl
@@ -35,6 +35,7 @@ all() ->
duplicate_case,
enumerate_1_case,
enumerate_2_case,
+ enumerate_3_case,
filter_case,
filtermap_case,
flatlength_case,
@@ -159,6 +160,9 @@ enumerate_1_case(Config) ->
enumerate_2_case(Config) ->
do_proptest(prop_enumerate_2, Config).
+enumerate_3_case(Config) ->
+ do_proptest(prop_enumerate_3, Config).
+
filter_case(Config) ->
do_proptest(prop_filter, Config).
diff --git a/lib/stdlib/test/property_test/lists_prop.erl b/lib/stdlib/test/property_test/lists_prop.erl
index 00b518ff83..68c087b76d 100644
--- a/lib/stdlib/test/property_test/lists_prop.erl
+++ b/lib/stdlib/test/property_test/lists_prop.erl
@@ -240,6 +240,28 @@ prop_enumerate_2() ->
lists:enumerate(StartIndex, InList) =:= ExpList
).
+%% enumerate/3
+prop_enumerate_3() ->
+ ?FORALL(
+ {StartIndex, Step, InList, ExpList},
+ ?LET(
+ {N, S},
+ {integer(), integer()},
+ ?LET(
+ {L, {_, EL}},
+ gen_list_fold(
+ gen_any(),
+ fun(T, {I, Acc}) ->
+ {I + S, Acc ++ [{I, T}]}
+ end,
+ {N, []}
+ ),
+ {N, S, L, EL}
+ )
+ ),
+ lists:enumerate(StartIndex, Step, InList) =:= ExpList
+ ).
+
%% filter/2
prop_filter() ->
?FORALL(
--
2.35.3