Skip to content

Commit 07d5b60

Browse files
authored
Merge pull request #9209 from Maria-12648430/supervisor_stop
Introduce `supervisor:stop/1,3` OTP-19800
2 parents 44b8fbe + cb02c7a commit 07d5b60

File tree

3 files changed

+112
-5
lines changed

3 files changed

+112
-5
lines changed

lib/stdlib/src/supervisor.erl

Lines changed: 41 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -302,7 +302,8 @@ but the map is preferred.
302302
delete_child/2, terminate_child/2,
303303
which_children/1, which_child/2,
304304
count_children/1, check_childspecs/1,
305-
check_childspecs/2, get_childspec/2]).
305+
check_childspecs/2, get_childspec/2,
306+
stop/1, stop/3]).
306307

307308
%% Internal exports
308309
-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
@@ -830,6 +831,45 @@ processes:
830831
count_children(Supervisor) ->
831832
call(Supervisor, count_children).
832833

834+
-doc(#{equiv => stop(SupRef, normal, infinity)}).
835+
-doc(#{since => <<"OTP 28.0">>}).
836+
-spec stop(SupRef :: sup_ref()) -> ok.
837+
stop(Supervisor) ->
838+
gen_server:stop(Supervisor).
839+
840+
-doc """
841+
Stop a supervisor.
842+
843+
Orders the supervisor specified by `SupRef` to exit
844+
with the specified `Reason` and waits for it to terminate.
845+
The supervisor will terminate all its children
846+
before exiting.
847+
848+
The function returns `ok` if the supervisor terminates
849+
with the expected reason. Any other reason than `normal`, `shutdown`,
850+
or `{shutdown,Term}` causes an error report to be issued using `m:logger`.
851+
An exit signal with the same reason is sent to linked processes and ports.
852+
853+
`Timeout` is an integer that specifies how many milliseconds to wait
854+
for the supervisor to terminate, or the atom `infinity` to wait indefinitely.
855+
If the supervisor has not terminated within the specified time,
856+
the call exits the calling process with reason `timeout`.
857+
858+
If the process does not exist, the call exits the calling process
859+
with reason `noproc`, or with reason `{nodedown,Node}`
860+
if the connection fails to the remote `Node` where the supervisor runs.
861+
862+
> #### Warning {: .warning }
863+
>
864+
> Calling this function from a (sub-)child process of the given supervisor
865+
> will result in a deadlock which will last until either the shutdown timeout
866+
> of the child or the timeout given to `stop/3` has expired.
867+
""".
868+
-doc(#{since => <<"OTP 28.0">>}).
869+
-spec stop(SupRef :: sup_ref(), Reason :: term(), Timeout :: timeout()) -> ok.
870+
stop(Supervisor, Reason, Timeout) ->
871+
gen_server:stop(Supervisor, Reason, Timeout).
872+
833873
call(Supervisor, Req) ->
834874
gen_server:call(Supervisor, Req, infinity).
835875

lib/stdlib/test/supervisor_1.erl

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -74,10 +74,8 @@ handle_info({'EXIT',_,{shutdown,Term}}, State) ->
7474
{stop, {shutdown,Term}, State};
7575

7676
handle_info({sleep, Time}, State) ->
77-
io:format("FOO: ~p~n", [Time]),
7877
timer:sleep(Time),
79-
io:format("FOO: sleept~n", []),
80-
handle_info({sleep, Time}, State);
78+
{noreply, State};
8179

8280
handle_info(_, State) ->
8381
{noreply, State}.

lib/stdlib/test/supervisor_SUITE.erl

Lines changed: 70 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -49,6 +49,8 @@
4949
sup_stop_infinity/1, sup_stop_timeout/1, sup_stop_timeout_dynamic/1,
5050
sup_stop_brutal_kill/1, sup_stop_brutal_kill_dynamic/1,
5151
sup_stop_race/1, sup_stop_non_shutdown_exit_dynamic/1, auto_hibernate/1,
52+
sup_stop_manual/1, sup_stop_manual_timeout/1,
53+
sup_stop_race/1, sup_stop_non_shutdown_exit_dynamic/1,
5254
child_adm/1, child_adm_simple/1, child_specs/1, child_specs_map/1,
5355
extra_return/1, sup_flags/1]).
5456

@@ -141,7 +143,8 @@ groups() ->
141143
{sup_stop, [],
142144
[sup_stop_infinity, sup_stop_timeout, sup_stop_timeout_dynamic,
143145
sup_stop_brutal_kill, sup_stop_brutal_kill_dynamic,
144-
sup_stop_race, sup_stop_non_shutdown_exit_dynamic]},
146+
sup_stop_race, sup_stop_non_shutdown_exit_dynamic,
147+
sup_stop_manual, sup_stop_manual_timeout]},
145148
{normal_termination, [],
146149
[external_start_no_progress_log, permanent_normal, transient_normal, temporary_normal]},
147150
{shutdown_termination, [],
@@ -654,6 +657,72 @@ sup_stop_non_shutdown_exit_dynamic(Config) when is_list(Config) ->
654657
[temporary, transient, permanent]
655658
).
656659

660+
%%-------------------------------------------------------------------------
661+
%% Tests that children are shut down when a supervisor is stopped via
662+
%% supervisor:stop/1
663+
%% Since supervisors are gen_servers and the basic functionality of the
664+
%% stop functions is already tested in gen_server_SUITE, we only make
665+
%% sure that children are terminated correctly when applied to a
666+
%% supervisor.
667+
sup_stop_manual(Config) when is_list(Config) ->
668+
process_flag(trap_exit, true),
669+
{ok, Pid} = start_link({ok, {{one_for_one, 2, 3600}, []}}),
670+
Child1 = {child1, {supervisor_1, start_child, []},
671+
permanent, brutal_kill, worker, []},
672+
Child2 = {child2, {supervisor_1, start_child, []},
673+
permanent, 1000, worker, []},
674+
Child3 = {child3, {supervisor_1, start_child, []},
675+
permanent, 1000, worker, []},
676+
{ok, CPid1} = supervisor:start_child(sup_test, Child1),
677+
link(CPid1),
678+
{ok, CPid2} = supervisor:start_child(sup_test, Child2),
679+
link(CPid2),
680+
{ok, CPid3} = supervisor:start_child(sup_test, Child3),
681+
link(CPid3),
682+
683+
CPid3 ! {sleep, 100000},
684+
685+
supervisor:stop(Pid),
686+
687+
check_exit_reason(Pid, normal),
688+
check_exit_reason(CPid1, killed),
689+
check_exit_reason(CPid2, shutdown),
690+
check_exit_reason(CPid3, killed).
691+
692+
%%-------------------------------------------------------------------------
693+
%% Tests that children are shut down when a supervisor is stopped via
694+
%% supervisor:stop/3, even if the stop call times out.
695+
%% Since supervisors are gen_servers and the basic functionality of the
696+
%% stop functions is already tested in gen_server_SUITE, we only make
697+
%% sure that children are terminated correctly when applied to a
698+
%% supervisor.
699+
sup_stop_manual_timeout(Config) when is_list(Config) ->
700+
process_flag(trap_exit, true),
701+
{ok, Pid} = start_link({ok, {{one_for_one, 2, 3600}, []}}),
702+
Child1 = {child1, {supervisor_1, start_child, []},
703+
permanent, 5000, worker, []},
704+
Child2 = {child2, {supervisor_1, start_child, []},
705+
permanent, 1000, worker, []},
706+
{ok, CPid1} = supervisor:start_child(sup_test, Child1),
707+
link(CPid1),
708+
{ok, CPid2} = supervisor:start_child(sup_test, Child2),
709+
link(CPid2),
710+
711+
CPid1 ! {sleep, 1000},
712+
713+
try
714+
supervisor:stop(Pid, normal, 100)
715+
of
716+
ok -> ct:fail(expected_timeout)
717+
catch
718+
exit:timeout ->
719+
ok
720+
end,
721+
722+
check_exit_reason(Pid, normal),
723+
check_exit_reason(CPid1, shutdown),
724+
check_exit_reason(CPid2, shutdown).
725+
657726
%%-------------------------------------------------------------------------
658727
%% The start function provided to start a child may return {ok, Pid}
659728
%% or {ok, Pid, Info}, if it returns the latter check that the

0 commit comments

Comments
 (0)