Skip to content

Commit 1be501f

Browse files
committed
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. That would cause three of the test cases to fail. Instead of failing, don't attempt to verify BIFs residing in preloaded modules when running the tests in a git repo.
1 parent c24e439 commit 1be501f

File tree

1 file changed

+39
-36
lines changed

1 file changed

+39
-36
lines changed

erts/emulator/test/bif_SUITE.erl

Lines changed: 39 additions & 36 deletions
Original file line numberDiff line numberDiff line change
@@ -199,18 +199,17 @@ shadow_comments(_Config) ->
199199
List1 = [MFA || {M,_,_}=MFA <- List0, M =/= erlang],
200200
List = List1 ++ ErlangList,
201201
HasTypes = [MFA || {M,F,A}=MFA <- List,
202-
erl_bif_types:is_known(M, F, A)],
203-
Path = get_code_path(),
204-
BifRel = sofs:relation(HasTypes, [{m,f,a}]),
205-
BifModules = sofs:to_external(sofs:projection(1, BifRel)),
206-
AbstrByModule = [extract_abstract(Mod, Path) || Mod <- BifModules],
202+
erl_bif_types:is_known(M, F, A)],
203+
BifModules = bif_modules(HasTypes),
204+
AbstrByModule = [extract_abstract(Mod) || Mod <- BifModules],
207205
Specs0 = [extract_specs(Mod, Abstr) ||
208206
{Mod,Abstr} <- AbstrByModule],
209207
Specs = lists:append(Specs0),
210208
SpecFuns0 = [F || {F,_} <- Specs],
211209
SpecFuns = sofs:relation(SpecFuns0, [{m,f,a}]),
210+
BifRel = sofs:relation(HasTypes, [{m,f,a}]),
212211
HasTypesAndSpecs = sofs:intersection(BifRel, SpecFuns),
213-
Commented0 = lists:append([extract_comments(Mod, Path) ||
212+
Commented0 = lists:append([extract_comments(Mod) ||
214213
Mod <- BifModules]),
215214
Commented = sofs:relation(Commented0, [{m,f,a}]),
216215
{NoComments0,_,NoBifSpecs0} =
@@ -246,8 +245,8 @@ shadow_comments(_Config) ->
246245
ct:fail(erl_bif_types)
247246
end.
248247

249-
extract_comments(Mod, Path) ->
250-
Beam = which(Mod, Path),
248+
extract_comments(Mod) ->
249+
Beam = which(Mod),
251250
SrcDir = filename:join(filename:dirname(filename:dirname(Beam)), "src"),
252251
Src = filename:join(SrcDir, atom_to_list(Mod) ++ ".erl"),
253252
{ok,Bin} = file:read_file(Src),
@@ -267,13 +266,12 @@ specs(_) ->
267266
List0 = erlang:system_info(snifs),
268267

269268
%% Ignore all operators.
270-
List = [MFA || MFA <- List0, not is_operator(MFA)],
269+
List1 = [MFA || MFA <- List0, not is_operator(MFA)],
271270

272271
%% Extract specs from the abstract code for all BIFs.
273-
Path = get_code_path(),
274-
BifRel = sofs:relation(List, [{m,f,a}]),
275-
BifModules = sofs:to_external(sofs:projection(1, BifRel)),
276-
AbstrByModule = [extract_abstract(Mod, Path) || Mod <- BifModules],
272+
BifModules = bif_modules(List1),
273+
List = [MFA || {M,_,_}=MFA <- List1, lists:member(M, BifModules)],
274+
AbstrByModule = [extract_abstract(Mod) || Mod <- BifModules],
277275
Specs0 = [extract_specs(Mod, Abstr) ||
278276
{Mod,Abstr} <- AbstrByModule],
279277
Specs = lists:append(Specs0),
@@ -312,10 +310,8 @@ make_mfa(M, {M,_,_}=MFA) -> MFA.
312310

313311
improper_bif_stubs(_) ->
314312
Bifs = erlang:system_info(snifs),
315-
Path = get_code_path(),
316-
BifRel = sofs:relation(Bifs, [{m,f,a}]),
317-
BifModules = sofs:to_external(sofs:projection(1, BifRel)),
318-
AbstrByModule = [extract_abstract(Mod, Path) || Mod <- BifModules],
313+
BifModules = bif_modules(Bifs),
314+
AbstrByModule = [extract_abstract(Mod) || Mod <- BifModules],
319315
Funcs0 = [extract_functions(Mod, Abstr) ||
320316
{Mod,Abstr} <- AbstrByModule],
321317
Funcs = lists:append(Funcs0),
@@ -1792,35 +1788,42 @@ busy_wait_go() ->
17921788

17931789
id(I) -> I.
17941790

1795-
%% Get code path, including the path for the erts application.
1796-
get_code_path() ->
1797-
Erts = filename:join([code:root_dir(),"erts","preloaded","ebin"]),
1798-
case filelib:is_dir(Erts) of
1799-
true->
1800-
[Erts|code:get_path()];
1801-
_ ->
1802-
code:get_path()
1791+
bif_modules(MFAs) ->
1792+
BifRel = sofs:relation(MFAs, [{m,f,a}]),
1793+
BifModules = sofs:to_external(sofs:projection(1, BifRel)),
1794+
case is_otp_installed() of
1795+
true ->
1796+
BifModules;
1797+
false ->
1798+
%% Running in an uninstalled system. The preloaded modules
1799+
%% don't contain any abstract code.
1800+
io:put_chars("** Running in an uninstalled system. Not verifying pre-loaded modules\n"
1801+
"** because they don't have debug_info chunks.\n"),
1802+
[M || M <- BifModules, code:which(M) =/= preloaded]
18031803
end.
18041804

1805-
which(Mod, Path) ->
1806-
which_1(atom_to_list(Mod) ++ ".beam", Path).
1805+
is_otp_installed() ->
1806+
LibDir = code:lib_dir(),
1807+
ErtsDir = code:lib_dir(erts),
1808+
lists:prefix(LibDir, ErtsDir).
18071809

1808-
which_1(Base, [D|Ds]) ->
1809-
Path = filename:join(D, Base),
1810-
case filelib:is_regular(Path) of
1811-
true -> Path;
1812-
false -> which_1(Base, Ds)
1813-
end.
18141810
print_mfa({M,F,A}) ->
18151811
io:format("~p:~p/~p", [M,F,A]).
18161812

1817-
extract_abstract(Mod, Path) ->
1818-
Beam = which(Mod, Path),
1813+
which(Mod) ->
1814+
case code:which(Mod) of
1815+
preloaded ->
1816+
filename:join([code:lib_dir(erts), "ebin", atom_to_list(Mod) ++ ".beam"]);
1817+
Beam when is_list(Beam) ->
1818+
Beam
1819+
end.
1820+
1821+
extract_abstract(Mod) ->
1822+
Beam = which(Mod),
18191823
{ok,{Mod,[{abstract_code,{raw_abstract_v1,Abstr}}]}} =
18201824
beam_lib:chunks(Beam, [abstract_code]),
18211825
{Mod,Abstr}.
18221826

1823-
18241827
tok_loop() ->
18251828
tok_loop(hej).
18261829

0 commit comments

Comments
 (0)