Skip to content

Commit

Permalink
Merge pull request #1564 from tsloughter/reset_profile_hooks
Browse files Browse the repository at this point in the history
reset hooks under profiles for application opts
  • Loading branch information
tsloughter authored Jun 2, 2017
2 parents 5ab3230 + 48dc973 commit 8750a67
Show file tree
Hide file tree
Showing 2 changed files with 40 additions and 11 deletions.
33 changes: 24 additions & 9 deletions src/rebar_app_discover.erl
Original file line number Diff line number Diff line change
Expand Up @@ -97,11 +97,11 @@ merge_deps(AppInfo, State) ->
%% the application they are defined at. If an umbrella structure is used and
%% they are deifned at the top level they will instead run in the context of
%% the State and at the top level, not as part of an application.
Default = reset_hooks(rebar_state:default(State)),
CurrentProfiles = rebar_state:current_profiles(State),
Default = reset_hooks(rebar_state:default(State), CurrentProfiles),
{C, State1} = project_app_config(AppInfo, State),
AppInfo0 = rebar_app_info:update_opts(AppInfo, Default, C),

CurrentProfiles = rebar_state:current_profiles(State1),
Name = rebar_app_info:name(AppInfo0),

%% We reset the opts here to default so no profiles are applied multiple times
Expand Down Expand Up @@ -171,17 +171,33 @@ project_app_config(AppInfo, State) ->
maybe_reset_hooks(Dir, Opts, State) ->
case ec_file:real_dir_path(rebar_dir:root_dir(State)) of
Dir ->
reset_hooks(Opts);
CurrentProfiles = rebar_state:current_profiles(State),
reset_hooks(Opts, CurrentProfiles);
_ ->
Opts
end.

%% @doc make the hooks empty for a given set of options
-spec reset_hooks(Opts) -> Opts when Opts :: rebar_dict().
reset_hooks(Opts) ->
lists:foldl(fun(Key, OptsAcc) ->
rebar_opts:set(OptsAcc, Key, [])
end, Opts, [post_hooks, pre_hooks, provider_hooks, artifacts]).
-spec reset_hooks(Opts, Profiles) ->
Opts when
Opts :: rebar_dict(),
Profiles :: [atom()].
reset_hooks(Opts, CurrentProfiles) ->
AllHooks = [post_hooks, pre_hooks, provider_hooks, artifacts],
Opts1 = lists:foldl(fun(Key, OptsAcc) ->
rebar_opts:set(OptsAcc, Key, [])
end, Opts, AllHooks),
Profiles = rebar_opts:get(Opts1, profiles, []),
Profiles1 = lists:map(fun({P, ProfileOpts}) ->
case lists:member(P, CurrentProfiles) of
true ->
{P, [X || X={Key, _} <- ProfileOpts,
not lists:member(Key, AllHooks)]};
false ->
{P, ProfileOpts}
end
end, Profiles),
rebar_opts:set(Opts1, profiles, Profiles1).

%% @private find the directories for all apps, while detecting their source dirs
%% Returns the app dir with the respective src_dirs for them, in that order,
Expand Down Expand Up @@ -422,4 +438,3 @@ find_config_src(AppDir, Default) ->
%% TODO: handle profiles I guess, but we don't have that info
proplists:get_value(src_dirs, Terms, Default)
end.

18 changes: 16 additions & 2 deletions test/rebar_hooks_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@
build_and_clean_app/1,
escriptize_artifacts/1,
run_hooks_once/1,
run_hooks_once_profiles/1,
run_hooks_for_plugins/1,
eunit_app_hooks/1,
deps_hook_namespace/1]).
Expand All @@ -33,8 +34,9 @@ end_per_testcase(_, _Config) ->
catch meck:unload().

all() ->
[build_and_clean_app, run_hooks_once, escriptize_artifacts,
run_hooks_for_plugins, deps_hook_namespace, eunit_app_hooks].
[build_and_clean_app, run_hooks_once, run_hooks_once_profiles,
escriptize_artifacts, run_hooks_for_plugins, deps_hook_namespace,
eunit_app_hooks].

%% Test post provider hook cleans compiled project app, leaving it invalid
build_and_clean_app(Config) ->
Expand Down Expand Up @@ -98,6 +100,18 @@ run_hooks_once(Config) ->
rebar_test_utils:create_app(AppDir, Name, Vsn, [kernel, stdlib]),
rebar_test_utils:run_and_check(Config, RebarConfig, ["compile"], {ok, [{app, Name, valid}]}).

%% test that even if a hook is defined at the project level in a used profile
%% the hook is not run for each application in the project umbrella
run_hooks_once_profiles(Config) ->
AppDir = ?config(apps, Config),

Name = rebar_test_utils:create_random_name("app1_"),
Vsn = rebar_test_utils:create_random_vsn(),
RebarConfig = [{profiles, [{hooks, [{pre_hooks, [{compile, "mkdir blah"}]}]}]}],
rebar_test_utils:create_config(AppDir, RebarConfig),
rebar_test_utils:create_app(AppDir, Name, Vsn, [kernel, stdlib]),
rebar_test_utils:run_and_check(Config, RebarConfig, ["as", "hooks", "compile"], {ok, [{app, Name, valid}]}).

deps_hook_namespace(Config) ->
mock_git_resource:mock([{deps, [{some_dep, "0.0.1"}]}]),
Deps = rebar_test_utils:expand_deps(git, [{"some_dep", "0.0.1", []}]),
Expand Down

0 comments on commit 8750a67

Please sign in to comment.