Skip to content

Commit

Permalink
Augment gen_server timeout handling
Browse files Browse the repository at this point in the history
Co-authored-by: Jan Uhlig <[email protected]>
  • Loading branch information
Maria-12648430 and juhlig committed Jan 13, 2025
1 parent 9c918d8 commit 9789858
Showing 1 changed file with 52 additions and 1 deletion.
53 changes: 52 additions & 1 deletion lib/stdlib/src/gen_server.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2058,7 +2058,7 @@ With argument `How` equivalent to
Module :: module(),
Options :: [enter_loop_opt()],
State :: term(),
How :: timeout() | 'hibernate' | {'continue', term()}
How :: timeout() | {'timeout', timeout(), term()} | 'hibernate' | {'continue', term()}
) ->
no_return().
%%
Expand All @@ -2071,6 +2071,10 @@ enter_loop(Mod, Options, State, ServerName = {via, _, _})
when is_atom(Mod), is_list(Options) ->
enter_loop(Mod, Options, State, ServerName, infinity);
%%
enter_loop(Mod, Options, State, {timeout, Time, _} = Timeout)
when is_atom(Mod), is_list(Options), ?is_timeout(Time) ->
enter_loop(Mod, Options, State, self(), Timeout);
%%
enter_loop(Mod, Options, State, TimeoutOrHibernate)
when is_atom(Mod), is_list(Options), ?is_timeout(TimeoutOrHibernate);
is_atom(Mod), is_list(Options), TimeoutOrHibernate =:= hibernate ->
Expand Down Expand Up @@ -2143,6 +2147,15 @@ according to `ServerName`.
) ->
no_return().
%%
enter_loop(Mod, Options, State, ServerName, {timeout, Time, _} = Timeout)
when is_atom(Mod), is_list(Options), ?is_timeout(Time) ->
Name = gen:get_proc_name(ServerName),
Parent = gen:get_parent(),
Debug = gen:debug_options(Name, Options),
HibernateAfterTimeout = gen:hibernate_after(Options),
CbCache = create_callback_cache(Mod),
loop(Parent, Name, State, CbCache, Timeout, HibernateAfterTimeout, Debug);
%%
enter_loop(Mod, Options, State, ServerName, TimeoutOrHibernate)
when is_atom(Mod), is_list(Options), ?is_timeout(TimeoutOrHibernate);
is_atom(Mod), is_list(Options), TimeoutOrHibernate =:= hibernate ->
Expand Down Expand Up @@ -2187,6 +2200,12 @@ init_it(Starter, Parent, Name0, Mod, Args, Options) ->
loop(
Parent, Name, State, CbCache, infinity,
HibernateAfterTimeout, Debug);
{ok, {ok, State, {timeout, Time, _} = Timeout}}
when ?is_timeout(Time) ->
proc_lib:init_ack(Starter, {ok, self()}),
loop(
Parent, Name, State, CbCache, Timeout,
HibernateAfterTimeout, Debug);
{ok, {ok, State, TimeoutOrHibernate}}
when ?is_timeout(TimeoutOrHibernate);
TimeoutOrHibernate =:= hibernate ->
Expand Down Expand Up @@ -2264,6 +2283,15 @@ loop(Parent, Name, State, CbCache, infinity, HibernateAfterTimeout, Debug) ->
loop(Parent, Name, State, CbCache, hibernate, HibernateAfterTimeout, Debug)
end;

loop(Parent, Name, State, CbCache, {timeout, Time, TimeoutMsg} = Timeout, HibernateAfterTimeout, Debug) ->
Msg = receive
Input ->
Input
after Time ->
{timeout, TimeoutMsg}
end,
decode_msg(Msg, Parent, Name, State, CbCache, Timeout, HibernateAfterTimeout, Debug, false);

loop(Parent, Name, State, CbCache, Time, HibernateAfterTimeout, Debug) ->
Msg = receive
Input ->
Expand Down Expand Up @@ -2412,6 +2440,13 @@ handle_msg({'$gen_call', From, Msg}, Parent, Name, State, CbCache, HibernateAfte
{ok, {reply, Reply, NState}} ->
reply(From, Reply),
loop(Parent, Name, NState, CbCache, infinity, HibernateAfterTimeout, []);
{ok, {reply, Reply, NState, {timeout, infinity, _}}} ->
reply(From, Reply),
loop(Parent, Name, NState, CbCache, infinity, HibernateAfterTimeout, []);
{ok, {reply, Reply, NState, {timeout, Time, _} = Timeout}}
when ?is_timeout(Time) ->
reply(From, Reply),
loop(Parent, Name, NState, CbCache, Timeout, HibernateAfterTimeout, []);
{ok, {reply, Reply, NState, TimeoutOrHibernate}}
when ?is_timeout(TimeoutOrHibernate);
TimeoutOrHibernate =:= hibernate ->
Expand Down Expand Up @@ -2439,6 +2474,13 @@ handle_msg({'$gen_call', From, Msg}, Parent, Name, State, CbCache, HibernateAfte
{ok, {reply, Reply, NState}} ->
Debug1 = reply(Name, From, Reply, NState, Debug),
loop(Parent, Name, NState, CbCache, infinity, HibernateAfterTimeout, Debug1);
{ok, {reply, Reply, NState, {timeout, infinity, _}}} ->
Debug1 = reply(Name, From, Reply, NState, Debug),
loop(Parent, Name, NState, CbCache, infinity, HibernateAfterTimeout, Debug1);
{ok, {reply, Reply, NState, {timeout, Time, _} = Timeout}}
when ?is_timeout(Time) ->
Debug1 = reply(Name, From, Reply, NState, Debug),
loop(Parent, Name, NState, CbCache, Timeout, HibernateAfterTimeout, Debug1);
{ok, {reply, Reply, NState, TimeoutOrHibernate}}
when ?is_timeout(TimeoutOrHibernate);
TimeoutOrHibernate =:= hibernate ->
Expand Down Expand Up @@ -2466,6 +2508,11 @@ handle_common_reply(Reply, Parent, Name, From, Msg, CbCache, HibernateAfterTimeo
case Reply of
{ok, {noreply, NState}} ->
loop(Parent, Name, NState, CbCache, infinity, HibernateAfterTimeout, []);
{ok, {noreply, NState, {timeout, infinity, _}}} ->
loop(Parent, Name, NState, CbCache, infinity, HibernateAfterTimeout, []);
{ok, {noreply, NState, {timeout, Time, _} = Timeout}}
when ?is_timeout(Time) ->
loop(Parent, Name, NState, CbCache, Timeout, HibernateAfterTimeout, []);
{ok, {noreply, NState, TimeoutOrHibernate}}
when ?is_timeout(TimeoutOrHibernate);
TimeoutOrHibernate =:= hibernate ->
Expand All @@ -2487,6 +2534,10 @@ handle_common_reply(Reply, Parent, Name, From, Msg, CbCache, HibernateAfterTimeo
Debug1 = sys:handle_debug(Debug, fun print_event/3, Name,
{noreply, NState}),
loop(Parent, Name, NState, CbCache, infinity, HibernateAfterTimeout, Debug1);
{ok, {noreply, NState, {timeout, Time, _} = Timeout}}
when ?is_timeout(Time) ->
Debug1 = sys:handle_debug(Debug, fun print_event/3, Name, {noreply, NState}),
loop(Parent, Name, NState, CbCache, Timeout, HibernateAfterTimeout, Debug1);
{ok, {noreply, NState, TimeoutOrHibernate}}
when ?is_timeout(TimeoutOrHibernate);
TimeoutOrHibernate =:= hibernate ->
Expand Down

0 comments on commit 9789858

Please sign in to comment.