Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
42 changes: 41 additions & 1 deletion lib/stdlib/src/supervisor.erl
Original file line number Diff line number Diff line change
Expand Up @@ -302,7 +302,8 @@ but the map is preferred.
delete_child/2, terminate_child/2,
which_children/1, which_child/2,
count_children/1, check_childspecs/1,
check_childspecs/2, get_childspec/2]).
check_childspecs/2, get_childspec/2,
stop/1, stop/3]).

%% Internal exports
-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
Expand Down Expand Up @@ -829,6 +830,45 @@ processes:
count_children(Supervisor) ->
call(Supervisor, count_children).

-doc(#{equiv => stop(SupRef, normal, infinity)}).
-doc(#{since => <<"OTP 28.0">>}).
-spec stop(SupRef :: sup_ref()) -> ok.
stop(Supervisor) ->
gen_server:stop(Supervisor).

-doc """
Stop a supervisor.

Orders the supervisor specified by `SupRef` to exit
with the specified `Reason` and waits for it to terminate.
The supervisor will terminate all its children
before exiting.

The function returns `ok` if the supervisor terminates
with the expected reason. Any other reason than `normal`, `shutdown`,
or `{shutdown,Term}` causes an error report to be issued using `m:logger`.
An exit signal with the same reason is sent to linked processes and ports.

`Timeout` is an integer that specifies how many milliseconds to wait
for the supervisor to terminate, or the atom `infinity` to wait indefinitely.
If the supervisor has not terminated within the specified time,
the call exits the calling process with reason `timeout`.

If the process does not exist, the call exits the calling process
with reason `noproc`, or with reason `{nodedown,Node}`
if the connection fails to the remote `Node` where the supervisor runs.

> #### Warning {: .warning }
>
> Calling this function from a (sub-)child process of the given supervisor
> will result in a deadlock which will last until either the shutdown timeout
> of the child or the timeout given to `stop/3` has expired.
""".
-doc(#{since => <<"OTP 28.0">>}).
-spec stop(SupRef :: sup_ref(), Reason :: term(), Timeout :: timeout()) -> ok.
stop(Supervisor, Reason, Timeout) ->
gen_server:stop(Supervisor, Reason, Timeout).

call(Supervisor, Req) ->
gen_server:call(Supervisor, Req, infinity).

Expand Down
4 changes: 1 addition & 3 deletions lib/stdlib/test/supervisor_1.erl
Original file line number Diff line number Diff line change
Expand Up @@ -74,10 +74,8 @@ handle_info({'EXIT',_,{shutdown,Term}}, State) ->
{stop, {shutdown,Term}, State};

handle_info({sleep, Time}, State) ->
io:format("FOO: ~p~n", [Time]),
timer:sleep(Time),
io:format("FOO: sleept~n", []),
handle_info({sleep, Time}, State);
{noreply, State};

handle_info(_, State) ->
{noreply, State}.
Expand Down
71 changes: 70 additions & 1 deletion lib/stdlib/test/supervisor_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -49,6 +49,8 @@
sup_stop_infinity/1, sup_stop_timeout/1, sup_stop_timeout_dynamic/1,
sup_stop_brutal_kill/1, sup_stop_brutal_kill_dynamic/1,
sup_stop_race/1, sup_stop_non_shutdown_exit_dynamic/1, auto_hibernate/1,
sup_stop_manual/1, sup_stop_manual_timeout/1,
sup_stop_race/1, sup_stop_non_shutdown_exit_dynamic/1,
child_adm/1, child_adm_simple/1, child_specs/1, child_specs_map/1,
extra_return/1, sup_flags/1]).

Expand Down Expand Up @@ -141,7 +143,8 @@ groups() ->
{sup_stop, [],
[sup_stop_infinity, sup_stop_timeout, sup_stop_timeout_dynamic,
sup_stop_brutal_kill, sup_stop_brutal_kill_dynamic,
sup_stop_race, sup_stop_non_shutdown_exit_dynamic]},
sup_stop_race, sup_stop_non_shutdown_exit_dynamic,
sup_stop_manual, sup_stop_manual_timeout]},
{normal_termination, [],
[external_start_no_progress_log, permanent_normal, transient_normal, temporary_normal]},
{shutdown_termination, [],
Expand Down Expand Up @@ -654,6 +657,72 @@ sup_stop_non_shutdown_exit_dynamic(Config) when is_list(Config) ->
[temporary, transient, permanent]
).

%%-------------------------------------------------------------------------
%% Tests that children are shut down when a supervisor is stopped via
%% supervisor:stop/1
%% Since supervisors are gen_servers and the basic functionality of the
%% stop functions is already tested in gen_server_SUITE, we only make
%% sure that children are terminated correctly when applied to a
%% supervisor.
sup_stop_manual(Config) when is_list(Config) ->
process_flag(trap_exit, true),
{ok, Pid} = start_link({ok, {{one_for_one, 2, 3600}, []}}),
Child1 = {child1, {supervisor_1, start_child, []},
permanent, brutal_kill, worker, []},
Child2 = {child2, {supervisor_1, start_child, []},
permanent, 1000, worker, []},
Child3 = {child3, {supervisor_1, start_child, []},
permanent, 1000, worker, []},
{ok, CPid1} = supervisor:start_child(sup_test, Child1),
link(CPid1),
{ok, CPid2} = supervisor:start_child(sup_test, Child2),
link(CPid2),
{ok, CPid3} = supervisor:start_child(sup_test, Child3),
link(CPid3),

CPid3 ! {sleep, 100000},

supervisor:stop(Pid),

check_exit_reason(Pid, normal),
check_exit_reason(CPid1, killed),
check_exit_reason(CPid2, shutdown),
check_exit_reason(CPid3, killed).

%%-------------------------------------------------------------------------
%% Tests that children are shut down when a supervisor is stopped via
%% supervisor:stop/3, even if the stop call times out.
%% Since supervisors are gen_servers and the basic functionality of the
%% stop functions is already tested in gen_server_SUITE, we only make
%% sure that children are terminated correctly when applied to a
%% supervisor.
sup_stop_manual_timeout(Config) when is_list(Config) ->
process_flag(trap_exit, true),
{ok, Pid} = start_link({ok, {{one_for_one, 2, 3600}, []}}),
Child1 = {child1, {supervisor_1, start_child, []},
permanent, 5000, worker, []},
Child2 = {child2, {supervisor_1, start_child, []},
permanent, 1000, worker, []},
{ok, CPid1} = supervisor:start_child(sup_test, Child1),
link(CPid1),
{ok, CPid2} = supervisor:start_child(sup_test, Child2),
link(CPid2),

CPid1 ! {sleep, 1000},

try
supervisor:stop(Pid, normal, 100)
of
ok -> ct:fail(expected_timeout)
catch
exit:timeout ->
ok
end,

check_exit_reason(Pid, normal),
check_exit_reason(CPid1, shutdown),
check_exit_reason(CPid2, shutdown).

%%-------------------------------------------------------------------------
%% The start function provided to start a child may return {ok, Pid}
%% or {ok, Pid, Info}, if it returns the latter check that the
Expand Down
Loading