File dializer-relax-check-plt.patch of Package erlang
diff -Ndurp otp_src_26.0-rc3/lib/dialyzer/src/dialyzer_cplt.erl otp_src_26.0-rc3-dializer-relax-check-plt/lib/dialyzer/src/dialyzer_cplt.erl
--- otp_src_26.0-rc3/lib/dialyzer/src/dialyzer_cplt.erl 2023-04-12 11:49:17.000000000 +0300
+++ otp_src_26.0-rc3-dializer-relax-check-plt/lib/dialyzer/src/dialyzer_cplt.erl 2023-04-30 21:44:14.722780923 +0300
@@ -163,12 +163,7 @@ included_files1(FileName) ->
Error
end.
-check_version(#file_plt{version = ?VSN, implementation_md5 = ImplMd5}) ->
- case compute_new_md5(ImplMd5, [], []) of
- ok -> ok;
- {differ, _, _} -> error;
- {error, _} -> error
- end;
+check_version(#file_plt{version = ?VSN}) -> ok;
check_version(#file_plt{}) -> error.
get_record_from_file(FileName) ->
@@ -305,15 +300,16 @@ check_plt(FileName, RemoveFiles, AddFile
check_plt1(FileName, RemoveFiles, AddFiles) ->
case get_record_from_file(FileName) of
{ok, #file_plt{file_md5_list = Md5, mod_deps = ModDeps} = Rec} ->
+ Md5Res = compute_new_md5(Md5, RemoveFiles, AddFiles),
case check_version(Rec) of
ok ->
- case compute_new_md5(Md5, RemoveFiles, AddFiles) of
+ case Md5Res of
ok -> ok;
{differ, NewMd5, DiffMd5} -> {differ, NewMd5, DiffMd5, ModDeps};
{error, _What} = Err -> Err
end;
error ->
- case compute_new_md5(Md5, RemoveFiles, AddFiles) of
+ case Md5Res of
ok -> {old_version, Md5};
{differ, NewMd5, _DiffMd5} -> {old_version, NewMd5};
{error, _What} = Err -> Err
@@ -362,19 +358,9 @@ compute_md5_from_files(Files) ->
lists:keysort(1, [{F, compute_md5_from_file(F)} || F <- Files]).
compute_md5_from_file(File) ->
- case beam_lib:all_chunks(File) of
- {ok, _, Chunks} ->
- %% We cannot use beam_lib:md5 because it does not consider
- %% the debug_info chunk, where typespecs are likely stored.
- %% So we consider almost all chunks except the useless ones.
- Filtered = [[ID, Chunk] || {ID, Chunk} <- Chunks, ID =/= "CInf", ID =/= "Docs"],
- erlang:md5(lists:sort(Filtered));
- {error, beam_lib, {file_error, _, enoent}} ->
- Msg = io_lib:format("File not found: ~ts\n", [File]),
- plt_error(Msg);
- {error, beam_lib, _} ->
- Msg = io_lib:format("Could not compute MD5 for .beam: ~ts\n", [File]),
- plt_error(Msg)
+ case beam_lib:md5(File) of
+ {ok, {_, MD5}} -> MD5;
+ E -> plt_error(beam_lib:format_error(E))
end.
init_diff_list(RemoveFiles, AddFiles) ->
diff -Ndurp otp_src_26.0-rc3/lib/dialyzer/src/dialyzer_iplt.erl otp_src_26.0-rc3-dializer-relax-check-plt/lib/dialyzer/src/dialyzer_iplt.erl
--- otp_src_26.0-rc3/lib/dialyzer/src/dialyzer_iplt.erl 2023-04-12 11:49:17.000000000 +0300
+++ otp_src_26.0-rc3-dializer-relax-check-plt/lib/dialyzer/src/dialyzer_iplt.erl 2023-04-30 21:45:07.709661034 +0300
@@ -181,12 +181,7 @@ included_modules1(FileName) ->
Error
end.
-check_version(#ifile_plt{version = ?VSN, implementation_md5 = ImplMd5}) ->
- case compute_new_md5(ImplMd5, [], [], implementation_module_paths()) of
- ok -> ok;
- {differ, _, _} -> error;
- {error, _} -> error
- end;
+check_version(#ifile_plt{version = ?VSN}) -> ok;
check_version(#ifile_plt{}) -> error.
get_record_from_file(FileName) ->
@@ -361,9 +356,10 @@ find_files_to_remove_and_add(Md5, PltMod
check_version_and_compute_md5(Rec, RemoveFiles, AddFiles, ModuleToPathLookup) ->
Md5 = Rec#ifile_plt.module_md5_list,
+ Md5Res = compute_new_md5(Md5, RemoveFiles, AddFiles, ModuleToPathLookup),
case check_version(Rec) of
ok ->
- case compute_new_md5(Md5, RemoveFiles, AddFiles, ModuleToPathLookup) of
+ case Md5Res of
ok -> ok;
{differ, NewMd5, DiffMd5} ->
IncrementalData = get_incremental_data(Rec),
@@ -375,7 +371,7 @@ check_version_and_compute_md5(Rec, Remov
{error, _What} = Err -> Err
end;
error ->
- case compute_new_md5(Md5, RemoveFiles, AddFiles, ModuleToPathLookup) of
+ case Md5Res of
ok -> {old_version, Md5};
{differ, NewMd5, _DiffMd5} -> {old_version, NewMd5};
{error, _What} = Err -> Err
@@ -444,44 +440,14 @@ compute_md5_from_files(ModuleToPathLooku
lists:keysort(1, lists:zip(Modules, Hashes)).
compute_md5_from_file(File) ->
- case beam_lib:chunks(File, [debug_info]) of
- {ok, {ModuleName, [{debug_info, {debug_info_v1, Backend, Data}}]}} ->
- %% We cannot use beam_lib:md5 because it includes
- %% non-portable or otherwise irrelvant data that would
- %% cause the PLT to be invalidated needlessly too often
- case Backend:debug_info(erlang_v1, ModuleName, Data, []) of
- {ok, Code} ->
- StabilisedCode = lists:filtermap(fun (Form) -> make_stable(ModuleName, Form) end, Code),
- StabilisedCodeBin = erlang:term_to_binary(StabilisedCode),
- erlang:md5(StabilisedCodeBin);
- {error, Reason} ->
- Msg = io_lib:format("Could not compute MD5 for .beam (debug_info error) - did you forget to set the debug_info compilation option? ~ts ~tw\n", [File, Reason]),
- throw({dialyzer_error, Msg})
- end;
- {ok, {_, [{debug_info, no_debug_info}]}} ->
- Msg = io_lib:format("Could not compute MD5 for .beam (debug_info missing): ~ts\n", [File]),
- throw({dialyzer_error, Msg});
- {error, beam_lib, {file_error, _, enoent}} ->
- Msg = io_lib:format("File not found: ~ts\n", [File]),
- plt_error(Msg);
- {error, beam_lib, _} ->
- Msg = io_lib:format("Could not compute MD5 for .beam: ~ts\n", [File]),
- plt_error(Msg)
+ case beam_lib:md5(File) of
+ {ok, {_, MD5}} -> MD5;
+ E -> plt_error(beam_lib:format_error(E))
end.
%% Absolute paths in -file attributes make beam file hashes brittle, since the
%% same beam built elsewhere will contain a different absolute path, despite
%% being semantically identical.
-%%
-%% Here, we replace the full path with just the basename. This is very similar
-%% to the effect of the +deterministic option, by by doing this rewriting here,
-%% we gain some of those determinism benefits even when the build is not run
-%% with +deterministic.
-make_stable(_, {attribute, Anno, file, {SrcFilePath, Line}}) ->
- {true, {attribute, Anno, file, {filename:basename(SrcFilePath), Line}}};
-
-make_stable(_, Attr) ->
- {true, Attr}.
init_diff_list(RemoveFiles, AddFiles) ->
RemoveSet0 = sets:from_list([beam_file_to_module(F) || F <- RemoveFiles]),