Skip to content

Commit

Permalink
Merge pull request #2697 from ferd/support-project-local-plugins
Browse files Browse the repository at this point in the history
Add support for project-local plugins
  • Loading branch information
ferd authored Apr 27, 2022
2 parents 55e3c41 + 2af0af1 commit d574535
Show file tree
Hide file tree
Showing 10 changed files with 328 additions and 27 deletions.
2 changes: 1 addition & 1 deletion .github/workflows/shelltests.yml
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,7 @@ jobs:
- name: Install and run shelltestrunner
run: |
sudo apt-get update
sudo apt-get install -y shelltestrunner build-essential
sudo apt-get install -y shelltestrunner build-essential cmake liblz4-dev
cd rebar3_tests
mix local.hex --force
./run_tests.sh
1 change: 1 addition & 0 deletions src/rebar.hrl
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,7 @@
-define(DEFAULT_BASE_DIR, "_build").
-define(DEFAULT_ROOT_DIR, ".").
-define(DEFAULT_PROJECT_APP_DIRS, ["apps/*", "lib/*", "."]).
-define(DEFAULT_PROJECT_PLUGIN_DIRS, ["plugins/*"]).
-define(DEFAULT_CHECKOUTS_DIR, "_checkouts").
-define(DEFAULT_CHECKOUTS_OUT_DIR, "checkouts").
-define(DEFAULT_DEPS_DIR, "lib").
Expand Down
4 changes: 2 additions & 2 deletions src/rebar_app_discover.erl
Original file line number Diff line number Diff line change
Expand Up @@ -64,8 +64,8 @@ do(State, LibDirs) ->
OutDir = filename:join(DepsDir, Name),
AppInfo2 = rebar_app_info:out_dir(AppInfo1, OutDir),
ProjectDeps1 = lists:delete(Name, ProjectDeps),
rebar_state:project_apps(StateAcc1
,rebar_app_info:deps(AppInfo2, ProjectDeps1));
rebar_state:project_apps(StateAcc1,
rebar_app_info:deps(AppInfo2, ProjectDeps1));
false ->
?INFO("Ignoring ~ts", [Name]),
StateAcc
Expand Down
3 changes: 2 additions & 1 deletion src/rebar_app_info.erl
Original file line number Diff line number Diff line change
Expand Up @@ -638,7 +638,8 @@ valid(#app_info_t{valid=Valid}) ->

%% @doc sets whether the app is valid (built) or not. If left unset,
%% rebar3 will do the detection of the status itself.
-spec valid(t(), boolean()) -> t().
%% Explicitly setting the value to `undefined' can force a re-evaluation.
-spec valid(t(), boolean() | undefined) -> t().
valid(AppInfo=#app_info_t{}, Valid) ->
AppInfo#app_info_t{valid=Valid}.

Expand Down
7 changes: 7 additions & 0 deletions src/rebar_dir.erl
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,7 @@
checkouts_out_dir/2,
plugins_dir/1,
lib_dirs/1,
project_plugin_dirs/1,
home_dir/0,
global_config_dir/1,
global_config/1,
Expand Down Expand Up @@ -127,6 +128,12 @@ plugins_dir(State) ->
lib_dirs(State) ->
rebar_state:get(State, project_app_dirs, ?DEFAULT_PROJECT_APP_DIRS).

%% @doc returns the list of relative path where the project plugins can
%% be located.
-spec project_plugin_dirs(rebar_state:t()) -> [file:filename_all()].
project_plugin_dirs(State) ->
rebar_state:get(State, project_plugin_dirs, ?DEFAULT_PROJECT_PLUGIN_DIRS).

%% @doc returns the user's home directory.
-spec home_dir() -> file:filename_all().
home_dir() ->
Expand Down
121 changes: 113 additions & 8 deletions src/rebar_plugins.erl
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,8 @@
,project_apps_install/1
,install/2
,handle_plugins/3
,handle_plugins/4]).
,handle_plugins/4
,discover_plugins/1]).

-include("rebar.hrl").

Expand Down Expand Up @@ -94,10 +95,11 @@ handle_plugins(Profile, Plugins, State, Upgrade) ->
Locks = rebar_state:lock(State),
DepsDir = rebar_state:get(State, deps_dir, ?DEFAULT_DEPS_DIR),
State1 = rebar_state:set(State, deps_dir, ?DEFAULT_PLUGINS_DIR),
SrcPlugins = discover_plugins(Plugins, State),
%% Install each plugin individually so if one fails to install it doesn't effect the others
{_PluginProviders, State2} =
lists:foldl(fun(Plugin, {PluginAcc, StateAcc}) ->
{NewPlugins, NewState} = handle_plugin(Profile, Plugin, StateAcc, Upgrade),
{NewPlugins, NewState} = handle_plugin(Profile, Plugin, StateAcc, SrcPlugins, Upgrade),
NewState1 = rebar_state:create_logic_providers(NewPlugins, NewState),
{PluginAcc++NewPlugins, NewState1}
end, {[], State1}, Plugins),
Expand All @@ -106,24 +108,34 @@ handle_plugins(Profile, Plugins, State, Upgrade) ->
State3 = rebar_state:set(State2, deps_dir, DepsDir),
rebar_state:lock(State3, Locks).

handle_plugin(Profile, Plugin, State, Upgrade) ->
handle_plugin(Profile, Plugin, State, SrcPlugins, Upgrade) ->
try
{Apps, State2} = rebar_prv_install_deps:handle_deps_as_profile(Profile, State, [Plugin], Upgrade),
{no_cycle, Sorted} = rebar_prv_install_deps:find_cycles(Apps),
%% Inject top-level src plugins as project apps, so that they get skipped
%% by the installation as already seen
ProjectApps = rebar_state:project_apps(State),
State0 = rebar_state:project_apps(State, SrcPlugins),
%% We however have to pick the deps of top-level apps and promote them
%% directly to make sure they are installed if they were not also at the top level
TopDeps = top_level_deps(State, SrcPlugins),
%% Install the plugins
{Apps, State1} = rebar_prv_install_deps:handle_deps_as_profile(Profile, State0, [Plugin|TopDeps], Upgrade),
{no_cycle, Sorted} = rebar_prv_install_deps:find_cycles(SrcPlugins++Apps),
ToBuild = rebar_prv_install_deps:cull_compile(Sorted, []),
%% Return things to normal
State2 = rebar_state:project_apps(State1, ProjectApps),

%% Add already built plugin deps to the code path
ToBuildPaths = [rebar_app_info:ebin_dir(A) || A <- ToBuild],
PreBuiltPaths = [Ebin || A <- Apps,
PreBuiltPaths = [Ebin || A <- Sorted,
Ebin <- [rebar_app_info:ebin_dir(A)],
not lists:member(Ebin, ToBuildPaths)],
code:add_pathsa(PreBuiltPaths),

%% Build plugin and its deps
build_plugins(ToBuild, Apps, State2),
build_plugins(ToBuild, Sorted, State2),

%% Add newly built deps and plugin to code path
State3 = rebar_state:update_all_plugin_deps(State2, Apps),
State3 = rebar_state:update_all_plugin_deps(State2, Sorted),
NewCodePaths = [rebar_app_info:ebin_dir(A) || A <- ToBuild],

%% Store plugin code paths so we can remove them when compiling project apps
Expand Down Expand Up @@ -172,3 +184,96 @@ validate_plugin(Plugin) ->
end
end.

discover_plugins([], _) ->
%% don't search if nothing is declared
[];
discover_plugins(_, State) ->
discover_plugins(State).

discover_plugins(State) ->
%% only support this mode in an umbrella project to avoid cases where
%% this is used in a project intended to be an installed dependency and accidentally
%% relies on vendoring when not intended. Also skip for global plugins, this would
%% make no sense.
case lists:member(global, rebar_state:current_profiles(State)) orelse not is_umbrella(State) of
true ->
[];
false ->
%% Inject source paths for plugins to allow vendoring and umbrella
%% top-level declarations
BaseDir = rebar_state:dir(State),
LibDirs = rebar_dir:project_plugin_dirs(State),
Dirs = [filename:join(BaseDir, LibDir) || LibDir <- LibDirs],
RebarOpts = rebar_state:opts(State),
SrcDirs = rebar_dir:src_dirs(RebarOpts, ["src"]),
Found = rebar_app_discover:find_apps(Dirs, SrcDirs, all, State),
?DEBUG("Found local plugins: ~p~n"
"\tusing config: {project_plugin_dirs, ~p}",
[[rebar_utils:to_atom(rebar_app_info:name(F)) || F <- Found],
LibDirs]),
PluginsDir = rebar_dir:plugins_dir(State),
SetUp = lists:map(fun(App) ->
Name = rebar_app_info:name(App),
OutDir = filename:join(PluginsDir, Name),
prepare_plugin(rebar_app_info:out_dir(App, OutDir))
end, Found),
rebar_utils:sort_deps(SetUp)
end.

is_umbrella(State) ->
%% We can't know if this is an umbrella project before running app discovery,
%% but plugins are installed before app discovery. So we do a heuristic.
%% The lib dirs we search contain things such as apps/, lib/, etc.
%% which contain sub-applications. Then there's a final search for the
%% local directory ("."), which finds the top-level app in a non-umbrella
%% project.
%%
%% So what we do here is look for the library directories without the ".",
%% and if none of these paths exist but one of the src_dirs exist, then
%% we know this is not an umbrella application.
Root = rebar_dir:root_dir(State),
LibPaths = lists:usort(rebar_dir:lib_dirs(State)) -- ["."],
SrcPaths = rebar_dir:src_dirs(rebar_state:opts(State), ["src"]),
lists:any(fun(Dir) -> [] == filelib:wildcard(filename:join(Root, Dir)) end, LibPaths)
andalso
lists:all(fun(Dir) -> not filelib:is_dir(filename:join(Root, Dir)) end, SrcPaths).

prepare_plugin(AppInfo) ->
%% We need to handle plugins as dependencies to avoid re-building them
%% continuously. So here we copy the app directories to the dep location
%% and then change the AppInfo record to be redirected to the dep location.
AppDir = rebar_app_info:dir(AppInfo),
OutDir = rebar_app_info:out_dir(AppInfo),
rebar_prv_compile:copy_app_dirs(AppInfo, AppDir, OutDir),
Relocated = rebar_app_info:dir(AppInfo, OutDir),
case needs_rebuild(AppInfo) of
true -> rebar_app_info:valid(Relocated, false); % force recompilation
false -> rebar_app_info:valid(Relocated, undefined) % force revalidation
end.

top_level_deps(State, Apps) ->
CurrentProfiles = rebar_state:current_profiles(State),
Keys = lists:append([[{plugins, P}, {deps, P}] || P <- CurrentProfiles]),
RawDeps = lists:foldl(fun(App, Acc) ->
%% Only support the profiles we would with regular plugins?
lists:append([rebar_app_info:get(App, Key, []) || Key <- Keys]) ++ Acc
end, [], Apps),
rebar_utils:tup_dedup(RawDeps).

needs_rebuild(AppInfo) ->
%% if source files are newer than built files then the code was edited
%% and can't be considered valid -- force a rebuild.
%%
%% we do this by reusing the compiler code for Erlang as a heuristic for
%% files to check. The actual compiler provider will do an in-depth
%% validation of each module that may or may not need recompiling.
#{src_dirs := SrcD, include_dirs := InclD,
out_mappings := List} = rebar_compiler_erl:context(AppInfo),
SrcDirs = SrcD++InclD,
OutDirs = [Dir || {_Ext, Dir} <- List],
newest_stamp(OutDirs) < newest_stamp(SrcDirs).

newest_stamp(DirList) ->
lists:max([0] ++
[filelib:last_modified(F)
|| F <- rebar_utils:find_files_in_dirs(DirList, ".+", true)]).
1 change: 1 addition & 0 deletions src/rebar_prv_compile.erl
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@
format_error/1]).

-export([compile/2, compile/3, compile/4]).
-export([copy_app_dirs/3]).

-include_lib("providers/include/providers.hrl").
-include("rebar.hrl").
Expand Down
36 changes: 23 additions & 13 deletions src/rebar_prv_plugins_upgrade.erl
Original file line number Diff line number Diff line change
Expand Up @@ -69,27 +69,37 @@ upgrade(Plugin, State) ->
Dep ->
Dep
end,

LocalPlugins = [rebar_utils:to_atom(rebar_app_info:name(App))
|| App <- rebar_plugins:discover_plugins(State)],
case Dep of
not_found ->
?PRV_ERROR({not_found, Plugin});
{ok, P, Profile} ->
State1 = rebar_state:set(State, deps_dir, ?DEFAULT_PLUGINS_DIR),
maybe_update_pkg(P, State1),
{Apps, State2} = rebar_prv_install_deps:handle_deps_as_profile(Profile, State1, [P], true),
case lists:member(P, LocalPlugins) of
true ->
?INFO("Plugin ~p is defined locally and does not need upgrading", [P]),
{ok, State};
false ->
do_upgrade(State, P, Profile)
end
end.

{no_cycle, Sorted} = rebar_prv_install_deps:find_cycles(Apps),
ToBuild = rebar_prv_install_deps:cull_compile(Sorted, []),
do_upgrade(State, P, Profile) ->
State1 = rebar_state:set(State, deps_dir, ?DEFAULT_PLUGINS_DIR),
maybe_update_pkg(P, State1),
{Apps, State2} = rebar_prv_install_deps:handle_deps_as_profile(Profile, State1, [P], true),

%% Add already built plugin deps to the code path
CodePaths = [rebar_app_info:ebin_dir(A) || A <- Apps -- ToBuild],
code:add_pathsa(CodePaths),
{no_cycle, Sorted} = rebar_prv_install_deps:find_cycles(Apps),
ToBuild = rebar_prv_install_deps:cull_compile(Sorted, []),

%% Build plugin and its deps
_ = build_plugin(ToBuild, State2),
%% Add already built plugin deps to the code path
CodePaths = [rebar_app_info:ebin_dir(A) || A <- Apps -- ToBuild],
code:add_pathsa(CodePaths),

{ok, State}
end.
%% Build plugin and its deps
_ = build_plugin(ToBuild, State2),

{ok, State}.

find_plugin(Plugin, Profiles, State) ->
ec_lists:search(fun(Profile) ->
Expand Down
Loading

0 comments on commit d574535

Please sign in to comment.