No build reason found for SDK:ppc64le

File 0540-Fix-crash-in-c-ls-1.patch of Package erlang

From 8541bdef08b72a6d117cf2179c50f9526674ebda Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Mon, 31 May 2021 05:51:43 +0200
Subject: [PATCH] Fix crash in c:ls/1

A call to `c:ls/1` with a filename given as an atom would crash.
Example:

    1> c:ls('/bin/sh').
    ** exception error: bad argument
         in function  length/1
            called as length('/bin/sh')
            *** argument 1: not a list
         in call from c:lengths/2 (c.erl, line 1083)
         in call from c:ls_print/1 (c.erl, line 1071)

While at it, also handle an iolist properly.

Closes #4916
---
 lib/stdlib/src/c.erl        | 20 ++++++++++++++------
 lib/stdlib/test/c_SUITE.erl |  5 ++++-
 2 files changed, 18 insertions(+), 7 deletions(-)

diff --git a/lib/stdlib/src/c.erl b/lib/stdlib/src/c.erl
index 80127bc31b..aa2b87ca05 100644
--- a/lib/stdlib/src/c.erl
+++ b/lib/stdlib/src/c.erl
@@ -38,7 +38,7 @@
 -export([appcall/4]).
 
 -import(lists, [reverse/1,flatten/1,sublist/3,sort/1,keysort/2,
-		max/1,min/1,foreach/2,foldl/3,flatmap/2]).
+		foreach/2,foldl/3,flatmap/2]).
 -import(io, [format/1, format/2]).
 
 %%-----------------------------------------------------------------------
@@ -1056,11 +1056,15 @@ ls() ->
 -spec ls(Dir) -> 'ok' when
       Dir :: file:name().
 
-ls(Dir) ->
-    case file:list_dir(Dir) of
+ls(Dir0) ->
+    case file:list_dir(Dir0) of
 	{ok, Entries} ->
 	    ls_print(sort(Entries));
 	{error, enotdir} ->
+            Dir = if
+                      is_list(Dir0) -> lists:flatten(Dir0);
+                      true -> Dir0
+                  end,
 	    ls_print([Dir]);
 	{error, Error} ->
 	    format("~ts\n", [file:format_error(Error)])
@@ -1068,7 +1072,7 @@ ls(Dir) ->
 
 ls_print([]) -> ok;
 ls_print(L) ->
-    Width = min([max(lengths(L, [])), 40]) + 5,
+    Width = erlang:min(max_length(L, 0), 40) + 5,
     ls_print(L, Width, 0).
 
 ls_print(X, Width, Len) when Width + Len >= 80 ->
@@ -1080,8 +1084,12 @@ ls_print([H|T], Width, Len) ->
 ls_print([], _, _) ->
     io:nl().
 
-lengths([H|T], L) -> lengths(T, [length(H)|L]);
-lengths([], L)    -> L.
+max_length([H|T], L) when is_atom(H) ->
+    max_length([atom_to_list(H)|T], L);
+max_length([H|T], L) ->
+    max_length(T, erlang:max(length(H), L));
+max_length([], L) ->
+    L.
 
 w(X) ->
     io_lib:write(X).
diff --git a/lib/stdlib/test/c_SUITE.erl b/lib/stdlib/test/c_SUITE.erl
index bd84cdd228..c63fe492be 100644
--- a/lib/stdlib/test/c_SUITE.erl
+++ b/lib/stdlib/test/c_SUITE.erl
@@ -178,7 +178,10 @@ ls(Config) when is_list(Config) ->
     ok = c:ls(Directory),
     File = filename:join(Directory, "m.erl"),
     ok = c:ls(File),
-    ok = c:ls("no_such_file").
+    ok = c:ls([[[[File]]]]),
+    ok = c:ls("no_such_file"),
+    ok = c:ls(list_to_atom(code:which(c))),
+    ok.
 
 %% Check that c:memory/[0,1] returns consistent results.
 memory(Config) when is_list(Config) ->
-- 
2.26.2

openSUSE Build Service is sponsored by