File 4171-dialyzer-Introduce-the-input_list_file-option.patch of Package erlang

From b3cddcc9ffc9b5333d144a9f6d4a78f8db9be3a1 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Fri, 9 Sep 2022 05:59:30 +0200
Subject: [PATCH] dialyzer: Introduce the --input_list_file option

The --input_list_file option makes it possible to give Dialyzer
the list of files to analyse in a file, which is useful if there
are too many files to fit on the command line.
---
 lib/dialyzer/doc/src/dialyzer.xml      |  5 +++
 lib/dialyzer/src/dialyzer_cl_parse.erl | 18 ++++++++
 lib/dialyzer/test/dialyzer_SUITE.erl   | 61 ++++++++++++++++++++++++--
 3 files changed, 80 insertions(+), 4 deletions(-)

diff --git a/lib/dialyzer/doc/src/dialyzer.xml b/lib/dialyzer/doc/src/dialyzer.xml
index 5dd40a595b..7cb0312975 100644
--- a/lib/dialyzer/doc/src/dialyzer.xml
+++ b/lib/dialyzer/doc/src/dialyzer.xml
@@ -176,6 +176,11 @@ dialyzer --apps inets ssl ./ebin ../other_lib/ebin/my_module.beam</code>
         <p>When analyzing from source, pass the <c>include_dir</c>
           to Dialyzer. (**)</p>
       </item>
+      <tag><c>--input_list_file file</c></tag>
+      <item>
+        <p>Analyze the file names that are listed in the specified file
+	(one file name per line).</p>
+      </item>
       <tag><c>--no_check_plt</c></tag>
       <item>
         <p>Skip the PLT check when running Dialyzer. This is useful when
diff --git a/lib/dialyzer/src/dialyzer_cl_parse.erl b/lib/dialyzer/src/dialyzer_cl_parse.erl
index a3ec1b92f1..0bdfe609d9 100644
--- a/lib/dialyzer/src/dialyzer_cl_parse.erl
+++ b/lib/dialyzer/src/dialyzer_cl_parse.erl
@@ -97,6 +97,11 @@ cl(["-I", Dir|T]) ->
 cl(["-I"++Dir|T]) ->
   append_include(Dir),
   cl(T);
+cl(["--input_list_file"]) ->
+  cl_error("No input list file specified");
+cl(["--input_list_file",File|L]) ->
+  read_input_list_file(File),
+  cl(L);
 cl(["-c"++_|T]) ->
   NewTail = command_line(T),
   cl(NewTail);
@@ -240,6 +245,16 @@ command_line(T0) ->
   end,
   T.
 
+read_input_list_file(File) ->
+  case file:read_file(File) of
+    {ok,Bin} ->
+      Files = binary:split(Bin, <<"\n">>, [trim_all,global]),
+      NewFiles = [binary_to_list(string:trim(F)) || F <- Files],
+      append_var(dialyzer_options_files, NewFiles);
+    {error,Reason} ->
+      cl_error(io_lib:format("Reading of ~s failed: ~s", [File,file:format_error(Reason)]))
+  end.
+
 -spec cl_error(deep_string()) -> no_return().
 
 cl_error(Str) ->
@@ -382,6 +397,9 @@ Options:
       Same as the previous but the specified directories are searched
       recursively for subdirectories containing .erl or .beam files in
       them, depending on the type of analysis.
+  --input_list_file file
+      Specify the name of a file that contains the names of the files
+      to be analyzed (one file name per line).
   --apps applications
       Option typically used when building or modifying a plt as in:
         dialyzer --build_plt --apps erts kernel stdlib mnesia ...
diff --git a/lib/dialyzer/test/dialyzer_SUITE.erl b/lib/dialyzer/test/dialyzer_SUITE.erl
index d46181f66f..9f462d5525 100644
--- a/lib/dialyzer/test/dialyzer_SUITE.erl
+++ b/lib/dialyzer/test/dialyzer_SUITE.erl
@@ -22,7 +22,7 @@
 -include_lib("common_test/include/ct.hrl").
 
 %% Default timetrap timeout (set in init_per_testcase).
--define(default_timeout, ?t:minutes(1)).
+-define(default_timeout, ?t:minutes(10)).
 -define(application, dialyzer).
 
 %% Test server specific exports
@@ -31,12 +31,12 @@
 -export([init_per_testcase/2, end_per_testcase/2]).
 
 %% Test cases must be exported.
--export([app_test/1, appup_test/1]).
+-export([app_test/1, appup_test/1, file_list/1]).
 
 suite() -> [{ct_hooks,[ts_install_cth]}].
 
 all() ->
-    [app_test, appup_test].
+    [app_test, appup_test, file_list].
 
 groups() ->
     [].
@@ -55,7 +55,7 @@ end_per_group(_GroupName, Config) ->
 
 
 init_per_testcase(_Case, Config) ->
-    ?line Dog=test_server:timetrap(?default_timeout),
+    Dog=test_server:timetrap(?default_timeout),
     [{watchdog, Dog}|Config].
 end_per_testcase(_Case, Config) ->
     Dog=?config(watchdog, Config),
@@ -76,3 +76,56 @@ app_test(Config) when is_list(Config) ->
 %% Test that the .appup file does not contain any `basic' errors
 appup_test(Config) when is_list(Config) ->
     ok = ?t:appup_test(dialyzer).
+
+file_list(Config) ->
+    PrivDir = proplists:get_value(priv_dir, Config),
+
+    case dialyzer_common:check_plt(PrivDir) of
+        fail -> ct:fail("Plt creation/check failed");
+        ok -> ok
+    end,
+
+    Files = generate_modules(PrivDir, 26),
+    ListFile = filename:join(PrivDir, "list_of_files"),
+    ok = file:write_file(ListFile, [lists:join("\n", Files), "\n"]),
+
+    Expected = expected(Files),
+    ExpectedFile = filename:join(PrivDir, "expected"),
+    ok = file:write_file(ExpectedFile, Expected),
+
+    Plt = dialyzer_common:plt_file(PrivDir),
+    Result = os:cmd("dialyzer --plt " ++ Plt ++ " -q --src --input_list_file " ++ ListFile),
+    ResultFile = filename:join(PrivDir, "result"),
+    ok = file:write_file(ResultFile, Result),
+
+    case file_utils:diff(ResultFile, ExpectedFile) of
+        same ->
+            ok;
+        Diff ->
+            io:format("~p\n", [Diff]),
+            ct:fail(unexpected_result)
+    end.
+
+generate_modules(_Dir, 0) ->
+    [];
+generate_modules(Dir, N) ->
+    Name = "module_" ++ integer_to_list(N),
+    File = filename:join(Dir, Name ++ ".erl"),
+    Code = <<"-module(",(list_to_binary(Name))/binary,").\n",
+             "-export([main/1]).\n",
+             "main(L) ->\n",
+             "  case list_to_atom(L) of\n",
+             "    Atom when is_atom(Atom) -> {ok,Atom};\n",
+             "    _ -> error\n",
+             "  end.\n"
+           >>,
+    ok = file:write_file(File, Code),
+    [File|generate_modules(Dir, N - 1)].
+
+expected(Files0) ->
+    Files = lists:sort(Files0),
+    S = "\n" ++
+        [filename:basename(F) ++
+             ":6: The variable _ can never match since previous clauses completely covered the type \n"
+         "          atom()\n" || F <- Files],
+    iolist_to_binary(S).
-- 
2.35.3

openSUSE Build Service is sponsored by