File 5551-lists-enable-zip-functions-to-work-on-lists-of-diffe.patch of Package erlang

From 93748a8d841efc8f8246074ca721607efecebe2d Mon Sep 17 00:00:00 2001
From: Maria Scott <maria-12648430@hnc-agency.org>
Date: Wed, 5 Oct 2022 11:58:26 +0200
Subject: [PATCH] lists: enable zip functions to work on lists of different
 lengths
MIME-Version: 1.0
Content-Type: text/plain; charset=UTF-8
Content-Transfer-Encoding: 8bit

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>
---
 lib/stdlib/doc/src/lists.xml                  |  45 +++-
 lib/stdlib/src/lists.erl                      | 148 ++++++++++++-
 lib/stdlib/test/lists_SUITE.erl               | 208 +++++++++++++++++-
 lib/stdlib/test/lists_property_test_SUITE.erl |  40 +++-
 lib/stdlib/test/property_test/lists_prop.erl  | 194 +++++++++++++++-
 5 files changed, 603 insertions(+), 32 deletions(-)

diff --git a/lib/stdlib/doc/src/lists.xml b/lib/stdlib/doc/src/lists.xml
index d2d9870aee..00caf89d23 100644
--- a/lib/stdlib/doc/src/lists.xml
+++ b/lib/stdlib/doc/src/lists.xml
@@ -1069,35 +1069,69 @@ splitwith(Pred, List) ->
 
     <func>
       <name name="zip" arity="2" since=""/>
+      <name name="zip" arity="3" since="OTP 26.0"/>
       <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 26.0"/>
       <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 26.0"/>
       <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>
@@ -1109,13 +1143,16 @@ splitwith(Pred, List) ->
 
     <func>
       <name name="zipwith3" arity="4" since=""/>
+      <name name="zipwith3" arity="5" since="OTP 26.0"/>
       <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>
diff --git a/lib/stdlib/src/lists.erl b/lib/stdlib/src/lists.erl
index d2cb5aab3c..c5eda49253 100644
--- a/lib/stdlib/src/lists.erl
+++ b/lib/stdlib/src/lists.erl
@@ -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,
@@ -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]).
@@ -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}].
@@ -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}].
@@ -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].
@@ -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
diff --git a/lib/stdlib/test/lists_SUITE.erl b/lib/stdlib/test/lists_SUITE.erl
index b369b6918e..b5cbcd98c7 100644
--- a/lib/stdlib/test/lists_SUITE.erl
+++ b/lib/stdlib/test/lists_SUITE.erl
@@ -55,6 +55,10 @@
 	 ufunsort_error/1,
 	 uniq_1/1, uniq_2/1,
 	 zip_unzip/1, zip_unzip3/1, zipwith/1, zipwith3/1,
+	 zip_fail/1, zip_trim/1, zip_pad/1,
+	 zip3_fail/1, zip3_trim/1, zip3_pad/1,
+	 zipwith_fail/1, zipwith_trim/1, zipwith_pad/1,
+	 zipwith3_fail/1, zipwith3_trim/1, zipwith3_pad/1,
 	 filter_partition/1, 
 	 join/1,
 	 otp_5939/1, otp_6023/1, otp_6606/1, otp_7230/1,
@@ -121,7 +125,11 @@ groups() ->
      {flatten, [parallel],
       [flatten_1, flatten_2, flatten_1_e, flatten_2_e]},
      {tickets, [parallel], [otp_5939, otp_6023, otp_6606, otp_7230]},
-     {zip, [parallel], [zip_unzip, zip_unzip3, zipwith, zipwith3]},
+     {zip, [parallel], [zip_unzip, zip_unzip3, zipwith, zipwith3,
+			zip_fail, zip_trim, zip_pad,
+		        zip3_fail, zip3_trim, zip3_pad,
+		        zipwith_fail, zipwith_trim, zipwith_pad,
+		        zipwith3_fail, zipwith3_trim, zipwith3_pad]},
      {uniq, [parallel], [uniq_1, uniq_2]},
      {misc, [parallel], [reverse, member, dropwhile, takewhile,
 			 filter_partition, suffix, subtract, join,
@@ -2362,6 +2370,41 @@ zip_unzip(Config) when is_list(Config) ->
     {'EXIT',{function_clause,_}} = (catch lists:zip([a], [b,c])),
     ok.
 
+zip_fail(Config) when is_list(Config) ->
+    [] = lists:zip([], [], fail),
+    {'EXIT', {function_clause, _}} = (catch lists:zip([a], [], fail)),
+    {'EXIT', {function_clause, _}} = (catch lists:zip([], [c], fail)),
+
+    [{a, c}] = lists:zip([a], [c], fail),
+    {'EXIT', {function_clause, _}} = (catch lists:zip([a, b], [c], fail)),
+    {'EXIT', {function_clause, _}} = (catch lists:zip([a], [c, d], fail)),
+
+    ok.
+
+zip_trim(Config) when is_list(Config) ->
+    [] = lists:zip([], [], trim),
+    [] = lists:zip([a], [], trim),
+    [] = lists:zip([], [c], trim),
+
+    [{a, c}] = lists:zip([a], [c], trim),
+    [{a, c}] = lists:zip([a, b], [c], trim),
+    [{a, c}] = lists:zip([a], [c, d], trim),
+
+    ok.
+
+zip_pad(Config) when is_list(Config) ->
+    How = {pad, {x, y}},
+
+    [] = lists:zip([], [], How),
+    [{a, y}] = lists:zip([a], [], How),
+    [{x, c}] = lists:zip([], [c], How),
+
+    [{a, c}] = lists:zip([a], [c], How),
+    [{a, c}, {b, y}] = lists:zip([a, b], [c], How),
+    [{a, c}, {x, d}] = lists:zip([a], [c, d], How),
+
+    ok.
+
 %% Test lists:zip3/3, lists:unzip3/1.
 zip_unzip3(Config) when is_list(Config) ->
     [] = lists:zip3([], [], []),
@@ -2388,6 +2431,65 @@ zip_unzip3(Config) when is_list(Config) ->
 
     ok.
 
+zip3_fail(Config) when is_list(Config) ->
+    [] = lists:zip3([], [], [], fail),
+    {'EXIT', {function_clause, _}} = (catch lists:zip3([a], [], [], fail)),
+    {'EXIT', {function_clause, _}} = (catch lists:zip3([], [c], [], fail)),
+    {'EXIT', {function_clause, _}} = (catch lists:zip3([a], [c], [], fail)),
+    {'EXIT', {function_clause, _}} = (catch lists:zip3([], [], [e], fail)),
+    {'EXIT', {function_clause, _}} = (catch lists:zip3([a], [], [e], fail)),
+    {'EXIT', {function_clause, _}} = (catch lists:zip3([], [c], [e], fail)),
+
+    [{a, c, e}] = lists:zip3([a], [c], [e], fail),
+    {'EXIT', {function_clause, _}} = (catch lists:zip3([a, b], [c], [e], fail)),
+    {'EXIT', {function_clause, _}} = (catch lists:zip3([a], [c, d], [e], fail)),
+    {'EXIT', {function_clause, _}} = (catch lists:zip3([a, b], [c, d], [e], fail)),
+    {'EXIT', {function_clause, _}} = (catch lists:zip3([a], [c], [e, f], fail)),
+    {'EXIT', {function_clause, _}} = (catch lists:zip3([a, b], [c], [e, f], fail)),
+    {'EXIT', {function_clause, _}} = (catch lists:zip3([a], [c, d], [e, f], fail)),
+
+    ok.
+
+zip3_trim(Config) when is_list(Config) ->
+    [] = lists:zip3([], [], [], trim),
+    [] = lists:zip3([a], [], [], trim),
+    [] = lists:zip3([], [c], [], trim),
+    [] = lists:zip3([a], [c], [], trim),
+    [] = lists:zip3([], [], [e], trim),
+    [] = lists:zip3([a], [], [e], trim),
+    [] = lists:zip3([], [c], [e], trim),
+
+    [{a, c, e}] = lists:zip3([a], [c], [e], trim),
+    [{a, c, e}] = lists:zip3([a, b], [c], [e], trim),
+    [{a, c, e}] = lists:zip3([a], [c, d], [e], trim),
+    [{a, c, e}] = lists:zip3([a, b], [c, d], [e], trim),
+    [{a, c, e}] = lists:zip3([a], [c], [e, f], trim),
+    [{a, c, e}] = lists:zip3([a, b], [c], [e, f], trim),
+    [{a, c, e}] = lists:zip3([a], [c, d], [e, f], trim),
+
+    ok.
+
+zip3_pad(Config) when is_list(Config) ->
+    How = {pad, {x, y, z}},
+
+    [] = lists:zip3([], [], [], How),
+    [{a, y, z}] = lists:zip3([a], [], [], How),
+    [{x, c, z}] = lists:zip3([], [c], [], How),
+    [{a, c, z}] = lists:zip3([a], [c], [], How),
+    [{x, y, e}] = lists:zip3([], [], [e], How),
+    [{a, y, e}] = lists:zip3([a], [], [e], How),
+    [{x, c, e}] = lists:zip3([], [c], [e], How),
+
+    [{a, c, e}] = lists:zip3([a], [c], [e], How),
+    [{a, c, e}, {b, y, z}] = lists:zip3([a, b], [c], [e], How),
+    [{a, c, e}, {x, d, z}] = lists:zip3([a], [c, d], [e], How),
+    [{a, c, e}, {b, d, z}] = lists:zip3([a, b], [c, d], [e], How),
+    [{a, c, e}, {x, y, f}] = lists:zip3([a], [c], [e, f], How),
+    [{a, c, e}, {b, y, f}] = lists:zip3([a, b], [c], [e, f], How),
+    [{a, c, e}, {x, d, f}] = lists:zip3([a], [c, d], [e, f], How),
+
+    ok.
+
 %% Test lists:zipwith/3.
 zipwith(Config) when is_list(Config) ->
     Zip = fun(A, B) -> [A|B] end,
@@ -2410,6 +2512,47 @@ zipwith(Config) when is_list(Config) ->
     {'EXIT',{function_clause,_}} = (catch lists:zipwith(Zip, [a], [b,c])),
     ok.
 
+zipwith_fail(Config) when is_list(Config) ->
+    Zip = fun(A, B) -> A * B end,
+
+    [] = lists:zipwith(Zip, [], [], fail),
+    {'EXIT', {function_clause, _}} = (catch lists:zipwith(Zip, [2], [], fail)),
+    {'EXIT', {function_clause, _}} = (catch lists:zipwith(Zip, [], [5], fail)),
+
+    [2 * 5] = lists:zipwith(Zip, [2], [5], fail),
+    {'EXIT', {function_clause, _}} = (catch lists:zipwith(Zip, [2, 3], [5], fail)),
+    {'EXIT', {function_clause, _}} = (catch lists:zipwith(Zip, [2], [5, 7], fail)),
+
+    ok.
+
+zipwith_trim(Config) when is_list(Config) ->
+    Zip = fun(A, B) -> A * B end,
+
+    [] = lists:zipwith(Zip, [], [], trim),
+    [] = lists:zipwith(Zip, [2], [], trim),
+    [] = lists:zipwith(Zip, [], [5], trim),
+
+    [2 * 5] = lists:zipwith(Zip, [2], [5], trim),
+    [2 * 5] = lists:zipwith(Zip, [2, 3], [5], trim),
+    [2 * 5] = lists:zipwith(Zip, [2], [5, 7], trim),
+
+    ok.
+
+zipwith_pad(Config) when is_list(Config) ->
+    How = {pad, {17, 19}},
+
+    Zip = fun(A, B) -> A * B end,
+
+    [] = lists:zipwith(Zip, [], [], How),
+    [ 2 * 19] = lists:zipwith(Zip, [2], [], How),
+    [17 *  5] = lists:zipwith(Zip, [], [5], How),
+
+    [2 * 5] = lists:zipwith(Zip, [2], [5], How),
+    [2 * 5,  3 * 19] = lists:zipwith(Zip, [2, 3], [5], How),
+    [2 * 5, 17 *  7] = lists:zipwith(Zip, [2], [5, 7], How),
+
+    ok.
+
 %% Test lists:zipwith3/4.
 zipwith3(Config) when is_list(Config) ->
     Zip = fun(A, B, C) -> [A,B,C] end,
@@ -2434,6 +2577,69 @@ zipwith3(Config) when is_list(Config) ->
 
     ok.
 
+zipwith3_fail(Config) when is_list(Config) ->
+    Zip = fun(A, B, C) -> A * B * C end,
+
+    [] = lists:zipwith3(Zip, [], [], [], fail),
+    {'EXIT', {function_clause, _}} = (catch lists:zipwith3(Zip, [2], [], [], fail)),
+    {'EXIT', {function_clause, _}} = (catch lists:zipwith3(Zip, [], [5], [], fail)),
+    {'EXIT', {function_clause, _}} = (catch lists:zipwith3(Zip, [2], [5], [], fail)),
+    {'EXIT', {function_clause, _}} = (catch lists:zipwith3(Zip, [], [], [11], fail)),
+    {'EXIT', {function_clause, _}} = (catch lists:zipwith3(Zip, [2], [], [11], fail)),
+    {'EXIT', {function_clause, _}} = (catch lists:zipwith3(Zip, [], [5], [11], fail)),
+
+    [2 * 5 * 11] = lists:zipwith3(Zip, [2], [5], [11], fail),
+    {'EXIT', {function_clause, _}} = (catch lists:zipwith3(Zip, [2, 3], [5], [11], fail)),
+    {'EXIT', {function_clause, _}} = (catch lists:zipwith3(Zip, [2], [5, 7], [11], fail)),
+    {'EXIT', {function_clause, _}} = (catch lists:zipwith3(Zip, [2, 3], [5, 7], [11], fail)),
+    {'EXIT', {function_clause, _}} = (catch lists:zipwith3(Zip, [2], [5], [11, 13], fail)),
+    {'EXIT', {function_clause, _}} = (catch lists:zipwith3(Zip, [2, 3], [5], [11, 13], fail)),
+    {'EXIT', {function_clause, _}} = (catch lists:zipwith3(Zip, [2], [5, 7], [11, 13], fail)),
+
+    ok.
+
+zipwith3_trim(Config) when is_list(Config) ->
+    Zip = fun(A, B, C) -> A * B * C end,
+
+    [] = lists:zipwith3(Zip, [], [], [], trim),
+    [] = lists:zipwith3(Zip, [2], [], [], trim),
+    [] = lists:zipwith3(Zip, [], [5], [], trim),
+    [] = lists:zipwith3(Zip, [], [], [11], trim),
+    [] = lists:zipwith3(Zip, [2], [], [11], trim),
+    [] = lists:zipwith3(Zip, [], [5], [11], trim),
+
+    [2 * 5 * 11] = lists:zipwith3(Zip, [2], [5], [11], trim),
+    [2 * 5 * 11] = lists:zipwith3(Zip, [2, 3], [5], [11], trim),
+    [2 * 5 * 11] = lists:zipwith3(Zip, [2], [5, 7], [11], trim),
+    [2 * 5 * 11] = lists:zipwith3(Zip, [2], [5], [11, 13], trim),
+    [2 * 5 * 11] = lists:zipwith3(Zip, [2, 3], [5], [11, 13], trim),
+    [2 * 5 * 11] = lists:zipwith3(Zip, [2], [5, 7], [11, 13], trim),
+
+    ok.
+
+zipwith3_pad(Config) when is_list(Config) ->
+    How = {pad, {17, 19, 23}},
+
+    Zip = fun(A, B, C) -> A * B * C end,
+
+    [] = lists:zipwith3(Zip, [], [], [], How),
+    [ 2 * 19 * 23] = lists:zipwith3(Zip, [2], [], [], How),
+    [17 *  5 * 23] = lists:zipwith3(Zip, [], [5], [], How),
+    [ 2 *  5 * 23] = lists:zipwith3(Zip, [2], [5], [], How),
+    [17 * 19 * 11] = lists:zipwith3(Zip, [], [], [11], How),
+    [ 2 * 19 * 11] = lists:zipwith3(Zip, [2], [], [11], How),
+    [17 *  5 * 11] = lists:zipwith3(Zip, [], [5], [11], How),
+
+    [2 * 5 * 11] = lists:zipwith3(Zip, [2], [5], [11], How),
+    [2 * 5 * 11,  3 * 19 * 23] = lists:zipwith3(Zip, [2, 3], [5], [11], How),
+    [2 * 5 * 11, 17 *  7 * 23] = lists:zipwith3(Zip, [2], [5, 7], [11], How),
+    [2 * 5 * 11,  3 *  7 * 23] = lists:zipwith3(Zip, [2, 3], [5, 7], [11], How),
+    [2 * 5 * 11, 17 * 19 * 13] = lists:zipwith3(Zip, [2], [5], [11, 13], How),
+    [2 * 5 * 11,  3 * 19 * 13] = lists:zipwith3(Zip, [2, 3], [5], [11, 13], How),
+    [2 * 5 * 11, 17 *  7 * 13] = lists:zipwith3(Zip, [2], [5, 7], [11, 13], How),
+
+    ok.
+
 %% Test lists:join/2
 join(Config) when is_list(Config) ->
     A = [a,b,c],
diff --git a/lib/stdlib/test/lists_property_test_SUITE.erl b/lib/stdlib/test/lists_property_test_SUITE.erl
index fee088a396..8b94f841f5 100644
--- a/lib/stdlib/test/lists_property_test_SUITE.erl
+++ b/lib/stdlib/test/lists_property_test_SUITE.erl
@@ -97,10 +97,14 @@ all() ->
         unzip3_case,
         usort_1_case,
         usort_2_case,
-        zip_case,
-        zip3_case,
-        zipwith_case,
-        zipwith3_case
+        zip_2_case,
+        zip_3_case,
+        zip3_3_case,
+        zip3_4_case,
+        zipwith_3_case,
+        zipwith_4_case,
+        zipwith3_4_case,
+        zipwith3_5_case
     ].
 
 init_per_suite(Config) ->
@@ -377,15 +381,27 @@ usort_1_case(Config) ->
 usort_2_case(Config) ->
     do_proptest(prop_usort_2, Config).
 
-zip_case(Config) ->
-    do_proptest(prop_zip, Config).
+zip_2_case(Config) ->
+    do_proptest(prop_zip_2, Config).
 
-zip3_case(Config) ->
-    do_proptest(prop_zip3, Config).
+zip_3_case(Config) ->
+    do_proptest(prop_zip_3, Config).
 
-zipwith_case(Config) ->
-    do_proptest(prop_zipwith, Config).
+zip3_3_case(Config) ->
+    do_proptest(prop_zip3_3, Config).
 
-zipwith3_case(Config) ->
-    do_proptest(prop_zipwith3, Config).
+zip3_4_case(Config) ->
+    do_proptest(prop_zip3_4, Config).
+
+zipwith_3_case(Config) ->
+    do_proptest(prop_zipwith_3, Config).
+
+zipwith_4_case(Config) ->
+    do_proptest(prop_zipwith_4, Config).
+
+zipwith3_4_case(Config) ->
+    do_proptest(prop_zipwith3_4, Config).
+
+zipwith3_5_case(Config) ->
+    do_proptest(prop_zipwith3_5, Config).
 
diff --git a/lib/stdlib/test/property_test/lists_prop.erl b/lib/stdlib/test/property_test/lists_prop.erl
index 6df00335c6..c6f3cb7c9b 100644
--- a/lib/stdlib/test/property_test/lists_prop.erl
+++ b/lib/stdlib/test/property_test/lists_prop.erl
@@ -1269,7 +1269,7 @@ prop_usort_2() ->
     ).
 
 %% zip/2
-prop_zip() ->
+prop_zip_2() ->
     ?FORALL(
         {ExpList, {InList1, InList2}},
         gen_list_fold(
@@ -1282,8 +1282,44 @@ prop_zip() ->
         lists:zip(InList1, InList2) =:= ExpList
     ).
 
+%% zip/3
+prop_zip_3() ->
+	?FORALL(
+		{{ExpList, {InList1, InList2}}, ExtraList},
+		{
+			gen_list_fold(
+				{gen_any(), gen_any()},
+				fun({T1, T2}, {L1, L2}) ->
+					{L1 ++ [T1], L2 ++ [T2]}
+				end,
+				{[], []}
+			),
+			non_empty(gen_list())
+		},
+		begin
+			Tag = make_ref(),
+
+			Res1 = ExpList =:= lists:zip(InList1, InList2, fail) andalso
+			       ExpList =:= lists:zip(InList1, InList2, trim) andalso
+			       ExpList =:= lists:zip(InList1, InList2, {pad, {Tag, Tag}}),
+
+			Res2 = try lists:zip(InList1, InList2 ++ ExtraList, fail) of _ -> false catch error:_ -> true end andalso
+			       try lists:zip(InList1 ++ ExtraList, InList2, fail) of _ -> false catch error:_ -> true end,
+
+			Res3 = ExpList =:= lists:zip(InList1, InList2 ++ ExtraList, trim) andalso
+			       ExpList =:= lists:zip(InList1 ++ ExtraList, InList2, trim),
+
+			Padded1 = lists:zip(InList1, InList2 ++ ExtraList, {pad, {Tag, Tag}}),
+			Padded2 = lists:zip(InList1 ++ ExtraList, InList2, {pad, {Tag, Tag}}),
+			Res4 = Padded1 =:= ExpList ++ [{Tag, X} || X <- ExtraList] andalso
+			       Padded2 =:= ExpList ++ [{X, Tag} || X <- ExtraList],
+
+			Res1 andalso Res2 andalso Res3 andalso Res4
+		end
+	).
+
 %% zip3/3
-prop_zip3() ->
+prop_zip3_3() ->
     ?FORALL(
         {ExpList, {InList1, InList2, InList3}},
         gen_list_fold(
@@ -1296,8 +1332,60 @@ prop_zip3() ->
         lists:zip3(InList1, InList2, InList3) =:= ExpList
     ).
 
+%% zip3/4
+prop_zip3_4() ->
+	?FORALL(
+		{{ExpList, {InList1, InList2, InList3}}, ExtraList},
+		{
+			gen_list_fold(
+				{gen_any(), gen_any(), gen_any()},
+				fun({T1, T2, T3}, {L1, L2, L3}) ->
+					{L1 ++ [T1], L2 ++ [T2], L3 ++ [T3]}
+				end,
+				{[], [], []}
+			),
+			non_empty(gen_list())
+		},
+		begin
+			Tag = make_ref(),
+
+			Res1 = ExpList =:= lists:zip3(InList1, InList2, InList3, fail) andalso
+			       ExpList =:= lists:zip3(InList1, InList2, InList3, trim) andalso
+			       ExpList =:= lists:zip3(InList1, InList2, InList3, {pad, {Tag, Tag, Tag}}),
+
+			Res2 = try lists:zip3(InList1, InList2, InList3 ++ ExtraList, fail) of _ -> false catch error:_ -> true end andalso
+			       try lists:zip3(InList1, InList2 ++ ExtraList, InList3, fail) of _ -> false catch error:_ -> true end andalso
+			       try lists:zip3(InList1, InList2 ++ ExtraList, InList3 ++ ExtraList, fail) of _ -> false catch error:_ -> true end andalso
+			       try lists:zip3(InList1 ++ ExtraList, InList2, InList3, fail) of _ -> false catch error:_ -> true end andalso
+			       try lists:zip3(InList1 ++ ExtraList, InList2, InList3 ++ ExtraList, fail) of _ -> false catch error:_ -> true end andalso
+			       try lists:zip3(InList1 ++ ExtraList, InList2 ++ ExtraList, InList3, fail) of _ -> false catch error:_ -> true end,
+
+			Res3 = ExpList =:= lists:zip3(InList1, InList2, InList3 ++ ExtraList, trim) andalso
+			       ExpList =:= lists:zip3(InList1, InList2 ++ ExtraList, InList3, trim) andalso
+			       ExpList =:= lists:zip3(InList1, InList2 ++ ExtraList, InList3 ++ ExtraList, trim) andalso
+			       ExpList =:= lists:zip3(InList1 ++ ExtraList, InList2, InList3, trim) andalso
+			       ExpList =:= lists:zip3(InList1 ++ ExtraList, InList2, InList3 ++ ExtraList, trim) andalso
+			       ExpList =:= lists:zip3(InList1 ++ ExtraList, InList2 ++ ExtraList, InList3, trim),
+
+			Padded1 = lists:zip3(InList1, InList2, InList3 ++ ExtraList, {pad, {Tag, Tag, Tag}}),
+			Padded2 = lists:zip3(InList1, InList2 ++ ExtraList, InList3, {pad, {Tag, Tag, Tag}}),
+			Padded3 = lists:zip3(InList1, InList2 ++ ExtraList, InList3 ++ ExtraList, {pad, {Tag, Tag, Tag}}),
+			Padded4 = lists:zip3(InList1 ++ ExtraList, InList2, InList3, {pad, {Tag, Tag, Tag}}),
+			Padded5 = lists:zip3(InList1 ++ ExtraList, InList2, InList3 ++ ExtraList, {pad, {Tag, Tag, Tag}}),
+			Padded6 = lists:zip3(InList1 ++ ExtraList, InList2 ++ ExtraList, InList3, {pad, {Tag, Tag, Tag}}),
+			Res4 = Padded1 =:= ExpList ++ [{Tag, Tag, X} || X <- ExtraList] andalso
+			       Padded2 =:= ExpList ++ [{Tag, X, Tag} || X <- ExtraList] andalso
+			       Padded3 =:= ExpList ++ [{Tag, X, X} || X <- ExtraList] andalso
+			       Padded4 =:= ExpList ++ [{X, Tag, Tag} || X <- ExtraList] andalso
+			       Padded5 =:= ExpList ++ [{X, Tag, X} || X <- ExtraList] andalso
+			       Padded6 =:= ExpList ++ [{X, X, Tag} || X <- ExtraList],
+
+			Res1 andalso Res2 andalso Res3 andalso Res4
+		end
+	).
+
 %% zipwith/3
-prop_zipwith() ->
+prop_zipwith_3() ->
     ?FORALL(
         {ZipFn, InList1, InList2, ExpList},
         ?LET(
@@ -1318,8 +1406,49 @@ prop_zipwith() ->
         lists:zipwith(ZipFn, InList1, InList2) =:= ExpList
     ).
 
+%% zipwith/4
+prop_zipwith_4() ->
+	?FORALL(
+		{ZipFn, InList1, InList2, ExpList, ExtraList},
+		?LET(
+			{Extra, Fn},
+			{non_empty(gen_list()), function2(gen_any())},
+			?LET(
+				{_, {L1, L2, Z}},
+				gen_list_fold(
+					{gen_any(), gen_any()},
+					fun({T1, T2}, {L1, L2, Z}) ->
+						{L1 ++ [T1], L2 ++ [T2], Z ++ [Fn(T1, T2)]}
+					end,
+					{[], [], []}
+				),
+				{Fn, L1, L2, Z, Extra}
+			)
+		),
+		begin
+			Tag = make_ref(),
+
+			Res1 = ExpList =:= lists:zipwith(ZipFn, InList1, InList2, fail) andalso
+			       ExpList =:= lists:zipwith(ZipFn, InList1, InList2, trim) andalso
+			       ExpList =:= lists:zipwith(ZipFn, InList1, InList2, {pad, {Tag, Tag}}),
+
+			Res2 = try lists:zipwith(ZipFn, InList1, InList2 ++ ExtraList, fail) of _ -> false catch error:_ -> true end andalso
+			       try lists:zipwith(ZipFn, InList1 ++ ExtraList, InList2, fail) of _ -> false catch error:_ -> true end,
+
+			Res3 = ExpList =:= lists:zipwith(ZipFn, InList1, InList2 ++ ExtraList, trim) andalso
+			       ExpList =:= lists:zipwith(ZipFn, InList1 ++ ExtraList, InList2, trim),
+
+			Padded1 = lists:zipwith(ZipFn, InList1, InList2 ++ ExtraList, {pad, {Tag, Tag}}),
+			Padded2 = lists:zipwith(ZipFn, InList1 ++ ExtraList, InList2, {pad, {Tag, Tag}}),
+			Res4 = Padded1 =:= ExpList ++ [ZipFn(Tag, X) || X <- ExtraList] andalso
+			       Padded2 =:= ExpList ++ [ZipFn(X, Tag) || X <- ExtraList],
+
+			Res1 andalso Res2 andalso Res3 andalso Res4
+		end
+	).
+
 %% zipwith3/4
-prop_zipwith3() ->
+prop_zipwith3_4() ->
     ?FORALL(
         {ZipFn, InList1, InList2, InList3, ExpList},
         ?LET(
@@ -1340,6 +1469,63 @@ prop_zipwith3() ->
         lists:zipwith3(ZipFn, InList1, InList2, InList3) =:= ExpList
     ).
 
+%% zipwith3/5
+prop_zipwith3_5() ->
+	?FORALL(
+		{ZipFn, InList1, InList2, InList3, ExpList, ExtraList},
+		?LET(
+			{Extra, Fn},
+			{non_empty(gen_list()), function3(gen_any())},
+			?LET(
+				{_, {L1, L2, L3, Z}},
+				gen_list_fold(
+					{gen_any(), gen_any(), gen_any()},
+					fun({T1, T2, T3}, {L1, L2, L3, Z}) ->
+						{L1 ++ [T1], L2 ++ [T2], L3 ++ [T3], Z ++ [Fn(T1, T2, T3)]}
+					end,
+					{[], [], [], []}
+				),
+				{Fn, L1, L2, L3, Z, Extra}
+			)
+		),
+		begin
+			Tag = make_ref(),
+
+			Res1 = ExpList =:= lists:zipwith3(ZipFn, InList1, InList2, InList3, fail) andalso
+			       ExpList =:= lists:zipwith3(ZipFn, InList1, InList2, InList3, trim) andalso
+			       ExpList =:= lists:zipwith3(ZipFn, InList1, InList2, InList3, {pad, {Tag, Tag, Tag}}),
+
+			Res2 = try lists:zipwith3(ZipFn, InList1, InList2, InList3 ++ ExtraList, fail) of _ -> false catch error:_ -> true end andalso
+			       try lists:zipwith3(ZipFn, InList1, InList2 ++ ExtraList, InList3, fail) of _ -> false catch error:_ -> true end andalso
+			       try lists:zipwith3(ZipFn, InList1, InList2 ++ ExtraList, InList3 ++ ExtraList, fail) of _ -> false catch error:_ -> true end andalso
+			       try lists:zipwith3(ZipFn, InList1 ++ ExtraList, InList2, InList3, fail) of _ -> false catch error:_ -> true end andalso
+			       try lists:zipwith3(ZipFn, InList1 ++ ExtraList, InList2, InList3 ++ ExtraList, fail) of _ -> false catch error:_ -> true end andalso
+			       try lists:zipwith3(ZipFn, InList1 ++ ExtraList, InList2 ++ ExtraList, InList3, fail) of _ -> false catch error:_ -> true end,
+
+			Res3 = ExpList =:= lists:zipwith3(ZipFn, InList1, InList2, InList3 ++ ExtraList, trim) andalso
+			       ExpList =:= lists:zipwith3(ZipFn, InList1, InList2 ++ ExtraList, InList3, trim) andalso
+			       ExpList =:= lists:zipwith3(ZipFn, InList1, InList2 ++ ExtraList, InList3 ++ ExtraList, trim) andalso
+			       ExpList =:= lists:zipwith3(ZipFn, InList1 ++ ExtraList, InList2, InList3, trim) andalso
+			       ExpList =:= lists:zipwith3(ZipFn, InList1 ++ ExtraList, InList2, InList3 ++ ExtraList, trim) andalso
+			       ExpList =:= lists:zipwith3(ZipFn, InList1 ++ ExtraList, InList2 ++ ExtraList, InList3, trim),
+
+			Padded1 = lists:zipwith3(ZipFn, InList1, InList2, InList3 ++ ExtraList, {pad, {Tag, Tag, Tag}}),
+			Padded2 = lists:zipwith3(ZipFn, InList1, InList2 ++ ExtraList, InList3, {pad, {Tag, Tag, Tag}}),
+			Padded3 = lists:zipwith3(ZipFn, InList1, InList2 ++ ExtraList, InList3 ++ ExtraList, {pad, {Tag, Tag, Tag}}),
+			Padded4 = lists:zipwith3(ZipFn, InList1 ++ ExtraList, InList2, InList3, {pad, {Tag, Tag, Tag}}),
+			Padded5 = lists:zipwith3(ZipFn, InList1 ++ ExtraList, InList2, InList3 ++ ExtraList, {pad, {Tag, Tag, Tag}}),
+			Padded6 = lists:zipwith3(ZipFn, InList1 ++ ExtraList, InList2 ++ ExtraList, InList3, {pad, {Tag, Tag, Tag}}),
+			Res4 = Padded1 =:= ExpList ++ [ZipFn(Tag, Tag, X) || X <- ExtraList] andalso
+			       Padded2 =:= ExpList ++ [ZipFn(Tag, X, Tag) || X <- ExtraList] andalso
+			       Padded3 =:= ExpList ++ [ZipFn(Tag, X, X) || X <- ExtraList] andalso
+			       Padded4 =:= ExpList ++ [ZipFn(X, Tag, Tag) || X <- ExtraList] andalso
+			       Padded5 =:= ExpList ++ [ZipFn(X, Tag, X) || X <- ExtraList] andalso
+			       Padded6 =:= ExpList ++ [ZipFn(X, X, Tag) || X <- ExtraList],
+
+			Res1 andalso Res2 andalso Res3 andalso Res4
+		end
+	).
+
 %%%%%%%%%%%%%%%%%%
 %%% Generators %%%
 %%%%%%%%%%%%%%%%%%
-- 
2.35.3

openSUSE Build Service is sponsored by