Skip to content

Commit

Permalink
Clean up, some tests
Browse files Browse the repository at this point in the history
  • Loading branch information
ferd committed Oct 8, 2018
1 parent 10e6099 commit 62eb63d
Show file tree
Hide file tree
Showing 2 changed files with 75 additions and 9 deletions.
47 changes: 41 additions & 6 deletions src/rebar_paths.erl
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,11 @@
-type targets() :: [target(), ...].
-export_type([target/0, targets/0]).
-export([set_paths/2, unset_paths/2]).
-export([clashing_apps/2]).

-ifdef(TEST).
-export([misloaded_modules/3]).
-endif.

-spec set_paths(targets(), rebar_state:t()) -> ok.
set_paths(UserTargets, State) ->
Expand All @@ -13,8 +18,8 @@ set_paths(UserTargets, State) ->
Paths = lists:append([P || {_, P} <- GroupPaths]),
[code:del_path(P) || P <- Paths],
code:add_pathsa(lists:reverse(Paths)),
% set path breaks with escripts
%true = code:set_path(lists:append([P || {_, P} <- GroupPaths])),
% set path breaks with escripts; we gotta do it by hand
% true = code:set_path(lists:append([P || {_, P} <- GroupPaths])),
AppGroups = app_groups(Targets, State),
purge_and_load(AppGroups, code:all_loaded(), sets:new()),
ok.
Expand All @@ -28,6 +33,16 @@ unset_paths(UserTargets, State) ->
purge(Paths, code:all_loaded()),
ok.

clashing_apps(Targets, State) ->
AppGroups = app_groups(Targets, State),
AppNames = [{G, sets:from_list(
[rebar_app_info:name(App) || App <- Apps]
)} || {G, Apps} <- AppGroups],
clashing_app_names(sets:new(), AppNames, []).

%%%%%%%%%%%%%%%
%%% PRIVATE %%%
%%%%%%%%%%%%%%%

%% The paths are to be set in the reverse order; i.e. the default
%% path is always last when possible (minimize cases where a build
Expand Down Expand Up @@ -77,9 +92,9 @@ purge_and_load([{_Group, Apps}|Rest], ModPaths, Seen) ->
App <- Apps,
rebar_app_info:name(App) =:= AppName],
%% 2)
%% TODO: add extra dirs (and test), and possibly the stdlib
%% (no need for extra_src_dirs since those get put into ebin;
%% also no need for OTP libs; we want to allow overtaking them)
GoodAppPaths = [rebar_app_info:ebin_dir(App) || App <- GoodApps],
%% ++ [code:lib_dir()],
%% 3)
[begin
AtomApp = binary_to_atom(AppName, utf8),
Expand Down Expand Up @@ -118,12 +133,12 @@ purge_and_load([{_Group, Apps}|Rest], ModPaths, Seen) ->
purge_and_load(Rest, ModPaths,
sets:union(Seen, sets:from_list(AppNames))).


purge(Paths, ModPaths) ->
SortedPaths = lists:sort(Paths),
lists:map(fun purge_mod/1, lists:usort(
[Mod || {Mod, Path} <- ModPaths,
is_list(Path), % not 'preloaded' or mocked
any_prefix(Path, Paths)]
any_prefix(Path, SortedPaths)]
)).

misloaded_modules(Mods, GoodAppPaths, ModPaths) ->
Expand Down Expand Up @@ -152,6 +167,26 @@ purge_mod(Mod) ->
code:delete(Mod)
end.


%% This is a tricky O(n²) check since we want to
%% know whether an app clashes with any of the top priority groups.
%%
%% For example, let's say we have `[deps, plugins]', then we want
%% to find the plugins that clash with deps:
%%
%% `[{deps, [ClashingPlugins]}, {plugins, []}]'
%%
%% In case we'd ever have alternative or additional types, we can
%% find all clashes from other 'groups'.
clashing_app_names(_, [], Acc) ->
lists:reverse(Acc);
clashing_app_names(PrevNames, [{G,AppNames} | Rest], Acc) ->
CurrentNames = sets:subtract(AppNames, PrevNames),
NextNames = sets:subtract(sets:union([A || {_, A} <- Rest]), PrevNames),
Clashes = sets:intersection(CurrentNames, NextNames),
NewAcc = [{G, sets:to_list(Clashes)} | Acc],
clashing_app_names(sets:union(PrevNames, CurrentNames), Rest, NewAcc).

path_groups(Targets, State) ->
[{Target, get_paths(Target, State)} || Target <- Targets].

Expand Down
37 changes: 34 additions & 3 deletions test/rebar_paths_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -4,11 +4,16 @@
-compile(export_all).

all() ->
[%clashing_apps,
[clashing_apps,
check_modules,
set_paths
set_paths,
misloaded_mods
].

%%%%%%%%%%%%%%%%%%
%%% TEST SETUP %%%
%%%%%%%%%%%%%%%%%%

init_per_testcase(Case, Config) ->
BasePaths = code:get_path(),
%% This test checks that the right module sets get loaded; however, we must
Expand Down Expand Up @@ -90,13 +95,17 @@ compile_fake_appmod(App) ->
{ok, _, Bin} = compile:forms(Mod),
ok = file:write_file(filename:join([OutDir, <<Name/binary, ".beam">>]), Bin).

%%%%%%%%%%%%%
%%% TESTS %%%
%%%%%%%%%%%%%

clashing_apps(Config) ->
Clashes = rebar_paths:clashing_apps([deps, plugins],
?config(state, Config)),
ct:pal("Clashes: ~p", [Clashes]),

?assertEqual([<<"relx">>, <<"rp_a">>], lists:sort(proplists:get_value(deps, Clashes))),
?assertEqual(undefined, proplists:get_value(plugins, Clashes)),
?assertEqual([], proplists:get_value(plugins, Clashes)),
ok.

set_paths(Config) ->
Expand Down Expand Up @@ -201,6 +210,28 @@ check_modules(Config) ->
?assertEqual(3, length(relx:module_info(exports))), % can't replace bundled
ok.

misloaded_mods(_Config) ->
Res = rebar_paths:misloaded_modules(
[a,b,c,d,e,f],
["/1/2/3/4",
"/1/2/4",
"/2/1/1",
"/3/4/5"],
[{a, "/0/1/2/file.beam"},
{aa, "/1/2/3/4/file.beam"},
{b, "/1/2/3/4/file.beam"},
{c, "/2/1/file.beam"},
{f, preloaded},
{d, "/3/5/7/file.beam"},
{e, "/3/4/5/file.beam"}]
),
?assertEqual([a,c,d], Res),
ok.

%%%%%%%%%%%%%%%
%%% HELPERS %%%
%%%%%%%%%%%%%%%

find_first_instance(Frag, []) ->
{not_found, Frag};
find_first_instance(Frag, [Path|Rest]) ->
Expand Down

0 comments on commit 62eb63d

Please sign in to comment.