aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test/gen_server_SUITE.erl
diff options
context:
space:
mode:
authorJosé Valim <[email protected]>2017-06-22 19:54:26 +0200
committerJosé Valim <[email protected]>2017-08-05 18:58:52 +0200
commit69e009e3e1ad899a4609ff327a08512c86dba374 (patch)
treec4a431d3c7c7f8b8e02de0fe1ceb8028c61b56df /lib/stdlib/test/gen_server_SUITE.erl
parentf52748254f17ba42e344798e8c787a1e3361fa33 (diff)
downloadotp-69e009e3e1ad899a4609ff327a08512c86dba374.tar.gz
otp-69e009e3e1ad899a4609ff327a08512c86dba374.tar.bz2
otp-69e009e3e1ad899a4609ff327a08512c86dba374.zip
Add {continue, Term} and handle_continue/2 to gen_server
If the gen_server process needs to perform an action immediately after initialization or to break the execution of a callback into multiple steps, it can return {continue, term()} in place of the time-out or hibernation value, which will immediately invoke the handle_continue/2 callback with the given term. This provides a more accessible approach to after initialization compared to proc_lib+enter_loop that is also guaranteed to be safe. It also allows callbacks that need to do lengthy or stateful work to checkpoint the state throughout multiple iterations. This can be useful, for example, when implementing behaviours on top of gen_server.
Diffstat (limited to 'lib/stdlib/test/gen_server_SUITE.erl')
-rw-r--r--lib/stdlib/test/gen_server_SUITE.erl111
1 files changed, 99 insertions, 12 deletions
diff --git a/lib/stdlib/test/gen_server_SUITE.erl b/lib/stdlib/test/gen_server_SUITE.erl
index 2e9dc4d4fb..2bc220fef2 100644
--- a/lib/stdlib/test/gen_server_SUITE.erl
+++ b/lib/stdlib/test/gen_server_SUITE.erl
@@ -27,7 +27,7 @@
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
init_per_group/2,end_per_group/2]).
-export([start/1, crash/1, call/1, cast/1, cast_fast/1,
- info/1, abcast/1, multicall/1, multicall_down/1,
+ continue/1, info/1, abcast/1, multicall/1, multicall_down/1,
call_remote1/1, call_remote2/1, call_remote3/1,
call_remote_n1/1, call_remote_n2/1, call_remote_n3/1, spec_init/1,
spec_init_local_registered_parent/1,
@@ -37,7 +37,8 @@
get_state/1, replace_state/1, call_with_huge_message_queue/1,
undef_handle_call/1, undef_handle_cast/1, undef_handle_info/1,
undef_init/1, undef_code_change/1, undef_terminate1/1,
- undef_terminate2/1, undef_in_terminate/1, undef_in_handle_info/1
+ undef_terminate2/1, undef_in_terminate/1, undef_in_handle_info/1,
+ undef_handle_continue/1
]).
-export([stop1/1, stop2/1, stop3/1, stop4/1, stop5/1, stop6/1, stop7/1,
@@ -52,7 +53,7 @@
%% The gen_server behaviour
--export([init/1, handle_call/3, handle_cast/2,
+-export([init/1, handle_call/3, handle_cast/2, handle_continue/2,
handle_info/2, code_change/3, terminate/2, format_status/2]).
suite() ->
@@ -61,7 +62,7 @@ suite() ->
all() ->
[start, {group,stop}, crash, call, cast, cast_fast, info, abcast,
- multicall, multicall_down, call_remote1, call_remote2,
+ continue, multicall, multicall_down, call_remote1, call_remote2,
call_remote3, call_remote_n1, call_remote_n2,
call_remote_n3, spec_init,
spec_init_local_registered_parent,
@@ -76,7 +77,7 @@ groups() ->
[{stop, [],
[stop1, stop2, stop3, stop4, stop5, stop6, stop7, stop8, stop9, stop10]},
{undef_callbacks, [],
- [undef_handle_call, undef_handle_cast, undef_handle_info,
+ [undef_handle_call, undef_handle_cast, undef_handle_info, undef_handle_continue,
undef_init, undef_code_change, undef_terminate1, undef_terminate2]}].
@@ -458,6 +459,47 @@ call(Config) when is_list(Config) ->
ok.
%% --------------------------------------
+%% Test handle_continue.
+%% --------------------------------------
+
+continue(Config) when is_list(Config) ->
+ {ok, Pid} = gen_server:start_link(gen_server_SUITE, {continue, self()}, []),
+ [{Pid, continue}, {Pid, after_continue}] = read_replies(Pid),
+
+ gen_server:call(Pid, {continue_reply, self()}),
+ [{Pid, continue}, {Pid, after_continue}] = read_replies(Pid),
+
+ gen_server:call(Pid, {continue_noreply, self()}),
+ [{Pid, continue}, {Pid, after_continue}] = read_replies(Pid),
+
+ gen_server:cast(Pid, {continue_noreply, self()}),
+ [{Pid, continue}, {Pid, after_continue}] = read_replies(Pid),
+
+ Pid ! {continue_noreply, self()},
+ [{Pid, continue}, {Pid, after_continue}] = read_replies(Pid),
+
+ Pid ! {continue_continue, self()},
+ [{Pid, before_continue}, {Pid, continue}, {Pid, after_continue}] = read_replies(Pid),
+
+ Ref = monitor(process, Pid),
+ Pid ! continue_stop,
+ verify_down_reason(Ref, Pid, normal).
+
+read_replies(Pid) ->
+ receive
+ {Pid, ack} -> read_replies()
+ after
+ 1000 -> ct:fail({continue, ack})
+ end.
+
+read_replies() ->
+ receive
+ Msg -> [Msg | read_replies()]
+ after
+ 0 -> []
+ end.
+
+%% --------------------------------------
%% Test call to nonexisting processes on remote nodes
%% --------------------------------------
@@ -1346,7 +1388,7 @@ echo_loop() ->
%% Test the default implementation of terminate if the callback module
%% does not export it
undef_terminate1(Config) when is_list(Config) ->
- {ok, Server} = gen_server:start(oc_server, [], []),
+ {ok, Server} = oc_server:start(),
MRef = monitor(process, Server),
ok = gen_server:stop(Server),
ok = verify_down_reason(MRef, Server, normal).
@@ -1354,7 +1396,7 @@ undef_terminate1(Config) when is_list(Config) ->
%% Test the default implementation of terminate if the callback module
%% does not export it
undef_terminate2(Config) when is_list(Config) ->
- {ok, Server} = gen_server:start(oc_server, [], []),
+ {ok, Server} = oc_server:start(),
MRef = monitor(process, Server),
ok = gen_server:stop(Server, {error, test}, infinity),
ok = verify_down_reason(MRef, Server, {error, test}).
@@ -1377,7 +1419,7 @@ undef_init(_Config) ->
%% The upgrade should fail if code_change is expected in the callback module
%% but not exported, but the server should continue with the old code
undef_code_change(Config) when is_list(Config) ->
- {ok, Server} = gen_server:start(oc_server, [], []),
+ {ok, Server} = oc_server:start(),
{error, {'EXIT', {undef, [{oc_server, code_change, [_, _, _], _}|_]}}}
= fake_upgrade(Server, ?MODULE),
true = is_process_alive(Server).
@@ -1385,7 +1427,7 @@ undef_code_change(Config) when is_list(Config) ->
%% The server should crash if the handle_call callback is
%% not exported in the callback module
undef_handle_call(_Config) ->
- {ok, Server} = gen_server:start(oc_server, [], []),
+ {ok, Server} = oc_server:start(),
try
gen_server:call(Server, call_msg),
ct:fail(should_crash)
@@ -1397,17 +1439,25 @@ undef_handle_call(_Config) ->
%% The server should crash if the handle_cast callback is
%% not exported in the callback module
undef_handle_cast(_Config) ->
- {ok, Server} = gen_server:start(oc_server, [], []),
+ {ok, Server} = oc_server:start(),
MRef = monitor(process, Server),
gen_server:cast(Server, cast_msg),
verify_undef_down(MRef, Server, oc_server, handle_cast),
ok.
+%% The server should crash if the handle_continue callback is
+%% not exported in the callback module
+undef_handle_continue(_Config) ->
+ {ok, Server} = oc_server:start(continue),
+ MRef = monitor(process, Server),
+ verify_undef_down(MRef, Server, oc_server, handle_continue),
+ ok.
+
%% The server should log but not crash if the handle_info callback is
%% calling an undefined function
undef_handle_info(Config) when is_list(Config) ->
error_logger_forwarder:register(),
- {ok, Server} = gen_server:start(oc_server, [], []),
+ {ok, Server} = oc_server:start(),
Server ! hej,
wait_until_processed(Server, hej, 10),
true = is_process_alive(Server),
@@ -1570,8 +1620,11 @@ init(hibernate) ->
init(sleep) ->
ct:sleep(1000),
{ok, []};
+init({continue, Pid}) ->
+ self() ! {after_continue, Pid},
+ {ok, [], {continue, {message, Pid}}};
init({state,State}) ->
- {ok, State}.
+ {ok,State}.
handle_call(started_p, _From, State) ->
io:format("FROZ"),
@@ -1604,6 +1657,12 @@ handle_call(shutdown_reason, _From, _State) ->
handle_call({call_undef_fun, Mod, Fun}, _From, State) ->
Mod:Fun(),
{reply, ok, State};
+handle_call({continue_reply, Pid}, _From, State) ->
+ self() ! {after_continue, Pid},
+ {reply, ok, State, {continue, {message, Pid}}};
+handle_call({continue_noreply, Pid}, From, State) ->
+ self() ! {after_continue, Pid},
+ {noreply, State, {continue, {message, Pid, From}}};
handle_call(stop_shutdown_reason, _From, State) ->
{stop,{shutdown,stop_reason},State}.
@@ -1620,6 +1679,9 @@ handle_cast(hibernate_later, _State) ->
handle_cast({call_undef_fun, Mod, Fun}, State) ->
Mod:Fun(),
{noreply, State};
+handle_cast({continue_noreply, Pid}, State) ->
+ self() ! {after_continue, Pid},
+ {noreply, State, {continue, {message, Pid}}};
handle_cast({From, stop}, State) ->
io:format("BAZ"),
{stop, {From,stopped}, State}.
@@ -1657,9 +1719,34 @@ handle_info(continue, From) ->
{noreply, []};
handle_info({From, stop}, State) ->
{stop, {From,stopped_info}, State};
+handle_info({after_continue, Pid}, State) ->
+ Pid ! {self(), after_continue},
+ Pid ! {self(), ack},
+ {noreply, State};
+handle_info({continue_noreply, Pid}, State) ->
+ self() ! {after_continue, Pid},
+ {noreply, State, {continue, {message, Pid}}};
+handle_info({continue_continue, Pid}, State) ->
+ {noreply, State, {continue, {continue, Pid}}};
+handle_info(continue_stop, State) ->
+ {noreply, State, {continue, stop}};
handle_info(_Info, State) ->
{noreply, State}.
+handle_continue({continue, Pid}, State) ->
+ Pid ! {self(), before_continue},
+ self() ! {after_continue, Pid},
+ {noreply, State, {continue, {message, Pid}}};
+handle_continue(stop, State) ->
+ {stop, normal, State};
+handle_continue({message, Pid}, State) ->
+ Pid ! {self(), continue},
+ {noreply, State};
+handle_continue({message, Pid, From}, State) ->
+ Pid ! {self(), continue},
+ gen_server:reply(From, ok),
+ {noreply, State}.
+
code_change(_OldVsn,
{new, {undef_in_code_change, {Mod, Fun}}} = State,
_Extra) ->