Skip to content

Commit

Permalink
Fix clean hooks when override are presents
Browse files Browse the repository at this point in the history
The issue appears to be that because the 'clean' operation might be run
while dependencies have not yet been compiled, we applied a partial app
detection mechanism with `rebar_app_disover:find_apps(..., ..., all,
...)`, which worked to parse "invalid" (unbuilt) apps, but also did not
apply overrides.

Instead, we trust the `install_deps` provider dependency by reusing the
apps as they were fully parsed _if_ they were valid, and falling back to
the `rebar_app_discover:find_apps/4` call only to cover the unreadable
ones.

This, it turns out, has the side effect of properly applying hooks when
apps are fully parsed, and fixes #2862

Note that we can only clean paths safely if the discovery steps for the
apps is done with the right profile and options, which may also impact
configurations and hooks.

So rather than duplicating that, we invoke the 'as' provider. This also
opens the door on choosing a different provider (such as 'app_discover'
only) down the road if the -a option isn't given.
  • Loading branch information
ferd committed Feb 20, 2024
1 parent 8207d82 commit c4dce2d
Show file tree
Hide file tree
Showing 2 changed files with 18 additions and 4 deletions.
19 changes: 16 additions & 3 deletions apps/rebar/src/rebar_prv_clean.erl
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@
-include("rebar.hrl").

-define(PROVIDER, clean).
-define(DEPS, [app_discovery, install_deps]).
-define(DEPS, []).

%% ===================================================================
%% Public API
Expand All @@ -37,15 +37,28 @@ do(State) ->
Providers = rebar_state:providers(State),
{All, Profiles, Specific} = handle_args(State),

State1 = rebar_state:apply_profiles(State, [list_to_atom(X) || X <- Profiles]),
%% Invoke provider deps as the desired profile(s) so the discovery of
%% apps respects profile options.
State0 = rebar_state:command_args(
State,
lists:join(",", ["default"|Profiles]) ++ ["install_deps"]
),
{ok, State1} = rebar_prv_as:do(State0),

Cwd = rebar_dir:get_cwd(),
rebar_hooks:run_all_hooks(Cwd, pre, ?PROVIDER, Providers, State1),

if All; Specific =/= [] ->
DepsDir = rebar_dir:deps_dir(State1),
DepsDirs = filelib:wildcard(filename:join(DepsDir, "*")),
AllApps = rebar_app_discover:find_apps(DepsDirs, all, State),
ProjectApps = rebar_state:project_apps(State1),
Deps = rebar_state:all_deps(State1),
KnownAppNames = [rebar_app_info:name(App) || App <- ProjectApps++Deps],
ParsedApps = rebar_app_discover:find_apps(DepsDirs, all, State1),
AllApps = ProjectApps ++ Deps ++
[App || App <- ParsedApps,
not lists:member(rebar_app_info:name(App),
KnownAppNames)],
Filter = case All of
true -> fun(_) -> true end;
false -> fun(AppInfo) -> filter_name(AppInfo, Specific) end
Expand Down
3 changes: 2 additions & 1 deletion apps/rebar/test/rebar_as_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -198,4 +198,5 @@ clean_as_profile(Config) ->
rebar_test_utils:run_and_check(Config,
[],
["clean", "-a", "-p", "foo"],
{ok, [{app, Name, invalid}]}).
{ok, [{app, Name, invalid}]}),
ok.

0 comments on commit c4dce2d

Please sign in to comment.