Skip to content

Commit

Permalink
Merge pull request #8741 from IngelaAndin/ingela/stdlib/sup-progress/G…
Browse files Browse the repository at this point in the history
…H-8715/OTP-19202

stdlib: Do not progress report dynamically started supervisors
  • Loading branch information
IngelaAndin authored Sep 2, 2024
2 parents 40561ee + 62ba338 commit d3a9459
Show file tree
Hide file tree
Showing 2 changed files with 51 additions and 22 deletions.
28 changes: 19 additions & 9 deletions lib/stdlib/src/supervisor.erl
Original file line number Diff line number Diff line change
Expand Up @@ -926,7 +926,7 @@ init_dynamic(_State, StartSpec) ->
start_children(Children, SupName) ->
Start =
fun(Id,Child) ->
case do_start_child(SupName, Child) of
case do_start_child(SupName, Child, info_report) of
{ok, undefined} when ?is_temporary(Child) ->
remove;
{ok, Pid} ->
Expand All @@ -940,16 +940,16 @@ start_children(Children, SupName) ->
end,
children_map(Start,Children).

do_start_child(SupName, Child) ->
do_start_child(SupName, Child, Report) ->
#child{mfargs = {M, F, Args}} = Child,
case do_start_child_i(M, F, Args) of
{ok, Pid} when is_pid(Pid) ->
NChild = Child#child{pid = Pid},
report_progress(NChild, SupName),
report_progress(NChild, SupName, Report),
{ok, Pid};
{ok, Pid, Extra} when is_pid(Pid) ->
NChild = Child#child{pid = Pid},
report_progress(NChild, SupName),
report_progress(NChild, SupName, Report),
{ok, Pid, Extra};
Other ->
Other
Expand Down Expand Up @@ -1025,7 +1025,7 @@ handle_call({restart_child, _Id}, _From, State) when ?is_simple(State) ->
handle_call({restart_child, Id}, _From, State) ->
case find_child(Id, State) of
{ok, Child} when Child#child.pid =:= undefined ->
case do_start_child(State#state.name, Child) of
case do_start_child(State#state.name, Child, debug_report) of
{ok, Pid} ->
NState = set_pid(Pid, Id, State),
{reply, {ok, Pid}, NState};
Expand Down Expand Up @@ -1253,7 +1253,7 @@ update_chsp(#child{id=Id}=OldChild, NewDb) ->
handle_start_child(Child, State) ->
case find_child(Child#child.id, State) of
error ->
case do_start_child(State#state.name, Child) of
case do_start_child(State#state.name, Child, debug_report) of
{ok, undefined} when ?is_temporary(Child) ->
{{ok, undefined}, State};
{ok, Pid} ->
Expand Down Expand Up @@ -1387,7 +1387,7 @@ restart(simple_one_for_one, Child, State0) ->
end;
restart(one_for_one, #child{id=Id} = Child, State) ->
OldPid = Child#child.pid,
case do_start_child(State#state.name, Child) of
case do_start_child(State#state.name, Child, info_report) of
{ok, Pid} ->
NState = set_pid(Pid, Id, State),
{ok, NState};
Expand Down Expand Up @@ -2114,7 +2114,7 @@ extract_child(Child) ->
{shutdown, Child#child.shutdown},
{child_type, Child#child.child_type}].

report_progress(Child, SupName) ->
report_progress(Child, SupName, info_report) ->
?LOG_INFO(#{label=>{supervisor,progress},
report=>[{supervisor,SupName},
{started,extract_child(Child)}]},
Expand All @@ -2123,7 +2123,17 @@ report_progress(Child, SupName) ->
logger_formatter=>#{title=>"PROGRESS REPORT"},
error_logger=>#{tag=>info_report,
type=>progress,
report_cb=>fun supervisor:format_log/1}}).
report_cb=>fun supervisor:format_log/1}});
report_progress(Child, SupName, debug_report) ->
?LOG_DEBUG(#{label=>{supervisor,progress},
report=>[{supervisor,SupName},
{started,extract_child(Child)}]},
#{domain=>[otp,sasl],
report_cb=>fun supervisor:format_log/2,
logger_formatter=>#{title=>"PROGRESS REPORT"},
error_logger=>#{tag=>info_report,
type=>progress,
report_cb=>fun supervisor:format_log/1}}).

%% format_log/1 is the report callback used by Logger handler
%% error_logger only. It is kept for backwards compatibility with
Expand Down
45 changes: 32 additions & 13 deletions lib/stdlib/test/supervisor_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@

%% Internal export
-export([init/1, terminate_all_children/1,
middle9212/0, gen_server9212/0, handle_info/2, start_registered_name/1]).
middle9212/0, gen_server9212/0, handle_info/2, start_registered_name/1, log/2]).

%% API tests
-export([ sup_start_normal/1, sup_start_ignore_init/1,
Expand All @@ -51,13 +51,12 @@
extra_return/1, sup_flags/1]).

%% Tests concept permanent, transient and temporary
-export([ permanent_normal/1, transient_normal/1,
temporary_normal/1,
permanent_shutdown/1, transient_shutdown/1,
temporary_shutdown/1,
faulty_application_shutdown/1,
permanent_abnormal/1, transient_abnormal/1,
temporary_abnormal/1, temporary_bystander/1]).
-export([external_start_no_progress_log/1,
permanent_normal/1, transient_normal/1, temporary_normal/1,
permanent_shutdown/1, transient_shutdown/1, temporary_shutdown/1,
faulty_application_shutdown/1,
permanent_abnormal/1, transient_abnormal/1,
temporary_abnormal/1, temporary_bystander/1]).

%% Restart strategy tests
-export([ multiple_restarts/1,
Expand Down Expand Up @@ -96,7 +95,7 @@
%%-------------------------------------------------------------------------

suite() ->
[{ct_hooks,[ts_install_cth]},
[%{ct_hooks,[ts_install_cth]},
{timetrap,{minutes,1}}].

all() ->
Expand Down Expand Up @@ -140,7 +139,7 @@ groups() ->
sup_stop_brutal_kill, sup_stop_brutal_kill_dynamic,
sup_stop_race, sup_stop_non_shutdown_exit_dynamic]},
{normal_termination, [],
[permanent_normal, transient_normal, temporary_normal]},
[external_start_no_progress_log, permanent_normal, transient_normal, temporary_normal]},
{shutdown_termination, [],
[permanent_shutdown, transient_shutdown, temporary_shutdown,
faulty_application_shutdown]},
Expand Down Expand Up @@ -1047,17 +1046,29 @@ sup_flags(_Config) ->

ok.

%%-------------------------------------------------------------------------
external_start_no_progress_log(Config) when is_list(Config) ->
ok = logger:add_handler(?MODULE, ?MODULE, #{test_case_pid => self()}),
Filter = {fun logger_filters:domain/2,{log,sub,[otp,sasl]}},
logger:add_handler_filter(?MODULE, filter_non_sasl, Filter),
logger:set_module_level([supervisor], info),
permanent_normal(Config),
receive
ok ->
ok = logger:remove_handler(?MODULE);
{fail, Msg} ->
ok = logger:remove_handler(?MODULE),
ct:fail({"unexpected progress report", Msg})
end.

%%-------------------------------------------------------------------------
%% A permanent child should always be restarted.
permanent_normal(Config) when is_list(Config) ->
{ok, SupPid} = start_link({ok, {{one_for_one, 2, 3600}, []}}),
Child1 = {child1, {supervisor_1, start_child, []}, permanent, 1000,
worker, []},

{ok, CPid1} = supervisor:start_child(sup_test, Child1),

terminate(SupPid, CPid1, child1, normal),

[{child1, Pid ,worker,[]}] = supervisor:which_children(sup_test),
case is_pid(Pid) of
true ->
Expand Down Expand Up @@ -3819,3 +3830,11 @@ ensure_supervisor_is_stopped() ->
Pid ->
terminate(Pid, shutdown)
end.

%%-----------------------------------------------------------------
%% The Logger handler used.
%%-----------------------------------------------------------------
log(#{meta := #{mfa := {supervisor,do_restart,3}}}, #{test_case_pid := Pid}) ->
Pid ! ok;
log(#{level := info, msg := Msg}, #{test_case_pid := Pid}) ->
Pid ! {fail, Msg}.

0 comments on commit d3a9459

Please sign in to comment.