File 0124-Purge-restarts-before-and-after-hibernation.patch of Package erlang
From dc1252fcb9ff143524b03242348db7c7ec98b6a8 Mon Sep 17 00:00:00 2001
From: Jan Uhlig <juhlig@hnc-agency.org>
Date: Wed, 16 Jul 2025 13:56:34 +0200
Subject: [PATCH] Purge restarts before and after hibernation
---
lib/sasl/test/release_handler_SUITE.erl | 2 +-
lib/stdlib/src/supervisor.erl | 48 +++++++++++++++++++------
2 files changed, 39 insertions(+), 11 deletions(-)
diff --git a/lib/sasl/test/release_handler_SUITE.erl b/lib/sasl/test/release_handler_SUITE.erl
index 6c9665c52c..e30a7f6319 100644
--- a/lib/sasl/test/release_handler_SUITE.erl
+++ b/lib/sasl/test/release_handler_SUITE.erl
@@ -1663,7 +1663,7 @@ upgrade_supervisor(Conf) when is_list(Conf) ->
%% Check that the restart strategy and child spec is updated
{status, _, {module, _}, [_, _, _, _, [_,_,{data,[{"State",State}]}|_]]} =
rpc:call(Node,sys,get_status,[a_sup]),
- {state,_,RestartStrategy,{[a],Db},_,_,_,_,_,_,_,_,_,_,_} = State,
+ {state,_,RestartStrategy,{[a],Db},_,_,_,_,_,_,_,_,_,_,_,_} = State,
one_for_all = RestartStrategy, % changed from one_for_one
{child,_,_,_,_,_,brutal_kill,_,_} = maps:get(a,Db), % changed from timeout 2000
diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl
index 9154e739b0..28996bf5b3 100644
--- a/lib/stdlib/src/supervisor.erl
+++ b/lib/stdlib/src/supervisor.erl
@@ -478,6 +478,7 @@ see more details [above](`m:supervisor#sup_flags`).
dynamic_restarts = 0 :: non_neg_integer(),
auto_shutdown = never :: auto_shutdown(),
hibernate_after = infinity :: timeout(),
+ hibernating = false :: boolean(),
tag = make_ref() :: reference(),
module,
args}).
@@ -1015,6 +1016,9 @@ do_start_child_i(M, F, A) ->
-doc false.
-spec handle_call(call(), term(), state()) -> {'reply', term(), state(), gen_server:action()}.
+handle_call(Msg, From, #state{hibernating = true} = State) ->
+ handle_call(Msg, From, wakeup(State));
+
handle_call({start_child, EArgs}, _From, State) when ?is_simple(State) ->
Child = get_dynamic_child(State),
#child{mfargs = {M, F, A}} = Child,
@@ -1201,6 +1205,9 @@ count_child(#child{pid = Pid, child_type = supervisor},
-spec handle_cast({try_again_restart, reference(), child_id() | {'restarting',pid()}}, state()) ->
{'noreply', state(), gen_server:action()} | {stop, shutdown, state()}.
+handle_cast(Msg, #state{hibernating = true} = State) ->
+ handle_cast(Msg, wakeup(State));
+
handle_cast({try_again_restart, Tag, TryAgainId}, #state{tag = Tag} = State) ->
case find_child_and_args(TryAgainId, State) of
{ok, Child = #child{pid=?restarting(_)}} ->
@@ -1222,7 +1229,10 @@ handle_cast({try_again_restart, Tag, TryAgainId}, #state{tag = Tag} = State) ->
{'noreply', state(), gen_server:action()} | {'stop', 'shutdown', state()}.
handle_info({hibernate, Tag}, #state{tag = Tag} = State) ->
- {noreply, State, hibernate};
+ {noreply, enter_hibernation(State), hibernate};
+
+handle_info(Msg, #state{hibernating = true} = State) ->
+ handle_info(Msg, wakeup(State));
handle_info({'EXIT', Pid, Reason}, State) ->
case restart_child(Pid, Reason, State) of
@@ -1279,6 +1289,14 @@ code_change(_, State, _) ->
Error
end.
+enter_hibernation(State0) ->
+ State1 = purge_restarts(State0),
+ State1#state{hibernating = true}.
+
+wakeup(State0) ->
+ State1 = purge_restarts(State0),
+ State1#state{hibernating = false}.
+
update_childspec(State, StartSpec) when ?is_simple(State) ->
case check_startspec(StartSpec, State#state.auto_shutdown) of
{ok, {[_],_}=Children} ->
@@ -2184,23 +2202,23 @@ child_to_spec(#child{id = Id,
%% shortcut: if the intensity limit is 0, no restarts are allowed;
%% it is safe to disallow the restart flat out
-add_restart(State=#state{intensity=0}) ->
+add_restart(#state{intensity = 0} = State) ->
{terminate, State};
%% shortcut: if the number of restarts is below the intensity
%% limit, it is safe to allow the restart, add the restart to
%% the list and not care about expired restarts; to prevent
%% accumulating a large list of expired restarts over time,
%% this shortcut is limited to ?DIRTY_RESTART_LIMIT restarts
-add_restart(State=#state{intensity=I, restarts=R, nrestarts=NR})
+add_restart(#state{intensity = I, restarts = R, nrestarts = NR} = State)
when NR < min(I, ?DIRTY_RESTART_LIMIT) ->
- {ok, State#state{restarts=[erlang:monotonic_time(second)|R], nrestarts=NR + 1}};
+ {ok, State#state{restarts = [erlang:monotonic_time(second)|R], nrestarts = NR + 1}};
%% calculate the real number of restarts within the period
%% and remove expired restarts; based on the calculated number
%% of restarts, allow or disallow the restart
-add_restart(State=#state{intensity=I, period=P, restarts=R}) ->
+add_restart(#state{intensity = I, period = P, restarts = R} = State) ->
Now = erlang:monotonic_time(second),
- Treshold = Now - P,
- case can_restart(I - 1, Treshold, R, [], 0) of
+ Threshold = Now - P,
+ case can_restart(I - 1, Threshold, R, [], 0) of
{true, NR1, R1} ->
{ok, State#state{restarts = [Now|R1], nrestarts = NR1 + 1}};
{false, NR1, R1} ->
@@ -2209,12 +2227,22 @@ add_restart(State=#state{intensity=I, period=P, restarts=R}) ->
can_restart(_, _, [], Acc, NR) ->
{true, NR, lists:reverse(Acc)};
-can_restart(_, Treshold, [Restart|_], Acc, NR) when Restart < Treshold ->
+can_restart(_, Threshold, [Restart|_], Acc, NR) when Restart < Threshold ->
{true, NR, lists:reverse(Acc)};
can_restart(0, _, [_|_], Acc, NR) ->
{false, NR, lists:reverse(Acc)};
-can_restart(N, Treshold, [Restart|Restarts], Acc, NR) ->
- can_restart(N - 1, Treshold, Restarts, [Restart|Acc], NR + 1).
+can_restart(N, Threshold, [Restart|Restarts], Acc, NR) ->
+ can_restart(N - 1, Threshold, Restarts, [Restart|Acc], NR + 1).
+
+purge_restarts(#state{period = P, restarts = [R|_]} = State) ->
+ case erlang:monotonic_time(second) - P of
+ Threshold when R < Threshold ->
+ State#state{restarts = [], nrestarts = 0};
+ _ ->
+ State
+ end;
+purge_restarts(State) ->
+ State.
%%% ------------------------------------------------------
%%% Error and progress reporting.
--
2.43.0