File 4505-Disallow-invalid-auto_shutdown-and-significant-combi.patch of Package erlang
From 3c86822dbdd5d09814e1b0395b0be0fd699830a1 Mon Sep 17 00:00:00 2001
From: juhlig <juhlig@hnc-agency.org>
Date: Tue, 30 Mar 2021 18:06:49 +0200
Subject: [PATCH 05/13] Disallow invalid auto_shutdown and significant
combinations
---
lib/stdlib/src/supervisor.erl | 54 ++++++++------
lib/stdlib/test/supervisor_SUITE.erl | 101 +++++++++++++++++++--------
2 files changed, 104 insertions(+), 51 deletions(-)
diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl
index 6197a58ee9..a26a8654f7 100644
--- a/lib/stdlib/src/supervisor.erl
+++ b/lib/stdlib/src/supervisor.erl
@@ -265,7 +265,7 @@ call(Supervisor, Req) ->
ChildSpecs :: [child_spec()],
Result :: 'ok' | {'error', Error :: term()}.
check_childspecs(ChildSpecs) when is_list(ChildSpecs) ->
- case check_startspec(ChildSpecs) of
+ case check_startspec(ChildSpecs, undefined) of
{ok, _} -> ok;
Error -> {error, Error}
end;
@@ -324,7 +324,7 @@ init({SupName, Mod, Args}) ->
init_children(State, StartSpec) ->
SupName = State#state.name,
- case check_startspec(StartSpec) of
+ case check_startspec(StartSpec, State#state.auto_shutdown) of
{ok, Children} ->
case start_children(Children, SupName) of
{ok, NChildren} ->
@@ -338,7 +338,7 @@ init_children(State, StartSpec) ->
end.
init_dynamic(State, [StartSpec]) ->
- case check_startspec([StartSpec]) of
+ case check_startspec([StartSpec], State#state.auto_shutdown) of
{ok, Children} ->
{ok, dyn_init(State#state{children = Children})};
Error ->
@@ -429,7 +429,7 @@ handle_call({start_child, EArgs}, _From, State) when ?is_simple(State) ->
end;
handle_call({start_child, ChildSpec}, _From, State) ->
- case check_childspec(ChildSpec) of
+ case check_childspec(ChildSpec, State#state.auto_shutdown) of
{ok, Child} ->
{Resp, NState} = handle_start_child(Child, State),
{reply, Resp, NState};
@@ -638,14 +638,14 @@ code_change(_, State, _) ->
end.
update_childspec(State, StartSpec) when ?is_simple(State) ->
- case check_startspec(StartSpec) of
+ case check_startspec(StartSpec, State#state.auto_shutdown) of
{ok, {[_],_}=Children} ->
{ok, State#state{children = Children}};
Error ->
{error, Error}
end;
update_childspec(State, StartSpec) ->
- case check_startspec(StartSpec) of
+ case check_startspec(StartSpec, State#state.auto_shutdown) of
{ok, Children} ->
OldC = State#state.children, % In reverse start order !
NewC = update_childspec1(OldC, Children, []),
@@ -1334,40 +1334,47 @@ supname(N, _) -> N.
%%% ------------------------------------------------------
%%% Check that the children start specification is valid.
%%% Input: [child_spec()]
+%%% auto_shutdown()
%%% Returns: {ok, [child_rec()]} | Error
%%% ------------------------------------------------------
-check_startspec(Children) -> check_startspec(Children, [], #{}).
+check_startspec(Children, AutoShutdown) ->
+ check_startspec(Children, [], #{}, AutoShutdown).
-check_startspec([ChildSpec|T], Ids, Db) ->
- case check_childspec(ChildSpec) of
+check_startspec([ChildSpec|T], Ids, Db, AutoShutdown) ->
+ case check_childspec(ChildSpec, AutoShutdown) of
{ok, #child{id=Id}=Child} ->
case maps:is_key(Id, Db) of
%% The error message duplicate_child_name is kept for
%% backwards compatibility, although
%% duplicate_child_id would be more correct.
true -> {duplicate_child_name, Id};
- false -> check_startspec(T, [Id | Ids], Db#{Id=>Child})
+ false -> check_startspec(T, [Id | Ids], Db#{Id=>Child},
+ AutoShutdown)
end;
Error -> Error
end;
-check_startspec([], Ids, Db) ->
+check_startspec([], Ids, Db, _AutoShutdown) ->
{ok, {lists:reverse(Ids),Db}}.
-check_childspec(ChildSpec) when is_map(ChildSpec) ->
- catch do_check_childspec(maps:merge(?default_child_spec,ChildSpec));
-check_childspec({Id, Func, RestartType, Shutdown, ChildType, Mods}) ->
+check_childspec(ChildSpec, AutoShutdown) when is_map(ChildSpec) ->
+ catch do_check_childspec(maps:merge(?default_child_spec,ChildSpec),
+ AutoShutdown);
+check_childspec({Id, Func, RestartType, Shutdown, ChildType, Mods},
+ AutoShutdown) ->
check_childspec(#{id => Id,
start => Func,
restart => RestartType,
significant => false,
shutdown => Shutdown,
type => ChildType,
- modules => Mods});
-check_childspec(X) -> {invalid_child_spec, X}.
+ modules => Mods},
+ AutoShutdown);
+check_childspec(X, _AutoShutdown) -> {invalid_child_spec, X}.
do_check_childspec(#{restart := RestartType,
- type := ChildType} = ChildSpec)->
+ type := ChildType} = ChildSpec,
+ AutoShutdown)->
Id = case ChildSpec of
#{id := I} -> I;
_ -> throw(missing_id)
@@ -1383,7 +1390,7 @@ do_check_childspec(#{restart := RestartType,
#{significant := Signf} -> Signf;
_ -> false
end,
- validSignificant(Significant),
+ validSignificant(Significant, RestartType, AutoShutdown),
validChildType(ChildType),
Shutdown = case ChildSpec of
#{shutdown := S} -> S;
@@ -1416,8 +1423,15 @@ validRestartType(temporary) -> true;
validRestartType(transient) -> true;
validRestartType(RestartType) -> throw({invalid_restart_type, RestartType}).
-validSignificant(Significant) when is_boolean(Significant) -> true;
-validSignificant(Significant) -> throw({invalid_significant, Significant}).
+validSignificant(true, permanent, _AutoShutdown) ->
+ throw({invalid_significant, true});
+validSignificant(true, _RestartType, never) ->
+ throw({invalid_significant, true});
+validSignificant(Significant, _RestartType, _AutoShutdown)
+ when is_boolean(Significant) ->
+ true;
+validSignificant(Significant, _RestartType, _AutoShutdown) ->
+ throw({invalid_significant, Significant}).
validShutdown(Shutdown)
when is_integer(Shutdown), Shutdown > 0 -> true;
diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl
index d6c74d098e..c38b51487f 100644
--- a/lib/stdlib/test/supervisor_SUITE.erl
+++ b/lib/stdlib/test/supervisor_SUITE.erl
@@ -758,7 +758,7 @@ child_specs(Config) when is_list(Config) ->
%% Tests child specs (map form), invalid formats should be rejected.
child_specs_map(Config) when is_list(Config) ->
process_flag(trap_exit, true),
- {ok, Pid} = start_link({ok, {{one_for_one, 2, 3600}, []}}),
+ {ok, Pid} = start_link({ok, {#{}, []}}),
{error, _} = supervisor:start_child(sup_test, hej),
CS0 = #{id => child, start => {m, f, [a]}},
@@ -805,9 +805,16 @@ child_specs_map(Config) when is_list(Config) ->
supervisor:check_childspecs([B10]),
lists:foreach(
- fun (ChildSpec) ->
- ChildSpec1 = maps:filter(fun (_, V) -> V =/= undefined end, ChildSpec),
- ok = supervisor:check_childspecs([ChildSpec1])
+ fun
+ (ChildSpec = #{restart := undefined, significant := true}) ->
+ ChildSpec1 = maps:filter(fun (_, V) -> V =/= undefined end, ChildSpec),
+ {error, {invalid_significant, true}} = supervisor:check_childspecs([ChildSpec1]);
+ (ChildSpec = #{restart := permanent, significant := true}) ->
+ ChildSpec1 = maps:filter(fun (_, V) -> V =/= undefined end, ChildSpec),
+ {error, {invalid_significant, true}} = supervisor:check_childspecs([ChildSpec1]);
+ (ChildSpec) ->
+ ChildSpec1 = maps:filter(fun (_, V) -> V =/= undefined end, ChildSpec),
+ ok = supervisor:check_childspecs([ChildSpec1])
end,
[
CS0#{restart => Restart,
@@ -842,6 +849,10 @@ child_specs_map(Config) when is_list(Config) ->
{error,{bad_start_spec,[CS0,CS0]}} =
start_link({ok, {{simple_one_for_one, 2, 3600}, [CS0,CS0]}}),
+ %% auto_shutdown => never should not accept significant children
+ {error, {start_spec, {invalid_significant, true}}} =
+ start_link({ok, {#{auto_shutdown => never}, [CS0#{significant => true}]}}),
+
ok.
%%-------------------------------------------------------------------------
@@ -3184,17 +3195,15 @@ significant_upgrade_never_any(_Config) ->
restart => transient,
significant => true},
{ok, Sup1} = start_link({ok, {#{auto_shutdown => never}, []}}),
- {ok, ChildPid1} = supervisor:start_child(Sup1, Child1),
- {ok, ChildPid2} = supervisor:start_child(Sup1, Child2),
- link(ChildPid1),
- link(ChildPid2),
+ {error, {invalid_significant, true}} = supervisor:start_child(Sup1, Child1),
S1 = sys:get_state(Sup1),
ok = fake_upgrade(Sup1, {ok, {#{auto_shutdown => any_significant}, []}}),
S2 = sys:get_state(Sup1),
true = (S1 /= S2),
- error = check_exit([ChildPid1], 1000),
- error = check_exit([ChildPid2], 1000),
- error = check_exit([Sup1], 1000),
+ {ok, ChildPid1} = supervisor:start_child(Sup1, Child1),
+ {ok, ChildPid2} = supervisor:start_child(Sup1, Child2),
+ link(ChildPid1),
+ link(ChildPid2),
terminate(ChildPid1, normal),
ok = check_exit([ChildPid1, ChildPid2, Sup1]),
ok.
@@ -3206,6 +3215,10 @@ significant_upgrade_any_never(_Config) ->
start => {supervisor_1, start_child, []},
restart => transient,
significant => true},
+ Child2 = #{id => child2,
+ start => {supervisor_1, start_child, []},
+ restart => transient,
+ significant => true},
{ok, Sup1} = start_link({ok, {#{auto_shutdown => any_significant}, []}}),
{ok, ChildPid1} = supervisor:start_child(Sup1, Child1),
link(ChildPid1),
@@ -3215,9 +3228,14 @@ significant_upgrade_any_never(_Config) ->
true = (S1 /= S2),
error = check_exit([ChildPid1], 1000),
error = check_exit([Sup1], 1000),
+ {error, {invalid_significant, true}} = supervisor:start_child(Sup1, Child2),
terminate(ChildPid1, normal),
ok = check_exit([ChildPid1]),
error = check_exit([Sup1], 1000),
+ {ok, ChildPid2} = supervisor:restart_child(Sup1, child1),
+ link(ChildPid2),
+ terminate(Sup1, shutdown),
+ ok = check_exit([ChildPid2, Sup1]),
ok.
% Test upgrading auto-shutdown from never to all_significant.
@@ -3232,17 +3250,15 @@ significant_upgrade_never_all(_Config) ->
restart => transient,
significant => true},
{ok, Sup1} = start_link({ok, {#{auto_shutdown => never}, []}}),
- {ok, ChildPid1} = supervisor:start_child(Sup1, Child1),
- {ok, ChildPid2} = supervisor:start_child(Sup1, Child2),
- link(ChildPid1),
- link(ChildPid2),
+ {error, {invalid_significant, true}} = supervisor:start_child(Sup1, Child1),
S1 = sys:get_state(Sup1),
ok = fake_upgrade(Sup1, {ok, {#{auto_shutdown => all_significant}, []}}),
S2 = sys:get_state(Sup1),
true = (S1 /= S2),
- error = check_exit([ChildPid1], 1000),
- error = check_exit([ChildPid2], 1000),
- error = check_exit([Sup1], 1000),
+ {ok, ChildPid1} = supervisor:start_child(Sup1, Child1),
+ {ok, ChildPid2} = supervisor:start_child(Sup1, Child2),
+ link(ChildPid1),
+ link(ChildPid2),
terminate(ChildPid1, normal),
ok = check_exit([ChildPid1]),
error = check_exit([ChildPid2], 1000),
@@ -3258,6 +3274,10 @@ significant_upgrade_all_never(_Config) ->
start => {supervisor_1, start_child, []},
restart => transient,
significant => true},
+ Child2 = #{id => child2,
+ start => {supervisor_1, start_child, []},
+ restart => transient,
+ significant => true},
{ok, Sup1} = start_link({ok, {#{auto_shutdown => all_significant}, []}}),
{ok, ChildPid1} = supervisor:start_child(Sup1, Child1),
link(ChildPid1),
@@ -3267,9 +3287,14 @@ significant_upgrade_all_never(_Config) ->
true = (S1 /= S2),
error = check_exit([ChildPid1], 1000),
error = check_exit([Sup1], 1000),
+ {error, {invalid_significant, true}} = supervisor:start_child(Sup1, Child2),
terminate(ChildPid1, normal),
ok = check_exit([ChildPid1]),
error = check_exit([Sup1], 1000),
+ {ok, ChildPid2} = supervisor:restart_child(Sup1, child1),
+ link(ChildPid2),
+ terminate(Sup1, shutdown),
+ ok = check_exit([ChildPid2, Sup1]),
ok.
% Test upgrading auto-shutdown from any_significant to all_significant.
@@ -3343,36 +3368,50 @@ significant_upgrade_child(_Config) ->
restart => transient,
significant => true},
- % Start with a non-significant child, upgrade it to significant
- % and ensure that it triggers auto-shutdown.
- {ok, Sup1} = start_link({ok, {#{auto_shutdown => any_significant}, [Child1]}}),
+ % A supervisor with auto-shutdown set to never should not allow upgrading
+ % a non-significant child to significant.
+ {ok, Sup1} = start_link({ok, {#{auto_shutdown => never}, [Child1]}}),
[{child, ChildPid1, _, _}] = supervisor:which_children(Sup1),
link(ChildPid1),
S1_1 = sys:get_state(Sup1),
- ok = fake_upgrade(Sup1, {ok, {#{auto_shutdown => any_significant}, [Child2]}}),
+ {error, _} = fake_upgrade(Sup1, {ok, {#{auto_shutdown => never}, [Child2]}}),
S1_2 = sys:get_state(Sup1),
true = (S1_1 /= S1_2),
error = check_exit([ChildPid1], 1000),
error = check_exit([Sup1], 1000),
- terminate(ChildPid1, normal),
+ terminate(Sup1, shutdown),
ok = check_exit([ChildPid1, Sup1]),
- % Start with a significant child, upgrade it to non-significant
- % and ensure that it does not trigger auto-shutdown.
- {ok, Sup2} = start_link({ok, {#{auto_shutdown => any_significant}, [Child2]}}),
+ % Start with a non-significant child, upgrade it to significant
+ % and ensure that it triggers auto-shutdown.
+ {ok, Sup2} = start_link({ok, {#{auto_shutdown => any_significant}, [Child1]}}),
[{child, ChildPid2, _, _}] = supervisor:which_children(Sup2),
link(ChildPid2),
S2_1 = sys:get_state(Sup2),
- ok = fake_upgrade(Sup2, {ok, {#{auto_shutdown => any_significant}, [Child1]}}),
+ ok = fake_upgrade(Sup2, {ok, {#{auto_shutdown => any_significant}, [Child2]}}),
S2_2 = sys:get_state(Sup2),
true = (S2_1 /= S2_2),
error = check_exit([ChildPid2], 1000),
error = check_exit([Sup2], 1000),
terminate(ChildPid2, normal),
- ok = check_exit([ChildPid2]),
- error = check_exit([Sup2], 1000),
- terminate(Sup2, shutdown),
- ok = check_exit([Sup2]),
+ ok = check_exit([ChildPid2, Sup2]),
+
+ % Start with a significant child, upgrade it to non-significant
+ % and ensure that it does not trigger auto-shutdown.
+ {ok, Sup3} = start_link({ok, {#{auto_shutdown => any_significant}, [Child2]}}),
+ [{child, ChildPid3, _, _}] = supervisor:which_children(Sup3),
+ link(ChildPid3),
+ S3_1 = sys:get_state(Sup3),
+ ok = fake_upgrade(Sup3, {ok, {#{auto_shutdown => any_significant}, [Child1]}}),
+ S3_2 = sys:get_state(Sup3),
+ true = (S3_1 /= S3_2),
+ error = check_exit([ChildPid3], 1000),
+ error = check_exit([Sup3], 1000),
+ terminate(ChildPid3, normal),
+ ok = check_exit([ChildPid3]),
+ error = check_exit([Sup3], 1000),
+ terminate(Sup3, shutdown),
+ ok = check_exit([Sup3]),
ok.
--
2.26.2