Skip to content

Commit

Permalink
Merge pull request #1924 from ferd/allow-shell-breakpoints
Browse files Browse the repository at this point in the history
Allow Breakpoints during task runs
  • Loading branch information
ferd authored Oct 23, 2018
2 parents 78e0d79 + 9b03dac commit a112095
Show file tree
Hide file tree
Showing 2 changed files with 79 additions and 2 deletions.
43 changes: 42 additions & 1 deletion src/r3.erl
Original file line number Diff line number Diff line change
@@ -1,8 +1,9 @@
%%% @doc external alias for `rebar_agent' for more convenient
%%% calls from a shell.
-module(r3).
-export([do/1, do/2]).
-export([do/1, do/2, async_do/1, async_do/2, break/0, resume/0]).
-export(['$handle_undefined_function'/2]).
-include("rebar.hrl").

%% @doc alias for `rebar_agent:do/1'
-spec do(atom()) -> ok | {error, term()}.
Expand All @@ -12,6 +13,46 @@ do(Command) -> rebar_agent:do(Command).
-spec do(atom(), atom()) -> ok | {error, term()}.
do(Namespace, Command) -> rebar_agent:do(Namespace, Command).

%% @async_doc alias for `rebar_agent:async_do/1'
-spec async_do(atom()) -> ok | {error, term()}.
async_do(Command) -> rebar_agent:async_do(Command).

%% @async_doc alias for `rebar_agent:async_do/2'
-spec async_do(atom(), atom()) -> ok | {error, term()}.
async_do(Namespace, Command) -> rebar_agent:async_do(Namespace, Command).

break() ->
case whereis(rebar_agent) of % is the shell running
undefined ->
ok;
Pid ->
{dictionary, Dict} = process_info(Pid, dictionary),
case lists:keyfind(cmd_type, 1, Dict) of
{cmd_type, async} ->
Self = self(),
Ref = make_ref(),
spawn_link(fun() ->
register(r3_breakpoint_handler, self()),
receive
resume ->
Self ! Ref
end
end),
io:format(user, "~n=== BREAK ===~n", []),
receive
Ref -> ok
end;
_ ->
?DEBUG("ignoring breakpoint since command is not run "
"in async mode", []),
ok
end
end.

resume() ->
r3_breakpoint_handler ! resume,
ok.

%% @private defer to rebar_agent
'$handle_undefined_function'(Cmd, Args) ->
rebar_agent:'$handle_undefined_function'(Cmd, Args).
38 changes: 37 additions & 1 deletion src/rebar_agent.erl
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
%%% @doc Runs a process that holds a rebar3 state and can be used
%%% to statefully maintain loaded project state into a running VM.
-module(rebar_agent).
-export([start_link/1, do/1, do/2]).
-export([start_link/1, do/1, do/2, async_do/1, async_do/2]).
-export(['$handle_undefined_function'/2]).
-export([init/1,
handle_call/3, handle_cast/2, handle_info/2,
Expand Down Expand Up @@ -35,6 +35,18 @@ do(Namespace, Command) when is_atom(Namespace), is_atom(Command) ->
do(Namespace, Args) when is_atom(Namespace), is_list(Args) ->
gen_server:call(?MODULE, {cmd, Namespace, do, Args}, infinity).

-spec async_do(atom()) -> ok | {error, term()}.
async_do(Command) when is_atom(Command) ->
gen_server:cast(?MODULE, {cmd, Command});
async_do(Args) when is_list(Args) ->
gen_server:cast(?MODULE, {cmd, default, do, Args}).

-spec async_do(atom(), atom()) -> ok.
async_do(Namespace, Command) when is_atom(Namespace), is_atom(Command) ->
gen_server:cast(?MODULE, {cmd, Namespace, Command});
async_do(Namespace, Args) when is_atom(Namespace), is_list(Args) ->
gen_server:cast(?MODULE, {cmd, Namespace, do, Args}).

'$handle_undefined_function'(Cmd, [Namespace, Args]) ->
gen_server:call(?MODULE, {cmd, Namespace, Cmd, Args}, infinity);
'$handle_undefined_function'(Cmd, [Args]) ->
Expand All @@ -54,20 +66,44 @@ init(State) ->
%% @private
handle_call({cmd, Command}, _From, State=#state{state=RState, cwd=Cwd}) ->
MidState = maybe_show_warning(State),
put(cmd_type, sync),
{Res, NewRState} = run(default, Command, "", RState, Cwd),
put(cmd_type, undefined),
{reply, Res, MidState#state{state=NewRState}, hibernate};
handle_call({cmd, Namespace, Command}, _From, State = #state{state=RState, cwd=Cwd}) ->
MidState = maybe_show_warning(State),
put(cmd_type, sync),
{Res, NewRState} = run(Namespace, Command, "", RState, Cwd),
put(cmd_type, undefined),
{reply, Res, MidState#state{state=NewRState}, hibernate};
handle_call({cmd, Namespace, Command, Args}, _From, State = #state{state=RState, cwd=Cwd}) ->
MidState = maybe_show_warning(State),
put(cmd_type, sync),
{Res, NewRState} = run(Namespace, Command, Args, RState, Cwd),
put(cmd_type, undefined),
{reply, Res, MidState#state{state=NewRState}, hibernate};
handle_call(_Call, _From, State) ->
{noreply, State}.

%% @private
handle_cast({cmd, Command}, State=#state{state=RState, cwd=Cwd}) ->
MidState = maybe_show_warning(State),
put(cmd_type, async),
{_, NewRState} = run(default, Command, "", RState, Cwd),
put(cmd_type, undefined),
{noreply, MidState#state{state=NewRState}, hibernate};
handle_cast({cmd, Namespace, Command}, State = #state{state=RState, cwd=Cwd}) ->
MidState = maybe_show_warning(State),
put(cmd_type, async),
{_, NewRState} = run(Namespace, Command, "", RState, Cwd),
put(cmd_type, undefined),
{noreply, MidState#state{state=NewRState}, hibernate};
handle_cast({cmd, Namespace, Command, Args}, State = #state{state=RState, cwd=Cwd}) ->
MidState = maybe_show_warning(State),
put(cmd_type, async),
{_, NewRState} = run(Namespace, Command, Args, RState, Cwd),
put(cmd_type, undefined),
{noreply, MidState#state{state=NewRState}, hibernate};
handle_cast(_Cast, State) ->
{noreply, State}.

Expand Down

0 comments on commit a112095

Please sign in to comment.