aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test/gen_statem_SUITE.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test/gen_statem_SUITE.erl')
-rw-r--r--lib/stdlib/test/gen_statem_SUITE.erl247
1 files changed, 234 insertions, 13 deletions
diff --git a/lib/stdlib/test/gen_statem_SUITE.erl b/lib/stdlib/test/gen_statem_SUITE.erl
index 99ac0c3951..270f1c294a 100644
--- a/lib/stdlib/test/gen_statem_SUITE.erl
+++ b/lib/stdlib/test/gen_statem_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2016-2017. All Rights Reserved.
+%% Copyright Ericsson AB 2016-2018. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -21,7 +21,7 @@
-include_lib("common_test/include/ct.hrl").
--compile(export_all).
+-compile([export_all, nowarn_export_all]).
-behaviour(gen_statem).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -38,9 +38,10 @@ all() ->
{group, abnormal},
{group, abnormal_handle_event},
shutdown, stop_and_reply, state_enter, event_order,
- state_timeout, event_types, code_change,
+ state_timeout, event_types, generic_timers, code_change,
{group, sys},
- hibernate, enter_loop].
+ hibernate, auto_hibernate, enter_loop, {group, undef_callbacks},
+ undef_in_terminate].
groups() ->
[{start, [], tcs(start)},
@@ -50,7 +51,8 @@ groups() ->
{abnormal, [], tcs(abnormal)},
{abnormal_handle_event, [], tcs(abnormal)},
{sys, [], tcs(sys)},
- {sys_handle_event, [], tcs(sys)}].
+ {sys_handle_event, [], tcs(sys)},
+ {undef_callbacks, [], tcs(undef_callbacks)}].
tcs(start) ->
[start1, start2, start3, start4, start5, start6, start7,
@@ -62,8 +64,9 @@ tcs(abnormal) ->
tcs(sys) ->
[sys1, call_format_status,
error_format_status, terminate_crash_format,
- get_state, replace_state].
-
+ get_state, replace_state];
+tcs(undef_callbacks) ->
+ [undef_code_change, undef_terminate1, undef_terminate2].
init_per_suite(Config) ->
Config.
@@ -77,6 +80,11 @@ init_per_group(GroupName, Config)
GroupName =:= abnormal_handle_event;
GroupName =:= sys_handle_event ->
[{callback_mode,handle_event_function}|Config];
+init_per_group(undef_callbacks, Config) ->
+ DataDir = ?config(data_dir, Config),
+ StatemPath = filename:join(DataDir, "oc_statem.erl"),
+ {ok, oc_statem} = compile:file(StatemPath),
+ Config;
init_per_group(_GroupName, Config) ->
Config.
@@ -505,10 +513,10 @@ abnormal2(Config) ->
{ok,Pid} = gen_statem:start_link(?MODULE, start_arg(Config, []), []),
%% bad return value in the gen_statem loop
- {{bad_return_from_state_function,badreturn},_} =
+ {{{bad_return_from_state_function,badreturn},_},_} =
?EXPECT_FAILURE(gen_statem:call(Pid, badreturn), Reason),
receive
- {'EXIT',Pid,{bad_return_from_state_function,badreturn}} -> ok
+ {'EXIT',Pid,{{bad_return_from_state_function,badreturn},_}} -> ok
after 5000 ->
ct:fail(gen_statem_did_not_die)
end,
@@ -824,9 +832,14 @@ event_types(_Config) ->
%% Abusing the internal format of From...
#{init =>
fun () ->
- {ok, start, undefined}
+ {ok, start1, undefined,
+ [{next_event,internal,0}]}
end,
- start =>
+ start1 =>
+ fun (internal, 0, undefined) ->
+ {next_state, start2, undefined}
+ end,
+ start2 =>
fun ({call,_} = Call, Req, undefined) ->
{next_state, state1, undefined,
[{next_event,internal,1},
@@ -834,6 +847,7 @@ event_types(_Config) ->
{next_event,timeout,3},
{next_event,info,4},
{next_event,cast,5},
+ {next_event,{timeout,6}, 6},
{next_event,Call,Req}]}
end,
state1 =>
@@ -857,6 +871,10 @@ event_types(_Config) ->
{next_state, state6, undefined}
end,
state6 =>
+ fun ({timeout,6}, 6, undefined) ->
+ {next_state, state7, undefined}
+ end,
+ state7 =>
fun ({call,From}, stop, undefined) ->
{stop_and_reply, shutdown,
[{reply,From,stopped}]}
@@ -884,6 +902,69 @@ event_types(_Config) ->
+generic_timers(_Config) ->
+ process_flag(trap_exit, true),
+
+ Machine =
+ %% Abusing the internal format of From...
+ #{init =>
+ fun () ->
+ {ok, start, undefined}
+ end,
+ start =>
+ fun ({call,_} = Call, Req, undefined) ->
+ {next_state, state1, undefined,
+ [{{timeout,a},1500,1},
+ {state_timeout,1500,1},
+ {{timeout,b},1000,1},
+ {next_event,Call,Req}]}
+ end,
+ state1 =>
+ fun ({call,_} = Call, Req, undefined) ->
+ T = erlang:monotonic_time(millisecond) + 500,
+ {next_state, state2, undefined,
+ [{{timeout,c},T,2,{abs,true}},
+ {{timeout,d},0,2,[{abs,false}]},
+ {timeout,0,2},
+ {{timeout,b},infinity,2},
+ {{timeout,a},1000,{Call,Req}}]}
+ end,
+ state2 =>
+ fun ({timeout,d}, 2, undefined) ->
+ {next_state, state3, undefined}
+ end,
+ state3 =>
+ fun ({timeout,c}, 2, undefined) ->
+ {next_state, state4, undefined}
+ end,
+ state4 =>
+ fun ({timeout,a}, {{call,From},stop}, undefined) ->
+ {stop_and_reply, shutdown,
+ [{reply,From,stopped}]}
+ end},
+ {ok,STM} =
+ gen_statem:start_link(
+ ?MODULE, {map_statem,Machine,[]}, [{debug,[trace]}]),
+
+ stopped = gen_statem:call(STM, stop),
+ receive
+ {'EXIT',STM,shutdown} ->
+ ok
+ after 500 ->
+ ct:fail(did_not_stop)
+ end,
+
+ {noproc,_} =
+ ?EXPECT_FAILURE(gen_statem:call(STM, hej), Reason),
+ case flush() of
+ [] ->
+ ok;
+ Other2 ->
+ ct:fail({unexpected,Other2})
+ end.
+
+
+
sys1(Config) ->
{ok,Pid} = gen_statem:start(?MODULE, start_arg(Config, []), []),
{status, Pid, {module,gen_statem}, _} = sys:get_status(Pid),
@@ -984,7 +1065,7 @@ error_format_status(Config) ->
gen_statem:start(
?MODULE, start_arg(Config, {data,Data}), []),
%% bad return value in the gen_statem loop
- {{bad_return_from_state_function,badreturn},_} =
+ {{{bad_return_from_state_function,badreturn},_},_} =
?EXPECT_FAILURE(gen_statem:call(Pid, badreturn), Reason),
receive
{error,_,
@@ -1208,6 +1289,84 @@ hibernate(Config) ->
end,
ok = verify_empty_msgq().
+%% Auto-hibernation timeout
+auto_hibernate(Config) ->
+ OldFl = process_flag(trap_exit, true),
+ HibernateAfterTimeout = 100,
+
+ {ok,Pid} =
+ gen_statem:start_link(
+ ?MODULE, start_arg(Config, []), [{hibernate_after, HibernateAfterTimeout}]),
+ %% After init test
+ is_not_in_erlang_hibernate(Pid),
+ timer:sleep(HibernateAfterTimeout),
+ is_in_erlang_hibernate(Pid),
+ %% After info test
+ Pid ! {hping, self()},
+ receive
+ {Pid, hpong} ->
+ ok
+ after 1000 ->
+ ct:fail(info)
+ end,
+ is_not_in_erlang_hibernate(Pid),
+ timer:sleep(HibernateAfterTimeout),
+ is_in_erlang_hibernate(Pid),
+ %% After cast test
+ ok = gen_statem:cast(Pid, {hping, self()}),
+ receive
+ {Pid, hpong} ->
+ ok
+ after 1000 ->
+ ct:fail(cast)
+ end,
+ is_not_in_erlang_hibernate(Pid),
+ timer:sleep(HibernateAfterTimeout),
+ is_in_erlang_hibernate(Pid),
+ %% After call test
+ hpong = gen_statem:call(Pid, hping),
+ is_not_in_erlang_hibernate(Pid),
+ timer:sleep(HibernateAfterTimeout),
+ is_in_erlang_hibernate(Pid),
+ %% Timer test 1
+ TimerTimeout1 = 50,
+ ok = gen_statem:call(Pid, {arm_htimer, self(), TimerTimeout1}),
+ is_not_in_erlang_hibernate(Pid),
+ timer:sleep(TimerTimeout1),
+ is_not_in_erlang_hibernate(Pid),
+ receive
+ {Pid, htimer_armed} ->
+ ok
+ after 1000 ->
+ ct:fail(timer1)
+ end,
+ is_not_in_erlang_hibernate(Pid),
+ timer:sleep(HibernateAfterTimeout),
+ is_in_erlang_hibernate(Pid),
+ %% Timer test 2
+ TimerTimeout2 = 150,
+ ok = gen_statem:call(Pid, {arm_htimer, self(), TimerTimeout2}),
+ is_not_in_erlang_hibernate(Pid),
+ timer:sleep(HibernateAfterTimeout),
+ is_in_erlang_hibernate(Pid),
+ receive
+ {Pid, htimer_armed} ->
+ ok
+ after 1000 ->
+ ct:fail(timer2)
+ end,
+ is_not_in_erlang_hibernate(Pid),
+ timer:sleep(HibernateAfterTimeout),
+ is_in_erlang_hibernate(Pid),
+ stop_it(Pid),
+ process_flag(trap_exit, OldFl),
+ receive
+ {'EXIT',Pid,normal} -> ok
+ after 5000 ->
+ ct:fail(gen_statem_did_not_die)
+ end,
+ ok = verify_empty_msgq().
+
is_in_erlang_hibernate(Pid) ->
receive after 1 -> ok end,
is_in_erlang_hibernate_1(200, Pid).
@@ -1393,6 +1552,51 @@ enter_loop(Reg1, Reg2) ->
gen_statem:enter_loop(?MODULE, [], state0, [])
end.
+undef_code_change(_Config) ->
+ {ok, Statem} = gen_statem:start(oc_statem, [], []),
+ {error, {'EXIT',
+ {undef, [{oc_statem, code_change, [_, _, _, _], _}|_]}}}
+ = fake_upgrade(Statem, oc_statem).
+
+fake_upgrade(Pid, Mod) ->
+ sys:suspend(Pid),
+ sys:replace_state(Pid, fun(State) -> {new, State} end),
+ Ret = sys:change_code(Pid, Mod, old_vsn, []),
+ ok = sys:resume(Pid),
+ Ret.
+
+undef_terminate1(_Config) ->
+ {ok, Statem} = gen_statem:start(oc_statem, [], []),
+ MRef = monitor(process, Statem),
+ ok = gen_statem:stop(Statem),
+ verify_down(Statem, MRef, normal),
+ ok.
+
+undef_terminate2(_Config) ->
+ Reason = {error, test},
+ {ok, Statem} = oc_statem:start(),
+ MRef = monitor(process, Statem),
+ ok = gen_statem:stop(Statem, Reason, infinity),
+ verify_down(Statem, MRef, Reason).
+
+undef_in_terminate(_Config) ->
+ Data = {undef_in_terminate, {?MODULE, terminate}},
+ {ok, Statem} = gen_statem:start(?MODULE, {data, Data}, []),
+ try
+ gen_statem:stop(Statem),
+ ct:fail(should_crash)
+ catch
+ exit:{undef, [{?MODULE, terminate, _, _}|_]} ->
+ ok
+ end.
+
+verify_down(Statem, MRef, Reason) ->
+ receive
+ {'DOWN', MRef, process, Statem, Reason} ->
+ ok
+ after 5000 ->
+ ct:fail(default_terminate_failed)
+ end.
%% Test the order for multiple {next_event,T,C}
next_events(Config) ->
@@ -1571,6 +1775,9 @@ callback_mode() ->
terminate(_, _State, crash_terminate) ->
exit({crash,terminate});
+terminate(_, _State, {undef_in_terminate, {Mod, Fun}}) ->
+ Mod:Fun(),
+ ok;
terminate({From,stopped}, State, _Data) ->
From ! {self(),{stopped,State}},
ok;
@@ -1580,6 +1787,19 @@ terminate(_Reason, _State, _Data) ->
%% State functions
+idle(info, {hping,Pid}, _Data) ->
+ Pid ! {self(), hpong},
+ keep_state_and_data;
+idle(cast, {hping,Pid}, Data) ->
+ Pid ! {self(), hpong},
+ {keep_state, Data};
+idle({call, From}, hping, _Data) ->
+ {keep_state_and_data, [{reply, From, hpong}]};
+idle({call, From}, {arm_htimer, Pid, Timeout}, _Data) ->
+ {keep_state_and_data, [{reply, From, ok}, {timeout, Timeout, {arm_htimer, Pid}}]};
+idle(timeout, {arm_htimer, Pid}, _Data) ->
+ Pid ! {self(), htimer_armed},
+ keep_state_and_data;
idle(cast, {connect,Pid}, Data) ->
Pid ! accept,
{next_state,wfor_conf,Data,infinity}; % NoOp timeout just to test API
@@ -1597,8 +1817,9 @@ idle({call,From}, {delayed_answer,T}, Data) ->
throw({keep_state,Data})
end;
idle({call,From}, {timeout,Time}, _Data) ->
+ AbsTime = erlang:monotonic_time(millisecond) + Time,
{next_state,timeout,{From,Time},
- {timeout,Time,idle}};
+ {timeout,AbsTime,idle,[{abs,true}]}};
idle(cast, next_event, _Data) ->
{next_state,next_events,[a,b,c],
[{next_event,internal,a},