File 1321-stdlib-Fix-a-loop-when-using-io_lib-option-chars_lim.patch of Package erlang

From 881d3be01d659b40861ad8058730f6cb6dc9a5f8 Mon Sep 17 00:00:00 2001
From: Hans Bolinder <hasse@erlang.org>
Date: Fri, 28 May 2021 07:20:46 +0200
Subject: [PATCH] stdlib: Fix a loop when using io_lib option 'chars_limit'

See GH-4824: https://github.com/erlang/otp/pull/4824.

The fix of ERL-967, see https://github.com/erlang/otp/issues/4307,
proved to be inaccurate.

Thanks to Hareen (kvsrh) for tracking down the bug. The fix in
https://github.com/erlang/otp/pull/4842 is included.

A clause that breaks the infinite loop is also added. It will hide
further bugs, but it is deemed more important not to loop.
---
 lib/stdlib/src/io_lib_pretty.erl | 50 ++++++++++++++++++++++----------
 lib/stdlib/test/io_SUITE.erl     | 43 ++++++++++++++++++++++++---
 2 files changed, 74 insertions(+), 19 deletions(-)

diff --git a/lib/stdlib/src/io_lib_pretty.erl b/lib/stdlib/src/io_lib_pretty.erl
index 77f02eafe0..32c5415067 100644
--- a/lib/stdlib/src/io_lib_pretty.erl
+++ b/lib/stdlib/src/io_lib_pretty.erl
@@ -448,11 +448,11 @@ intermediate(Term, D, T, RF, Enc, Str) when T > 0 ->
     case If of
         {_, Len, Dots, _} when Dots =:= 0; Len > T; D =:= 1 ->
             If;
-        _ ->
-            find_upper(If, Term, T, D0, 2, D, RF, Enc, Str)
+        {_, Len, _, _} ->
+            find_upper(If, Term, T, D0, 2, D, RF, Enc, Str, Len)
     end.
 
-find_upper(Lower, Term, T, Dl, Dd, D, RF, Enc, Str) ->
+find_upper(Lower, Term, T, Dl, Dd, D, RF, Enc, Str, LastLen) ->
     Dd2 = Dd * 2,
     D1 = case D < 0 of
              true -> Dl + Dd2;
@@ -462,10 +462,11 @@ find_upper(Lower, Term, T, Dl, Dd, D, RF, Enc, Str) ->
     case If of
         {_, _, _Dots=0, _} -> % even if Len > T
             If;
-        {_, _Len=T, _, _} ->  % increasing the depth is meaningless
+        {_, LastLen, _, _} ->
+            %% Cannot happen if print_length() is free of bugs.
             If;
-        {_, Len, _, _} when Len < T, D1 < D orelse D < 0 ->
-	    find_upper(If, Term, T, D1, Dd2, D, RF, Enc, Str);
+        {_, Len, _, _} when Len =< T, D1 < D orelse D < 0 ->
+	    find_upper(If, Term, T, D1, Dd2, D, RF, Enc, Str, Len);
         _ ->
 	    search_depth(Lower, If, Term, T, Dl, D1, RF, Enc, Str)
     end.
@@ -612,11 +613,15 @@ print_length_map_pairs(Term, D, D0, T, RF, Enc, Str) when D =:= 1; T =:= 0->
            end,
     {dots, 3, 3, More};
 print_length_map_pairs({K, V, Iter}, D, D0, T, RF, Enc, Str) ->
-    Pair1 = print_length_map_pair(K, V, D0, tsub(T, 1), RF, Enc, Str),
-    {_, Len1, _, _} = Pair1,
     Next = maps:next(Iter),
+    T1 = case Next =:= none of
+             false -> tsub(T, 1);
+             true -> T
+         end,
+    Pair1 = print_length_map_pair(K, V, D0, T1, RF, Enc, Str),
+    {_, Len1, _, _} = Pair1,
     [Pair1 |
-     print_length_map_pairs(Next, D - 1, D0, tsub(T, Len1+1), RF, Enc, Str)].
+     print_length_map_pairs(Next, D - 1, D0, tsub(T1, Len1), RF, Enc, Str)].
 
 print_length_map_pair(K, V, D, T, RF, Enc, Str) ->
     {_, KL, KD, _} = P1 = print_length(K, D, T, RF, Enc, Str),
@@ -641,7 +646,10 @@ print_length_tuple1(Tuple, I, D, T, RF, Enc, Str) when D =:= 1; T =:= 0->
     {dots, 3, 3, More};
 print_length_tuple1(Tuple, I, D, T, RF, Enc, Str) ->
     E = element(I, Tuple),
-    T1 = tsub(T, 1),
+    T1 = case I =:= tuple_size(Tuple) of
+             false -> tsub(T, 1);
+             true -> T
+         end,
     {_, Len1, _, _} = Elem1 = print_length(E, D - 1, T1, RF, Enc, Str),
     T2 = tsub(T1, Len1),
     [Elem1 | print_length_tuple1(Tuple, I + 1, D - 1, T2, RF, Enc, Str)].
@@ -670,7 +678,10 @@ print_length_fields(Term, D, T, Tuple, I, RF, Enc, Str)
     {dots, 3, 3, More};
 print_length_fields([Def | Defs], D, T, Tuple, I, RF, Enc, Str) ->
     E = element(I, Tuple),
-    T1 = tsub(T, 1),
+    T1 = case I =:= tuple_size(Tuple) of
+             false -> tsub(T, 1);
+             true -> T
+         end,
     Field1 = print_length_field(Def, D - 1, T1, E, RF, Enc, Str),
     {_, Len1, _, _} = Field1,
     T2 = tsub(T1, Len1),
@@ -695,8 +706,13 @@ print_length_list1(Term, D, T, RF, Enc, Str) when D =:= 1; T =:= 0->
     More = fun(T1, Dd) -> ?FUNCTION_NAME(Term, D+Dd, T1, RF, Enc, Str) end,
     {dots, 3, 3, More};
 print_length_list1([E | Es], D, T, RF, Enc, Str) ->
-    {_, Len1, _, _} = Elem1 = print_length(E, D - 1, tsub(T, 1), RF, Enc, Str),
-    [Elem1 | print_length_list1(Es, D - 1, tsub(T, Len1 + 1), RF, Enc, Str)];
+    %% If E is the last element in list, don't account length for a comma.
+    T1 = case Es =:= [] of
+             false -> tsub(T, 1);
+             true -> T
+         end,
+    {_, Len1, _, _} = Elem1 = print_length(E, D - 1, T1, RF, Enc, Str),
+    [Elem1 | print_length_list1(Es, D - 1, tsub(T1, Len1), RF, Enc, Str)];
 print_length_list1(E, D, T, RF, Enc, Str) ->
     print_length(E, D - 1, T, RF, Enc, Str).
 
@@ -926,8 +942,12 @@ expand_list(Ifs, T, Dd, L0) ->
 expand_list([], _T, _Dd) ->
     [];
 expand_list([If | Ifs], T, Dd) ->
-    {_, Len1, _, _} = Elem1 = expand(If, tsub(T, 1), Dd),
-    [Elem1 | expand_list(Ifs, tsub(T, Len1 + 1), Dd)];
+    T1 = case Ifs =:= [] of
+             false -> tsub(T, 1);
+             true -> T
+         end,
+    {_, Len1, _, _} = Elem1 = expand(If, T1, Dd),
+    [Elem1 | expand_list(Ifs, tsub(T1, Len1), Dd)];
 expand_list({_, _, _, More}, T, Dd) ->
     More(T, Dd).
 
diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl
index 4eb5b1772c..025fcbc408 100644
--- a/lib/stdlib/test/io_SUITE.erl
+++ b/lib/stdlib/test/io_SUITE.erl
@@ -32,7 +32,8 @@
          io_with_huge_message_queue/1, format_string/1, format_neg_zero/1,
 	 maps/1, coverage/1, otp_14178_unicode_atoms/1, otp_14175/1,
          otp_14285/1, limit_term/1, otp_14983/1, otp_15103/1, otp_15076/1,
-         otp_15159/1, otp_15639/1, otp_15847/1, otp_15875/1]).
+         otp_15159/1, otp_15639/1, otp_15847/1, otp_15875/1,
+         chars_limit/1]).
 
 -export([pretty/2, trf/3]).
 
@@ -65,7 +66,7 @@ all() ->
      io_lib_width_too_small, io_with_huge_message_queue,
      format_string, maps, coverage, otp_14178_unicode_atoms, otp_14175,
      otp_14285, limit_term, otp_14983, otp_15103, otp_15076, otp_15159,
-     otp_15639, otp_15847, otp_15875].
+     otp_15639, otp_15847, otp_15875, chars_limit].
 
 %% Error cases for output.
 error_1(Config) when is_list(Config) ->
@@ -2604,7 +2605,7 @@ trunc_depth(D, Fun) ->
     "#{{...} => {...},...}" = Fun(M, D, 7),
     "#{{[...],...} => {[...],...},...}" = Fun(M, D, 22),
     "#{{[...],...} => {[...],...},[...] => [...]}" = Fun(M, D, 31),
-    "#{{[...],...} => {[...],...},[...] => [...]}" = Fun(M, D, 33),
+    "#{{[...],...} => {[...],...},[1|...] => [...]}" = Fun(M, D, 33),
     "#{{[1|...],[...]} => {[1|...],[...]},[1,2|...] => [...]}" =
         Fun(M, D, 50),
 
@@ -2749,5 +2750,39 @@ otp_15847(_Config) ->
     ok.
 
 otp_15875(_Config) ->
+    %% This test is moot due to the fix in GH-4842.
     S = io_lib:format("~tp", [[{0, [<<"00">>]}]], [{chars_limit, 18}]),
-    "[{0,[<<48,...>>]}]" = lists:flatten(S).
+    "[{0,[<<\"00\">>]}]" = lists:flatten(S).
+
+%% GH-4824, GH-4842, OTP-17459.
+chars_limit(_Config) ->
+    List = fun R(I) ->
+                   case I =:= 0 of true -> 0; false -> [I, R(I-1)] end
+           end,
+    Tuple = fun R(I) ->
+                   case I =:= 0 of true -> 0; false -> {I, R(I-1)} end
+           end,
+    Map = fun R(I) ->
+                   case I =:= 0 of true -> 0; false -> #{I => R(I-1)} end
+           end,
+    Record = fun R(I) ->
+                   case I =:= 0 of true -> 0; false -> {b, R(I-1)} end
+           end,
+    Test = fun (F, N, Lim) ->
+                   Opts = [{chars_limit, Lim},
+                           {record_print_fun, fun rfd/2}],
+                   [_|_] = io_lib_pretty:print(F(N), Opts)
+           end,
+    %% Used to loop:
+    Test(List, 1000, 1000),
+    Test(Tuple, 1000, 1000),
+    Test(Map, 1000, 1000),
+    Test(Record, 1000, 1000),
+
+    %% Misc sizes and char limits:
+    _ = [Test(What, N, CL) ||
+            N <- lists:seq(1, 50),
+            CL <- lists:seq(N, N*3),
+            What <- [List, Tuple, Map, Record]
+        ],
+    ok.
-- 
2.26.2

openSUSE Build Service is sponsored by