File 0784-bif_SUITE-Fix-failing-test-cases-when-run-in-a-git-r.patch of Package erlang
From a22c37876bd70e3166025705129ece245ad85d9c Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Mon, 11 Nov 2024 09:47:31 +0100
Subject: [PATCH] bif_SUITE: Fix failing test cases when run in a git repo
The preloaded BEAM files in `$ERL_TOP/erts/preloaded/ebin` in the git
repo longer contains debug information, causing three test cases to
fail. However, BEAM files with debug information can be found in
`$ERL_TOP/erts/ebin`.
Make sure that the test cases that need debug information pick up the
correct BEAM files.
---
erts/emulator/test/bif_SUITE.erl | 75 +++++++++++++++-----------------
1 file changed, 36 insertions(+), 39 deletions(-)
diff --git a/erts/emulator/test/bif_SUITE.erl b/erts/emulator/test/bif_SUITE.erl
index 196bb70cdc..ee951d9558 100644
--- a/erts/emulator/test/bif_SUITE.erl
+++ b/erts/emulator/test/bif_SUITE.erl
@@ -199,18 +199,17 @@ shadow_comments(_Config) ->
List1 = [MFA || {M,_,_}=MFA <- List0, M =/= erlang],
List = List1 ++ ErlangList,
HasTypes = [MFA || {M,F,A}=MFA <- List,
- erl_bif_types:is_known(M, F, A)],
- Path = get_code_path(),
- BifRel = sofs:relation(HasTypes, [{m,f,a}]),
- BifModules = sofs:to_external(sofs:projection(1, BifRel)),
- AbstrByModule = [extract_abstract(Mod, Path) || Mod <- BifModules],
+ erl_bif_types:is_known(M, F, A)],
+ BifModules = bif_modules(HasTypes),
+ AbstrByModule = [extract_abstract(Mod) || Mod <- BifModules],
Specs0 = [extract_specs(Mod, Abstr) ||
{Mod,Abstr} <- AbstrByModule],
Specs = lists:append(Specs0),
SpecFuns0 = [F || {F,_} <- Specs],
SpecFuns = sofs:relation(SpecFuns0, [{m,f,a}]),
+ BifRel = sofs:relation(HasTypes, [{m,f,a}]),
HasTypesAndSpecs = sofs:intersection(BifRel, SpecFuns),
- Commented0 = lists:append([extract_comments(Mod, Path) ||
+ Commented0 = lists:append([extract_comments(Mod) ||
Mod <- BifModules]),
Commented = sofs:relation(Commented0, [{m,f,a}]),
{NoComments0,_,NoBifSpecs0} =
@@ -246,9 +245,18 @@ shadow_comments(_Config) ->
ct:fail(erl_bif_types)
end.
-extract_comments(Mod, Path) ->
- Beam = which(Mod, Path),
- SrcDir = filename:join(filename:dirname(filename:dirname(Beam)), "src"),
+extract_comments(Mod) ->
+ Beam = which(Mod),
+ AppDir = filename:dirname(filename:dirname(Beam)),
+ SrcDir = case code:root_dir() =:= filename:dirname(AppDir) of
+ true ->
+ %% Running in an uninstalled system.
+ filename:join(AppDir, "preloaded/src");
+ false ->
+ %% Running in an installed system.
+ filename:join(AppDir, "src")
+ end,
+ io:format("~p\n", [SrcDir]),
Src = filename:join(SrcDir, atom_to_list(Mod) ++ ".erl"),
{ok,Bin} = file:read_file(Src),
Lines0 = binary:split(Bin, <<"\n">>, [global]),
@@ -267,13 +275,12 @@ specs(_) ->
List0 = erlang:system_info(snifs),
%% Ignore all operators.
- List = [MFA || MFA <- List0, not is_operator(MFA)],
+ List1 = [MFA || MFA <- List0, not is_operator(MFA)],
%% Extract specs from the abstract code for all BIFs.
- Path = get_code_path(),
- BifRel = sofs:relation(List, [{m,f,a}]),
- BifModules = sofs:to_external(sofs:projection(1, BifRel)),
- AbstrByModule = [extract_abstract(Mod, Path) || Mod <- BifModules],
+ BifModules = bif_modules(List1),
+ List = [MFA || {M,_,_}=MFA <- List1, lists:member(M, BifModules)],
+ AbstrByModule = [extract_abstract(Mod) || Mod <- BifModules],
Specs0 = [extract_specs(Mod, Abstr) ||
{Mod,Abstr} <- AbstrByModule],
Specs = lists:append(Specs0),
@@ -312,10 +319,8 @@ make_mfa(M, {M,_,_}=MFA) -> MFA.
improper_bif_stubs(_) ->
Bifs = erlang:system_info(snifs),
- Path = get_code_path(),
- BifRel = sofs:relation(Bifs, [{m,f,a}]),
- BifModules = sofs:to_external(sofs:projection(1, BifRel)),
- AbstrByModule = [extract_abstract(Mod, Path) || Mod <- BifModules],
+ BifModules = bif_modules(Bifs),
+ AbstrByModule = [extract_abstract(Mod) || Mod <- BifModules],
Funcs0 = [extract_functions(Mod, Abstr) ||
{Mod,Abstr} <- AbstrByModule],
Funcs = lists:append(Funcs0),
@@ -1792,35 +1797,27 @@ busy_wait_go() ->
id(I) -> I.
-%% Get code path, including the path for the erts application.
-get_code_path() ->
- Erts = filename:join([code:root_dir(),"erts","preloaded","ebin"]),
- case filelib:is_dir(Erts) of
- true->
- [Erts|code:get_path()];
- _ ->
- code:get_path()
- end.
-
-which(Mod, Path) ->
- which_1(atom_to_list(Mod) ++ ".beam", Path).
+bif_modules(MFAs) ->
+ BifRel = sofs:relation(MFAs, [{m,f,a}]),
+ sofs:to_external(sofs:projection(1, BifRel)).
-which_1(Base, [D|Ds]) ->
- Path = filename:join(D, Base),
- case filelib:is_regular(Path) of
- true -> Path;
- false -> which_1(Base, Ds)
- end.
print_mfa({M,F,A}) ->
io:format("~p:~p/~p", [M,F,A]).
-extract_abstract(Mod, Path) ->
- Beam = which(Mod, Path),
+which(Mod) ->
+ case code:which(Mod) of
+ preloaded ->
+ filename:join([code:lib_dir(erts), "ebin", atom_to_list(Mod) ++ ".beam"]);
+ Beam when is_list(Beam) ->
+ Beam
+ end.
+
+extract_abstract(Mod) ->
+ Beam = which(Mod),
{ok,{Mod,[{abstract_code,{raw_abstract_v1,Abstr}}]}} =
beam_lib:chunks(Beam, [abstract_code]),
{Mod,Abstr}.
-
tok_loop() ->
tok_loop(hej).
--
2.43.0