File 1022-Disallow-auto-shutdown-for-simple_one_for_one.patch of Package erlang
From 0898c3a04422f123bd6a5606d1d5561475fa16d2 Mon Sep 17 00:00:00 2001
From: Maria Scott <maria-12648430@hnc-agency.org>
Date: Mon, 11 Mar 2024 08:52:05 +0100
Subject: [PATCH 2/2] Disallow auto-shutdown for simple_one_for_one
---
lib/stdlib/src/supervisor.erl | 16 +++++------
lib/stdlib/test/supervisor_SUITE.erl | 42 +++++++++-------------------
2 files changed, 21 insertions(+), 37 deletions(-)
diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl
index b87b73ff3c..2000f9246a 100644
--- a/lib/stdlib/src/supervisor.erl
+++ b/lib/stdlib/src/supervisor.erl
@@ -1311,14 +1311,6 @@ do_auto_shutdown(Child, State) when not ?is_significant(Child) ->
{ok, State};
do_auto_shutdown(_Child, State=#state{auto_shutdown = any_significant}) ->
{shutdown, State};
-do_auto_shutdown(_Child, State=#state{auto_shutdown = all_significant})
- when ?is_simple(State) ->
- case dyn_size(State) of
- 0 ->
- {shutdown, State};
- _ ->
- {ok, State}
- end;
do_auto_shutdown(_Child, State=#state{auto_shutdown = all_significant}) ->
case
children_any(
@@ -1905,6 +1897,7 @@ do_check_flags(#{strategy := Strategy,
validIntensity(MaxIntensity),
validPeriod(Period),
validAutoShutdown(AutoShutdown),
+ validAutoShutdownForStrategy(AutoShutdown, Strategy),
Flags.
validStrategy(simple_one_for_one) -> true;
@@ -1926,6 +1919,13 @@ validAutoShutdown(any_significant) -> true;
validAutoShutdown(all_significant) -> true;
validAutoShutdown(What) -> throw({invalid_auto_shutdown, What}).
+validAutoShutdownForStrategy(any_significant, simple_one_for_one) ->
+ throw({bad_combination, [{auto_shutdown, any_significant}, {strategy, simple_one_for_one}]});
+validAutoShutdownForStrategy(all_significant, simple_one_for_one) ->
+ throw({bad_combination, [{auto_shutdown, all_significant}, {strategy, simple_one_for_one}]});
+validAutoShutdownForStrategy(_AutoShutdown, _Strategy) ->
+ true.
+
supname(self, Mod) -> {self(), Mod};
supname(N, _) -> N.
diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl
index 84af3c809e..b9fe0bacc5 100644
--- a/lib/stdlib/test/supervisor_SUITE.erl
+++ b/lib/stdlib/test/supervisor_SUITE.erl
@@ -3339,41 +3339,25 @@ significant_transient(_Config) ->
ok.
-% Test the auto-shutdown feature in a simple_one_for_one supervisor.
+% The auto-shutdown feature is not allowed with simple_one_for_one supervisors.
significant_simple(_Config) ->
process_flag(trap_exit, true),
Child1 = #{id => child1,
- start => {supervisor_1, start_child, []},
- restart => temporary,
- significant => true},
+ start => {supervisor_1, start_child, []}},
- % Test auto-shutdown on the exit of any significant child.
- {ok, Sup1} = start_link({ok, {#{strategy => simple_one_for_one,
- auto_shutdown => any_significant},
- [Child1]}}),
- {ok, ChildPid1_1} = supervisor:start_child(Sup1, []),
- {ok, ChildPid1_2} = supervisor:start_child(Sup1, []),
- link(ChildPid1_1),
- link(ChildPid1_2),
- terminate(ChildPid1_1, normal),
- ok = check_exit([ChildPid1_1, ChildPid1_2, Sup1]),
+ {error, {supervisor_data, {bad_combination, _}}} = start_link({ok, {#{strategy => simple_one_for_one,
+ auto_shutdown => any_significant},
+ [Child1]}}),
- % Test auto-shutdown on the exit of all significant children.
- {ok, Sup2} = start_link({ok, {#{strategy => simple_one_for_one,
- auto_shutdown => all_significant},
- [Child1]}}),
- {ok, ChildPid2_1} = supervisor:start_child(Sup2, []),
- {ok, ChildPid2_2} = supervisor:start_child(Sup2, []),
- link(ChildPid2_1),
- link(ChildPid2_2),
- terminate(ChildPid2_1, normal),
- ok = check_exit([ChildPid2_1]),
- error = check_exit([ChildPid2_2], 1000),
- error = check_exit([Sup2], 1000),
- terminate(ChildPid2_2, normal),
- ok = check_exit([ChildPid2_2, Sup2]),
+ {error, {supervisor_data, {bad_combination, _}}} = start_link({ok, {#{strategy => simple_one_for_one,
+ auto_shutdown => all_significant},
+ [Child1]}}),
- ok.
+ {ok, SupPid} = start_link({ok, {#{strategy => simple_one_for_one,
+ auto_shutdown => never},
+ [Child1]}}),
+ terminate(SupPid, shutdown),
+ check_exit([SupPid]).
% Test that terminations of significant children caused by
% the death of a sibling does not trigger auto-shutdown.
--
2.35.3