File 0570-dialyzer-Handle-files-missing-in-PLT-s-better.patch of Package erlang
From 6f1e0189be893db6bc78db15e039c597a90dbb43 Mon Sep 17 00:00:00 2001
From: Hans Bolinder <hasse@erlang.org>
Date: Tue, 29 Jun 2021 10:46:08 +0200
Subject: [PATCH] dialyzer: Handle files missing in PLT:s better
Dialyzer should not crash if a file included in a PLT no longer
exists.
See also https://github.com/erlang/otp/issues/4501.
---
.../src/dialyzer_analysis_callgraph.erl | 2 +-
lib/dialyzer/src/dialyzer_plt.erl | 22 ++++---
lib/dialyzer/test/plt_SUITE.erl | 62 ++++++++++++++++++-
3 files changed, 76 insertions(+), 10 deletions(-)
diff --git a/lib/dialyzer/src/dialyzer_plt.erl b/lib/dialyzer/src/dialyzer_plt.erl
index ba7404048e..8fd38a8922 100644
--- a/lib/dialyzer/src/dialyzer_plt.erl
+++ b/lib/dialyzer/src/dialyzer_plt.erl
@@ -410,14 +410,14 @@ find_duplicates(List) ->
-spec to_file(file:filename(), plt(), mod_deps(), {[file_md5()], mod_deps()}) -> 'ok'.
-%% Write the PLT to file, and deletes the PLT.
+%% Write the PLT to file, and delete the PLT.
to_file(FileName, Plt, ModDeps, MD5_OldModDeps) ->
Fun = fun() -> to_file1(FileName, Plt, ModDeps, MD5_OldModDeps) end,
Return = subproc(Fun),
delete(Plt),
case Return of
ok -> ok;
- Thrown -> throw(Thrown)
+ {error, Msg} -> plt_error(Msg)
end.
to_file1(FileName,
@@ -455,7 +455,7 @@ to_file1(FileName,
{error, Reason} ->
Msg = io_lib:format("Could not write PLT file ~ts: ~w\n",
[FileName, Reason]),
- {dialyzer_error, Msg}
+ {error, Msg}
end.
-type md5_diff() :: [{'differ', atom()} | {'removed', atom()}].
@@ -540,10 +540,10 @@ compute_md5_from_file(File) ->
erlang:md5(lists:sort(Filtered));
{error, beam_lib, {file_error, _, enoent}} ->
Msg = io_lib:format("File not found: ~ts\n", [File]),
- throw({dialyzer_error, Msg});
+ plt_error(Msg);
{error, beam_lib, _} ->
Msg = io_lib:format("Could not compute MD5 for .beam: ~ts\n", [File]),
- throw({dialyzer_error, Msg})
+ plt_error(Msg)
end.
init_diff_list(RemoveFiles, AddFiles) ->
@@ -600,10 +600,18 @@ tab2list(Tab) ->
dialyzer_utils:ets_tab2list(Tab).
subproc(Fun) ->
- F = fun() -> exit(Fun()) end,
+ F = fun() ->
+ exit(try Fun()
+ catch throw:T ->
+ {thrown, T}
+ end)
+ end,
{Pid, Ref} = erlang:spawn_monitor(F),
receive {'DOWN', Ref, process, Pid, Return} ->
- Return
+ case Return of
+ {thrown, T} -> throw(T);
+ _ -> Return
+ end
end.
%%---------------------------------------------------------------------------
diff --git a/lib/dialyzer/test/plt_SUITE.erl b/lib/dialyzer/test/plt_SUITE.erl
index 56ce32486b..800f1fd307 100644
--- a/lib/dialyzer/test/plt_SUITE.erl
+++ b/lib/dialyzer/test/plt_SUITE.erl
@@ -10,7 +10,7 @@
local_fun_same_as_callback/1,
remove_plt/1, run_plt_check/1, run_succ_typings/1,
bad_dialyzer_attr/1, merge_plts/1, bad_record_type/1,
- letrec_rvals/1]).
+ letrec_rvals/1, missing_plt_file/1]).
suite() ->
[{timetrap, ?plt_timeout}].
@@ -18,7 +18,7 @@ suite() ->
all() -> [build_plt, beam_tests, update_plt, run_plt_check,
remove_plt, run_succ_typings, local_fun_same_as_callback,
bad_dialyzer_attr, merge_plts, bad_record_type,
- letrec_rvals].
+ letrec_rvals, missing_plt_file].
build_plt(Config) ->
OutDir = ?config(priv_dir, Config),
@@ -431,6 +431,64 @@ check_done(_) ->
[] = run_dialyzer(plt_build, [BeamFile], [{output_plt, Plt}]),
ok.
+%% GH-4501
+missing_plt_file(Config) ->
+ PrivDir = ?config(priv_dir, Config),
+ PltFile = filename:join(PrivDir, "missing_plt_file.plt"),
+ Prog2 = <<"-module(missing_plt_file2).
+ t() -> foo.">>,
+ {ok, BeamFile2} = compile(Config, Prog2, missing_plt_file2, []),
+
+ true = missing_plt_file_1(Config, PltFile, BeamFile2),
+ true = missing_plt_file_2(Config, PltFile, BeamFile2),
+ true = missing_plt_file_3(),
+ ok.
+
+missing_plt_file_1(Config, PltFile, BeamFile2) ->
+ BeamFile = create(Config, PltFile),
+ ok = file:delete(BeamFile),
+ try succ(PltFile, BeamFile2), false
+ catch throw:{dialyzer_error, _} -> true
+ end.
+
+missing_plt_file_2(Config, PltFile, BeamFile2) ->
+ BeamFile = create(Config, PltFile),
+ ok = file:delete(BeamFile),
+
+ Cmd = "dialyzer -q --plt " ++ PltFile ++ " " ++ BeamFile2,
+ io:format("Cmd `~p'\n", [Cmd]),
+ "\ndialyzer: File not found: " ++ _ = os:cmd(Cmd),
+
+ try check(PltFile, BeamFile2), false
+ catch throw:{dialyzer_error, _} -> true
+ end.
+
+missing_plt_file_3() ->
+ try dialyzer_plt:from_file("no_such_file"), false
+ catch throw:{dialyzer_error, _} -> true
+ end.
+
+create(Config, PltFile) ->
+ Prog = <<"-module(missing_plt_file).
+ t() -> foo.">>,
+ {ok, BeamFile} = compile(Config, Prog, missing_plt_file, []),
+ Files = [BeamFile],
+ _ = file:delete(PltFile),
+ [] = dialyzer:run([{files,Files},
+ {output_plt, PltFile},
+ {analysis_type, plt_build}]),
+ BeamFile.
+
+succ(PltFile, BeamFile2) ->
+ Files = [BeamFile2],
+ dialyzer:run([{files, Files},
+ {plts,[PltFile]},
+ {analysis_type, succ_typings}]).
+
+check(PltFile, BeamFile2) ->
+ dialyzer:run([{plts,[PltFile]},
+ {analysis_type, plt_check}]).
+
erlang_beam() ->
case code:where_is_file("erlang.beam") of
non_existing ->
--
2.26.2