1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 1996-2018. All Rights Reserved.
5%%
6%% Licensed under the Apache License, Version 2.0 (the "License");
7%% you may not use this file except in compliance with the License.
8%% You may obtain a copy of the License at
9%%
10%%     http://www.apache.org/licenses/LICENSE-2.0
11%%
12%% Unless required by applicable law or agreed to in writing, software
13%% distributed under the License is distributed on an "AS IS" BASIS,
14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15%% See the License for the specific language governing permissions and
16%% limitations under the License.
17%%
18%% %CopyrightEnd%
19%%
20-module(gen_fsm_SUITE).
21
22-include_lib("common_test/include/ct.hrl").
23
24%% Test cases
25-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
26	 init_per_group/2,end_per_group/2]).
27
28-export([start1/1, start2/1, start3/1, start4/1, start5/1, start6/1,
29	 start7/1, start8/1, start9/1, start10/1, start11/1, start12/1]).
30
31-export([stop1/1, stop2/1, stop3/1, stop4/1, stop5/1, stop6/1, stop7/1,
32	 stop8/1, stop9/1, stop10/1]).
33
34-export([ abnormal1/1, abnormal2/1]).
35
36-export([shutdown/1]).
37
38-export([ sys1/1,
39	  call_format_status/1, error_format_status/1, terminate_crash_format/1,
40	  get_state/1, replace_state/1]).
41
42-export([undef_handle_event/1, undef_handle_sync_event/1, undef_handle_info/1,
43         undef_init/1, undef_code_change/1, undef_terminate1/1, undef_terminate2/1]).
44
45-export([undef_in_handle_info/1, undef_in_terminate/1]).
46
47-export([hibernate/1,auto_hibernate/1,hiber_idle/3,hiber_wakeup/3,hiber_idle/2,hiber_wakeup/2]).
48
49-export([enter_loop/1]).
50
51%% Exports for apply
52-export([enter_loop/2]).
53
54%% The gen_fsm behaviour
55-export([init/1, handle_event/3, handle_sync_event/4, terminate/3,
56	 handle_info/3, format_status/2, code_change/4]).
57-export([idle/2,	idle/3,
58	 timeout/2,
59	 wfor_conf/2,	wfor_conf/3,
60	 connected/2,	connected/3]).
61-export([state0/3]).
62
63
64%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
65
66
67suite() -> [{ct_hooks,[ts_install_cth]}].
68
69all() ->
70    [{group, start}, {group, abnormal}, shutdown,
71     {group, sys}, hibernate, auto_hibernate, enter_loop, {group, undef_callbacks},
72     undef_in_handle_info, undef_in_terminate].
73
74groups() ->
75    [{start, [],
76      [start1, start2, start3, start4, start5, start6, start7,
77       start8, start9, start10, start11, start12]},
78     {stop, [],
79      [stop1, stop2, stop3, stop4, stop5, stop6, stop7, stop8, stop9, stop10]},
80     {abnormal, [], [abnormal1, abnormal2]},
81     {sys, [],
82      [sys1, call_format_status, error_format_status, terminate_crash_format,
83       get_state, replace_state]},
84     {undef_callbacks, [],
85      [undef_handle_event, undef_handle_sync_event, undef_handle_info,
86       undef_init, undef_code_change, undef_terminate1, undef_terminate2]}].
87
88init_per_suite(Config) ->
89    Config.
90
91end_per_suite(_Config) ->
92    ok.
93
94init_per_group(undef_callbacks, Config) ->
95    DataDir = ?config(data_dir, Config),
96    Server = filename:join(DataDir, "oc_fsm.erl"),
97    {ok, oc_fsm} = compile:file(Server),
98    Config;
99init_per_group(_GroupName, Config) ->
100    Config.
101
102end_per_group(_GroupName, Config) ->
103    Config.
104
105%% anonymous
106start1(Config) when is_list(Config) ->
107    %%OldFl = process_flag(trap_exit, true),
108
109    {ok, Pid0} = gen_fsm:start_link(gen_fsm_SUITE, [], []),
110    ok = do_func_test(Pid0),
111    ok = do_sync_func_test(Pid0),
112    stop_it(Pid0),
113    %%    stopped = gen_fsm:sync_send_all_state_event(Pid0, stop),
114    %%    {'EXIT', {timeout,_}} =
115    %%	(catch gen_fsm:sync_send_event(Pid0, hej)),
116
117    [] = get_messages(),
118    %%process_flag(trap_exit, OldFl),
119    ok.
120
121%% anonymous w. shutdown
122start2(Config) when is_list(Config) ->
123    %% Dont link when shutdown
124    {ok, Pid0} = gen_fsm:start(gen_fsm_SUITE, [], []),
125    ok = do_func_test(Pid0),
126    ok = do_sync_func_test(Pid0),
127    MRef = monitor(process,Pid0),
128    shutdown_stopped =
129	gen_fsm:sync_send_all_state_event(Pid0, stop_shutdown),
130    receive {'DOWN',MRef,_,_,shutdown} -> ok end,
131    {'EXIT', {noproc,_}} =
132	(catch gen_fsm:sync_send_event(Pid0, hej)),
133
134    [] = get_messages(),
135    ok.
136
137%% anonymous with timeout
138start3(Config) when is_list(Config) ->
139    %%OldFl = process_flag(trap_exit, true),
140
141    {ok, Pid0} = gen_fsm:start(gen_fsm_SUITE, [], [{timeout,5}]),
142    ok = do_func_test(Pid0),
143    ok = do_sync_func_test(Pid0),
144    stop_it(Pid0),
145
146    {error, timeout} = gen_fsm:start(gen_fsm_SUITE, sleep,
147				     [{timeout,5}]),
148
149    [] = get_messages(),
150    %%process_flag(trap_exit, OldFl),
151    ok.
152
153%% anonymous with ignore
154start4(Config) when is_list(Config) ->
155    OldFl = process_flag(trap_exit, true),
156
157    ignore = gen_fsm:start(gen_fsm_SUITE, ignore, []),
158
159    [] = get_messages(),
160    process_flag(trap_exit, OldFl),
161    ok.
162
163%% anonymous with stop
164start5(Config) when is_list(Config) ->
165    OldFl = process_flag(trap_exit, true),
166
167    {error, stopped} = gen_fsm:start(gen_fsm_SUITE, stop, []),
168
169    [] = get_messages(),
170    process_flag(trap_exit, OldFl),
171    ok.
172
173%% anonymous linked
174start6(Config) when is_list(Config) ->
175    {ok, Pid} = gen_fsm:start_link(gen_fsm_SUITE, [], []),
176    ok = do_func_test(Pid),
177    ok = do_sync_func_test(Pid),
178    stop_it(Pid),
179
180    [] = get_messages(),
181
182    ok.
183
184%% global register linked
185start7(Config) when is_list(Config) ->
186    {ok, Pid} =
187	gen_fsm:start_link({global, my_fsm}, gen_fsm_SUITE, [], []),
188    {error, {already_started, Pid}} =
189	gen_fsm:start_link({global, my_fsm}, gen_fsm_SUITE, [], []),
190    {error, {already_started, Pid}} =
191	gen_fsm:start({global, my_fsm}, gen_fsm_SUITE, [], []),
192
193    ok = do_func_test(Pid),
194    ok = do_sync_func_test(Pid),
195    ok = do_func_test({global, my_fsm}),
196    ok = do_sync_func_test({global, my_fsm}),
197    stop_it({global, my_fsm}),
198
199    [] = get_messages(),
200    ok.
201
202
203%% local register
204start8(Config) when is_list(Config) ->
205    %%OldFl = process_flag(trap_exit, true),
206
207    {ok, Pid} =
208	gen_fsm:start({local, my_fsm}, gen_fsm_SUITE, [], []),
209    {error, {already_started, Pid}} =
210	gen_fsm:start({local, my_fsm}, gen_fsm_SUITE, [], []),
211
212    ok = do_func_test(Pid),
213    ok = do_sync_func_test(Pid),
214    ok = do_func_test(my_fsm),
215    ok = do_sync_func_test(my_fsm),
216    stop_it(Pid),
217
218    [] = get_messages(),
219    %%process_flag(trap_exit, OldFl),
220    ok.
221
222%% local register linked
223start9(Config) when is_list(Config) ->
224    %%OldFl = process_flag(trap_exit, true),
225
226    {ok, Pid} =
227	gen_fsm:start_link({local, my_fsm}, gen_fsm_SUITE, [], []),
228    {error, {already_started, Pid}} =
229	gen_fsm:start({local, my_fsm}, gen_fsm_SUITE, [], []),
230
231    ok = do_func_test(Pid),
232    ok = do_sync_func_test(Pid),
233    ok = do_func_test(my_fsm),
234    ok = do_sync_func_test(my_fsm),
235    stop_it(Pid),
236
237    [] = get_messages(),
238    %%process_flag(trap_exit, OldFl),
239    ok.
240
241%% global register
242start10(Config) when is_list(Config) ->
243    {ok, Pid} =
244	gen_fsm:start({global, my_fsm}, gen_fsm_SUITE, [], []),
245    {error, {already_started, Pid}} =
246	gen_fsm:start({global, my_fsm}, gen_fsm_SUITE, [], []),
247    {error, {already_started, Pid}} =
248	gen_fsm:start_link({global, my_fsm}, gen_fsm_SUITE, [], []),
249
250    ok = do_func_test(Pid),
251    ok = do_sync_func_test(Pid),
252    ok = do_func_test({global, my_fsm}),
253    ok = do_sync_func_test({global, my_fsm}),
254    stop_it({global, my_fsm}),
255
256    [] = get_messages(),
257    ok.
258
259
260%% Stop registered processes
261start11(Config) when is_list(Config) ->
262    {ok, Pid} =
263	gen_fsm:start_link({local, my_fsm}, gen_fsm_SUITE, [], []),
264    stop_it(Pid),
265
266    {ok, _Pid1} =
267	gen_fsm:start_link({local, my_fsm}, gen_fsm_SUITE, [], []),
268    stop_it(my_fsm),
269
270    {ok, Pid2} =
271	gen_fsm:start({global, my_fsm}, gen_fsm_SUITE, [], []),
272    stop_it(Pid2),
273    receive after 1 -> true end,
274    Result =
275	gen_fsm:start({global, my_fsm}, gen_fsm_SUITE, [], []),
276    io:format("Result = ~p~n",[Result]),
277    {ok, _Pid3} = Result,
278    stop_it({global, my_fsm}),
279
280    [] = get_messages(),
281    ok.
282
283%% Via register linked
284start12(Config) when is_list(Config) ->
285    dummy_via:reset(),
286    {ok, Pid} =
287	gen_fsm:start_link({via, dummy_via, my_fsm}, gen_fsm_SUITE, [], []),
288    {error, {already_started, Pid}} =
289	gen_fsm:start_link({via, dummy_via, my_fsm}, gen_fsm_SUITE, [], []),
290    {error, {already_started, Pid}} =
291	gen_fsm:start({via, dummy_via, my_fsm}, gen_fsm_SUITE, [], []),
292
293    ok = do_func_test(Pid),
294    ok = do_sync_func_test(Pid),
295    ok = do_func_test({via, dummy_via, my_fsm}),
296    ok = do_sync_func_test({via, dummy_via, my_fsm}),
297    stop_it({via, dummy_via, my_fsm}),
298
299    [] = get_messages(),
300    ok.
301
302
303%% Anonymous, reason 'normal'
304stop1(_Config) ->
305    {ok, Pid} = gen_fsm:start(?MODULE, [], []),
306    ok = gen_fsm:stop(Pid),
307    false = erlang:is_process_alive(Pid),
308    {'EXIT',noproc} = (catch gen_fsm:stop(Pid)),
309    ok.
310
311%% Anonymous, other reason
312stop2(_Config) ->
313    {ok,Pid} = gen_fsm:start(?MODULE, [], []),
314    ok = gen_fsm:stop(Pid, other_reason, infinity),
315    false = erlang:is_process_alive(Pid),
316    ok.
317
318%% Anonymous, invalid timeout
319stop3(_Config) ->
320    {ok,Pid} = gen_fsm:start(?MODULE, [], []),
321    {'EXIT',_} = (catch gen_fsm:stop(Pid, other_reason, invalid_timeout)),
322    true = erlang:is_process_alive(Pid),
323    ok = gen_fsm:stop(Pid),
324    false = erlang:is_process_alive(Pid),
325    ok.
326
327%% Registered name
328stop4(_Config) ->
329    {ok,Pid} = gen_fsm:start({local,to_stop},?MODULE, [], []),
330    ok = gen_fsm:stop(to_stop),
331    false = erlang:is_process_alive(Pid),
332    {'EXIT',noproc} = (catch gen_fsm:stop(to_stop)),
333    ok.
334
335%% Registered name and local node
336stop5(_Config) ->
337    {ok,Pid} = gen_fsm:start({local,to_stop},?MODULE, [], []),
338    ok = gen_fsm:stop({to_stop,node()}),
339    false = erlang:is_process_alive(Pid),
340    {'EXIT',noproc} = (catch gen_fsm:stop({to_stop,node()})),
341    ok.
342
343%% Globally registered name
344stop6(_Config) ->
345    {ok, Pid} = gen_fsm:start({global, to_stop}, ?MODULE, [], []),
346    ok = gen_fsm:stop({global,to_stop}),
347    false = erlang:is_process_alive(Pid),
348    {'EXIT',noproc} = (catch gen_fsm:stop({global,to_stop})),
349    ok.
350
351%% 'via' registered name
352stop7(_Config) ->
353    dummy_via:reset(),
354    {ok, Pid} = gen_fsm:start({via, dummy_via, to_stop},
355			      ?MODULE, [], []),
356    ok = gen_fsm:stop({via, dummy_via, to_stop}),
357    false = erlang:is_process_alive(Pid),
358    {'EXIT',noproc} = (catch gen_fsm:stop({via, dummy_via, to_stop})),
359    ok.
360
361%% Anonymous on remote node
362stop8(_Config) ->
363    {ok,Node} = test_server:start_node(gen_fsm_SUITE_stop8,slave,[]),
364    Dir = filename:dirname(code:which(?MODULE)),
365    rpc:call(Node,code,add_path,[Dir]),
366    {ok, Pid} = rpc:call(Node,gen_fsm,start,[?MODULE,[],[]]),
367    ok = gen_fsm:stop(Pid),
368    false = rpc:call(Node,erlang,is_process_alive,[Pid]),
369    {'EXIT',noproc} = (catch gen_fsm:stop(Pid)),
370    true = test_server:stop_node(Node),
371    {'EXIT',{{nodedown,Node},_}} = (catch gen_fsm:stop(Pid)),
372    ok.
373
374%% Registered name on remote node
375stop9(_Config) ->
376    {ok,Node} = test_server:start_node(gen_fsm_SUITE_stop9,slave,[]),
377    Dir = filename:dirname(code:which(?MODULE)),
378    rpc:call(Node,code,add_path,[Dir]),
379    {ok, Pid} = rpc:call(Node,gen_fsm,start,[{local,to_stop},?MODULE,[],[]]),
380    ok = gen_fsm:stop({to_stop,Node}),
381    undefined = rpc:call(Node,erlang,whereis,[to_stop]),
382    false = rpc:call(Node,erlang,is_process_alive,[Pid]),
383    {'EXIT',noproc} = (catch gen_fsm:stop({to_stop,Node})),
384    true = test_server:stop_node(Node),
385    {'EXIT',{{nodedown,Node},_}} = (catch gen_fsm:stop({to_stop,Node})),
386    ok.
387
388%% Globally registered name on remote node
389stop10(_Config) ->
390    {ok,Node} = test_server:start_node(gen_fsm_SUITE_stop10,slave,[]),
391    Dir = filename:dirname(code:which(?MODULE)),
392    rpc:call(Node,code,add_path,[Dir]),
393    {ok, Pid} = rpc:call(Node,gen_fsm,start,[{global,to_stop},?MODULE,[],[]]),
394    ok = global:sync(),
395    ok = gen_fsm:stop({global,to_stop}),
396    false = rpc:call(Node,erlang,is_process_alive,[Pid]),
397    {'EXIT',noproc} = (catch gen_fsm:stop({global,to_stop})),
398    true = test_server:stop_node(Node),
399    {'EXIT',noproc} = (catch gen_fsm:stop({global,to_stop})),
400    ok.
401
402%% Check that time outs in calls work
403abnormal1(Config) when is_list(Config) ->
404    {ok, _Pid} = gen_fsm:start({local, my_fsm}, gen_fsm_SUITE, [], []),
405
406    %% timeout call.
407    delayed = gen_fsm:sync_send_event(my_fsm, {delayed_answer,1}, 100),
408    {'EXIT',{timeout,_}} =
409	(catch gen_fsm:sync_send_event(my_fsm, {delayed_answer,10}, 1)),
410    receive
411	Msg ->
412	    %% Ignore the delayed answer from the server.
413	    io:format("Delayed message: ~p", [Msg])
414    end,
415
416    [] = get_messages(),
417    ok.
418
419%% Check that bad return values makes the fsm crash. Note that we must
420%% trap exit since we must link to get the real bad_return_ error
421abnormal2(Config) when is_list(Config) ->
422    OldFl = process_flag(trap_exit, true),
423    {ok, Pid} =
424	gen_fsm:start_link(gen_fsm_SUITE, [], []),
425
426    %% bad return value in the gen_fsm loop
427    {'EXIT',{{bad_return_value, badreturn},_}} =
428	(catch gen_fsm:sync_send_event(Pid, badreturn)),
429
430    [{'EXIT',Pid,{bad_return_value,badreturn}}] = get_messages(),
431    process_flag(trap_exit, OldFl),
432    ok.
433
434shutdown(Config) when is_list(Config) ->
435    error_logger_forwarder:register(),
436
437    process_flag(trap_exit, true),
438
439    {ok,Pid0} = gen_fsm:start_link(gen_fsm_SUITE, [], []),
440    ok = do_func_test(Pid0),
441    ok = do_sync_func_test(Pid0),
442    {shutdown,reason} =
443	gen_fsm:sync_send_all_state_event(Pid0, stop_shutdown_reason),
444    receive {'EXIT',Pid0,{shutdown,reason}} -> ok end,
445    process_flag(trap_exit, false),
446
447    {'EXIT', {noproc,_}} =
448	(catch gen_fsm:sync_send_event(Pid0, hej)),
449
450    receive
451	Any ->
452	    io:format("Unexpected: ~p", [Any]),
453	    ct:fail(failed)
454    after 500 ->
455	    ok
456    end,
457
458    ok.
459
460
461
462sys1(Config) when is_list(Config) ->
463    {ok, Pid} =
464	gen_fsm:start(gen_fsm_SUITE, [], []),
465    {status, Pid, {module,gen_fsm}, _} = sys:get_status(Pid),
466    sys:suspend(Pid),
467    {'EXIT', {timeout,_}} =
468	(catch gen_fsm:sync_send_event(Pid, hej)),
469    sys:resume(Pid),
470    stop_it(Pid).
471
472call_format_status(Config) when is_list(Config) ->
473    {ok, Pid} = gen_fsm:start(gen_fsm_SUITE, [], []),
474    Status = sys:get_status(Pid),
475    {status, Pid, _Mod, [_PDict, running, _, _, Data]} = Status,
476    [format_status_called | _] = lists:reverse(Data),
477    stop_it(Pid),
478
479    %% check that format_status can handle a name being an atom (pid is
480    %% already checked by the previous test)
481    {ok, Pid2} = gen_fsm:start({local, gfsm}, gen_fsm_SUITE, [], []),
482    Status2 = sys:get_status(gfsm),
483    {status, Pid2, _Mod, [_PDict2, running, _, _, Data2]} = Status2,
484    [format_status_called | _] = lists:reverse(Data2),
485    stop_it(Pid2),
486
487    %% check that format_status can handle a name being a term other than a
488    %% pid or atom
489    GlobalName1 = {global, "CallFormatStatus"},
490    {ok, Pid3} = gen_fsm:start(GlobalName1, gen_fsm_SUITE, [], []),
491    Status3 = sys:get_status(GlobalName1),
492    {status, Pid3, _Mod, [_PDict3, running, _, _, Data3]} = Status3,
493    [format_status_called | _] = lists:reverse(Data3),
494    stop_it(Pid3),
495    GlobalName2 = {global, {name, "term"}},
496    {ok, Pid4} = gen_fsm:start(GlobalName2, gen_fsm_SUITE, [], []),
497    Status4 = sys:get_status(GlobalName2),
498    {status, Pid4, _Mod, [_PDict4, running, _, _, Data4]} = Status4,
499    [format_status_called | _] = lists:reverse(Data4),
500    stop_it(Pid4),
501
502    %% check that format_status can handle a name being a term other than a
503    %% pid or atom
504    dummy_via:reset(),
505    ViaName1 = {via, dummy_via, "CallFormatStatus"},
506    {ok, Pid5} = gen_fsm:start(ViaName1, gen_fsm_SUITE, [], []),
507    Status5 = sys:get_status(ViaName1),
508    {status, Pid5, _Mod, [_PDict5, running, _, _, Data5]} = Status5,
509    [format_status_called | _] = lists:reverse(Data5),
510    stop_it(Pid5),
511    ViaName2 = {via, dummy_via, {name, "term"}},
512    {ok, Pid6} = gen_fsm:start(ViaName2, gen_fsm_SUITE, [], []),
513    Status6 = sys:get_status(ViaName2),
514    {status, Pid6, _Mod, [_PDict6, running, _, _, Data6]} = Status6,
515    [format_status_called | _] = lists:reverse(Data6),
516    stop_it(Pid6).
517
518
519
520error_format_status(Config) when is_list(Config) ->
521    error_logger_forwarder:register(),
522    OldFl = process_flag(trap_exit, true),
523    StateData = "called format_status",
524    Parent = self(),
525    {ok, Pid} = gen_fsm:start(gen_fsm_SUITE, {state_data, StateData}, []),
526    %% bad return value in the gen_fsm loop
527    {'EXIT',{{bad_return_value, badreturn},_}} =
528	(catch gen_fsm:sync_send_event(Pid, badreturn)),
529    receive
530	{error,_GroupLeader,{Pid,
531			     "** State machine "++_,
532			     [Pid,badreturn,Parent,idle,{formatted,StateData},
533                              {bad_return_value,badreturn}|_]}} ->
534	    ok;
535	Other ->
536	    io:format("Unexpected: ~p", [Other]),
537	    ct:fail(failed)
538    end,
539    process_flag(trap_exit, OldFl),
540    ok.
541
542terminate_crash_format(Config) when is_list(Config) ->
543    error_logger_forwarder:register(),
544    OldFl = process_flag(trap_exit, true),
545    StateData = crash_terminate,
546    Parent = self(),
547    {ok, Pid} = gen_fsm:start(gen_fsm_SUITE, {state_data, StateData}, []),
548    stop_it(Pid),
549    receive
550	{error,_GroupLeader,{Pid,
551			     "** State machine "++_,
552			     [Pid,stop,Parent,idle,{formatted, StateData},
553                              {crash,terminate}|_]}} ->
554	    ok;
555	Other ->
556	    io:format("Unexpected: ~p", [Other]),
557	    ct:fail(failed)
558    after 5000 ->
559	    io:format("Timeout: expected error logger msg", []),
560	    ct:fail(failed)
561    end,
562    process_flag(trap_exit, OldFl),
563    ok.
564
565
566get_state(Config) when is_list(Config) ->
567    State = self(),
568    {ok, Pid} = gen_fsm:start(?MODULE, {state_data, State}, []),
569    {idle, State} = sys:get_state(Pid),
570    {idle, State} = sys:get_state(Pid, 5000),
571    stop_it(Pid),
572
573    %% check that get_state can handle a name being an atom (pid is
574    %% already checked by the previous test)
575    {ok, Pid2} = gen_fsm:start({local, gfsm}, gen_fsm_SUITE, {state_data, State}, []),
576    {idle, State} = sys:get_state(gfsm),
577    {idle, State} = sys:get_state(gfsm, 5000),
578    stop_it(Pid2),
579
580    %% check that get_state works when pid is sys suspended
581    {ok, Pid3} = gen_fsm:start(gen_fsm_SUITE, {state_data, State}, []),
582    {idle, State} = sys:get_state(Pid3),
583    ok = sys:suspend(Pid3),
584    {idle, State} = sys:get_state(Pid3, 5000),
585    ok = sys:resume(Pid3),
586    stop_it(Pid3),
587    ok.
588
589replace_state(Config) when is_list(Config) ->
590    State = self(),
591    {ok, Pid} = gen_fsm:start(?MODULE, {state_data, State}, []),
592    {idle, State} = sys:get_state(Pid),
593    NState1 = "replaced",
594    Replace1 = fun({StateName, _}) -> {StateName, NState1} end,
595    {idle, NState1} = sys:replace_state(Pid, Replace1),
596    {idle, NState1} = sys:get_state(Pid),
597    NState2 = "replaced again",
598    Replace2 = fun({idle, _}) -> {state0, NState2} end,
599    {state0, NState2} = sys:replace_state(Pid, Replace2, 5000),
600    {state0, NState2} = sys:get_state(Pid),
601    %% verify no change in state if replace function crashes
602    Replace3 = fun(_) -> error(fail) end,
603    {'EXIT',{{callback_failed,
604	      {gen_fsm,system_replace_state},{error,fail}},_}} =
605	(catch sys:replace_state(Pid, Replace3)),
606    {state0, NState2} = sys:get_state(Pid),
607    %% verify state replaced if process sys suspended
608    ok = sys:suspend(Pid),
609    Suffix2 = " and again",
610    NState3 = NState2 ++ Suffix2,
611    Replace4 = fun({StateName, _}) -> {StateName, NState3} end,
612    {state0, NState3} = sys:replace_state(Pid, Replace4),
613    ok = sys:resume(Pid),
614    {state0, NState3} = sys:get_state(Pid, 5000),
615    stop_it(Pid),
616    ok.
617
618%% Hibernation
619hibernate(Config) when is_list(Config) ->
620    OldFl = process_flag(trap_exit, true),
621
622    {ok, Pid0} = gen_fsm:start_link(?MODULE, hiber_now, []),
623    is_in_erlang_hibernate(Pid0),
624    stop_it(Pid0),
625    receive
626	{'EXIT',Pid0,normal} -> ok
627    end,
628
629    {ok, Pid} = gen_fsm:start_link(?MODULE, hiber, []),
630    true = ({current_function,{erlang,hibernate,3}} =/=
631		erlang:process_info(Pid,current_function)),
632    hibernating = gen_fsm:sync_send_event(Pid, hibernate_sync),
633    is_in_erlang_hibernate(Pid),
634    good_morning = gen_fsm:sync_send_event(Pid, wakeup_sync),
635    is_not_in_erlang_hibernate(Pid),
636    hibernating = gen_fsm:sync_send_event(Pid, hibernate_sync),
637    is_in_erlang_hibernate(Pid),
638    five_more = gen_fsm:sync_send_event(Pid, snooze_sync),
639    is_in_erlang_hibernate(Pid),
640    good_morning = gen_fsm:sync_send_event(Pid, wakeup_sync),
641    is_not_in_erlang_hibernate(Pid),
642    ok = gen_fsm:send_event(Pid, hibernate_async),
643    is_in_erlang_hibernate(Pid),
644    ok = gen_fsm:send_event(Pid, wakeup_async),
645    is_not_in_erlang_hibernate(Pid),
646    ok = gen_fsm:send_event(Pid, hibernate_async),
647    is_in_erlang_hibernate(Pid),
648    ok = gen_fsm:send_event(Pid, snooze_async),
649    is_in_erlang_hibernate(Pid),
650    ok = gen_fsm:send_event(Pid, wakeup_async),
651    is_not_in_erlang_hibernate(Pid),
652
653    Pid ! hibernate_later,
654    true = ({current_function,{erlang,hibernate,3}} =/=
655		erlang:process_info(Pid, current_function)),
656    is_in_erlang_hibernate(Pid),
657
658    'alive!' = gen_fsm:sync_send_event(Pid,'alive?'),
659    true = ({current_function,{erlang,hibernate,3}} =/=
660		erlang:process_info(Pid, current_function)),
661    Pid ! hibernate_now,
662    is_in_erlang_hibernate(Pid),
663
664    'alive!' = gen_fsm:sync_send_event(Pid,'alive?'),
665    true = ({current_function,{erlang,hibernate,3}} =/=
666		erlang:process_info(Pid, current_function)),
667
668    hibernating = gen_fsm:sync_send_all_state_event(Pid, hibernate_sync),
669    is_in_erlang_hibernate(Pid),
670    good_morning = gen_fsm:sync_send_all_state_event(Pid, wakeup_sync),
671    is_not_in_erlang_hibernate(Pid),
672    hibernating = gen_fsm:sync_send_all_state_event(Pid, hibernate_sync),
673    is_in_erlang_hibernate(Pid),
674    five_more = gen_fsm:sync_send_all_state_event(Pid, snooze_sync),
675    is_in_erlang_hibernate(Pid),
676    good_morning = gen_fsm:sync_send_all_state_event(Pid, wakeup_sync),
677    is_not_in_erlang_hibernate(Pid),
678    ok = gen_fsm:send_all_state_event(Pid, hibernate_async),
679    is_in_erlang_hibernate(Pid),
680    ok  = gen_fsm:send_all_state_event(Pid, wakeup_async),
681    is_not_in_erlang_hibernate(Pid),
682    ok = gen_fsm:send_all_state_event(Pid, hibernate_async),
683    is_in_erlang_hibernate(Pid),
684    ok = gen_fsm:send_all_state_event(Pid, snooze_async),
685    is_in_erlang_hibernate(Pid),
686    ok = gen_fsm:send_all_state_event(Pid, wakeup_async),
687    is_not_in_erlang_hibernate(Pid),
688
689    hibernating = gen_fsm:sync_send_all_state_event(Pid, hibernate_sync),
690    is_in_erlang_hibernate(Pid),
691    sys:suspend(Pid),
692    is_in_erlang_hibernate(Pid),
693    sys:resume(Pid),
694    is_in_erlang_hibernate(Pid),
695    receive after 1000 -> ok end,
696    is_in_erlang_hibernate(Pid),
697
698    good_morning  = gen_fsm:sync_send_all_state_event(Pid, wakeup_sync),
699    is_not_in_erlang_hibernate(Pid),
700    stop_it(Pid),
701    receive
702	{'EXIT',Pid,normal} -> ok
703    end,
704
705    [] = get_messages(),
706    process_flag(trap_exit, OldFl),
707    ok.
708
709%% Auto hibernation
710auto_hibernate(Config) when is_list(Config) ->
711    OldFl = process_flag(trap_exit, true),
712    HibernateAfterTimeout = 100,
713    State = {auto_hibernate_state},
714    {ok, Pid} = gen_fsm:start_link({local, my_test_name_auto_hibernate}, ?MODULE, {state_data, State}, [{hibernate_after, HibernateAfterTimeout}]),
715    %% After init test
716    is_not_in_erlang_hibernate(Pid),
717    timer:sleep(HibernateAfterTimeout),
718    is_in_erlang_hibernate(Pid),
719    %% Get state test
720    {_, State} = sys:get_state(my_test_name_auto_hibernate),
721    is_in_erlang_hibernate(Pid),
722    %% Sync send event test
723    'alive!' = gen_fsm:sync_send_event(Pid,'alive?'),
724    is_not_in_erlang_hibernate(Pid),
725    timer:sleep(HibernateAfterTimeout),
726    is_in_erlang_hibernate(Pid),
727    %% Send event test
728    ok = gen_fsm:send_all_state_event(Pid,{'alive?', self()}),
729    wfor(yes),
730    is_not_in_erlang_hibernate(Pid),
731    timer:sleep(HibernateAfterTimeout),
732    is_in_erlang_hibernate(Pid),
733    %% Info test
734    Pid ! {self(), handle_info},
735    wfor({Pid, handled_info}),
736    is_not_in_erlang_hibernate(Pid),
737    timer:sleep(HibernateAfterTimeout),
738    is_in_erlang_hibernate(Pid),
739    stop_it(Pid),
740    receive
741        {'EXIT',Pid,normal} -> ok
742    end,
743    process_flag(trap_exit, OldFl),
744    ok.
745
746is_in_erlang_hibernate(Pid) ->
747    receive after 1 -> ok end,
748    is_in_erlang_hibernate_1(200, Pid).
749
750is_in_erlang_hibernate_1(0, Pid) ->
751    io:format("~p\n", [erlang:process_info(Pid, current_function)]),
752    ct:fail(not_in_erlang_hibernate_3);
753is_in_erlang_hibernate_1(N, Pid) ->
754    {current_function,MFA} = erlang:process_info(Pid, current_function),
755    case MFA of
756	{erlang,hibernate,3} ->
757	    ok;
758	_ ->
759	    receive after 10 -> ok end,
760	    is_in_erlang_hibernate_1(N-1, Pid)
761    end.
762
763is_not_in_erlang_hibernate(Pid) ->
764    receive after 1 -> ok end,
765    is_not_in_erlang_hibernate_1(200, Pid).
766
767is_not_in_erlang_hibernate_1(0, Pid) ->
768    io:format("~p\n", [erlang:process_info(Pid, current_function)]),
769    ct:fail(not_in_erlang_hibernate_3);
770is_not_in_erlang_hibernate_1(N, Pid) ->
771    {current_function,MFA} = erlang:process_info(Pid, current_function),
772    case MFA of
773	{erlang,hibernate,3} ->
774	    receive after 10 -> ok end,
775	    is_not_in_erlang_hibernate_1(N-1, Pid);
776	_ ->
777	    ok
778    end.
779
780%% Test gen_fsm:enter_loop/4,5,6.
781enter_loop(Config) when is_list(Config) ->
782    OldFlag = process_flag(trap_exit, true),
783
784    dummy_via:reset(),
785
786    %% Locally registered process + {local, Name}
787    {ok, Pid1a} =
788	proc_lib:start_link(?MODULE, enter_loop, [local, local]),
789    yes = gen_fsm:sync_send_event(Pid1a, 'alive?'),
790    stopped = gen_fsm:sync_send_event(Pid1a, stop),
791    receive
792	{'EXIT', Pid1a, normal} ->
793	    ok
794    after 5000 ->
795	    ct:fail(gen_fsm_did_not_die)
796    end,
797
798    %% Unregistered process + {local, Name}
799    {ok, Pid1b} =
800	proc_lib:start_link(?MODULE, enter_loop, [anon, local]),
801    receive
802	{'EXIT', Pid1b, process_not_registered} ->
803	    ok
804    after 5000 ->
805	    ct:fail(gen_fsm_did_not_die)
806    end,
807
808    %% Globally registered process + {global, Name}
809    {ok, Pid2a} =
810	proc_lib:start_link(?MODULE, enter_loop, [global, global]),
811    yes = gen_fsm:sync_send_event(Pid2a, 'alive?'),
812    stopped = gen_fsm:sync_send_event(Pid2a, stop),
813    receive
814	{'EXIT', Pid2a, normal} ->
815	    ok
816    after 5000 ->
817	    ct:fail(gen_fsm_did_not_die)
818    end,
819
820    %% Unregistered process + {global, Name}
821    {ok, Pid2b} =
822	proc_lib:start_link(?MODULE, enter_loop, [anon, global]),
823    receive
824	{'EXIT', Pid2b, process_not_registered_globally} ->
825	    ok
826    after 5000 ->
827	    ct:fail(gen_fsm_did_not_die)
828    end,
829
830    %% Unregistered process + no name
831    {ok, Pid3} =
832	proc_lib:start_link(?MODULE, enter_loop, [anon, anon]),
833    yes = gen_fsm:sync_send_event(Pid3, 'alive?'),
834    stopped = gen_fsm:sync_send_event(Pid3, stop),
835    receive
836	{'EXIT', Pid3, normal} ->
837	    ok
838    after 5000 ->
839	    ct:fail(gen_fsm_did_not_die)
840    end,
841
842    %% Process not started using proc_lib
843    Pid4 =
844	spawn_link(gen_fsm, enter_loop, [?MODULE, [], state0, []]),
845    receive
846	{'EXIT', Pid4, process_was_not_started_by_proc_lib} ->
847	    ok
848    after 5000 ->
849	    ct:fail(gen_fsm_did_not_die)
850    end,
851
852    %% Make sure I am the parent, ie that ordering a shutdown will
853    %% result in the process terminating with Reason==shutdown
854    {ok, Pid5} =
855	proc_lib:start_link(?MODULE, enter_loop, [anon, anon]),
856    yes = gen_fsm:sync_send_event(Pid5, 'alive?'),
857    exit(Pid5, shutdown),
858    receive
859	{'EXIT', Pid5, shutdown} ->
860	    ok
861    after 5000 ->
862	    ct:fail(gen_fsm_did_not_die)
863    end,
864
865    %% Make sure gen_fsm:enter_loop does not accept {local,Name}
866    %% when it's another process than the calling one which is
867    %% registered under that name
868    register(armitage, self()),
869    {ok, Pid6a} =
870	proc_lib:start_link(?MODULE, enter_loop, [anon, local]),
871    receive
872	{'EXIT', Pid6a, process_not_registered} ->
873	    ok
874    after 1000 ->
875	    ct:fail(gen_fsm_started)
876    end,
877    unregister(armitage),
878
879    %% Make sure gen_fsm:enter_loop does not accept {global,Name}
880    %% when it's another process than the calling one which is
881    %% registered under that name
882    global:register_name(armitage, self()),
883    {ok, Pid6b} =
884	proc_lib:start_link(?MODULE, enter_loop, [anon, global]),
885    receive
886	{'EXIT', Pid6b, process_not_registered_globally} ->
887	    ok
888    after 1000 ->
889	    ct:fail(gen_fsm_started)
890    end,
891    global:unregister_name(armitage),
892
893    dummy_via:register_name(armitage, self()),
894    {ok, Pid6c} =
895	proc_lib:start_link(?MODULE, enter_loop, [anon, via]),
896    receive
897	{'EXIT', Pid6c, {process_not_registered_via, dummy_via}} ->
898	    ok
899    after 1000 ->
900	    ct:fail({gen_fsm_started, process_info(self(), messages)})
901    end,
902    dummy_via:unregister_name(armitage),
903
904    process_flag(trap_exit, OldFlag),
905    ok.
906
907enter_loop(Reg1, Reg2) ->
908    process_flag(trap_exit, true),
909    case Reg1 of
910	local -> register(armitage, self());
911	global -> global:register_name(armitage, self());
912	via -> dummy_via:register_name(armitage, self());
913	anon -> ignore
914    end,
915    proc_lib:init_ack({ok, self()}),
916    case Reg2 of
917	local ->
918	    gen_fsm:enter_loop(?MODULE, [], state0, [], {local,armitage});
919	global ->
920	    gen_fsm:enter_loop(?MODULE, [], state0, [], {global,armitage});
921	via ->
922	    gen_fsm:enter_loop(?MODULE, [], state0, [],
923			       {via, dummy_via, armitage});
924	anon ->
925	    gen_fsm:enter_loop(?MODULE, [], state0, [])
926    end.
927
928%% Start should return an undef error if init isn't implemented
929undef_init(Config) when is_list(Config) ->
930    {error, {undef, [{oc_init_fsm, init, [[]], []}|_]}}
931        =  gen_fsm:start(oc_init_fsm, [], []),
932    ok.
933
934%% Test that the server crashes correctly if the handle_event callback is
935%% not exported in the callback module
936undef_handle_event(Config) when is_list(Config) ->
937    {ok, FSM} = gen_fsm:start(oc_fsm, [], []),
938    MRef = monitor(process, FSM),
939    gen_fsm:send_all_state_event(FSM, state_name),
940    ok = verify_undef_down(MRef, FSM, oc_fsm, handle_event).
941
942%% Test that the server crashes correctly if the handle_sync_event callback is
943%% not exported in the callback module
944undef_handle_sync_event(Config) when is_list(Config) ->
945    {ok, FSM} = gen_fsm:start(oc_fsm, [], []),
946    try
947        gen_fsm:sync_send_all_state_event(FSM, state_name),
948        ct:fail(should_crash)
949    catch exit:{{undef, [{oc_fsm, handle_sync_event, _, _}|_]},_} ->
950        ok
951    end.
952
953%% The fsm should log but not crash if the handle_info callback is
954%% calling an undefined function
955undef_handle_info(Config) when is_list(Config) ->
956    error_logger_forwarder:register(),
957    {ok, FSM} = gen_fsm:start(oc_fsm, [], []),
958    MRef = monitor(process, FSM),
959    FSM ! hej,
960    receive
961        {'DOWN', MRef, process, FSM, _} ->
962            ct:fail(should_not_crash)
963    after 500 ->
964        ok
965    end,
966    receive
967        {warning_msg, _GroupLeader,
968         {FSM, "** Undefined handle_info in " ++ _, [oc_fsm, hej]}} ->
969            ok;
970        Other ->
971            io:format("Unexpected: ~p", [Other]),
972            ct:fail(failed)
973    end.
974
975%% The upgrade should fail if code_change is expected in the callback module
976%% but not exported, but the fsm should continue with the old code
977undef_code_change(Config) when is_list(Config) ->
978    {ok, FSM} = gen_fsm:start(oc_fsm, [], []),
979    {error, {'EXIT', {undef, [{oc_fsm, code_change, [_, _, _, _], _}|_]}}}
980        = fake_upgrade(FSM, oc_fsm),
981    ok.
982
983%% Test the default implementation of terminate with normal reason if the
984%% callback module does not export it
985undef_terminate1(Config) when is_list(Config) ->
986    {ok, FSM} = gen_fsm:start(oc_fsm, [], []),
987    MRef = monitor(process, FSM),
988    ok = gen_fsm:stop(FSM),
989    ok = verify_down_reason(MRef, FSM, normal).
990
991%% Test the default implementation of terminate with error reason if the
992%% callback module does not export it
993undef_terminate2(Config) when is_list(Config) ->
994    {ok, FSM} = gen_fsm:start(oc_fsm, [], []),
995    MRef = monitor(process, FSM),
996    ok = gen_fsm:stop(FSM, {error, test}, infinity),
997    ok = verify_down_reason(MRef, FSM, {error, test}).
998
999%% Test that the server crashes correctly if the handle_info callback is
1000%% calling an undefined function
1001undef_in_handle_info(Config) when is_list(Config) ->
1002    {ok, FSM} = gen_fsm:start(?MODULE, [], []),
1003    MRef = monitor(process, FSM),
1004    FSM ! {call_undef_fun, {?MODULE, handle_info}},
1005    verify_undef_down(MRef, FSM, ?MODULE, handle_info),
1006    ok.
1007
1008%% Test that the server crashes correctly if the terminate callback is
1009%% calling an undefined function
1010undef_in_terminate(Config) when is_list(Config) ->
1011    State = {undef_in_terminate, {?MODULE, terminate}},
1012    {ok, FSM} = gen_fsm:start(?MODULE, {state_data, State}, []),
1013    try
1014        ok = gen_fsm:stop(FSM),
1015        ct:fail(failed)
1016    catch
1017        exit:{undef, [{?MODULE, terminate, _, _}|_]} ->
1018            ok
1019    end.
1020
1021%%
1022%% Functionality check
1023%%
1024
1025wfor(Msg) ->
1026    receive
1027	Msg -> ok
1028    after 5000 ->
1029	    throw(timeout)
1030    end.
1031
1032
1033stop_it(FSM) ->
1034    stopped = gen_fsm:sync_send_all_state_event(FSM, stop),
1035    {'EXIT',_} = 	(catch gen_fsm:sync_send_event(FSM, hej)),
1036    ok.
1037
1038
1039
1040do_func_test(FSM) ->
1041    ok = gen_fsm:send_all_state_event(FSM, {'alive?', self()}),
1042    wfor(yes),
1043    ok = do_connect(FSM),
1044    ok = gen_fsm:send_all_state_event(FSM, {'alive?', self()}),
1045    wfor(yes),
1046    _ = [do_msg(FSM) || _ <- lists:seq(1, 3)],
1047    ok = gen_fsm:send_all_state_event(FSM, {'alive?', self()}),
1048    wfor(yes),
1049    ok = do_disconnect(FSM),
1050    ok = gen_fsm:send_all_state_event(FSM, {'alive?', self()}),
1051    wfor(yes),
1052    ok.
1053
1054
1055do_connect(FSM) ->
1056    check_state(FSM, idle),
1057    gen_fsm:send_event(FSM, {connect, self()}),
1058    wfor(accept),
1059    check_state(FSM, wfor_conf),
1060    gen_fsm:send_event(FSM, confirmation),
1061    check_state(FSM, connected),
1062    ok.
1063
1064do_msg(FSM) ->
1065    check_state(FSM, connected),
1066    R = make_ref(),
1067    ok = gen_fsm:send_event(FSM, {msg, R, self(), hej_pa_dig_quasimodo}),
1068    wfor({ak, R}).
1069
1070
1071do_disconnect(FSM) ->
1072    ok = gen_fsm:send_event(FSM, disconnect),
1073    check_state(FSM, idle).
1074
1075check_state(FSM, State) ->
1076    case gen_fsm:sync_send_all_state_event(FSM, {get, self()}) of
1077	{state, State, _} -> ok
1078    end.
1079
1080do_sync_func_test(FSM) ->
1081    yes = gen_fsm:sync_send_all_state_event(FSM, 'alive?'),
1082    ok = do_sync_connect(FSM),
1083    yes = gen_fsm:sync_send_all_state_event(FSM, 'alive?'),
1084    _ = [do_sync_msg(FSM) || _ <- lists:seq(1, 3)],
1085    yes = gen_fsm:sync_send_all_state_event(FSM, 'alive?'),
1086    ok = do_sync_disconnect(FSM),
1087    yes = gen_fsm:sync_send_all_state_event(FSM, 'alive?'),
1088    check_state(FSM, idle),
1089    ok = gen_fsm:sync_send_event(FSM, {timeout,200}),
1090    yes = gen_fsm:sync_send_all_state_event(FSM, 'alive?'),
1091    check_state(FSM, idle),
1092    ok.
1093
1094
1095do_sync_connect(FSM) ->
1096    check_state(FSM, idle),
1097    accept = gen_fsm:sync_send_event(FSM, {connect, self()}),
1098    check_state(FSM, wfor_conf),
1099    yes = gen_fsm:sync_send_event(FSM, confirmation),
1100    check_state(FSM, connected),
1101    ok.
1102
1103do_sync_msg(FSM) ->
1104    check_state(FSM, connected),
1105    R = make_ref(),
1106    Res = gen_fsm:sync_send_event(FSM, {msg, R, self(), hej_pa_dig_quasimodo}),
1107    if  Res == {ak, R} ->
1108	    ok
1109    end.
1110
1111do_sync_disconnect(FSM) ->
1112    yes = gen_fsm:sync_send_event(FSM, disconnect),
1113    check_state(FSM, idle).
1114
1115verify_down_reason(MRef, Pid, Reason) ->
1116    receive
1117        {'DOWN', MRef, process, Pid, Reason} ->
1118            ok;
1119        {'DOWN', MRef, process, Pid, Other}->
1120            ct:fail({wrong_down_reason, Other})
1121    after 5000 ->
1122        ct:fail(should_shutdown)
1123    end.
1124
1125verify_undef_down(MRef, Pid, Mod, Fun) ->
1126    ok = receive
1127        {'DOWN', MRef, process, Pid,
1128         {undef, [{Mod, Fun, _, _}|_]}} ->
1129            ok
1130    after 5000 ->
1131        ct:fail(should_crash)
1132    end.
1133
1134fake_upgrade(Pid, Mod) ->
1135    sys:suspend(Pid),
1136    sys:replace_state(Pid, fun(State) -> {new, State} end),
1137    Ret = sys:change_code(Pid, Mod, old_vsn, []),
1138    ok = sys:resume(Pid),
1139    Ret.
1140
1141%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1142%%
1143%% The Finite State Machine
1144%%
1145%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1146
1147init(ignore) ->
1148    ignore;
1149init(stop) ->
1150    {stop, stopped};
1151init(stop_shutdown) ->
1152    {stop, shutdown};
1153init(sleep) ->
1154    timer:sleep(1000),
1155    {ok, idle, data};
1156init({timeout, T}) ->
1157    {ok, idle, state, T};
1158init(hiber) ->
1159    {ok, hiber_idle, []};
1160init(hiber_now) ->
1161    {ok, hiber_idle, [], hibernate};
1162init({state_data, StateData}) ->
1163    {ok, idle, StateData};
1164init(_) ->
1165    {ok, idle, state_data}.
1166
1167terminate(_, _State, crash_terminate) ->
1168    exit({crash, terminate});
1169terminate(_, _, {undef_in_terminate, {Mod, Fun}}) ->
1170    Mod:Fun(),
1171    ok;
1172terminate({From, stopped}, State, _Data) ->
1173    From ! {self(), {stopped, State}},
1174    ok;
1175terminate(_Reason, _State, _Data) ->
1176    ok.
1177
1178
1179idle({connect, Pid}, Data) ->
1180    Pid ! accept,
1181    {next_state, wfor_conf, Data};
1182idle(badreturn, _Data) ->
1183    badreturn;
1184idle(_, Data) ->
1185    {next_state, idle, Data}.
1186
1187idle({connect, _Pid}, _From, Data) ->
1188    {reply, accept, wfor_conf, Data};
1189idle({delayed_answer, T}, _From, Data) ->
1190    timer:sleep(T),
1191    {reply, delayed, idle, Data};
1192idle(badreturn, _From, _Data) ->
1193    badreturn;
1194idle({timeout,Time}, From, _Data) ->
1195    gen_fsm:send_event_after(Time, {timeout,Time}),
1196    {next_state, timeout, From};
1197idle('alive?', _From, Data) ->
1198    {reply, 'alive!', idle, Data};
1199idle(_, _From, Data) ->
1200    {reply, 'eh?', idle, Data}.
1201
1202timeout({timeout,Time}, From) ->
1203    Ref = gen_fsm:start_timer(Time, {timeout,Time}),
1204    {next_state, timeout, {From,Ref}};
1205timeout({timeout,Ref,{timeout,Time}}, {From,Ref}) ->
1206    Ref2 = gen_fsm:start_timer(Time, ok),
1207    Cref = gen_fsm:start_timer(Time, cancel),
1208    Time4 = Time*4,
1209    receive after Time4 -> ok end,
1210    _= gen_fsm:cancel_timer(Cref),
1211    {next_state, timeout, {From,Ref2}};
1212timeout({timeout,Ref2,ok},{From,Ref2}) ->
1213    gen_fsm:reply(From, ok),
1214    {next_state, idle, state}.
1215
1216wfor_conf(confirmation, Data) ->
1217    {next_state, connected, Data};
1218wfor_conf(_, Data) ->
1219    {next_state, idle, Data}.
1220
1221wfor_conf(confirmation, _From, Data) ->
1222    {reply, yes, connected, Data};
1223wfor_conf(_, _From, Data) ->
1224    {reply, 'eh?', idle, Data}.
1225
1226connected({msg, Ref, From, _Msg}, Data) ->
1227    From ! {ak, Ref},
1228    {next_state, connected, Data};
1229connected(disconnect, Data) ->
1230    {next_state, idle, Data};
1231connected(_, Data) ->
1232    {next_state, connected, Data}.
1233
1234connected({msg, Ref, _From, _Msg}, _, Data) ->
1235    {reply, {ak, Ref}, connected, Data};
1236connected(disconnect, _From, Data) ->
1237    {reply, yes, idle, Data};
1238connected(_, _, Data) ->
1239    {reply, 'eh?', connected, Data}.
1240
1241state0('alive?', _From, Data) ->
1242    {reply, yes, state0, Data};
1243state0(stop, _From, Data) ->
1244    {stop, normal, stopped, Data}.
1245
1246hiber_idle('alive?', _From, Data) ->
1247    {reply, 'alive!', hiber_idle, Data};
1248hiber_idle(hibernate_sync, _From, Data) ->
1249    {reply, hibernating, hiber_wakeup, Data,hibernate}.
1250hiber_idle(timeout, hibernate_me) ->
1251    %% Arrive here from handle_info(hibernate_later,...)
1252    {next_state, hiber_idle, [], hibernate};
1253hiber_idle(hibernate_async, Data) ->
1254    {next_state,hiber_wakeup, Data, hibernate}.
1255
1256hiber_wakeup(wakeup_sync,_From,Data) ->
1257    {reply,good_morning,hiber_idle,Data};
1258hiber_wakeup(snooze_sync,_From,Data) ->
1259    {reply,five_more,hiber_wakeup,Data,hibernate}.
1260hiber_wakeup(wakeup_async,Data) ->
1261    {next_state,hiber_idle,Data};
1262hiber_wakeup(snooze_async,Data) ->
1263    {next_state,hiber_wakeup,Data,hibernate}.
1264
1265
1266handle_info(hibernate_now, _SName, _State) ->
1267    %% Arrive here from by direct ! from testcase
1268    {next_state, hiber_idle, [], hibernate};
1269handle_info(hibernate_later, _SName, _State) ->
1270    {next_state, hiber_idle, hibernate_me, 1000};
1271handle_info({call_undef_fun, {Mod, Fun}}, State, Data) ->
1272    Mod:Fun(),
1273    {next_state, State, Data};
1274handle_info({From, handle_info}, SName, State) ->
1275    From ! {self(), handled_info},
1276    {next_state, SName, State};
1277handle_info(Info, _State, Data) ->
1278    {stop, {unexpected,Info}, Data}.
1279
1280handle_event(hibernate_async, hiber_idle, Data) ->
1281    {next_state,hiber_wakeup, Data, hibernate};
1282handle_event(wakeup_async,hiber_wakeup,Data) ->
1283    {next_state,hiber_idle,Data};
1284handle_event(snooze_async,hiber_wakeup,Data) ->
1285    {next_state,hiber_wakeup,Data,hibernate};
1286handle_event({get, Pid}, State, Data) ->
1287    Pid ! {state, State, Data},
1288    {next_state, State, Data};
1289handle_event(stop, _State, Data) ->
1290    {stop, normal, Data};
1291handle_event(stop_shutdown, _State, Data) ->
1292    {stop, shutdown, Data};
1293handle_event(stop_shutdown_reason, _State, Data) ->
1294    {stop, shutdown, Data};
1295handle_event({'alive?', Pid}, State, Data) ->
1296    Pid ! yes,
1297    {next_state, State, Data}.
1298
1299handle_sync_event(hibernate_sync, _From, hiber_idle, Data) ->
1300    {reply, hibernating, hiber_wakeup, Data, hibernate};
1301handle_sync_event(wakeup_sync,_From,hiber_wakeup, Data) ->
1302    {reply,good_morning,hiber_idle,Data};
1303handle_sync_event(snooze_sync,_From,hiber_wakeup,Data) ->
1304    {reply,five_more,hiber_wakeup,Data,hibernate};
1305handle_sync_event('alive?', _From, State, Data) ->
1306    {reply, yes, State, Data};
1307handle_sync_event(stop, _From, _State, Data) ->
1308    {stop, normal, stopped, Data};
1309handle_sync_event(stop_shutdown, _From, _State, Data) ->
1310    {stop, shutdown, shutdown_stopped, Data};
1311handle_sync_event(stop_shutdown_reason, _From, _State, Data) ->
1312    {stop, {shutdown,reason}, {shutdown,reason}, Data};
1313handle_sync_event({get, _Pid}, _From, State, Data) ->
1314    {reply, {state, State, Data}, State, Data}.
1315
1316format_status(terminate, [_Pdict, StateData]) ->
1317    {formatted, StateData};
1318format_status(normal, [_Pdict, _StateData]) ->
1319    [format_status_called].
1320
1321code_change(_OldVsn, State,
1322            {idle, {undef_in_code_change, {Mod, Fun}}} = Data, _Extra) ->
1323    Mod:Fun(),
1324    {ok, State, Data};
1325code_change(_OldVsn, State, Data, _Extra) ->
1326    {ok, State, Data}.
1327
1328get_messages() ->
1329    receive
1330	Msg -> [Msg|get_messages()]
1331    after 1 -> []
1332    end.
1333