Skip to content

Commit

Permalink
Merge pull request #1907 from ferd/refactor-env-paths
Browse files Browse the repository at this point in the history
Refactor env path handling and fix some bugs related to it
  • Loading branch information
ferd authored Oct 15, 2018
2 parents 86519cf + fb6de6e commit 7bfc811
Show file tree
Hide file tree
Showing 16 changed files with 523 additions and 55 deletions.
15 changes: 14 additions & 1 deletion src/rebar3.erl
Original file line number Diff line number Diff line change
Expand Up @@ -175,7 +175,20 @@ run_aux(State, RawArgs) ->

State10 = rebar_state:code_paths(State9, default, code:get_path()),

rebar_core:init_command(rebar_state:command_args(State10, Args), Task).
case rebar_core:init_command(rebar_state:command_args(State10, Args), Task) of
{ok, State11} ->
case rebar_state:get(State11, caller, command_line) of
api ->
rebar_paths:unset_paths([deps, plugins], State11),
{ok, State11};
_ ->
{ok, State11}
end;
Other ->
Other
end.



%% @doc set up base configuration having to do with verbosity, where
%% to find config files, and so on, and return an internal rebar3 state term.
Expand Down
17 changes: 17 additions & 0 deletions src/rebar_api.erl
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,8 @@
expand_env_variable/3,
get_arch/0,
wordsize/0,
set_paths/2,
unset_paths/2,
add_deps_to_path/1,
restore_code_path/1,
processing_base_dir/1,
Expand Down Expand Up @@ -67,6 +69,21 @@ get_arch() ->
wordsize() ->
rebar_utils:wordsize().

%% @doc Set code paths. Takes arguments of the form
%% `[plugins, deps]' or `[deps, plugins]' and ensures the
%% project's app and dependencies are set in the right order
%% for the next bit of execution
-spec set_paths(rebar_paths:targets(), rebar_state:t()) -> ok.
set_paths(List, State) ->
rebar_paths:set_paths(List, State).

%% @doc Unsets code paths. Takes arguments of the form
%% `[plugins, deps]' or `[deps, plugins]' and ensures the
%% paths are no longer active.
-spec unset_paths(rebar_paths:targets(), rebar_state:t()) -> ok.
unset_paths(List, State) ->
rebar_paths:unset_paths(List, State).

%% @doc Add deps to the code path
-spec add_deps_to_path(rebar_state:t()) -> ok.
add_deps_to_path(State) ->
Expand Down
7 changes: 3 additions & 4 deletions src/rebar_compiler.erl
Original file line number Diff line number Diff line change
Expand Up @@ -34,11 +34,10 @@
-define(RE_PREFIX, "^(?!\\._)").

compile_all(Compilers, AppInfo) ->
OutDir = rebar_utils:to_list(rebar_app_info:out_dir(AppInfo)),

EbinDir = rebar_utils:to_list(rebar_app_info:ebin_dir(AppInfo)),
%% Make sure that outdir is on the path
ok = rebar_file_utils:ensure_dir(OutDir),
true = code:add_patha(filename:absname(OutDir)),
ok = rebar_file_utils:ensure_dir(EbinDir),
true = code:add_patha(filename:absname(EbinDir)),

%% necessary for erlang:function_exported/3 to work as expected
%% called here for clarity as it's required by both opts_changed/2
Expand Down
5 changes: 2 additions & 3 deletions src/rebar_hooks.erl
Original file line number Diff line number Diff line change
Expand Up @@ -42,16 +42,15 @@ run_provider_hooks_(Dir, Type, Command, Providers, TypeHooks, State) ->
[] ->
State;
HookProviders ->
PluginDepsPaths = lists:usort(rebar_state:code_paths(State, all_plugin_deps)),
code:add_pathsa(PluginDepsPaths),
rebar_paths:set_paths([plugins], State),
Providers1 = rebar_state:providers(State),
State1 = rebar_state:providers(rebar_state:dir(State, Dir), Providers++Providers1),
case rebar_core:do(HookProviders, State1) of
{error, ProviderName} ->
?DEBUG(format_error({bad_provider, Type, Command, ProviderName}), []),
throw(?PRV_ERROR({bad_provider, Type, Command, ProviderName}));
{ok, State2} ->
rebar_utils:remove_from_code_path(PluginDepsPaths),
rebar_paths:set_paths([deps], State2),
State2
end
end.
Expand Down
2 changes: 1 addition & 1 deletion src/rebar_packages.erl
Original file line number Diff line number Diff line change
Expand Up @@ -84,7 +84,7 @@ get_package(Dep, Vsn, Hash, Repos, Table, State) ->
not_found
end.

new_package_table() ->
new_package_table() ->
?PACKAGE_TABLE = ets:new(?PACKAGE_TABLE, [named_table, public, ordered_set, {keypos, 2}]),
ets:insert(?PACKAGE_TABLE, {?PACKAGE_INDEX_VERSION, package_index_version}).

Expand Down
208 changes: 208 additions & 0 deletions src/rebar_paths.erl
Original file line number Diff line number Diff line change
@@ -0,0 +1,208 @@
-module(rebar_paths).
-include("rebar.hrl").

-type target() :: deps | plugins.
-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/2]).
-endif.

-spec set_paths(targets(), rebar_state:t()) -> ok.
set_paths(UserTargets, State) ->
Targets = normalize_targets(UserTargets),
GroupPaths = path_groups(Targets, State),
Paths = lists:append(lists:reverse([P || {_, P} <- GroupPaths])),
code:add_pathsa(Paths),
AppGroups = app_groups(Targets, State),
purge_and_load(AppGroups, sets:new()),
ok.

-spec unset_paths(targets(), rebar_state:t()) -> ok.
unset_paths(UserTargets, State) ->
Targets = normalize_targets(UserTargets),
GroupPaths = path_groups(Targets, State),
Paths = lists:append([P || {_, P} <- GroupPaths]),
[code:del_path(P) || P <- Paths],
purge(Paths, code:all_loaded()),
ok.

-spec clashing_apps(targets(), rebar_state:t()) -> [{target(), [binary()]}].
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
%% tool version clashes with an app's), and put the highest priorities
%% first.
-spec normalize_targets(targets()) -> targets().
normalize_targets(List) ->
%% Plan for the eventuality of getting values piped in
%% from future versions of rebar3, possibly from plugins and so on,
%% which means we'd risk failing kind of violently. We only support
%% deps and plugins
TmpList = lists:foldl(
fun(deps, [deps | _] = Acc) -> Acc;
(plugins, [plugins | _] = Acc) -> Acc;
(deps, Acc) -> [deps | Acc -- [deps]];
(plugins, Acc) -> [plugins | Acc -- [plugins]];
(_, Acc) -> Acc
end,
[],
List
),
lists:reverse(TmpList).

purge_and_load([], _) ->
ok;
purge_and_load([{_Group, Apps}|Rest], Seen) ->
%% We have: a list of all applications in the current priority group,
%% a list of all loaded modules with their active path, and a list of
%% seen applications.
%%
%% We do the following:
%% 1. identify the apps that have not been solved yet
%% 2. find the paths for all apps in the current group
%% 3. unload and reload apps that may have changed paths in order
%% to get updated module lists and specs
%% (we ignore started apps and apps that have not run for this)
%% This part turns out to be the bottleneck of this module, so
%% to speed it up, using clash detection proves useful:
%% only reload apps that clashed since others are unlikely to
%% conflict in significant ways
%% 4. create a list of modules to check from that app list—only loaded
%% modules make sense to check.
%% 5. check the modules to match their currently loaded paths with
%% the path set from the apps in the current group; modules
%% that differ must be purged; others can stay

%% 1)
AppNames = [AppName || App <- Apps,
AppName <- [rebar_app_info:name(App)],
not sets:is_element(AppName, Seen)],
GoodApps = [App || AppName <- AppNames,
App <- Apps,
rebar_app_info:name(App) =:= AppName],
%% 2)
%% (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],
%% 3)
[begin
AtomApp = binary_to_atom(AppName, utf8),
%% blind load/unload won't interrupt an already-running app,
%% preventing odd errors, maybe!
case application:unload(AtomApp) of
ok -> application:load(AtomApp);
_ -> ok
end
end || AppName <- AppNames,
%% Shouldn't unload ourselves; rebar runs without ever
%% being started and unloading breaks logging!
AppName =/= <<"rebar">>],

%% 4)
CandidateMods = lists:append(
%% Start by asking the currently loaded app (if loaded)
%% since it would be the primary source of conflicting modules
[case application:get_key(AppName, modules) of
{ok, Mods} ->
Mods;
undefined ->
%% if not found, parse the app file on disk, in case
%% the app's modules are used without it being loaded
case rebar_app_info:app_details(App) of
[] -> [];
Details -> proplists:get_value(modules, Details, [])
end
end || App <- GoodApps,
AppName <- [binary_to_atom(rebar_app_info:name(App), utf8)]]
),
ModPaths = [{Mod,Path} || Mod <- CandidateMods,
erlang:function_exported(Mod, module_info, 0),
{file, Path} <- [code:is_loaded(Mod)]],

%% 5)
Mods = misloaded_modules(GoodAppPaths, ModPaths),
[purge_mod(Mod) || Mod <- Mods],

purge_and_load(Rest, sets:union(Seen, sets:from_list(AppNames))).

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

misloaded_modules(GoodAppPaths, ModPaths) ->
%% Identify paths that are invalid; i.e. app paths that cover an
%% app in the desired group, but are not in the desired group.
lists:usort(
[Mod || {Mod, Path} <- ModPaths,
is_list(Path), % not 'preloaded' or mocked
not any_prefix(Path, GoodAppPaths)]
).

any_prefix(Path, Paths) ->
lists:any(fun(P) -> lists:prefix(P, Path) end, Paths).

%% assume paths currently set are good; only unload a module so next call
%% uses the correctly set paths
purge_mod(Mod) ->
code:soft_purge(Mod) andalso code:delete(Mod).


%% 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].

app_groups(Targets, State) ->
[{Target, get_apps(Target, State)} || Target <- Targets].

get_paths(deps, State) ->
rebar_state:code_paths(State, all_deps);
get_paths(plugins, State) ->
rebar_state:code_paths(State, all_plugin_deps).

get_apps(deps, State) ->
%% The code paths for deps also include the top level apps
%% and the extras, which we don't have here; we have to
%% add the apps by hand
case rebar_state:project_apps(State) of
undefined -> [];
List -> List
end ++
rebar_state:all_deps(State);
get_apps(plugins, State) ->
rebar_state:all_plugin_deps(State).
4 changes: 1 addition & 3 deletions src/rebar_plugins.erl
Original file line number Diff line number Diff line change
Expand Up @@ -122,12 +122,10 @@ handle_plugin(Profile, Plugin, State, Upgrade) ->
%% Add newly built deps and plugin to code path
State3 = rebar_state:update_all_plugin_deps(State2, Apps),
NewCodePaths = [rebar_app_info:ebin_dir(A) || A <- ToBuild],
AllPluginEbins = filelib:wildcard(filename:join([rebar_dir:plugins_dir(State), "*", "ebin"])),
CodePaths = PreBuiltPaths++(AllPluginEbins--ToBuild),
code:add_pathsa(NewCodePaths++CodePaths),

%% Store plugin code paths so we can remove them when compiling project apps
State4 = rebar_state:update_code_paths(State3, all_plugin_deps, PreBuiltPaths++NewCodePaths),
rebar_paths:set_paths([plugins], State4),

{plugin_providers(Plugin), State4}
catch
Expand Down
12 changes: 5 additions & 7 deletions src/rebar_prv_common_test.erl
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@ do(State) ->

do(State, Tests) ->
?INFO("Running Common Test suites...", []),
rebar_utils:update_code(rebar_state:code_paths(State, all_deps), [soft_purge]),
rebar_paths:set_paths([deps, plugins], State),

%% Run ct provider prehooks
Providers = rebar_state:providers(State),
Expand All @@ -73,14 +73,14 @@ do(State, Tests) ->
ok ->
%% Run ct provider post hooks for all project apps and top level project hooks
rebar_hooks:run_project_and_app_hooks(Cwd, post, ?PROVIDER, Providers, State),
rebar_utils:cleanup_code_path(rebar_state:code_paths(State, default)),
rebar_paths:set_paths([plugins, deps], State),
{ok, State};
Error ->
rebar_utils:cleanup_code_path(rebar_state:code_paths(State, default)),
rebar_paths:set_paths([plugins, deps], State),
Error
end;
Error ->
rebar_utils:cleanup_code_path(rebar_state:code_paths(State, default)),
rebar_paths:set_paths([plugins, deps], State),
Error
end.

Expand Down Expand Up @@ -250,11 +250,9 @@ select_tests(State, ProjectApps, CmdOpts, CfgOpts) ->
end, SysConfigs),
%% NB: load the applications (from user directories too) to support OTP < 17
%% to our best ability.
OldPath = code:get_path(),
code:add_pathsa(rebar_state:code_paths(State, all_deps)),
rebar_paths:set_paths([deps, plugins], State),
[application:load(Application) || Config <- Configs, {Application, _} <- Config],
rebar_utils:reread_config(Configs),
code:set_path(OldPath),

Opts = merge_opts(CmdOpts,CfgOpts),
discover_tests(State, ProjectApps, Opts).
Expand Down
Loading

0 comments on commit 7bfc811

Please sign in to comment.