aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test/gen_fsm_SUITE.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test/gen_fsm_SUITE.erl')
-rw-r--r--lib/stdlib/test/gen_fsm_SUITE.erl433
1 files changed, 219 insertions, 214 deletions
diff --git a/lib/stdlib/test/gen_fsm_SUITE.erl b/lib/stdlib/test/gen_fsm_SUITE.erl
index e3da1a2271..d6bb002b5f 100644
--- a/lib/stdlib/test/gen_fsm_SUITE.erl
+++ b/lib/stdlib/test/gen_fsm_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2014. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2016. 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.
@@ -19,7 +19,7 @@
%%
-module(gen_fsm_SUITE).
--include_lib("test_server/include/test_server.hrl").
+-include_lib("common_test/include/ct.hrl").
%% Test cases
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
@@ -44,10 +44,9 @@
-export([enter_loop/1]).
%% Exports for apply
--export([do_msg/1, do_sync_msg/1]).
-export([enter_loop/2]).
-% The gen_fsm behaviour
+%% The gen_fsm behaviour
-export([init/1, handle_event/3, handle_sync_event/4, terminate/3,
handle_info/3, format_status/2]).
-export([idle/2, idle/3,
@@ -55,7 +54,7 @@
wfor_conf/2, wfor_conf/3,
connected/2, connected/3]).
-export([state0/3]).
-
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -93,97 +92,95 @@ end_per_group(_GroupName, Config) ->
start1(Config) when is_list(Config) ->
%%OldFl = process_flag(trap_exit, true),
- ?line {ok, Pid0} = gen_fsm:start_link(gen_fsm_SUITE, [], []),
- ?line ok = do_func_test(Pid0),
- ?line ok = do_sync_func_test(Pid0),
+ {ok, Pid0} = gen_fsm:start_link(gen_fsm_SUITE, [], []),
+ ok = do_func_test(Pid0),
+ ok = do_sync_func_test(Pid0),
stop_it(Pid0),
-%% ?line stopped = gen_fsm:sync_send_all_state_event(Pid0, stop),
-%% ?line {'EXIT', {timeout,_}} =
-%% (catch gen_fsm:sync_send_event(Pid0, hej)),
+ %% stopped = gen_fsm:sync_send_all_state_event(Pid0, stop),
+ %% {'EXIT', {timeout,_}} =
+ %% (catch gen_fsm:sync_send_event(Pid0, hej)),
- ?line test_server:messages_get(),
+ [] = get_messages(),
%%process_flag(trap_exit, OldFl),
- ok.
+ ok.
%% anonymous w. shutdown
start2(Config) when is_list(Config) ->
%% Dont link when shutdown
- ?line {ok, Pid0} = gen_fsm:start(gen_fsm_SUITE, [], []),
- ?line ok = do_func_test(Pid0),
- ?line ok = do_sync_func_test(Pid0),
- ?line shutdown_stopped =
+ {ok, Pid0} = gen_fsm:start(gen_fsm_SUITE, [], []),
+ ok = do_func_test(Pid0),
+ ok = do_sync_func_test(Pid0),
+ shutdown_stopped =
gen_fsm:sync_send_all_state_event(Pid0, stop_shutdown),
- ?line {'EXIT', {noproc,_}} =
+ {'EXIT', {noproc,_}} =
(catch gen_fsm:sync_send_event(Pid0, hej)),
- ?line test_server:messages_get(),
+ [] = get_messages(),
ok.
%% anonymous with timeout
start3(Config) when is_list(Config) ->
%%OldFl = process_flag(trap_exit, true),
- ?line {ok, Pid0} = gen_fsm:start(gen_fsm_SUITE, [], [{timeout,5}]),
- ?line ok = do_func_test(Pid0),
- ?line ok = do_sync_func_test(Pid0),
- ?line stop_it(Pid0),
-
- ?line {error, timeout} = gen_fsm:start(gen_fsm_SUITE, sleep,
- [{timeout,5}]),
+ {ok, Pid0} = gen_fsm:start(gen_fsm_SUITE, [], [{timeout,5}]),
+ ok = do_func_test(Pid0),
+ ok = do_sync_func_test(Pid0),
+ stop_it(Pid0),
+
+ {error, timeout} = gen_fsm:start(gen_fsm_SUITE, sleep,
+ [{timeout,5}]),
- test_server:messages_get(),
+ [] = get_messages(),
%%process_flag(trap_exit, OldFl),
ok.
%% anonymous with ignore
-start4(suite) -> [];
start4(Config) when is_list(Config) ->
OldFl = process_flag(trap_exit, true),
- ?line ignore = gen_fsm:start(gen_fsm_SUITE, ignore, []),
+ ignore = gen_fsm:start(gen_fsm_SUITE, ignore, []),
- test_server:messages_get(),
+ [] = get_messages(),
process_flag(trap_exit, OldFl),
ok.
%% anonymous with stop
-start5(suite) -> [];
start5(Config) when is_list(Config) ->
OldFl = process_flag(trap_exit, true),
- ?line {error, stopped} = gen_fsm:start(gen_fsm_SUITE, stop, []),
+ {error, stopped} = gen_fsm:start(gen_fsm_SUITE, stop, []),
- test_server:messages_get(),
+ [] = get_messages(),
process_flag(trap_exit, OldFl),
ok.
%% anonymous linked
start6(Config) when is_list(Config) ->
- ?line {ok, Pid} = gen_fsm:start_link(gen_fsm_SUITE, [], []),
- ?line ok = do_func_test(Pid),
- ?line ok = do_sync_func_test(Pid),
- ?line stop_it(Pid),
+ {ok, Pid} = gen_fsm:start_link(gen_fsm_SUITE, [], []),
+ ok = do_func_test(Pid),
+ ok = do_sync_func_test(Pid),
+ stop_it(Pid),
- test_server:messages_get(),
+ [] = get_messages(),
ok.
%% global register linked
start7(Config) when is_list(Config) ->
- ?line {ok, Pid} =
+ {ok, Pid} =
gen_fsm:start_link({global, my_fsm}, gen_fsm_SUITE, [], []),
- ?line {error, {already_started, Pid}} =
+ {error, {already_started, Pid}} =
gen_fsm:start_link({global, my_fsm}, gen_fsm_SUITE, [], []),
- ?line {error, {already_started, Pid}} =
+ {error, {already_started, Pid}} =
gen_fsm:start({global, my_fsm}, gen_fsm_SUITE, [], []),
-
- ?line ok = do_func_test(Pid),
- ?line ok = do_sync_func_test(Pid),
- ?line ok = do_func_test({global, my_fsm}),
- ?line ok = do_sync_func_test({global, my_fsm}),
- ?line stop_it({global, my_fsm}),
-
- test_server:messages_get(),
+
+ ok = do_func_test(Pid),
+ ok = do_sync_func_test(Pid),
+ ok = do_func_test({global, my_fsm}),
+ ok = do_sync_func_test({global, my_fsm}),
+ stop_it({global, my_fsm}),
+
+ [] = get_messages(),
ok.
@@ -191,18 +188,18 @@ start7(Config) when is_list(Config) ->
start8(Config) when is_list(Config) ->
%%OldFl = process_flag(trap_exit, true),
- ?line {ok, Pid} =
+ {ok, Pid} =
gen_fsm:start({local, my_fsm}, gen_fsm_SUITE, [], []),
- ?line {error, {already_started, Pid}} =
+ {error, {already_started, Pid}} =
gen_fsm:start({local, my_fsm}, gen_fsm_SUITE, [], []),
- ?line ok = do_func_test(Pid),
- ?line ok = do_sync_func_test(Pid),
- ?line ok = do_func_test(my_fsm),
- ?line ok = do_sync_func_test(my_fsm),
- ?line stop_it(Pid),
-
- test_server:messages_get(),
+ ok = do_func_test(Pid),
+ ok = do_sync_func_test(Pid),
+ ok = do_func_test(my_fsm),
+ ok = do_sync_func_test(my_fsm),
+ stop_it(Pid),
+
+ [] = get_messages(),
%%process_flag(trap_exit, OldFl),
ok.
@@ -210,80 +207,80 @@ start8(Config) when is_list(Config) ->
start9(Config) when is_list(Config) ->
%%OldFl = process_flag(trap_exit, true),
- ?line {ok, Pid} =
+ {ok, Pid} =
gen_fsm:start_link({local, my_fsm}, gen_fsm_SUITE, [], []),
- ?line {error, {already_started, Pid}} =
+ {error, {already_started, Pid}} =
gen_fsm:start({local, my_fsm}, gen_fsm_SUITE, [], []),
- ?line ok = do_func_test(Pid),
- ?line ok = do_sync_func_test(Pid),
- ?line ok = do_func_test(my_fsm),
- ?line ok = do_sync_func_test(my_fsm),
- ?line stop_it(Pid),
-
- test_server:messages_get(),
+ ok = do_func_test(Pid),
+ ok = do_sync_func_test(Pid),
+ ok = do_func_test(my_fsm),
+ ok = do_sync_func_test(my_fsm),
+ stop_it(Pid),
+
+ [] = get_messages(),
%%process_flag(trap_exit, OldFl),
ok.
%% global register
start10(Config) when is_list(Config) ->
- ?line {ok, Pid} =
+ {ok, Pid} =
gen_fsm:start({global, my_fsm}, gen_fsm_SUITE, [], []),
- ?line {error, {already_started, Pid}} =
+ {error, {already_started, Pid}} =
gen_fsm:start({global, my_fsm}, gen_fsm_SUITE, [], []),
- ?line {error, {already_started, Pid}} =
+ {error, {already_started, Pid}} =
gen_fsm:start_link({global, my_fsm}, gen_fsm_SUITE, [], []),
-
- ?line ok = do_func_test(Pid),
- ?line ok = do_sync_func_test(Pid),
- ?line ok = do_func_test({global, my_fsm}),
- ?line ok = do_sync_func_test({global, my_fsm}),
- ?line stop_it({global, my_fsm}),
-
- test_server:messages_get(),
+
+ ok = do_func_test(Pid),
+ ok = do_sync_func_test(Pid),
+ ok = do_func_test({global, my_fsm}),
+ ok = do_sync_func_test({global, my_fsm}),
+ stop_it({global, my_fsm}),
+
+ [] = get_messages(),
ok.
%% Stop registered processes
start11(Config) when is_list(Config) ->
- ?line {ok, Pid} =
+ {ok, Pid} =
gen_fsm:start_link({local, my_fsm}, gen_fsm_SUITE, [], []),
- ?line stop_it(Pid),
+ stop_it(Pid),
- ?line {ok, _Pid1} =
+ {ok, _Pid1} =
gen_fsm:start_link({local, my_fsm}, gen_fsm_SUITE, [], []),
- ?line stop_it(my_fsm),
-
- ?line {ok, Pid2} =
+ stop_it(my_fsm),
+
+ {ok, Pid2} =
gen_fsm:start({global, my_fsm}, gen_fsm_SUITE, [], []),
- ?line stop_it(Pid2),
+ stop_it(Pid2),
receive after 1 -> true end,
- ?line Result =
+ Result =
gen_fsm:start({global, my_fsm}, gen_fsm_SUITE, [], []),
io:format("Result = ~p~n",[Result]),
- ?line {ok, _Pid3} = Result,
- ?line stop_it({global, my_fsm}),
+ {ok, _Pid3} = Result,
+ stop_it({global, my_fsm}),
- test_server:messages_get(),
+ [] = get_messages(),
ok.
%% Via register linked
start12(Config) when is_list(Config) ->
- ?line dummy_via:reset(),
- ?line {ok, Pid} =
+ dummy_via:reset(),
+ {ok, Pid} =
gen_fsm:start_link({via, dummy_via, my_fsm}, gen_fsm_SUITE, [], []),
- ?line {error, {already_started, Pid}} =
+ {error, {already_started, Pid}} =
gen_fsm:start_link({via, dummy_via, my_fsm}, gen_fsm_SUITE, [], []),
- ?line {error, {already_started, Pid}} =
+ {error, {already_started, Pid}} =
gen_fsm:start({via, dummy_via, my_fsm}, gen_fsm_SUITE, [], []),
- ?line ok = do_func_test(Pid),
- ?line ok = do_sync_func_test(Pid),
- ?line ok = do_func_test({via, dummy_via, my_fsm}),
- ?line ok = do_sync_func_test({via, dummy_via, my_fsm}),
- ?line stop_it({via, dummy_via, my_fsm}),
+ ok = do_func_test(Pid),
+ ok = do_sync_func_test(Pid),
+ ok = do_func_test({via, dummy_via, my_fsm}),
+ ok = do_sync_func_test({via, dummy_via, my_fsm}),
+ stop_it({via, dummy_via, my_fsm}),
- test_server:messages_get(),
+ [] = get_messages(),
ok.
@@ -339,7 +336,7 @@ stop6(_Config) ->
stop7(_Config) ->
dummy_via:reset(),
{ok, Pid} = gen_fsm:start({via, dummy_via, to_stop},
- ?MODULE, [], []),
+ ?MODULE, [], []),
ok = gen_fsm:stop({via, dummy_via, to_stop}),
false = erlang:is_process_alive(Pid),
{'EXIT',noproc} = (catch gen_fsm:stop({via, dummy_via, to_stop})),
@@ -387,53 +384,57 @@ stop10(_Config) ->
ok.
%% Check that time outs in calls work
-abnormal1(suite) -> [];
abnormal1(Config) when is_list(Config) ->
{ok, _Pid} = gen_fsm:start({local, my_fsm}, gen_fsm_SUITE, [], []),
%% timeout call.
delayed = gen_fsm:sync_send_event(my_fsm, {delayed_answer,1}, 100),
{'EXIT',{timeout,_}} =
- (catch gen_fsm:sync_send_event(my_fsm, {delayed_answer,10}, 1)),
- test_server:messages_get(),
+ (catch gen_fsm:sync_send_event(my_fsm, {delayed_answer,10}, 1)),
+ receive
+ Msg ->
+ %% Ignore the delayed answer from the server.
+ io:format("Delayed message: ~p", [Msg])
+ end,
+
+ [] = get_messages(),
ok.
%% Check that bad return values makes the fsm crash. Note that we must
%% trap exit since we must link to get the real bad_return_ error
-abnormal2(suite) -> [];
abnormal2(Config) when is_list(Config) ->
OldFl = process_flag(trap_exit, true),
- ?line {ok, Pid} =
+ {ok, Pid} =
gen_fsm:start_link(gen_fsm_SUITE, [], []),
%% bad return value in the gen_fsm loop
- ?line {'EXIT',{{bad_return_value, badreturn},_}} =
+ {'EXIT',{{bad_return_value, badreturn},_}} =
(catch gen_fsm:sync_send_event(Pid, badreturn)),
-
- test_server:messages_get(),
+
+ [{'EXIT',Pid,{bad_return_value,badreturn}}] = get_messages(),
process_flag(trap_exit, OldFl),
ok.
shutdown(Config) when is_list(Config) ->
- ?line error_logger_forwarder:register(),
+ error_logger_forwarder:register(),
process_flag(trap_exit, true),
- ?line {ok,Pid0} = gen_fsm:start_link(gen_fsm_SUITE, [], []),
- ?line ok = do_func_test(Pid0),
- ?line ok = do_sync_func_test(Pid0),
- ?line {shutdown,reason} =
+ {ok,Pid0} = gen_fsm:start_link(gen_fsm_SUITE, [], []),
+ ok = do_func_test(Pid0),
+ ok = do_sync_func_test(Pid0),
+ {shutdown,reason} =
gen_fsm:sync_send_all_state_event(Pid0, stop_shutdown_reason),
receive {'EXIT',Pid0,{shutdown,reason}} -> ok end,
process_flag(trap_exit, false),
- ?line {'EXIT', {noproc,_}} =
+ {'EXIT', {noproc,_}} =
(catch gen_fsm:sync_send_event(Pid0, hej)),
receive
Any ->
- ?line io:format("Unexpected: ~p", [Any]),
- ?line ?t:fail()
+ io:format("Unexpected: ~p", [Any]),
+ ct:fail(failed)
after 500 ->
ok
end,
@@ -443,70 +444,70 @@ shutdown(Config) when is_list(Config) ->
sys1(Config) when is_list(Config) ->
- ?line {ok, Pid} =
+ {ok, Pid} =
gen_fsm:start(gen_fsm_SUITE, [], []),
- ?line {status, Pid, {module,gen_fsm}, _} = sys:get_status(Pid),
- ?line sys:suspend(Pid),
- ?line {'EXIT', {timeout,_}} =
+ {status, Pid, {module,gen_fsm}, _} = sys:get_status(Pid),
+ sys:suspend(Pid),
+ {'EXIT', {timeout,_}} =
(catch gen_fsm:sync_send_event(Pid, hej)),
- ?line sys:resume(Pid),
- ?line stop_it(Pid).
+ sys:resume(Pid),
+ stop_it(Pid).
call_format_status(Config) when is_list(Config) ->
- ?line {ok, Pid} = gen_fsm:start(gen_fsm_SUITE, [], []),
- ?line Status = sys:get_status(Pid),
- ?line {status, Pid, _Mod, [_PDict, running, _, _, Data]} = Status,
- ?line [format_status_called | _] = lists:reverse(Data),
- ?line stop_it(Pid),
+ {ok, Pid} = gen_fsm:start(gen_fsm_SUITE, [], []),
+ Status = sys:get_status(Pid),
+ {status, Pid, _Mod, [_PDict, running, _, _, Data]} = Status,
+ [format_status_called | _] = lists:reverse(Data),
+ stop_it(Pid),
%% check that format_status can handle a name being an atom (pid is
%% already checked by the previous test)
- ?line {ok, Pid2} = gen_fsm:start({local, gfsm}, gen_fsm_SUITE, [], []),
- ?line Status2 = sys:get_status(gfsm),
- ?line {status, Pid2, _Mod, [_PDict2, running, _, _, Data2]} = Status2,
- ?line [format_status_called | _] = lists:reverse(Data2),
- ?line stop_it(Pid2),
+ {ok, Pid2} = gen_fsm:start({local, gfsm}, gen_fsm_SUITE, [], []),
+ Status2 = sys:get_status(gfsm),
+ {status, Pid2, _Mod, [_PDict2, running, _, _, Data2]} = Status2,
+ [format_status_called | _] = lists:reverse(Data2),
+ stop_it(Pid2),
%% check that format_status can handle a name being a term other than a
%% pid or atom
GlobalName1 = {global, "CallFormatStatus"},
- ?line {ok, Pid3} = gen_fsm:start(GlobalName1, gen_fsm_SUITE, [], []),
- ?line Status3 = sys:get_status(GlobalName1),
- ?line {status, Pid3, _Mod, [_PDict3, running, _, _, Data3]} = Status3,
- ?line [format_status_called | _] = lists:reverse(Data3),
- ?line stop_it(Pid3),
+ {ok, Pid3} = gen_fsm:start(GlobalName1, gen_fsm_SUITE, [], []),
+ Status3 = sys:get_status(GlobalName1),
+ {status, Pid3, _Mod, [_PDict3, running, _, _, Data3]} = Status3,
+ [format_status_called | _] = lists:reverse(Data3),
+ stop_it(Pid3),
GlobalName2 = {global, {name, "term"}},
- ?line {ok, Pid4} = gen_fsm:start(GlobalName2, gen_fsm_SUITE, [], []),
- ?line Status4 = sys:get_status(GlobalName2),
- ?line {status, Pid4, _Mod, [_PDict4, running, _, _, Data4]} = Status4,
- ?line [format_status_called | _] = lists:reverse(Data4),
- ?line stop_it(Pid4),
+ {ok, Pid4} = gen_fsm:start(GlobalName2, gen_fsm_SUITE, [], []),
+ Status4 = sys:get_status(GlobalName2),
+ {status, Pid4, _Mod, [_PDict4, running, _, _, Data4]} = Status4,
+ [format_status_called | _] = lists:reverse(Data4),
+ stop_it(Pid4),
%% check that format_status can handle a name being a term other than a
%% pid or atom
- ?line dummy_via:reset(),
+ dummy_via:reset(),
ViaName1 = {via, dummy_via, "CallFormatStatus"},
- ?line {ok, Pid5} = gen_fsm:start(ViaName1, gen_fsm_SUITE, [], []),
- ?line Status5 = sys:get_status(ViaName1),
- ?line {status, Pid5, _Mod, [_PDict5, running, _, _, Data5]} = Status5,
- ?line [format_status_called | _] = lists:reverse(Data5),
- ?line stop_it(Pid5),
+ {ok, Pid5} = gen_fsm:start(ViaName1, gen_fsm_SUITE, [], []),
+ Status5 = sys:get_status(ViaName1),
+ {status, Pid5, _Mod, [_PDict5, running, _, _, Data5]} = Status5,
+ [format_status_called | _] = lists:reverse(Data5),
+ stop_it(Pid5),
ViaName2 = {via, dummy_via, {name, "term"}},
- ?line {ok, Pid6} = gen_fsm:start(ViaName2, gen_fsm_SUITE, [], []),
- ?line Status6 = sys:get_status(ViaName2),
- ?line {status, Pid6, _Mod, [_PDict6, running, _, _, Data6]} = Status6,
- ?line [format_status_called | _] = lists:reverse(Data6),
- ?line stop_it(Pid6).
+ {ok, Pid6} = gen_fsm:start(ViaName2, gen_fsm_SUITE, [], []),
+ Status6 = sys:get_status(ViaName2),
+ {status, Pid6, _Mod, [_PDict6, running, _, _, Data6]} = Status6,
+ [format_status_called | _] = lists:reverse(Data6),
+ stop_it(Pid6).
error_format_status(Config) when is_list(Config) ->
- ?line error_logger_forwarder:register(),
+ error_logger_forwarder:register(),
OldFl = process_flag(trap_exit, true),
StateData = "called format_status",
- ?line {ok, Pid} = gen_fsm:start(gen_fsm_SUITE, {state_data, StateData}, []),
+ {ok, Pid} = gen_fsm:start(gen_fsm_SUITE, {state_data, StateData}, []),
%% bad return value in the gen_fsm loop
- ?line {'EXIT',{{bad_return_value, badreturn},_}} =
+ {'EXIT',{{bad_return_value, badreturn},_}} =
(catch gen_fsm:sync_send_event(Pid, badreturn)),
receive
{error,_GroupLeader,{Pid,
@@ -514,10 +515,9 @@ error_format_status(Config) when is_list(Config) ->
[Pid,{_,_,badreturn},idle,{formatted,StateData},_]}} ->
ok;
Other ->
- ?line io:format("Unexpected: ~p", [Other]),
- ?line ?t:fail()
+ io:format("Unexpected: ~p", [Other]),
+ ct:fail(failed)
end,
- ?t:messages_get(),
process_flag(trap_exit, OldFl),
ok.
@@ -534,12 +534,11 @@ terminate_crash_format(Config) when is_list(Config) ->
ok;
Other ->
io:format("Unexpected: ~p", [Other]),
- ?t:fail()
+ ct:fail(failed)
after 5000 ->
io:format("Timeout: expected error logger msg", []),
- ?t:fail()
+ ct:fail(failed)
end,
- _ = ?t:messages_get(),
process_flag(trap_exit, OldFl),
ok.
@@ -603,7 +602,9 @@ hibernate(Config) when is_list(Config) ->
{ok, Pid0} = gen_fsm:start_link(?MODULE, hiber_now, []),
is_in_erlang_hibernate(Pid0),
stop_it(Pid0),
- test_server:messages_get(),
+ receive
+ {'EXIT',Pid0,normal} -> ok
+ end,
{ok, Pid} = gen_fsm:start_link(?MODULE, hiber, []),
true = ({current_function,{erlang,hibernate,3}} =/=
@@ -677,7 +678,11 @@ hibernate(Config) when is_list(Config) ->
good_morning = gen_fsm:sync_send_all_state_event(Pid, wakeup_sync),
is_not_in_erlang_hibernate(Pid),
stop_it(Pid),
- test_server:messages_get(),
+ receive
+ {'EXIT',Pid,normal} -> ok
+ end,
+
+ [] = get_messages(),
process_flag(trap_exit, OldFl),
ok.
@@ -687,7 +692,7 @@ is_in_erlang_hibernate(Pid) ->
is_in_erlang_hibernate_1(0, Pid) ->
io:format("~p\n", [erlang:process_info(Pid, current_function)]),
- ?t:fail(not_in_erlang_hibernate_3);
+ ct:fail(not_in_erlang_hibernate_3);
is_in_erlang_hibernate_1(N, Pid) ->
{current_function,MFA} = erlang:process_info(Pid, current_function),
case MFA of
@@ -704,7 +709,7 @@ is_not_in_erlang_hibernate(Pid) ->
is_not_in_erlang_hibernate_1(0, Pid) ->
io:format("~p\n", [erlang:process_info(Pid, current_function)]),
- ?t:fail(not_in_erlang_hibernate_3);
+ ct:fail(not_in_erlang_hibernate_3);
is_not_in_erlang_hibernate_1(N, Pid) ->
{current_function,MFA} = erlang:process_info(Pid, current_function),
case MFA of
@@ -715,108 +720,102 @@ is_not_in_erlang_hibernate_1(N, Pid) ->
ok
end.
-%%sys1(suite) -> [];
-%%sys1(_) ->
-
-enter_loop(suite) ->
- [];
-enter_loop(doc) ->
- ["Test gen_fsm:enter_loop/4,5,6"];
+%% Test gen_fsm:enter_loop/4,5,6.
enter_loop(Config) when is_list(Config) ->
OldFlag = process_flag(trap_exit, true),
- ?line dummy_via:reset(),
+ dummy_via:reset(),
%% Locally registered process + {local, Name}
- ?line {ok, Pid1a} =
+ {ok, Pid1a} =
proc_lib:start_link(?MODULE, enter_loop, [local, local]),
- ?line yes = gen_fsm:sync_send_event(Pid1a, 'alive?'),
- ?line stopped = gen_fsm:sync_send_event(Pid1a, stop),
+ yes = gen_fsm:sync_send_event(Pid1a, 'alive?'),
+ stopped = gen_fsm:sync_send_event(Pid1a, stop),
receive
{'EXIT', Pid1a, normal} ->
ok
after 5000 ->
- ?line test_server:fail(gen_fsm_did_not_die)
+ ct:fail(gen_fsm_did_not_die)
end,
%% Unregistered process + {local, Name}
- ?line {ok, Pid1b} =
+ {ok, Pid1b} =
proc_lib:start_link(?MODULE, enter_loop, [anon, local]),
receive
{'EXIT', Pid1b, process_not_registered} ->
ok
after 5000 ->
- ?line test_server:fail(gen_fsm_did_not_die)
+ ct:fail(gen_fsm_did_not_die)
end,
%% Globally registered process + {global, Name}
- ?line {ok, Pid2a} =
+ {ok, Pid2a} =
proc_lib:start_link(?MODULE, enter_loop, [global, global]),
- ?line yes = gen_fsm:sync_send_event(Pid2a, 'alive?'),
- ?line stopped = gen_fsm:sync_send_event(Pid2a, stop),
+ yes = gen_fsm:sync_send_event(Pid2a, 'alive?'),
+ stopped = gen_fsm:sync_send_event(Pid2a, stop),
receive
{'EXIT', Pid2a, normal} ->
ok
after 5000 ->
- ?line test_server:fail(gen_fsm_did_not_die)
+ ct:fail(gen_fsm_did_not_die)
end,
%% Unregistered process + {global, Name}
- ?line {ok, Pid2b} =
+ {ok, Pid2b} =
proc_lib:start_link(?MODULE, enter_loop, [anon, global]),
receive
{'EXIT', Pid2b, process_not_registered_globally} ->
ok
after 5000 ->
- ?line test_server:fail(gen_fsm_did_not_die)
+ ct:fail(gen_fsm_did_not_die)
end,
%% Unregistered process + no name
- ?line {ok, Pid3} =
+ {ok, Pid3} =
proc_lib:start_link(?MODULE, enter_loop, [anon, anon]),
- ?line yes = gen_fsm:sync_send_event(Pid3, 'alive?'),
- ?line stopped = gen_fsm:sync_send_event(Pid3, stop),
+ yes = gen_fsm:sync_send_event(Pid3, 'alive?'),
+ stopped = gen_fsm:sync_send_event(Pid3, stop),
receive
{'EXIT', Pid3, normal} ->
ok
after 5000 ->
- ?line test_server:fail(gen_fsm_did_not_die)
+ ct:fail(gen_fsm_did_not_die)
end,
%% Process not started using proc_lib
- ?line Pid4 =
+ Pid4 =
spawn_link(gen_fsm, enter_loop, [?MODULE, [], state0, []]),
receive
{'EXIT', Pid4, process_was_not_started_by_proc_lib} ->
ok
after 5000 ->
- ?line test_server:fail(gen_fsm_did_not_die)
+ ct:fail(gen_fsm_did_not_die)
end,
%% Make sure I am the parent, ie that ordering a shutdown will
%% result in the process terminating with Reason==shutdown
- ?line {ok, Pid5} =
+ {ok, Pid5} =
proc_lib:start_link(?MODULE, enter_loop, [anon, anon]),
- ?line yes = gen_fsm:sync_send_event(Pid5, 'alive?'),
- ?line exit(Pid5, shutdown),
+ yes = gen_fsm:sync_send_event(Pid5, 'alive?'),
+ exit(Pid5, shutdown),
receive
{'EXIT', Pid5, shutdown} ->
ok
after 5000 ->
- ?line test_server:fail(gen_fsm_did_not_die)
+ ct:fail(gen_fsm_did_not_die)
end,
%% Make sure gen_fsm:enter_loop does not accept {local,Name}
%% when it's another process than the calling one which is
%% registered under that name
register(armitage, self()),
- ?line {ok, Pid6a} =
+ {ok, Pid6a} =
proc_lib:start_link(?MODULE, enter_loop, [anon, local]),
receive
{'EXIT', Pid6a, process_not_registered} ->
ok
after 1000 ->
- ?line test_server:fail(gen_fsm_started)
+ ct:fail(gen_fsm_started)
end,
unregister(armitage),
@@ -824,25 +823,24 @@ enter_loop(Config) when is_list(Config) ->
%% when it's another process than the calling one which is
%% registered under that name
global:register_name(armitage, self()),
- ?line {ok, Pid6b} =
+ {ok, Pid6b} =
proc_lib:start_link(?MODULE, enter_loop, [anon, global]),
receive
{'EXIT', Pid6b, process_not_registered_globally} ->
ok
after 1000 ->
- ?line test_server:fail(gen_fsm_started)
+ ct:fail(gen_fsm_started)
end,
global:unregister_name(armitage),
dummy_via:register_name(armitage, self()),
- ?line {ok, Pid6c} =
+ {ok, Pid6c} =
proc_lib:start_link(?MODULE, enter_loop, [anon, via]),
receive
{'EXIT', Pid6c, {process_not_registered_via, dummy_via}} ->
ok
after 1000 ->
- ?line test_server:fail({gen_fsm_started, process_info(self(),
- messages)})
+ ct:fail({gen_fsm_started, process_info(self(), messages)})
end,
dummy_via:unregister_name(armitage),
@@ -883,8 +881,8 @@ wfor(Msg) ->
stop_it(FSM) ->
- ?line stopped = gen_fsm:sync_send_all_state_event(FSM, stop),
- ?line {'EXIT',_} = (catch gen_fsm:sync_send_event(FSM, hej)),
+ stopped = gen_fsm:sync_send_all_state_event(FSM, stop),
+ {'EXIT',_} = (catch gen_fsm:sync_send_event(FSM, hej)),
ok.
@@ -895,7 +893,7 @@ do_func_test(FSM) ->
ok = do_connect(FSM),
ok = gen_fsm:send_all_state_event(FSM, {'alive?', self()}),
wfor(yes),
- test_server:do_times(3, ?MODULE, do_msg, [FSM]),
+ _ = [do_msg(FSM) || _ <- lists:seq(1, 3)],
ok = gen_fsm:send_all_state_event(FSM, {'alive?', self()}),
wfor(yes),
ok = do_disconnect(FSM),
@@ -933,7 +931,7 @@ do_sync_func_test(FSM) ->
yes = gen_fsm:sync_send_all_state_event(FSM, 'alive?'),
ok = do_sync_connect(FSM),
yes = gen_fsm:sync_send_all_state_event(FSM, 'alive?'),
- test_server:do_times(3, ?MODULE, do_sync_msg, [FSM]),
+ _ = [do_sync_msg(FSM) || _ <- lists:seq(1, 3)],
yes = gen_fsm:sync_send_all_state_event(FSM, 'alive?'),
ok = do_sync_disconnect(FSM),
yes = gen_fsm:sync_send_all_state_event(FSM, 'alive?'),
@@ -964,7 +962,7 @@ do_sync_disconnect(FSM) ->
yes = gen_fsm:sync_send_event(FSM, disconnect),
check_state(FSM, idle).
-
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%%
@@ -979,7 +977,7 @@ init(stop) ->
init(stop_shutdown) ->
{stop, shutdown};
init(sleep) ->
- test_server:sleep(1000),
+ timer:sleep(1000),
{ok, idle, data};
init({timeout, T}) ->
{ok, idle, state, T};
@@ -1012,7 +1010,7 @@ idle(_, Data) ->
idle({connect, _Pid}, _From, Data) ->
{reply, accept, wfor_conf, Data};
idle({delayed_answer, T}, _From, Data) ->
- test_server:sleep(T),
+ timer:sleep(T),
{reply, delayed, idle, Data};
idle(badreturn, _From, _Data) ->
badreturn;
@@ -1070,8 +1068,8 @@ hiber_idle('alive?', _From, Data) ->
{reply, 'alive!', hiber_idle, Data};
hiber_idle(hibernate_sync, _From, Data) ->
{reply, hibernating, hiber_wakeup, Data,hibernate}.
-hiber_idle(timeout, hibernate_me) -> % Arrive here from
- % handle_info(hibernate_later,...)
+hiber_idle(timeout, hibernate_me) ->
+ %% Arrive here from handle_info(hibernate_later,...)
{next_state, hiber_idle, [], hibernate};
hiber_idle(hibernate_async, Data) ->
{next_state,hiber_wakeup, Data, hibernate}.
@@ -1084,9 +1082,10 @@ hiber_wakeup(wakeup_async,Data) ->
{next_state,hiber_idle,Data};
hiber_wakeup(snooze_async,Data) ->
{next_state,hiber_wakeup,Data,hibernate}.
-
-handle_info(hibernate_now, _SName, _State) -> % Arrive here from by direct ! from testcase
+
+handle_info(hibernate_now, _SName, _State) ->
+ %% Arrive here from by direct ! from testcase
{next_state, hiber_idle, [], hibernate};
handle_info(hibernate_later, _SName, _State) ->
{next_state, hiber_idle, hibernate_me, 1000};
@@ -1134,3 +1133,9 @@ format_status(terminate, [_Pdict, StateData]) ->
{formatted, StateData};
format_status(normal, [_Pdict, _StateData]) ->
[format_status_called].
+
+get_messages() ->
+ receive
+ Msg -> [Msg|get_messages()]
+ after 1 -> []
+ end.