File 6711-Introduce-supervisor-stop-1-3.patch of Package erlang
From cb02c7a7ef82893d4f516ab4a6bd39ef7c89a3c6 Mon Sep 17 00:00:00 2001
From: Maria Scott <maria-12648430@hnc-agency.org>
Date: Tue, 17 Dec 2024 09:55:51 +0100
Subject: [PATCH] Introduce supervisor:stop/1,3
---
lib/stdlib/src/supervisor.erl | 42 +++++++++++++++-
lib/stdlib/test/supervisor_1.erl | 4 +-
lib/stdlib/test/supervisor_SUITE.erl | 71 +++++++++++++++++++++++++++-
3 files changed, 112 insertions(+), 5 deletions(-)
diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl
index 9154e739b0..6d64b58722 100644
--- a/lib/stdlib/src/supervisor.erl
+++ b/lib/stdlib/src/supervisor.erl
@@ -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,
@@ -829,6 +830,14 @@ processes:
count_children(Supervisor) ->
call(Supervisor, count_children).
+-spec stop(SupRef :: sup_ref()) -> ok.
+stop(Supervisor) ->
+ gen_server:stop(Supervisor).
+
+-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).
diff --git a/lib/stdlib/test/supervisor_1.erl b/lib/stdlib/test/supervisor_1.erl
index 0bc4c21cfc..39ded5357d 100644
--- a/lib/stdlib/test/supervisor_1.erl
+++ b/lib/stdlib/test/supervisor_1.erl
@@ -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}.
diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl
index 54c02108f2..9b1dbc72b8 100644
--- a/lib/stdlib/test/supervisor_SUITE.erl
+++ b/lib/stdlib/test/supervisor_SUITE.erl
@@ -47,6 +47,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,
+ 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]).
@@ -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, [],
@@ -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
--
2.51.0