Skip to content

Commit

Permalink
Merge pull request #1075 from tsloughter/plugin_override
Browse files Browse the repository at this point in the history
add project_providers after initing default providers but allow overrides
  • Loading branch information
ferd committed Feb 22, 2016
2 parents 9b26c4f + ca64142 commit 2d2b8a7
Show file tree
Hide file tree
Showing 6 changed files with 108 additions and 18 deletions.
6 changes: 3 additions & 3 deletions src/rebar3.erl
Original file line number Diff line number Diff line change
Expand Up @@ -124,10 +124,10 @@ run_aux(State, RawArgs) ->
filename:join(filename:absname(rebar_state:dir(State3)), BaseDir)),

{ok, Providers} = application:get_env(rebar, providers),
%% Initializing project_plugins before providers allows top level plugins to take precedence
State5 = rebar_plugins:project_plugins_install(State4),
%% Providers can modify profiles stored in opts, so set default after initializing providers
State6 = rebar_state:create_logic_providers(Providers, State5),
State5 = rebar_state:create_logic_providers(Providers, State4),
%% Initializing project_plugins which can override default providers
State6 = rebar_plugins:project_plugins_install(State5),
State7 = rebar_plugins:top_level_install(State6),
State8 = rebar_state:default(State7, rebar_state:opts(State7)),

Expand Down
10 changes: 6 additions & 4 deletions src/rebar_plugins.erl
Original file line number Diff line number Diff line change
Expand Up @@ -19,10 +19,12 @@
-spec project_plugins_install(rebar_state:t()) -> rebar_state:t().
project_plugins_install(State) ->
Profiles = rebar_state:current_profiles(State),
lists:foldl(fun(Profile, StateAcc) ->
Plugins = rebar_state:get(State, {project_plugins, Profile}, []),
handle_plugins(Profile, Plugins, StateAcc)
end, State, Profiles).
State1 = rebar_state:allow_provider_overrides(State, true),
State2 = lists:foldl(fun(Profile, StateAcc) ->
Plugins = rebar_state:get(State, {project_plugins, Profile}, []),
handle_plugins(Profile, Plugins, StateAcc)
end, State1, Profiles),
rebar_state:allow_provider_overrides(State2, false).

-spec top_level_install(rebar_state:t()) -> rebar_state:t().
top_level_install(State) ->
Expand Down
18 changes: 14 additions & 4 deletions src/rebar_state.erl
Original file line number Diff line number Diff line change
Expand Up @@ -36,9 +36,10 @@

deps_names/1,


resources/1, resources/2, add_resource/2,
providers/1, providers/2, add_provider/2]).
providers/1, providers/2, add_provider/2,
allow_provider_overrides/1, allow_provider_overrides/2
]).

-include("rebar.hrl").
-include_lib("providers/include/providers.hrl").
Expand All @@ -63,7 +64,8 @@
all_deps = [] :: [rebar_app_info:t()],

resources = [],
providers = []}).
providers = [],
allow_provider_overrides = false :: boolean()}).

-export_type([t/0]).

Expand Down Expand Up @@ -370,8 +372,16 @@ providers(#state_t{providers=Providers}) ->
providers(State, NewProviders) ->
State#state_t{providers=NewProviders}.

allow_provider_overrides(#state_t{allow_provider_overrides=Allow}) ->
Allow.

allow_provider_overrides(State, Allow) ->
State#state_t{allow_provider_overrides=Allow}.

-spec add_provider(t(), providers:t()) -> t().
add_provider(State=#state_t{providers=Providers}, Provider) ->
add_provider(State=#state_t{providers=Providers, allow_provider_overrides=true}, Provider) ->
State#state_t{providers=[Provider | Providers]};
add_provider(State=#state_t{providers=Providers, allow_provider_overrides=false}, Provider) ->
Name = providers:impl(Provider),
Namespace = providers:namespace(Provider),
Module = providers:module(Provider),
Expand Down
11 changes: 7 additions & 4 deletions test/mock_git_resource.erl
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
%%% Mock a git resource and create an app magically for each URL submitted.
-module(mock_git_resource).
-export([mock/0, mock/1, unmock/0]).
-export([mock/0, mock/1, mock/2, unmock/0]).
-define(MOD, rebar_git_resource).

%%%%%%%%%%%%%%%%%
Expand All @@ -24,11 +24,14 @@ mock() -> mock([]).
| {pkg, App, term()},
Vsn :: string().
mock(Opts) ->
mock(Opts, create_app).

mock(Opts, CreateType) ->
meck:new(?MOD, [no_link]),
mock_lock(Opts),
mock_update(Opts),
mock_vsn(Opts),
mock_download(Opts),
mock_download(Opts, CreateType),
ok.

unmock() ->
Expand Down Expand Up @@ -98,7 +101,7 @@ mock_vsn(Opts) ->
%% `{deps, [{"app1", [{app2, ".*", {git, ...}}]}]}' -- basically
%% the `deps' option takes a key/value list of terms to output directly
%% into a `rebar.config' file to describe dependencies.
mock_download(Opts) ->
mock_download(Opts, CreateType) ->
Deps = proplists:get_value(deps, Opts, []),
Config = proplists:get_value(config, Opts, []),
Default = proplists:get_value(default_vsn, Opts, "0.0.0"),
Expand All @@ -110,7 +113,7 @@ mock_download(Opts) ->
{git, Url, {_, Vsn}} = normalize_git(Git, Overrides, Default),
App = app(Url),
AppDeps = proplists:get_value({App,Vsn}, Deps, []),
rebar_test_utils:create_app(
rebar_test_utils:CreateType(
Dir, App, Vsn,
[kernel, stdlib] ++ [element(1,D) || D <- AppDeps]
),
Expand Down
52 changes: 50 additions & 2 deletions test/rebar_plugins_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,8 @@
list/1,
upgrade/1,
sub_app_plugins/1,
sub_app_plugin_overrides/1]).
sub_app_plugin_overrides/1,
project_plugins/1]).

-include_lib("common_test/include/ct.hrl").
-include_lib("eunit/include/eunit.hrl").
Expand All @@ -34,7 +35,7 @@ end_per_testcase(_, _Config) ->
catch meck:unload().

all() ->
[compile_plugins, compile_global_plugins, complex_plugins, list, upgrade, sub_app_plugins, sub_app_plugin_overrides].
[compile_plugins, compile_global_plugins, complex_plugins, list, upgrade, sub_app_plugins, sub_app_plugin_overrides, project_plugins].

%% Tests that compiling a project installs and compiles the plugins of deps
compile_plugins(Config) ->
Expand Down Expand Up @@ -281,3 +282,50 @@ sub_app_plugin_overrides(Config) ->
Config, RConf, ["compile"],
{ok, [{app, Name}, {dep, Dep2Name, Vsn}, {plugin, DepName, Vsn2}, {plugin, PluginName}]}
).

%% Check that project plugins are first in providers even if they override defaults but that
%% normal plugins do not
project_plugins(Config) ->
AppDir = ?config(apps, Config),

Name = rebar_test_utils:create_random_name("app1_"),
Vsn = rebar_test_utils:create_random_vsn(),
rebar_test_utils:create_app(AppDir, Name, Vsn, [kernel, stdlib]),

DepName = rebar_test_utils:create_random_name("dep1_"),
PluginName = "compile",
PluginName2 = "release",

Plugins = rebar_test_utils:expand_deps(git, [{PluginName, Vsn, []}, {PluginName2, Vsn, []}]),
{SrcDeps, _} = rebar_test_utils:flat_deps(Plugins),
mock_git_resource:mock([{deps, SrcDeps}], create_plugin),

mock_pkg_resource:mock([{pkgdeps, [{{list_to_binary(DepName), list_to_binary(Vsn)}, []}]},
{config, [{plugins, [
{list_to_atom(PluginName),
{git, "http://site.com/user/"++PluginName++".git",
{tag, Vsn}}}]}]}]),

RConfFile =
rebar_test_utils:create_config(AppDir,
[{deps, [
list_to_atom(DepName)
]},
{project_plugins, [
{list_to_atom(PluginName2),
{git, "http://site.com/user/"++PluginName2++".git",
{tag, Vsn}}}]}]),
{ok, RConf} = file:consult(RConfFile),

%% Build with deps.
{ok, State} = rebar_test_utils:run_and_check(
Config, RConf, ["compile"],
{ok, [{app, Name}, {plugin, PluginName}, {plugin, PluginName2}, {dep, DepName}]}
),

%% Should have 2 release providers but only 1 compile provider
Release = [P || P <- rebar_state:providers(State), providers:impl(P) =:= release, providers:namespace(P) =:= default],
Compile = [P || P <- rebar_state:providers(State), providers:impl(P) =:= compile, providers:namespace(P) =:= default],

?assertEqual(length(Release), 2),
?assertEqual(length(Compile), 1).
29 changes: 28 additions & 1 deletion test/rebar_test_utils.erl
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
-include_lib("eunit/include/eunit.hrl").
-export([init_rebar_state/1, init_rebar_state/2, run_and_check/4, check_results/3]).
-export([expand_deps/2, flat_deps/1, top_level_deps/1]).
-export([create_app/4, create_eunit_app/4, create_empty_app/4,
-export([create_app/4, create_plugin/4, create_eunit_app/4, create_empty_app/4,
create_config/2, create_config/3, package_app/3]).
-export([create_random_name/1, create_random_vsn/0, write_src_file/2]).

Expand Down Expand Up @@ -82,6 +82,16 @@ create_app(AppDir, Name, Vsn, Deps) ->
write_app_src_file(AppDir, Name, Vsn, Deps),
rebar_app_info:new(Name, Vsn, AppDir, Deps).

%% @doc Creates a dummy plugin including:
%% - src/<file>.erl
%% - src/<file>.app.src
%% And returns a `rebar_app_info' object.
create_plugin(AppDir, Name, Vsn, Deps) ->
write_plugin_file(AppDir, Name ++ ".erl"),
write_src_file(AppDir, "not_a_real_src_" ++ Name ++ ".erl"),
write_app_src_file(AppDir, Name, Vsn, Deps),
rebar_app_info:new(Name, Vsn, AppDir, Deps).

%% @doc Creates a dummy application including:
%% - src/<file>.erl
%% - src/<file>.app.src
Expand Down Expand Up @@ -365,6 +375,11 @@ check_results(AppDir, Expected, ProfileRun) ->
?assert(filelib:is_dir(Dirname))
end, Expected).

write_plugin_file(Dir, Name) ->
Erl = filename:join([Dir, "src", Name]),
ok = filelib:ensure_dir(Erl),
ok = ec_file:write(Erl, plugin_src_file(Name)).

write_src_file(Dir, Name) ->
Erl = filename:join([Dir, "src", Name]),
ok = filelib:ensure_dir(Erl),
Expand Down Expand Up @@ -395,6 +410,18 @@ erl_src_file(Name) ->
"-export([main/0]).\n"
"main() -> ok.\n", [filename:basename(Name, ".erl")]).

plugin_src_file(Name) ->
io_lib:format("-module('~s').\n"
"-export([init/1]).\n"
"init(State) -> \n"
"Provider = providers:create([\n"
"{name, '~s'},\n"
"{module, '~s'}\n"
"]),\n"
"{ok, rebar_state:add_provider(State, Provider)}.\n", [filename:basename(Name, ".erl"),
filename:basename(Name, ".erl"),
filename:basename(Name, ".erl")]).

erl_eunitized_src_file(Name) ->
io_lib:format("-module('~s').\n"
"-export([main/0]).\n"
Expand Down

0 comments on commit 2d2b8a7

Please sign in to comment.