Skip to content

Commit

Permalink
Remove erl_prim_loader fallback on module lookup
Browse files Browse the repository at this point in the history
This address an issue where paths added via -pa/-pz
could never be effectively removed.

Closes #6692.
  • Loading branch information
josevalim authored and garazdawi committed Feb 2, 2024
1 parent 921c771 commit 179842f
Show file tree
Hide file tree
Showing 2 changed files with 16 additions and 8 deletions.
8 changes: 2 additions & 6 deletions lib/kernel/src/code_server.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1219,12 +1219,8 @@ mod_to_bin([{Dir, CacheKey}|Tail], ModFile, Cache) when is_integer(CacheKey) ->
{false, Cache1} ->
mod_to_bin(Tail, ModFile, Cache1)
end;
mod_to_bin([], ModFile, Cache) ->
%% At last, try also erl_prim_loader's own method
case erl_prim_loader:get_file(ModFile) of
error -> {error, Cache};
{ok,Bin,FName} -> {Bin, absname(FName), Cache}
end.
mod_to_bin([], _ModFile, Cache) ->
{error, Cache}.

with_cache(CacheKey, Dir, ModFile, Cache) ->
case Cache of
Expand Down
16 changes: 14 additions & 2 deletions lib/kernel/test/code_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,8 @@
soft_purge/1, is_loaded/1, all_loaded/1, all_available/1,
load_binary/1, dir_req/1, object_code/1, set_path_file/1,
upgrade/0, upgrade/1,
sticky_dir/1, pa_pz_option/1, add_del_path/1,
sticky_dir/1, add_del_path/1,
pa_pz_option/1, remove_pa_pz_option/1,
dir_disappeared/1, ext_mod_dep/1, clash/1,
where_is_file/1,
purge_stacktrace/1, mult_lib_roots/1, bad_erl_libs/1,
Expand Down Expand Up @@ -67,7 +68,8 @@ all() ->
delete, purge, purge_many_exits, soft_purge, is_loaded, all_loaded,
all_available, load_binary, dir_req, object_code, set_path_file,
upgrade, code_path_cache,
sticky_dir, pa_pz_option, add_del_path, dir_disappeared,
pa_pz_option, remove_pa_pz_option,
sticky_dir, add_del_path, dir_disappeared,
ext_mod_dep, clash, where_is_file,
purge_stacktrace, mult_lib_roots,
bad_erl_libs, code_archive, code_archive2, on_load,
Expand Down Expand Up @@ -839,6 +841,16 @@ pa_pz_option(Config) when is_list(Config) ->
[PzDir|_] = lists:reverse(Paths2),
peer:stop(Peer2).

%% Test that we can remove paths added via -pa and -pz.
remove_pa_pz_option(Config) when is_list(Config) ->
DDir = proplists:get_value(data_dir,Config),
PaDir = filename:join(DDir,"clash/foobar-0.1/ebin"),
{ok, Peer, Node} = ?CT_PEER(["-pa", PaDir]),
{_,_,_} = rpc:call(Node, code, get_object_code, [blarg]),
true = rpc:call(Node, code, del_path, [PaDir]),
error = rpc:call(Node, code, get_object_code, [blarg]),
peer:stop(Peer).

%% add_path, del_path should not cause priv_dir(App) to fail.
add_del_path(Config) when is_list(Config) ->
DDir = proplists:get_value(data_dir,Config),
Expand Down

0 comments on commit 179842f

Please sign in to comment.