Skip to content

Commit

Permalink
lists: enable zip functions to work on lists of different lengths
Browse files Browse the repository at this point in the history
This change enables the functions zip, zip3, zipwith and zipwith3 of the
lists module to accept an optional extra parameter which specifies the
behavior in case the given lists are of different lengths:

* fail: The call will fail with an error exception. This is the default,
        and the same as the current behavior.

* trim: The longer list(s) will be trimmed to the length of the shortest
        list, such that surplus elements in the longer list(s) will be
        ignored.

* {pad, Defaults}: The shorter list(s) will be padded to the length of the
                   longest list using the respective element(s) from the
                   given Defaults tuple.

Co-authored-by: Björn Gustavsson <bgustavsson@gmail.com>
Co-authored-by: Jan Uhlig <juhlig@hnc-agency.org>
  • Loading branch information
3 people committed Nov 17, 2022
1 parent 6664a6f commit 93748a8
Show file tree
Hide file tree
Showing 5 changed files with 603 additions and 32 deletions.
45 changes: 41 additions & 4 deletions lib/stdlib/doc/src/lists.xml
Original file line number Diff line number Diff line change
Expand Up @@ -1069,35 +1069,69 @@ splitwith(Pred, List) ->

<func>
<name name="zip" arity="2" since=""/>
<name name="zip" arity="3" since="OTP @OTP-18318@"/>
<fsummary>Zip two lists into a list of two-tuples.</fsummary>
<desc>
<p>"Zips" two lists of equal length into one list of two-tuples,
<p>"Zips" two lists into one list of two-tuples,
where the first element of each tuple is taken from the first
list and the second element is taken from the corresponding
element in the second list.</p>
<p>The <c><anno>How</anno></c> parameter specifies the behavior
if the given lists are of different lengths.</p>
<taglist>
<tag><c>fail</c></tag>
<item>The call will fail if the given lists are not of equal
length. This is the default.</item>
<tag><c>trim</c></tag>
<item>Surplus elements from the longer list will be ignored.
<p><em>Examples:</em></p>
<pre>
> <input>lists:zip([a, b], [1, 2, 3], trim).</input>
[{a,1},{b,2}]
> <input>lists:zip([a, b, c], [1, 2], trim).</input>
[{a,1},{b,2}]</pre>
</item>
<tag><c>{pad, Defaults}</c></tag>
<item>The shorter list will be padded to the length of the
longer list, using the respective elements from the given
<c>Defaults</c> tuple.
<p><em>Examples:</em></p>
<pre>
> <input>lists:zip([a, b], [1, 2, 3], {pad, {x, 0}}).</input>
[{a,1},{b,2},{x,3}]
> <input>lists:zip([a, b, c], [1, 2], {pad, {x, 0}}).</input>
[{a,1},{b,2},{c,0}]</pre>
</item>
</taglist>
</desc>
</func>

<func>
<name name="zip3" arity="3" since=""/>
<name name="zip3" arity="4" since="OTP @OTP-18318@"/>
<fsummary>Zip three lists into a list of three-tuples.</fsummary>
<desc>
<p>"Zips" three lists of equal length into one list of
<p>"Zips" three lists into one list of
three-tuples, where the first element of each tuple is taken
from the first list, the second element is taken from
the corresponding element in the second list, and the third
element is taken from the corresponding element in the third list.</p>
<p>For a description of the <c><anno>How</anno></c> parameter, see
<seemfa marker="#zip/3"><c>zip/3</c></seemfa>.</p>
</desc>
</func>

<func>
<name name="zipwith" arity="3" since=""/>
<name name="zipwith" arity="4" since="OTP @OTP-18318@"/>
<fsummary>Zip two lists into one list according to a fun.</fsummary>
<desc>
<p>Combines the elements of two lists of equal length into one list.
<p>Combines the elements of two lists into one list.
For each pair <c><anno>X</anno>, <anno>Y</anno></c> of list elements
from the two lists, the element in the result list is
<c><anno>Combine</anno>(<anno>X</anno>, <anno>Y</anno>)</c>.</p>
<p>For a description of the <c><anno>How</anno></c> parameter, see
<seemfa marker="#zip/3"><c>zip/3</c></seemfa>.</p>
<p><c>zipwith(fun(X, Y) -> {X,Y} end, List1, List2)</c> is
equivalent to <c>zip(List1, List2)</c>.</p>
<p><em>Example:</em></p>
Expand All @@ -1109,13 +1143,16 @@ splitwith(Pred, List) ->

<func>
<name name="zipwith3" arity="4" since=""/>
<name name="zipwith3" arity="5" since="OTP @OTP-18318@"/>
<fsummary>Zip three lists into one list according to a fun.</fsummary>
<desc>
<p>Combines the elements of three lists of equal length into one
<p>Combines the elements of three lists into one
list. For each triple <c><anno>X</anno>, <anno>Y</anno>,
<anno>Z</anno></c> of list elements from the three lists, the element
in the result list is <c><anno>Combine</anno>(<anno>X</anno>,
<anno>Y</anno>, <anno>Z</anno>)</c>.</p>
<p>For a description of the <c><anno>How</anno></c> parameter, see
<seemfa marker="#zip/3"><c>zip/3</c></seemfa>.</p>
<p><c>zipwith3(fun(X, Y, Z) -> {X,Y,Z} end, List1, List2, List3)</c> is
equivalent to <c>zip3(List1, List2, List3)</c>.</p>
<p><em>Examples:</em></p>
Expand Down
148 changes: 137 additions & 11 deletions lib/stdlib/src/lists.erl
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@
split/2, sublist/2, sublist/3,
subtract/2, suffix/2, sum/1,
uniq/1, unzip/1, unzip3/1,
zip/2, zip3/3]).
zip/2, zip/3, zip3/3, zip3/4]).

%% Functions taking a list of tuples and a position within the tuple.
-export([keydelete/3, keyreplace/4, keymap/3,
Expand All @@ -60,7 +60,7 @@
map/2, mapfoldl/3, mapfoldr/3,
partition/2, search/2,
splitwith/2, takewhile/2, uniq/2,
zipwith/3, zipwith3/4]).
zipwith/3, zipwith/4, zipwith3/4, zipwith3/5]).

%% Undocumented, but used within Erlang/OTP.
-export([zf/2]).
Expand Down Expand Up @@ -416,8 +416,35 @@ delete(_, []) -> [].
A :: term(),
B :: term().

zip([X | Xs], [Y | Ys]) -> [{X, Y} | zip(Xs, Ys)];
zip([], []) -> [].
zip(Xs, Ys) -> zip(Xs, Ys, fail).

-spec zip(List1, List2, How) -> List3 when
List1 :: [A],
List2 :: [B],
List3 :: [{A | DefaultA, B | DefaultB}],
A :: term(),
B :: term(),
How :: 'fail' | 'trim' | {'pad', {DefaultA, DefaultB}},
DefaultA :: term(),
DefaultB :: term().

zip([X | Xs], [Y | Ys], How) ->
[{X, Y} | zip(Xs, Ys, How)];
zip([], [], fail) ->
[];
zip([], [], trim) ->
[];
zip([], [], {pad, {_, _}}) ->
[];
zip([_ | _], [], trim) ->
[];
zip([], [_ | _], trim) ->
[];
zip([], [_ | _]=Ys, {pad, {X, _}}) ->
[{X, Y} || Y <- Ys];
zip([_ | _]=Xs, [], {pad, {_, Y}}) ->
[{X, Y} || X <- Xs].


%% Return {[X0, X1, ..., Xn], [Y0, Y1, ..., Yn]}, for a list [{X0, Y0},
%% {X1, Y1}, ..., {Xn, Yn}].
Expand Down Expand Up @@ -446,8 +473,43 @@ unzip([], Xs, Ys) -> {reverse(Xs), reverse(Ys)}.
B :: term(),
C :: term().

zip3([X | Xs], [Y | Ys], [Z | Zs]) -> [{X, Y, Z} | zip3(Xs, Ys, Zs)];
zip3([], [], []) -> [].
zip3(Xs, Ys, Zs) -> zip3(Xs, Ys, Zs, fail).

-spec zip3(List1, List2, List3, How) -> List4 when
List1 :: [A],
List2 :: [B],
List3 :: [C],
List4 :: [{A | DefaultA, B | DefaultB, C | DefaultC}],
A :: term(),
B :: term(),
C :: term(),
How :: 'fail' | 'trim' | {'pad', {DefaultA, DefaultB, DefaultC}},
DefaultA :: term(),
DefaultB :: term(),
DefaultC :: term().

zip3([X | Xs], [Y | Ys], [Z | Zs], How) ->
[{X, Y, Z} | zip3(Xs, Ys, Zs, How)];
zip3([], [], [], fail) ->
[];
zip3([], [], [], trim) ->
[];
zip3(Xs, Ys, Zs, trim) when is_list(Xs), is_list(Ys), is_list(Zs) ->
[];
zip3([], [], [], {pad, {_, _, _}}) ->
[];
zip3([], [], [_ |_]=Zs, {pad, {X, Y, _}}) ->
[{X, Y, Z} || Z <- Zs];
zip3([], [_ | _]=Ys, [], {pad, {X, _, Z}}) ->
[{X, Y, Z} || Y <- Ys];
zip3([_ | _]=Xs, [], [], {pad, {_, Y, Z}}) ->
[{X, Y, Z} || X <- Xs];
zip3([], [Y | Ys], [Z | Zs], {pad, {X, _, _}} = How) ->
[{X, Y, Z} | zip3([], Ys, Zs, How)];
zip3([X | Xs], [], [Z | Zs], {pad, {_, Y, _}} = How) ->
[{X, Y, Z} | zip3(Xs, [], Zs, How)];
zip3([X | Xs], [Y | Ys], [], {pad, {_, _, Z}} = How) ->
[{X, Y, Z} | zip3(Xs, Ys, [], How)].

%% Return {[X0, X1, ..., Xn], [Y0, Y1, ..., Yn], [Z0, Z1, ..., Zn]}, for
%% a list [{X0, Y0, Z0}, {X1, Y1, Z1}, ..., {Xn, Yn, Zn}].
Expand Down Expand Up @@ -480,8 +542,36 @@ unzip3([], Xs, Ys, Zs) ->
Y :: term(),
T :: term().

zipwith(F, [X | Xs], [Y | Ys]) -> [F(X, Y) | zipwith(F, Xs, Ys)];
zipwith(F, [], []) when is_function(F, 2) -> [].
zipwith(F, Xs, Ys) -> zipwith(F, Xs, Ys, fail).

-spec zipwith(Combine, List1, List2, How) -> List3 when
Combine :: fun((X | DefaultX, Y | DefaultY) -> T),
List1 :: [X],
List2 :: [Y],
List3 :: [T],
X :: term(),
Y :: term(),
How :: 'fail' | 'trim' | {'pad', {DefaultX, DefaultY}},
DefaultX :: term(),
DefaultY :: term(),
T :: term().

zipwith(F, [X | Xs], [Y | Ys], How) ->
[F(X, Y) | zipwith(F, Xs, Ys, How)];
zipwith(F, [], [], fail) when is_function(F, 2) ->
[];
zipwith(F, [], [], trim) when is_function(F, 2) ->
[];
zipwith(F, [], [], {pad, {_, _}}) when is_function(F, 2) ->
[];
zipwith(F, [_ | _], [], trim) when is_function(F, 2) ->
[];
zipwith(F, [], [_ | _], trim) when is_function(F, 2) ->
[];
zipwith(F, [], [_ | _]=Ys, {pad, {X, _}}) ->
[F(X, Y) || Y <- Ys];
zipwith(F, [_ | _]=Xs, [], {pad, {_, Y}}) ->
[F(X, Y) || X <- Xs].

%% Return [F(X0, Y0, Z0), F(X1, Y1, Z1), ..., F(Xn, Yn, Zn)] for lists
%% [X0, X1, ..., Xn], [Y0, Y1, ..., Yn] and [Z0, Z1, ..., Zn].
Expand All @@ -497,9 +587,45 @@ zipwith(F, [], []) when is_function(F, 2) -> [].
Z :: term(),
T :: term().

zipwith3(F, [X | Xs], [Y | Ys], [Z | Zs]) ->
[F(X, Y, Z) | zipwith3(F, Xs, Ys, Zs)];
zipwith3(F, [], [], []) when is_function(F, 3) -> [].
zipwith3(F, Xs, Ys, Zs) -> zipwith3(F, Xs, Ys, Zs, fail).

-spec zipwith3(Combine, List1, List2, List3, How) -> List4 when
Combine :: fun((X | DefaultX, Y | DefaultY, Z | DefaultZ) -> T),
List1 :: [X],
List2 :: [Y],
List3 :: [Z],
List4 :: [T],
X :: term(),
Y :: term(),
Z :: term(),
How :: 'fail' | 'trim' | {'pad', {DefaultX, DefaultY, DefaultZ}},
DefaultX :: term(),
DefaultY :: term(),
DefaultZ :: term(),
T :: term().

zipwith3(F, [X | Xs], [Y | Ys], [Z | Zs], How) ->
[F(X, Y, Z) | zipwith3(F, Xs, Ys, Zs, How)];
zipwith3(F, [], [], [], fail) when is_function(F, 3) ->
[];
zipwith3(F, [], [], [], trim) when is_function(F, 3) ->
[];
zipwith3(F, Xs, Ys, Zs, trim) when is_function(F, 3), is_list(Xs), is_list(Ys), is_list(Zs) ->
[];
zipwith3(F, [], [], [], {pad, {_, _, _}}) when is_function(F, 3) ->
[];
zipwith3(F, [], [], [_ | _]=Zs, {pad, {X, Y, _}}) ->
[F(X, Y, Z) || Z <- Zs];
zipwith3(F, [], [_ | _]=Ys, [], {pad, {X, _, Z}}) ->
[F(X, Y, Z) || Y <- Ys];
zipwith3(F, [_ | _]=Xs, [], [], {pad, {_, Y, Z}}) ->
[F(X, Y, Z) || X <- Xs];
zipwith3(F, [], [Y | Ys], [Z | Zs], {pad, {X, _, _}} = How) ->
[F(X, Y, Z) | zipwith3(F, [], Ys, Zs, How)];
zipwith3(F, [X | Xs], [], [Z | Zs], {pad, {_, Y, _}} = How) ->
[F(X, Y, Z) | zipwith3(F, Xs, [], Zs, How)];
zipwith3(F, [X | Xs], [Y | Ys], [], {pad, {_, _, Z}} = How) ->
[F(X, Y, Z) | zipwith3(F, Xs, Ys, [], How)].

%% sort(List) -> L
%% sorts the list L
Expand Down
Loading

0 comments on commit 93748a8

Please sign in to comment.