File 0108-logger-Fix-repeated-filesync-shutdown-timeout.patch of Package erlang
From 3bb17665ea77e1b549ae3f3da2c9189f019620ad Mon Sep 17 00:00:00 2001
From: Lukas Larsson <lukas@erlang.org>
Date: Mon, 28 Mar 2022 11:02:07 +0200
Subject: [PATCH] logger: Fix repeated filesync shutdown timeout
The commit 06cacbc (aka PR #4811) changed where the timer_server
is located in the supervisor tree of Kernel. This change caused
the timer_server to be terminated before logger, which meant that
the calls to timer:cancel from any logger backend would timeout.
We solve this by instead using erlang:start_timer for the repeated
filesync timer.
Closes #5780
---
lib/kernel/src/logger_h_common.erl | 58 ++++++++++++---------
lib/kernel/test/logger_disk_log_h_SUITE.erl | 11 ++--
lib/kernel/test/logger_std_h_SUITE.erl | 9 ++--
3 files changed, 47 insertions(+), 31 deletions(-)
diff --git a/lib/kernel/src/logger_h_common.erl b/lib/kernel/src/logger_h_common.erl
index bbd45ac73d..f0db587af1 100644
--- a/lib/kernel/src/logger_h_common.erl
+++ b/lib/kernel/src/logger_h_common.erl
@@ -260,17 +260,39 @@ handle_call(filesync, _From, State = #{id := Name,
{Result,HandlerState1} = Module:filesync(Name,sync,HandlerState),
{reply, Result, State#{handler_state=>HandlerState1, last_op=>sync}}.
+handle_cast({config_changed, CommonConfig, HConfig},
+ State = #{id := Name,
+ module := Module,
+ handler_state := HandlerState,
+ filesync_repeat_interval := OldFSyncInt}) ->
+ State1 =
+ case maps:get(filesync_repeat_interval,CommonConfig) of
+ OldFSyncInt ->
+ State;
+ FSyncInt ->
+ set_repeated_filesync(
+ cancel_repeated_filesync(
+ State#{filesync_repeat_interval=>FSyncInt}))
+ end,
+ HS = try Module:config_changed(Name, HConfig, HandlerState)
+ catch error:undef -> HandlerState
+ end,
+ {noreply, State1#{handler_state => HS}}.
+
%% If FILESYNC_REPEAT_INTERVAL is set to a millisec value, this
%% clause gets called repeatedly by the handler. In order to
%% guarantee that a filesync *always* happens after the last log
%% event, the repeat operation must be active!
-handle_cast(repeated_filesync,State = #{filesync_repeat_interval := no_repeat}) ->
+handle_info({timeout, TRef, repeated_filesync},
+ State = #{rep_sync_tref := TRef,
+ filesync_repeat_interval := no_repeat}) ->
%% This clause handles a race condition which may occur when
%% config changes filesync_repeat_interval from an integer value
%% to no_repeat.
{noreply,State};
-handle_cast(repeated_filesync,
+handle_info({timeout, TRef, repeated_filesync},
State = #{id := Name,
+ rep_sync_tref := TRef,
module := Module,
handler_state := HandlerState,
last_op := LastOp}) ->
@@ -282,25 +304,6 @@ handle_cast(repeated_filesync,
State#{handler_state => HS, last_op => sync}
end,
{noreply,set_repeated_filesync(State1)};
-handle_cast({config_changed, CommonConfig, HConfig},
- State = #{id := Name,
- module := Module,
- handler_state := HandlerState,
- filesync_repeat_interval := OldFSyncInt}) ->
- State1 =
- case maps:get(filesync_repeat_interval,CommonConfig) of
- OldFSyncInt ->
- State;
- FSyncInt ->
- set_repeated_filesync(
- cancel_repeated_filesync(
- State#{filesync_repeat_interval=>FSyncInt}))
- end,
- HS = try Module:config_changed(Name, HConfig, HandlerState)
- catch error:undef -> HandlerState
- end,
- {noreply, State1#{handler_state => HS}}.
-
handle_info(Info, #{id := Name, module := Module,
handler_state := HandlerState} = State) ->
{noreply,State#{handler_state => Module:handle_info(Name,Info,HandlerState)}}.
@@ -445,8 +448,7 @@ get_default_config() ->
set_repeated_filesync(#{filesync_repeat_interval:=FSyncInt} = State)
when is_integer(FSyncInt) ->
- {ok,TRef} = timer:apply_after(FSyncInt, gen_server, cast,
- [self(),repeated_filesync]),
+ TRef = erlang:start_timer(FSyncInt, self(), repeated_filesync),
State#{rep_sync_tref=>TRef};
set_repeated_filesync(State) ->
State.
@@ -454,7 +456,15 @@ set_repeated_filesync(State) ->
cancel_repeated_filesync(State) ->
case maps:take(rep_sync_tref,State) of
{TRef,State1} ->
- _ = timer:cancel(TRef),
+ case erlang:cancel_timer(TRef) of
+ false ->
+ %% Flush the timer message
+ receive
+ {timeout, TRef, _} -> ok
+ end;
+ _ ->
+ ok
+ end,
State1;
error ->
State
diff --git a/lib/kernel/test/logger_disk_log_h_SUITE.erl b/lib/kernel/test/logger_disk_log_h_SUITE.erl
index a4e4e52309..2c7a43faa7 100644
--- a/lib/kernel/test/logger_disk_log_h_SUITE.erl
+++ b/lib/kernel/test/logger_disk_log_h_SUITE.erl
@@ -656,10 +656,10 @@ sync(Config) ->
%% switch repeated filesync on and verify that the looping works
SyncInt = 1000,
WaitT = 4500,
- OneSync = {logger_h_common,handle_cast,repeated_filesync},
+ OneSync = {logger_h_common,handle_info,{timeout,repeated_filesync}},
%% receive 1 repeated_filesync per sec
- start_tracer([{{logger_h_common,handle_cast,2},
- [{[repeated_filesync,'_'],[],[{message,{caller}}]}]}],
+ start_tracer([{{logger_h_common,handle_info,2},
+ [{[{timeout,'_',repeated_filesync},'_'],[],[{message,{caller}}]}]}],
[OneSync || _ <- lists:seq(1, trunc(WaitT/SyncInt))]),
HConfig2 = HConfig#{filesync_repeat_interval => SyncInt},
@@ -1610,13 +1610,16 @@ tpl([{{M,F,A},MS}|Trace]) ->
tpl([]) ->
ok.
-tracer({trace,_,call,{logger_h_common,handle_cast,[Op|_]},Caller},
+tracer({trace,_,call,{logger_h_common = Mod,handle_cast = Func,[Op|_]},Caller},
{Pid,[{Mod,Func,Op}|Expected]}) ->
maybe_tracer_done(Pid,Expected,{Mod,Func,Op},Caller);
tracer({trace,_,call,{Mod=logger_disk_log_h,Func=disk_log_write,[_,_,Data]},Caller}, {Pid,[{Mod,Func,Data}|Expected]}) ->
maybe_tracer_done(Pid,Expected,{Mod,Func,Data},Caller);
tracer({trace,_,call,{Mod,Func,_},Caller}, {Pid,[{Mod,Func}|Expected]}) ->
maybe_tracer_done(Pid,Expected,{Mod,Func},Caller);
+tracer({trace,_,call,{logger_h_common = Mod,handle_info = Func,[{timeout,_,Op},_S]},Caller},
+ {Pid,[{Mod,Func,{timeout,Op}}|Expected]}) ->
+ maybe_tracer_done(Pid,Expected,{Mod,Func},Caller);
tracer({trace,_,call,Call,Caller}, {Pid,Expected}) ->
ct:log("Tracer got unexpected: ~p~nCaller: ~p~nExpected: ~p~n",[Call,Caller,Expected]),
Pid ! {tracer_got_unexpected,Call,Expected},
diff --git a/lib/kernel/test/logger_std_h_SUITE.erl b/lib/kernel/test/logger_std_h_SUITE.erl
index 08962eec0f..33310e8fad 100644
--- a/lib/kernel/test/logger_std_h_SUITE.erl
+++ b/lib/kernel/test/logger_std_h_SUITE.erl
@@ -817,10 +817,10 @@ sync(Config) ->
%% switch repeated filesync on and verify that the looping works
SyncInt = 1000,
WaitT = 4500,
- OneSync = {logger_h_common,handle_cast,repeated_filesync},
+ OneSync = {logger_h_common,handle_info,{timeout,repeated_filesync}},
%% receive 1 repeated_filesync per sec
- start_tracer([{{logger_h_common,handle_cast,2},
- [{[repeated_filesync,'_'],[],[]}]}],
+ start_tracer([{{logger_h_common,handle_info,2},
+ [{[{timeout,'_',repeated_filesync},'_'],[],[]}]}],
[OneSync || _ <- lists:seq(1, trunc(WaitT/SyncInt))]),
ok = logger:update_handler_config(?MODULE, config,
@@ -2182,6 +2182,9 @@ tracer({trace,_,call,{Mod=logger_std_h,Func=write_to_dev,[Data,_]}},
maybe_tracer_done(Pid,Expected,{Mod,Func,Data});
tracer({trace,_,call,{Mod,Func,_}}, {Pid,[{Mod,Func}|Expected]}) ->
maybe_tracer_done(Pid,Expected,{Mod,Func});
+tracer({trace,_,call,{logger_h_common = Mod,handle_info = Func,[{timeout,_,Op},_S]}},
+ {Pid,[{Mod,Func,{timeout,Op}}|Expected]}) ->
+ maybe_tracer_done(Pid,Expected,{Mod,Func});
tracer({trace,_,call,Call}, {Pid,Expected}) ->
ct:log("Tracer got unexpected: ~p~nExpected: ~p~n",[Call,Expected]),
Pid ! {tracer_got_unexpected,Call,Expected},
--
2.34.1