Skip to content

Commit

Permalink
Return callback module in supervisor format_status
Browse files Browse the repository at this point in the history
The previous implementation of supervisor:get_callback_module/1
used sys:get_status/1 to get the supervisor inner state and
retrieve the callback module. Such implementation forbids any
other supervisor implementation that has an internal state
different than the #state{} record in supervisor.erl.

This patch allows supervisors to return the callback module
as part of the sys:get_status/1 data, no longer coupling the
callback module implementation with the inner #state{} record.

Notice we have kept the clause matching the previous
sys:get_status/1 reply for backwards compatibility purposes.
  • Loading branch information
José Valim committed Mar 31, 2016
1 parent 10a218b commit 9ef5502
Show file tree
Hide file tree
Showing 2 changed files with 22 additions and 5 deletions.
15 changes: 12 additions & 3 deletions lib/stdlib/src/supervisor.erl
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@

%% Internal exports
-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
terminate/2, code_change/3]).
terminate/2, code_change/3, format_status/2]).
-export([try_again_restart/2]).

%% For release_handler only
Expand Down Expand Up @@ -264,8 +264,12 @@ cast(Supervisor, Req) ->
get_callback_module(Pid) ->
{status, _Pid, {module, _Mod},
[_PDict, _SysState, _Parent, _Dbg, Misc]} = sys:get_status(Pid),
[_Header, _Data, {data, [{"State", State}]}] = Misc,
State#state.module.
case Misc of
[_Header, _Data, {data, [{"State", {Mod, _}}]}] ->
Mod;
[_Header, _Data, {data, [{"State", State}]}] ->
State#state.module
end.

%%% ---------------------------------------------------
%%%
Expand Down Expand Up @@ -1456,3 +1460,8 @@ report_progress(Child, SupName) ->
Progress = [{supervisor, SupName},
{started, extract_child(Child)}],
error_logger:info_report(progress, Progress).

format_status(terminate, [_PDict, State]) ->
State;
format_status(_, [_PDict, State]) ->
[{data, [{"State", {State#state.module, State}}]}].
12 changes: 10 additions & 2 deletions lib/stdlib/test/supervisor_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -67,7 +67,7 @@

%% Misc tests
-export([child_unlink/1, tree/1, count_children/1,
count_restarting_children/1,
count_restarting_children/1, get_callback_module/1,
do_not_save_start_parameters_for_temporary_children/1,
do_not_save_child_specs_for_temporary_children/1,
simple_one_for_one_scale_many_temporary_children/1,
Expand All @@ -91,7 +91,7 @@ all() ->
{group, normal_termination},
{group, shutdown_termination},
{group, abnormal_termination}, child_unlink, tree,
count_children, count_restarting_children,
count_children, count_restarting_children, get_callback_module,
do_not_save_start_parameters_for_temporary_children,
do_not_save_child_specs_for_temporary_children,
simple_one_for_one_scale_many_temporary_children, temporary_bystander,
Expand Down Expand Up @@ -1508,6 +1508,14 @@ count_restarting_children(Config) when is_list(Config) ->
ok = supervisor:terminate_child(SupPid, Ch3_2),
[1,0,0,0] = get_child_counts(SupPid).

%%-------------------------------------------------------------------------
%% Test get_callback_module
get_callback_module(Config) when is_list(Config) ->
Child = {child, {supervisor_1, start_child, []}, temporary, 1000,
worker, []},
{ok, SupPid} = start_link({ok, {{simple_one_for_one, 2, 3600}, [Child]}}),
supervisor_SUITE = supervisor:get_callback_module(SupPid).

%%-------------------------------------------------------------------------
%% Temporary children shall not be restarted so they should not save
%% start parameters, as it potentially can take up a huge amount of
Expand Down

0 comments on commit 9ef5502

Please sign in to comment.