Skip to content

Commit

Permalink
Pass the state through on most hook calls
Browse files Browse the repository at this point in the history
  • Loading branch information
filmor committed Sep 16, 2024
1 parent 7da4837 commit 0038be1
Show file tree
Hide file tree
Showing 8 changed files with 54 additions and 53 deletions.
5 changes: 3 additions & 2 deletions apps/rebar/src/rebar_hooks.erl
Original file line number Diff line number Diff line change
Expand Up @@ -21,8 +21,9 @@ run_all_hooks(Dir, Type, Command, Providers, AppInfo, State) ->

run_all_hooks(Dir, Type, Command, Providers, State) ->
?DEBUG("Running hooks for ~p with configuration:", [Command]),
run_provider_hooks(Dir, Type, Command, Providers, rebar_state:opts(State), State),
run_hooks(Dir, Type, Command, rebar_state:opts(State), State).
State1 = run_provider_hooks(Dir, Type, Command, Providers, rebar_state:opts(State), State),
run_hooks(Dir, Type, Command, rebar_state:opts(State1), State1),
State1.

run_project_and_app_hooks(Dir, Type, Command, Providers, State) ->
ProjectApps = rebar_state:project_apps(State),
Expand Down
22 changes: 11 additions & 11 deletions apps/rebar/src/rebar_prv_clean.erl
Original file line number Diff line number Diff line change
Expand Up @@ -49,15 +49,15 @@ do(State) ->
{ok, State1} = rebar_prv_as:do(State0),

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

if All; Specific =/= [] ->
DepsDir = rebar_dir:deps_dir(State1),
DepsDir = rebar_dir:deps_dir(State2),
DepsDirs = filelib:wildcard(filename:join(DepsDir, "*")),
ProjectApps = rebar_state:project_apps(State1),
Deps = rebar_state:all_deps(State1),
ProjectApps = rebar_state:project_apps(State2),
Deps = rebar_state:all_deps(State2),
KnownAppNames = [rebar_app_info:name(App) || App <- ProjectApps++Deps],
ParsedApps = rebar_app_discover:find_apps(DepsDirs, all, State1),
ParsedApps = rebar_app_discover:find_apps(DepsDirs, all, State2),
AllApps = ProjectApps ++ Deps ++
[App || App <- ParsedApps,
not lists:member(rebar_app_info:name(App),
Expand All @@ -66,17 +66,17 @@ do(State) ->
true -> fun(_) -> true end;
false -> fun(AppInfo) -> filter_name(AppInfo, Specific) end
end,
clean_apps(State1, Providers, AllApps, Filter);
clean_apps(State2, Providers, AllApps, Filter);
true ->
ProjectApps = rebar_state:project_apps(State1),
clean_apps(State1, Providers, ProjectApps, fun(_) -> true end)
ProjectApps = rebar_state:project_apps(State2),
clean_apps(State2, Providers, ProjectApps, fun(_) -> true end)
end,

clean_extras(State1),
clean_extras(State2),

rebar_hooks:run_all_hooks(Cwd, post, ?PROVIDER, Providers, State1),
State3 = rebar_hooks:run_all_hooks(Cwd, post, ?PROVIDER, Providers, State2),

{ok, State1}.
{ok, State3}.

-spec format_error(any()) -> iolist().
format_error(Reason) ->
Expand Down
16 changes: 8 additions & 8 deletions apps/rebar/src/rebar_prv_common_test.erl
Original file line number Diff line number Diff line change
Expand Up @@ -65,24 +65,24 @@ do(State, Tests) ->
Cwd = rebar_dir:get_cwd(),

%% Run ct provider pre hooks for all project apps and top level project hooks
rebar_hooks:run_project_and_app_hooks(Cwd, pre, ?PROVIDER, Providers, State),
State1 = rebar_hooks:run_project_and_app_hooks(Cwd, pre, ?PROVIDER, Providers, State),

case Tests of
{ok, T} ->
case run_tests(State, T) of
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_paths:set_paths([plugins, deps], State),
symlink_to_last_ct_logs(State, T),
{ok, State};
State2 = rebar_hooks:run_project_and_app_hooks(Cwd, post, ?PROVIDER, Providers, State1),
rebar_paths:set_paths([plugins, deps], State2),
symlink_to_last_ct_logs(State2, T),
{ok, State2};
Error ->
rebar_paths:set_paths([plugins, deps], State),
symlink_to_last_ct_logs(State, T),
rebar_paths:set_paths([plugins, deps], State1),
symlink_to_last_ct_logs(State1, T),
Error
end;
Error ->
rebar_paths:set_paths([plugins, deps], State),
rebar_paths:set_paths([plugins, deps], State1),
Error
end.

Expand Down
14 changes: 7 additions & 7 deletions apps/rebar/src/rebar_prv_compile.erl
Original file line number Diff line number Diff line change
Expand Up @@ -66,25 +66,25 @@ handle_project_apps(Providers, State) ->
{ok, ProjectApps1} = rebar_digraph:compile_order(ProjectApps),

%% Run top level hooks *before* project apps compiled but *after* deps are
rebar_hooks:run_all_hooks(Cwd, pre, ?PROVIDER, Providers, State),
State1 = rebar_hooks:run_all_hooks(Cwd, pre, ?PROVIDER, Providers, State),

ProjectApps2 = copy_and_build_project_apps(State, Providers, ProjectApps1),
State2 = rebar_state:project_apps(State, ProjectApps2),
ProjectApps2 = copy_and_build_project_apps(State1, Providers, ProjectApps1),
State2 = rebar_state:project_apps(State1, ProjectApps2),

%% build extra_src_dirs in the root of multi-app projects
build_root_extras(State, ProjectApps2),
build_root_extras(State1, ProjectApps2),

State3 = update_code_paths(State2, ProjectApps2),

rebar_hooks:run_all_hooks(Cwd, post, ?PROVIDER, Providers, State3),
case rebar_state:has_all_artifacts(State3) of
State4 = rebar_hooks:run_all_hooks(Cwd, post, ?PROVIDER, Providers, State3),
case rebar_state:has_all_artifacts(State4) of
{false, File} ->
throw(?PRV_ERROR({missing_artifact, File}));
true ->
true
end,

State3.
State4.


-spec format_error(any()) -> iolist().
Expand Down
12 changes: 6 additions & 6 deletions apps/rebar/src/rebar_prv_edoc.erl
Original file line number Diff line number Diff line change
Expand Up @@ -38,10 +38,10 @@ do(State) ->
EdocOpts = rebar_state:get(State, edoc_opts, []),
ShouldAccPaths = not has_configured_paths(EdocOpts),
Cwd = rebar_state:dir(State),
rebar_hooks:run_all_hooks(Cwd, pre, ?PROVIDER, Providers, State),
State1 = rebar_hooks:run_all_hooks(Cwd, pre, ?PROVIDER, Providers, State),
Res = try
lists:foldl(fun(AppInfo, EdocOptsAcc) ->
rebar_hooks:run_all_hooks(Cwd, pre, ?PROVIDER, Providers, AppInfo, State),
rebar_hooks:run_all_hooks(Cwd, pre, ?PROVIDER, Providers, AppInfo, State1),
AppName = rebar_utils:to_list(rebar_app_info:name(AppInfo)),
?INFO("Running edoc for ~ts", [AppName]),
AppDir = rebar_app_info:dir(AppInfo),
Expand All @@ -50,7 +50,7 @@ do(State) ->
AppEdocOpts = merge_opts(rebar_opts:get(AppOpts, edoc_opts, []), EdocOptsAcc),
?DEBUG("{edoc_opts, ~p}.", [AppEdocOpts]),
AppRes = (catch edoc:application(list_to_atom(AppName), AppDir, AppEdocOpts)),
rebar_hooks:run_all_hooks(Cwd, post, ?PROVIDER, Providers, AppInfo, State),
rebar_hooks:run_all_hooks(Cwd, post, ?PROVIDER, Providers, AppInfo, State1),
case {AppRes, ShouldAccPaths} of
{ok, true} ->
%% edoc wants / on all OSes
Expand All @@ -67,13 +67,13 @@ do(State) ->
{app_failed, AppName} ->
{app_failed, AppName}
end,
rebar_hooks:run_all_hooks(Cwd, post, ?PROVIDER, Providers, State),
rebar_paths:set_paths([plugins, deps], State),
State2 = rebar_hooks:run_all_hooks(Cwd, post, ?PROVIDER, Providers, State1),
rebar_paths:set_paths([plugins, deps], State2),
case Res of
{app_failed, App} ->
?PRV_ERROR({app_failed, App});
_ ->
{ok, State}
{ok, State2}
end.

-spec format_error(any()) -> iolist().
Expand Down
16 changes: 8 additions & 8 deletions apps/rebar/src/rebar_prv_eunit.erl
Original file line number Diff line number Diff line change
Expand Up @@ -60,22 +60,22 @@ do(State, Tests) ->
%% Run eunit provider prehooks
Providers = rebar_state:providers(State),
Cwd = rebar_dir:get_cwd(),
rebar_hooks:run_project_and_app_hooks(Cwd, pre, ?PROVIDER, Providers, State),
State0 = rebar_hooks:run_project_and_app_hooks(Cwd, pre, ?PROVIDER, Providers, State),

case validate_tests(State, Tests) of
case validate_tests(State0, Tests) of
{ok, T} ->
case run_tests(State, T) of
case run_tests(State0, T) of
{ok, State1} ->
%% Run eunit provider posthooks
rebar_hooks:run_project_and_app_hooks(Cwd, post, ?PROVIDER, Providers, State1),
rebar_paths:set_paths([plugins, deps], State),
{ok, State1};
State2 = rebar_hooks:run_project_and_app_hooks(Cwd, post, ?PROVIDER, Providers, State1),
rebar_paths:set_paths([plugins, deps], State2),
{ok, State2};
Error ->
rebar_paths:set_paths([plugins, deps], State),
rebar_paths:set_paths([plugins, deps], State0),
Error
end;
Error ->
rebar_paths:set_paths([plugins, deps], State),
rebar_paths:set_paths([plugins, deps], State0),
Error
end.

Expand Down
14 changes: 7 additions & 7 deletions apps/rebar/src/rebar_prv_upgrade.erl
Original file line number Diff line number Diff line change
Expand Up @@ -45,13 +45,13 @@ init(State) ->
do(State) ->
Cwd = rebar_state:dir(State),
Providers = rebar_state:providers(State),
rebar_hooks:run_project_and_app_hooks(Cwd, pre, ?PROVIDER, Providers, State),
case do_(State) of
State1 = rebar_hooks:run_project_and_app_hooks(Cwd, pre, ?PROVIDER, Providers, State),
case do_(State1) of
{ok, NewState} ->
rebar_hooks:run_project_and_app_hooks(Cwd, post, ?PROVIDER, Providers, NewState),
{ok, NewState};
NewState1 = rebar_hooks:run_project_and_app_hooks(Cwd, post, ?PROVIDER, Providers, NewState),
{ok, NewState1};
Other ->
rebar_hooks:run_project_and_app_hooks(Cwd, post, ?PROVIDER, Providers, State),
_IgnoredState = rebar_hooks:run_project_and_app_hooks(Cwd, post, ?PROVIDER, Providers, State1),
Other
end.

Expand Down Expand Up @@ -130,12 +130,12 @@ format_error({transitive_dependency, Name}) ->
format_error({checkout_dependency, Name}) ->
io_lib:format("Dependency ~ts is a checkout dependency under _checkouts/ and checkouts cannot be upgraded.",
[Name]);
format_error(no_arg) ->
format_error(no_arg) ->
"Specify a list of dependencies to upgrade, or --all to upgrade them all";
format_error(Reason) ->
io_lib:format("~p", [Reason]).

handle_args(State) ->
handle_args(State) ->
{Args, _} = rebar_state:command_parsed_args(State),
All = proplists:get_value(all, Args, false),
Package = proplists:get_value(package, Args),
Expand Down
8 changes: 4 additions & 4 deletions apps/rebar/src/rebar_relx.erl
Original file line number Diff line number Diff line change
Expand Up @@ -50,7 +50,7 @@ do(Provider, State) ->

Providers = rebar_state:providers(State),
Cwd = rebar_state:dir(State),
rebar_hooks:run_project_and_app_hooks(Cwd, pre, Provider, Providers, State),
State1 = rebar_hooks:run_project_and_app_hooks(Cwd, pre, Provider, Providers, State),

Releases = releases_to_build(Provider, Opts, RelxState),

Expand All @@ -72,12 +72,12 @@ do(Provider, State) ->

relx:build_relup(Release, ToVsn, UpFromVsn, RelxState);
_ ->
parallel_run(Provider, Releases, all_apps(State), RelxState)
parallel_run(Provider, Releases, all_apps(State1), RelxState)
end,

rebar_hooks:run_project_and_app_hooks(Cwd, post, Provider, Providers, State),
State2 = rebar_hooks:run_project_and_app_hooks(Cwd, post, Provider, Providers, State1),

{ok, State}.
{ok, State2}.

read_relx_config(State, Options) ->
ConfigFile = proplists:get_value(config, Options, []),
Expand Down

0 comments on commit 0038be1

Please sign in to comment.