Skip to content

Commit

Permalink
[logger_olp] Avoid repeated calls to persistent_term:put
Browse files Browse the repository at this point in the history
`logger_otp` would call back to `persistent_term:put` on each iteration even when the mode wouldn't actually change. Even though `persistent_term:put` guards against changing value to the same avoiding the most expensive operations, it still aquires some locks and does potentially other fairly expensive work. We can avoid this with a simple check in `logger_olp` to try and update the value only if it has actually changed.
  • Loading branch information
michalmuskala committed Jun 29, 2024
1 parent e424399 commit effc59c
Showing 1 changed file with 23 additions and 21 deletions.
44 changes: 23 additions & 21 deletions lib/kernel/src/logger_olp.erl
Original file line number Diff line number Diff line change
Expand Up @@ -174,7 +174,7 @@ init([Name,Module,Args,Options]) ->
put(olp_ref,OlpRef),
try Module:init(Args) of
{ok,CBState} ->
set_mode(ModeRef, async),
set_mode(ModeRef, async, undefined),
T0 = ?timestamp(),
proc_lib:init_ack({ok,self(),OlpRef}),
%% Storing options in state to avoid copying
Expand Down Expand Up @@ -261,11 +261,11 @@ handle_cast(Msg, #{module:=Module, cb_state:=CBState} = State) ->
{stop, Reason, State#{cb_state=>CBState1}}
end.

handle_info(timeout, #{mode_ref:=ModeRef} = State) ->
handle_info(timeout, #{mode_ref:=ModeRef,mode:=Mode} = State) ->
State1 = notify(idle,State),
State2 = maybe_notify_mode_change(async,State1),
State2 = maybe_notify_mode_change(async,Mode,State1),
{noreply, State2#{idle => true,
mode => set_mode(ModeRef, async),
mode => set_mode(ModeRef, async, Mode),
burst_msg_count => 0}};
handle_info(Msg, #{module := Module, cb_state := CBState} = State) ->
case try_callback_call(Module,handle_info,[Msg, CBState]) of
Expand Down Expand Up @@ -344,7 +344,7 @@ do_load(Msg, CallOrCast, State) ->

%% this function is called by do_load/3 after an overload check
%% has been performed, where QLen > FlushQLen
flush(T1, State=#{id := _Name, last_load_ts := _T0, mode_ref := ModeRef}) ->
flush(T1, State=#{id := _Name, last_load_ts := _T0, mode_ref := ModeRef, mode := Mode}) ->
%% flush load messages in the mailbox (a limited number in order
%% to not cause long delays)
NewFlushed = flush_load(?FLUSH_MAX_N),
Expand All @@ -363,9 +363,9 @@ flush(T1, State=#{id := _Name, last_load_ts := _T0, mode_ref := ModeRef}) ->

State2 = ?update_max_time(?diff_time(T1,_T0),State1),
State3 = ?update_max_qlen(QLen1,State2),
State4 = maybe_notify_mode_change(async,State3),
State4 = maybe_notify_mode_change(async,Mode,State3),
{dropped,?update_other(flushed,FLUSHED,NewFlushed,
State4#{mode => set_mode(ModeRef,async),
State4#{mode => set_mode(ModeRef,async,Mode),
last_qlen => QLen1,
last_load_ts => T1})}.

Expand Down Expand Up @@ -494,16 +494,16 @@ check_load(State = #{id:=_Name, mode_ref := ModeRef, mode := Mode,
%% be dropped on the client side (never sent to
%% the olp process).
IncDrops = if Mode == drop -> 0; true -> 1 end,
{set_mode(ModeRef, drop), IncDrops,0};
{set_mode(ModeRef, drop, Mode), IncDrops,0};
QLen >= SyncModeQLen ->
{set_mode(ModeRef, sync), 0,0};
{set_mode(ModeRef, sync, Mode), 0,0};
true ->
{set_mode(ModeRef, async), 0,0}
{set_mode(ModeRef, async, Mode), 0,0}
end,
State1 = ?update_other(drops,DROPS,_NewDrops,State),
State2 = ?update_max_qlen(QLen,State1),
State3 = ?update_max_mem(Mem,State2),
State4 = maybe_notify_mode_change(Mode1,State3),
State4 = maybe_notify_mode_change(Mode1,Mode,State3),
{Mode1, QLen, Mem,
?update_other(flushes,FLUSHES,_NewFlushes,
State4#{last_qlen => QLen})}.
Expand Down Expand Up @@ -594,16 +594,18 @@ overload_levels_ok(Options) ->

get_mode(Ref) -> persistent_term:get(Ref, async).

set_mode(Ref, M) ->
true = is_atom(M), persistent_term:put(Ref, M), M.

maybe_notify_mode_change(drop,#{mode:=Mode0}=State)
when Mode0=/=drop ->
notify({mode_change,Mode0,drop},State);
maybe_notify_mode_change(Mode1,#{mode:=drop}=State)
when Mode1==async; Mode1==sync ->
notify({mode_change,drop,Mode1},State);
maybe_notify_mode_change(_,State) ->
set_mode(_Ref, NewMode, OldMode) when NewMode =:= OldMode -> NewMode;
set_mode(Ref, NewMode, _OldMode) when is_atom(NewMode) ->
persistent_term:put(Ref, NewMode),
NewMode.

maybe_notify_mode_change(drop,OldMode,State)
when OldMode=/=drop ->
notify({mode_change,OldMode,drop},State);
maybe_notify_mode_change(NewMode,drop,State)
when NewMode==async; NewMode==sync ->
notify({mode_change,drop,NewMode},State);
maybe_notify_mode_change(_,_,State) ->
State.

notify(Note,#{module:=Module,cb_state:=CBState}=State) ->
Expand Down

0 comments on commit effc59c

Please sign in to comment.