1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 2016-2020. 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_statem_SUITE).
21
22-include_lib("common_test/include/ct.hrl").
23
24-compile([export_all, nowarn_export_all]).
25-behaviour(gen_statem).
26
27%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
28
29suite() ->
30    [{ct_hooks,[ts_install_cth]},
31     {timetrap,{seconds,10}}].
32
33all() ->
34    [{group, start},
35     {group, start_handle_event},
36     {group, stop},
37     {group, stop_handle_event},
38     {group, abnormal},
39     {group, abnormal_handle_event},
40     shutdown, stop_and_reply, state_enter, event_order,
41     state_timeout, timeout_cancel_and_update,
42     event_types, generic_timers, code_change,
43     {group, sys},
44     hibernate, auto_hibernate, enter_loop, {group, undef_callbacks},
45     undef_in_terminate, {group, format_log},
46     reply_by_alias_with_payload].
47
48groups() ->
49    [{start, [], tcs(start)},
50     {start_handle_event, [], tcs(start)},
51     {stop, [], tcs(stop)},
52     {stop_handle_event, [], tcs(stop)},
53     {abnormal, [], tcs(abnormal)},
54     {abnormal_handle_event, [], tcs(abnormal)},
55     {sys, [], tcs(sys)},
56     {sys_handle_event, [], tcs(sys)},
57     {undef_callbacks, [], tcs(undef_callbacks)},
58     {format_log, [], tcs(format_log)}].
59
60tcs(start) ->
61    [start1, start2, start3, start4, start5, start6, start7,
62     start8, start9, start10, start11, start12, next_events];
63tcs(stop) ->
64    [stop1, stop2, stop3, stop4, stop5, stop6, stop7, stop8, stop9, stop10];
65tcs(abnormal) ->
66    [abnormal1, abnormal1clean, abnormal1dirty,
67     abnormal2, abnormal3, abnormal4];
68tcs(sys) ->
69    [sys1, call_format_status,
70     error_format_status, terminate_crash_format,
71     get_state, replace_state];
72tcs(undef_callbacks) ->
73    [undef_code_change, undef_terminate1, undef_terminate2,
74     pop_too_many];
75tcs(format_log) ->
76    [format_log_1, format_log_2].
77
78init_per_suite(Config) ->
79    Config.
80
81end_per_suite(_Config) ->
82    ok.
83
84init_per_group(GroupName, Config)
85  when GroupName =:= start_handle_event;
86       GroupName =:= stop_handle_event;
87       GroupName =:= abnormal_handle_event;
88       GroupName =:= sys_handle_event ->
89    [{callback_mode,handle_event_function}|Config];
90init_per_group(undef_callbacks, Config) ->
91    compile_oc_statem(Config),
92    Config;
93init_per_group(_GroupName, Config) ->
94    Config.
95
96end_per_group(_GroupName, Config) ->
97    Config.
98
99init_per_testcase(_CaseName, Config) ->
100    flush(),
101%%%    dbg:tracer(),
102%%%    dbg:p(all, c),
103%%%    dbg:tpl(gen_statem, cx),
104%%%    dbg:tpl(gen_statem, loop_receive, cx),
105%%%    dbg:tpl(gen_statem, loop_state_callback, cx),
106%%%    dbg:tpl(gen_statem, loop_callback_mode_result, cx),
107%%%    dbg:tpl(proc_lib, cx),
108%%%    dbg:tpl(gen, cx),
109%%%    dbg:tpl(sys, cx),
110    Config.
111
112end_per_testcase(_CaseName, Config) ->
113%%%    dbg:stop(),
114    Config.
115
116compile_oc_statem(Config) ->
117    DataDir = ?config(data_dir, Config),
118    StatemPath = filename:join(DataDir, "oc_statem.erl"),
119    {ok, oc_statem} = compile:file(StatemPath),
120    ok.
121
122%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
123-define(EXPECT_FAILURE(Code, Reason),
124	try begin Code end of
125	    Reason ->
126		ct:fail({unexpected,Reason})
127	catch
128	    error:Reason -> Reason;
129	    exit:Reason -> Reason
130	end).
131%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
132
133%% anonymous
134start1(Config) ->
135    %%OldFl = process_flag(trap_exit, true),
136
137    {ok,Pid0} =
138	gen_statem:start_link(?MODULE, start_arg(Config, []), [{debug,[trace]}]),
139    ok = do_func_test(Pid0),
140    ok = do_sync_func_test(Pid0),
141    stop_it(Pid0),
142%%    stopped = gen_statem:call(Pid0, stop),
143%%    timeout =
144%%	?EXPECT_FAILURE(gen_statem:call(Pid0, hej), Reason),
145
146    %%process_flag(trap_exit, OldFl),
147    ok = verify_empty_msgq(),
148
149    {ok,{Pid1,Mon1}} = gen_statem:start_monitor(?MODULE, start_arg(Config, []), []),
150    ok = do_func_test(Pid1),
151    ok = do_sync_func_test(Pid1),
152    stop_it(Pid1),
153    receive
154        {'DOWN', Mon1, process, Pid1, _Reason} ->
155            ok
156    end,
157    ok = verify_empty_msgq().
158
159%% anonymous w. shutdown
160start2(Config) ->
161    %% Dont link when shutdown
162    {ok,Pid0} =
163	gen_statem:start(?MODULE, start_arg(Config, []), []),
164    ok = do_func_test(Pid0),
165    ok = do_sync_func_test(Pid0),
166    stopped = gen_statem:call(Pid0, {stop,shutdown}),
167    check_stopped(Pid0),
168    ok = verify_empty_msgq().
169
170%% anonymous with timeout
171start3(Config) ->
172    %%OldFl = process_flag(trap_exit, true),
173
174    {ok,Pid0} =
175	gen_statem:start(?MODULE, start_arg(Config, []), [{timeout,5}]),
176    ok = do_func_test(Pid0),
177    ok = do_sync_func_test(Pid0),
178    stop_it(Pid0),
179
180    {error,timeout} =
181	gen_statem:start(
182	  ?MODULE, start_arg(Config, sleep), [{timeout,5}]),
183
184    %%process_flag(trap_exit, OldFl),
185    ok = verify_empty_msgq().
186
187%% anonymous with ignore
188start4(Config) ->
189    OldFl = process_flag(trap_exit, true),
190
191    ignore = gen_statem:start(?MODULE, start_arg(Config, ignore), []),
192
193    process_flag(trap_exit, OldFl),
194    ok = verify_empty_msgq().
195
196%% anonymous with stop
197start5(Config) ->
198    OldFl = process_flag(trap_exit, true),
199
200    {error,stopped} = gen_statem:start(?MODULE, start_arg(Config, stop), []),
201
202    process_flag(trap_exit, OldFl),
203    ok = verify_empty_msgq().
204
205%% anonymous linked
206start6(Config) ->
207    {ok,Pid} = gen_statem:start_link(?MODULE, start_arg(Config, []), []),
208    ok = do_func_test(Pid),
209    ok = do_sync_func_test(Pid),
210    stop_it(Pid),
211
212    ok = verify_empty_msgq().
213
214%% global register linked & monitored
215start7(Config) ->
216    STM = {global,my_stm},
217
218    {ok,Pid} =
219	gen_statem:start_link(STM, ?MODULE, start_arg(Config, []), []),
220    {error,{already_started,Pid}} =
221	gen_statem:start_link(STM, ?MODULE, start_arg(Config, []), []),
222    {error,{already_started,Pid}} =
223	gen_statem:start(STM, ?MODULE, start_arg(Config, []), []),
224    {error,{already_started,Pid}} =
225	gen_statem:start_monitor(STM, ?MODULE, start_arg(Config, []), []),
226
227    ok = do_func_test(Pid),
228    ok = do_sync_func_test(Pid),
229    ok = do_func_test(STM),
230    ok = do_sync_func_test(STM),
231    stop_it(STM),
232
233    ok = verify_empty_msgq(),
234
235    {ok,{Pid1,Mon1}} =
236	gen_statem:start_monitor(STM, ?MODULE, start_arg(Config, []), []),
237    {error,{already_started,Pid1}} =
238	gen_statem:start_link(STM, ?MODULE, start_arg(Config, []), []),
239    {error,{already_started,Pid1}} =
240	gen_statem:start(STM, ?MODULE, start_arg(Config, []), []),
241    {error,{already_started,Pid1}} =
242	gen_statem:start_monitor(STM, ?MODULE, start_arg(Config, []), []),
243
244    ok = do_func_test(Pid1),
245    ok = do_sync_func_test(Pid1),
246    ok = do_func_test(STM),
247    ok = do_sync_func_test(STM),
248    stop_it(STM),
249
250    receive
251        {'DOWN', Mon1, process, Pid1, _Reason} ->
252            ok
253    end,
254
255    ok = verify_empty_msgq().
256
257
258%% local register
259start8(Config) ->
260    %%OldFl = process_flag(trap_exit, true),
261    Name = my_stm,
262    STM = {local,Name},
263
264    {ok,Pid} =
265	gen_statem:start(STM, ?MODULE, start_arg(Config, []), []),
266    {error,{already_started,Pid}} =
267	gen_statem:start(STM, ?MODULE, start_arg(Config, []), []),
268
269    ok = do_func_test(Pid),
270    ok = do_sync_func_test(Pid),
271    ok = do_func_test(Name),
272    ok = do_sync_func_test(Name),
273    stop_it(Pid),
274
275    %%process_flag(trap_exit, OldFl),
276    ok = verify_empty_msgq().
277
278%% local register linked & monitored
279start9(Config) ->
280    %%OldFl = process_flag(trap_exit, true),
281    Name = my_stm,
282    STM = {local,Name},
283
284    {ok,Pid} =
285	gen_statem:start_link(STM, ?MODULE, start_arg(Config, []), []),
286    {error,{already_started,Pid}} =
287	gen_statem:start(STM, ?MODULE, start_arg(Config, []), []),
288
289    ok = do_func_test(Pid),
290    ok = do_sync_func_test(Pid),
291    ok = do_func_test(Name),
292    ok = do_sync_func_test(Name),
293    stop_it(Pid),
294
295    %%process_flag(trap_exit, OldFl),
296    ok = verify_empty_msgq(),
297
298    {ok,{Pid1,Mon1}} =
299	gen_statem:start_monitor(STM, ?MODULE, start_arg(Config, []), []),
300    {error,{already_started,Pid1}} =
301	gen_statem:start_monitor(STM, ?MODULE, start_arg(Config, []), []),
302
303    ok = do_func_test(Pid1),
304    ok = do_sync_func_test(Pid1),
305    ok = do_func_test(Name),
306    ok = do_sync_func_test(Name),
307    stop_it(Pid1),
308
309    receive
310        {'DOWN', Mon1, process, Pid1, _Reason} ->
311            ok
312    end,
313
314    ok = verify_empty_msgq().
315
316%% global register
317start10(Config) ->
318    STM = {global,my_stm},
319
320    {ok,Pid} =
321	gen_statem:start(STM, ?MODULE, start_arg(Config, []), []),
322    {error,{already_started,Pid}} =
323	gen_statem:start(STM, ?MODULE, start_arg(Config, []), []),
324    {error,{already_started,Pid}} =
325	gen_statem:start_link(STM, ?MODULE, start_arg(Config, []), []),
326
327    ok = do_func_test(Pid),
328    ok = do_sync_func_test(Pid),
329    ok = do_func_test(STM),
330    ok = do_sync_func_test(STM),
331    stop_it(STM),
332
333    ok = verify_empty_msgq().
334
335%% Stop registered processes
336start11(Config) ->
337    Name = my_stm,
338    LocalSTM = {local,Name},
339    GlobalSTM = {global,Name},
340
341    {ok,Pid} =
342	gen_statem:start_link(LocalSTM, ?MODULE, start_arg(Config, []), []),
343    stop_it(Pid),
344
345    {ok,_Pid1} =
346	gen_statem:start_link(LocalSTM, ?MODULE, start_arg(Config, []), []),
347    stop_it(Name),
348
349    {ok,Pid2} =
350	gen_statem:start(GlobalSTM, ?MODULE, start_arg(Config, []), []),
351    stop_it(Pid2),
352    receive after 1 -> true end,
353    Result =
354	gen_statem:start(GlobalSTM, ?MODULE, start_arg(Config, []), []),
355    ct:log("Result = ~p~n",[Result]),
356    {ok,_Pid3} = Result,
357    stop_it(GlobalSTM),
358
359    ok = verify_empty_msgq().
360
361%% Via register linked
362start12(Config) ->
363    dummy_via:reset(),
364    VIA = {via,dummy_via,my_stm},
365
366    {ok,Pid} =
367	gen_statem:start_link(VIA, ?MODULE, start_arg(Config, []), []),
368    {error,{already_started,Pid}} =
369	gen_statem:start_link(VIA, ?MODULE, start_arg(Config, []), []),
370    {error,{already_started,Pid}} =
371	gen_statem:start(VIA, ?MODULE, start_arg(Config, []), []),
372
373    ok = do_func_test(Pid),
374    ok = do_sync_func_test(Pid),
375    ok = do_func_test(VIA),
376    ok = do_sync_func_test(VIA),
377    stop_it(VIA),
378
379    ok = verify_empty_msgq().
380
381
382%% Anonymous, reason 'normal'
383stop1(Config) ->
384    {ok,Pid} = gen_statem:start(?MODULE, start_arg(Config, []), []),
385    ok = gen_statem:stop(Pid),
386    false = erlang:is_process_alive(Pid),
387    noproc =
388	?EXPECT_FAILURE(gen_statem:stop(Pid), Reason).
389
390%% Anonymous, other reason
391stop2(Config) ->
392    {ok,Pid} = gen_statem:start(?MODULE, start_arg(Config, []), []),
393    ok = gen_statem:stop(Pid, other_reason, infinity),
394    false = erlang:is_process_alive(Pid),
395    ok.
396
397%% Anonymous, invalid timeout
398stop3(Config) ->
399    {ok,Pid} = gen_statem:start(?MODULE, start_arg(Config, []), []),
400    _ =
401	?EXPECT_FAILURE(
402	   gen_statem:stop(Pid, other_reason, invalid_timeout),
403	   Reason),
404    true = erlang:is_process_alive(Pid),
405    ok = gen_statem:stop(Pid),
406    false = erlang:is_process_alive(Pid),
407    ok.
408
409%% Registered name
410stop4(Config) ->
411    {ok,Pid} =
412	gen_statem:start(
413	  {local,to_stop},?MODULE, start_arg(Config, []), []),
414    ok = gen_statem:stop(to_stop),
415    false = erlang:is_process_alive(Pid),
416    noproc =
417	?EXPECT_FAILURE(gen_statem:stop(to_stop), Reason),
418    ok.
419
420%% Registered name and local node
421stop5(Config) ->
422    Name = to_stop,
423    {ok,Pid} =
424	gen_statem:start(
425	  {local,Name},?MODULE, start_arg(Config, []), []),
426    ok = gen_statem:stop({Name,node()}),
427    false = erlang:is_process_alive(Pid),
428    noproc =
429	?EXPECT_FAILURE(gen_statem:stop({Name,node()}), Reason),
430    ok.
431
432%% Globally registered name
433stop6(Config) ->
434    STM = {global,to_stop},
435    {ok,Pid} = gen_statem:start(STM, ?MODULE, start_arg(Config, []), []),
436    ok = gen_statem:stop(STM),
437    false = erlang:is_process_alive(Pid),
438    noproc =
439	?EXPECT_FAILURE(gen_statem:stop(STM), Reason),
440    ok.
441
442%% 'via' registered name
443stop7(Config) ->
444    VIA = {via,dummy_via,to_stop},
445    dummy_via:reset(),
446    {ok,Pid} = gen_statem:start(VIA, ?MODULE, start_arg(Config, []), []),
447    ok = gen_statem:stop(VIA),
448    false = erlang:is_process_alive(Pid),
449    noproc =
450	?EXPECT_FAILURE(gen_statem:stop(VIA), Reason),
451    ok.
452
453%% Anonymous on remote node
454stop8(Config) ->
455    Node = gen_statem_stop8,
456    {ok,NodeName} = ct_slave:start(Node),
457    Statem =
458        try
459            Dir = filename:dirname(code:which(?MODULE)),
460            rpc:block_call(NodeName, code, add_path, [Dir]),
461            {ok,Pid} =
462                rpc:block_call(
463                  NodeName, gen_statem,start,
464                  [?MODULE,start_arg(Config, []),[]]),
465            ok = gen_statem:stop(Pid),
466            false = rpc:block_call(NodeName, erlang, is_process_alive, [Pid]),
467            noproc =
468                ?EXPECT_FAILURE(gen_statem:stop(Pid), Reason1),
469            Pid
470        after
471            {ok,NodeName} = ct_slave:stop(Node)
472        end,
473    {{nodedown,NodeName},{sys,terminate,_}} =
474	?EXPECT_FAILURE(gen_statem:stop(Statem), Reason2),
475    ok.
476
477%% Registered name on remote node
478stop9(Config) ->
479    Name = to_stop,
480    LocalSTM = {local,Name},
481    Node = gen_statem__stop9,
482    {ok,NodeName} = ct_slave:start(Node),
483    Statem =
484        try
485            STM = {Name,NodeName},
486            Dir = filename:dirname(code:which(?MODULE)),
487            rpc:block_call(NodeName, code, add_path, [Dir]),
488            {ok,Pid} =
489                rpc:block_call(
490                  NodeName, gen_statem, start,
491                  [LocalSTM,?MODULE,start_arg(Config, []),[]]),
492            ok = gen_statem:stop(STM),
493            undefined = rpc:block_call(NodeName,erlang,whereis,[Name]),
494            false = rpc:block_call(NodeName,erlang,is_process_alive,[Pid]),
495            noproc =
496                ?EXPECT_FAILURE(gen_statem:stop(STM), Reason1),
497            STM
498        after
499            {ok,NodeName} = ct_slave:stop(Node)
500        end,
501    {{nodedown,NodeName},{sys,terminate,_}} =
502	?EXPECT_FAILURE(gen_statem:stop(Statem), Reason2),
503    ok.
504
505%% Globally registered name on remote node
506stop10(Config) ->
507    Node = gen_statem_stop10,
508    STM = {global,to_stop},
509    {ok,NodeName} = ct_slave:start(Node),
510    try
511        Dir = filename:dirname(code:which(?MODULE)),
512        rpc:block_call(NodeName,code,add_path,[Dir]),
513        {ok,Pid} =
514            rpc:block_call(
515              NodeName, gen_statem, start,
516              [STM,?MODULE,start_arg(Config, []),[]]),
517        global:sync(),
518        ok = gen_statem:stop(STM),
519        false = rpc:block_call(NodeName, erlang, is_process_alive, [Pid]),
520        noproc =
521            ?EXPECT_FAILURE(gen_statem:stop(STM), Reason1)
522    after
523        {ok,NodeName} = ct_slave:stop(Node)
524    end,
525    noproc =
526	?EXPECT_FAILURE(gen_statem:stop(STM), Reason2),
527    ok.
528
529%% Check that time outs in calls work
530abnormal1(Config) ->
531    Name = abnormal1,
532    LocalSTM = {local,Name},
533
534    {ok, _Pid} =
535	gen_statem:start(LocalSTM, ?MODULE, start_arg(Config, []), []),
536
537    %% timeout call.
538    delayed = gen_statem:call(Name, {delayed_answer,100}, 2000),
539    {timeout,_} =
540	?EXPECT_FAILURE(
541	   gen_statem:call(Name, {delayed_answer,2000}, 100),
542	   Reason),
543    ok = gen_statem:stop(Name),
544    ct:sleep(1100),
545    ok = verify_empty_msgq().
546
547%% Check that time outs in calls work
548abnormal1clean(Config) ->
549    Name = abnormal1clean,
550    LocalSTM = {local,Name},
551
552    {ok, _Pid} =
553	gen_statem:start(LocalSTM, ?MODULE, start_arg(Config, []), []),
554
555    %% timeout call.
556    delayed =
557	gen_statem:call(Name, {delayed_answer,1}, {clean_timeout,100}),
558    {timeout,_} =
559	?EXPECT_FAILURE(
560	   gen_statem:call(
561	     Name, {delayed_answer,1000}, {clean_timeout,10}),
562	   Reason),
563    ok = gen_statem:stop(Name),
564    ct:sleep(1100),
565    ok = verify_empty_msgq().
566
567%% Check that time outs in calls work
568abnormal1dirty(Config) ->
569    Name = abnormal1dirty,
570    LocalSTM = {local,Name},
571
572    {ok, _Pid} =
573	gen_statem:start(LocalSTM, ?MODULE, start_arg(Config, []), []),
574
575    %% timeout call.
576    delayed =
577	gen_statem:call(Name, {delayed_answer,1}, {dirty_timeout,100}),
578    {timeout,_} =
579	?EXPECT_FAILURE(
580	   gen_statem:call(
581	     Name, {delayed_answer,1000}, {dirty_timeout,10}),
582	   Reason),
583    ok = gen_statem:stop(Name),
584    ct:sleep(1100),
585    case flush() of
586	[] -> ok
587    end.
588
589%% Check that bad return values makes the stm crash. Note that we must
590%% trap exit since we must link to get the real bad_return_ error
591abnormal2(Config) ->
592    OldFl = process_flag(trap_exit, true),
593    {ok,Pid} =
594        gen_statem:start_link(
595          ?MODULE, start_arg(Config, []), [{debug,[log]}]),
596
597    %% bad return value in the gen_statem loop
598    Cause = bad_return_from_state_function,
599    {{{Cause,badreturn},_},_} =
600	?EXPECT_FAILURE(gen_statem:call(Pid, badreturn), Reason),
601    receive
602	{'EXIT',Pid,{{Cause,badreturn},_}} -> ok
603    after 5000 ->
604	    ct:fail(gen_statem_did_not_die)
605    end,
606
607    process_flag(trap_exit, OldFl),
608    ok = verify_empty_msgq().
609
610%% Check that bad return actions makes the stm crash. Note that we must
611%% trap exit since we must link to get the real bad_return_ error
612abnormal3(Config) ->
613    OldFl = process_flag(trap_exit, true),
614    {ok,Pid} =
615        gen_statem:start_link(
616          ?MODULE, start_arg(Config, []), [{debug,[log]}]),
617
618    %% bad return value in the gen_statem loop
619    Cause = bad_action_from_state_function,
620    {{{Cause,badaction},_},_} =
621	?EXPECT_FAILURE(gen_statem:call(Pid, badaction), Reason),
622    receive
623	{'EXIT',Pid,{{Cause,badaction},_}} -> ok
624    after 5000 ->
625	    ct:fail(gen_statem_did_not_die)
626    end,
627
628    process_flag(trap_exit, OldFl),
629    ok = verify_empty_msgq().
630
631%% Check that bad timeout actions makes the stm crash. Note that we must
632%% trap exit since we must link to get the real bad_return_ error
633abnormal4(Config) ->
634    OldFl = process_flag(trap_exit, true),
635    {ok,Pid} =
636        gen_statem:start_link(
637          ?MODULE, start_arg(Config, []), [{debug,[log]}]),
638
639    %% bad return value in the gen_statem loop
640    BadTimeout = {badtimeout,4711,ouch},
641    Cause = bad_action_from_state_function,
642    {{{Cause,BadTimeout},_},_} =
643	?EXPECT_FAILURE(gen_statem:call(Pid, {badtimeout,BadTimeout}), Reason),
644    receive
645	{'EXIT',Pid,{{Cause,BadTimeout},_}} -> ok
646    after 5000 ->
647	    ct:fail(gen_statem_did_not_die)
648    end,
649
650    process_flag(trap_exit, OldFl),
651    ok = verify_empty_msgq().
652
653shutdown(Config) ->
654    process_flag(trap_exit, true),
655
656    {ok,Pid0} = gen_statem:start_link(?MODULE, start_arg(Config, []), []),
657    ok = do_func_test(Pid0),
658    ok = do_sync_func_test(Pid0),
659    stopped = gen_statem:call(Pid0, {stop,{shutdown,reason}}),
660    receive {'EXIT',Pid0,{shutdown,reason}} -> ok end,
661    process_flag(trap_exit, false),
662
663    {noproc,_} =
664	?EXPECT_FAILURE(gen_statem:call(Pid0, hej), Reason),
665
666    receive
667	Any ->
668	    ct:log("Unexpected: ~p", [Any]),
669	    ct:fail({unexpected,Any})
670    after 500 ->
671	    ok
672    end.
673
674
675
676stop_and_reply(_Config) ->
677    process_flag(trap_exit, true),
678
679    Machine =
680	%% Abusing the internal format of From...
681	#{init =>
682	      fun () ->
683		      {ok,start,undefined}
684	      end,
685	  start =>
686	      fun (cast, {echo,From1,Reply1}, undefined) ->
687		      {next_state,wait,{reply,From1,Reply1}}
688	      end,
689	  wait =>
690	      fun (cast, {stop_and_reply,Reason,From2,Reply2},R1) ->
691		      {stop_and_reply,Reason,
692		       [R1,{reply,From2,Reply2}]}
693	      end},
694    {ok,STM} =
695	gen_statem:start_link(?MODULE, {map_statem,Machine,[]}, []),
696
697    Self = self(),
698    Tag1 = make_ref(),
699    gen_statem:cast(STM, {echo,{Self,Tag1},reply1}),
700    Tag2 = make_ref(),
701    gen_statem:cast(STM, {stop_and_reply,reason,{Self,Tag2},reply2}),
702    case flush() of
703	[{Tag1,reply1},{Tag2,reply2},{'EXIT',STM,reason}] ->
704	    ok;
705	Other1 ->
706	    ct:fail({unexpected,Other1})
707    end,
708
709    {noproc,_} =
710	?EXPECT_FAILURE(gen_statem:call(STM, hej), Reason),
711    case flush() of
712	[] ->
713	    ok;
714	Other2 ->
715	    ct:fail({unexpected,Other2})
716    end.
717
718
719
720state_enter(_Config) ->
721    process_flag(trap_exit, true),
722    Self = self(),
723
724    Machine =
725	%% Abusing the internal format of From...
726	#{init =>
727	      fun () ->
728		      {ok,start,1}
729	      end,
730	  start =>
731	      fun (enter, Prev, N) ->
732		      Self ! {N,enter,start,Prev},
733		      {keep_state,N + 1};
734		  (internal, Prev, N) ->
735		      Self ! {N,internal,start,Prev},
736		      {keep_state,N + 1};
737                  (timeout, M, N) ->
738                      {keep_state, N + 1,
739                       {reply, {Self,N}, {timeout,M}}};
740		  ({call,From}, repeat, N) ->
741		      {repeat_state,N + 1,
742		       [{reply,From,{N,repeat,start}}]};
743		  ({call,From}, echo, N) ->
744		      {next_state,wait,N + 1,
745		       [{reply,From,{N,echo,start}},{timeout,0,N}]};
746		  ({call,From}, {stop,Reason}, N) ->
747		      {stop_and_reply,Reason,
748		       [{reply,From,{N,stop}}],N + 1}
749	      end,
750	  wait =>
751	      fun (enter, Prev, N) when N < 5 ->
752		      {repeat_state,N + 1,
753		       [{reply,{Self,N},{enter,Prev}},
754                        {timeout,0,N},
755                        {state_timeout,0,N}]};
756		  (enter, Prev, N) ->
757		      Self ! {N,enter,wait,Prev},
758		      {keep_state,N + 1,
759                       [{timeout,0,N},
760                        {state_timeout,0,N}]};
761                  (timeout, M, N) ->
762                      {keep_state, N + 1,
763                       {reply, {Self,N}, {timeout,M}}};
764                  (state_timeout, M, N) ->
765                      {keep_state, N + 1,
766                       {reply, {Self,N}, {state_timeout,M}}};
767		  ({call,From}, repeat, N) ->
768		      {repeat_state_and_data,
769		       [{reply,From,{N,repeat,wait}},
770                        {timeout,0,N}]};
771		  ({call,From}, echo, N) ->
772		      {next_state,start,N + 1,
773		       [{next_event,internal,wait},
774			{reply,From,{N,echo,wait}}]}
775	      end},
776    {ok,STM} =
777	gen_statem:start_link(
778	  ?MODULE, {map_statem,Machine,[state_enter]},
779          [{debug,[trace,{log,17}]}]),
780    ok = sys:log(STM, false),
781    ok = sys:log(STM, true),
782
783    [{1,enter,start,start}] = flush(),
784    {2,echo,start} = gen_statem:call(STM, echo),
785    [{3,{enter,start}},
786     {4,{enter,start}},
787     {5,enter,wait,start},
788     {6,{timeout,5}},
789     {7,{state_timeout,5}}] = flush(),
790    {wait,[8|_]} = sys:get_state(STM),
791    {8,repeat,wait} = gen_statem:call(STM, repeat),
792    [{8,enter,wait,wait},
793     {9,{timeout,8}},
794     {10,{state_timeout,8}}] = flush(),
795    {11,echo,wait} = gen_statem:call(STM, echo),
796    [{12,enter,start,wait},
797     {13,internal,start,wait}] = flush(),
798    {14,repeat,start} = gen_statem:call(STM, repeat),
799    [{15,enter,start,start}] = flush(),
800
801    {ok,Log} = sys:log(STM, get),
802    io:format("sys:log ~p~n", [Log]),
803    ok = sys:log(STM, print),
804
805    {16,stop} = gen_statem:call(STM, {stop,bye}),
806    [{'EXIT',STM,bye}] = flush(),
807
808    {noproc,_} =
809	?EXPECT_FAILURE(gen_statem:call(STM, hej), Reason),
810    case flush() of
811	[] ->
812	    ok;
813	Other2 ->
814	    ct:fail({unexpected,Other2})
815    end.
816
817
818
819event_order(_Config) ->
820    process_flag(trap_exit, true),
821
822    Machine =
823	%% Abusing the internal format of From...
824	#{init =>
825	      fun () ->
826		      {ok,start,undefined}
827	      end,
828	  start =>
829	      fun (cast, _, _) ->
830		      {keep_state_and_data,postpone}; %% Handled in 'buffer'
831		  ({call,From}, {buffer,Pid,[Tag3,Tag4,Tag5]},
832		   undefined) ->
833		      {next_state,buffer,[],
834		       [{next_event,internal,{reply,{Pid,Tag3},ok3}},
835			{next_event,internal,{reply,{Pid,Tag4},ok4}},
836			{timeout,0,{reply,{Pid,Tag5},ok5}},
837			%% The timeout should not happen since there
838			%% are events that cancel it i.e next_event
839			%% and postponed
840			{reply,From,ok}]}
841	      end,
842	  buffer =>
843	      fun (internal, Reply, Replies) ->
844		      {keep_state,[Reply|Replies]};
845		  (timeout, Reply, Replies) ->
846		      {keep_state,[Reply|Replies]};
847		  (cast, Reply, Replies) ->
848		      {keep_state,[Reply|Replies]};
849		  ({call,From}, {stop,Reason}, Replies) ->
850		      {next_state,stop,undefined,
851		       lists:reverse(
852			 Replies,
853			 [{reply,From,ok},
854			  {next_event,internal,{stop,Reason}}])}
855	      end,
856	  stop =>
857	      fun (internal, Result, undefined) ->
858		      Result
859	      end},
860
861    {ok,STM} = gen_statem:start_link(?MODULE, {map_statem,Machine,[]}, []),
862    Self = self(),
863    Tag1 = make_ref(),
864    gen_statem:cast(STM, {reply,{Self,Tag1},ok1}),
865    Tag2 = make_ref(),
866    gen_statem:cast(STM, {reply,{Self,Tag2},ok2}),
867    Tag3 = make_ref(),
868    Tag4 = make_ref(),
869    Tag5 = make_ref(),
870    ok = gen_statem:call(STM, {buffer,Self,[Tag3,Tag4,Tag5]}),
871    ok = gen_statem:call(STM, {stop,reason}),
872    case flush() of
873	[{Tag3,ok3},{Tag4,ok4},{Tag1,ok1},{Tag2,ok2},
874	 {'EXIT',STM,reason}] ->
875	    ok;
876	Other1 ->
877	    ct:fail({unexpected,Other1})
878    end,
879
880    {noproc,_} =
881	?EXPECT_FAILURE(gen_statem:call(STM, hej), Reason),
882    case flush() of
883	[] ->
884	    ok;
885	Other2 ->
886	    ct:fail({unexpected,Other2})
887    end.
888
889
890
891state_timeout(_Config) ->
892    process_flag(trap_exit, true),
893
894    Machine =
895	#{init =>
896	      fun () ->
897		      {ok,start,0}
898	      end,
899	  start =>
900	      fun
901		  ({call,From}, {go,Time}, 0)  ->
902		      self() ! message_to_self,
903		      {next_state, state1, {Time,From},
904		       %% Verify that internal events goes before external
905		       [{timeout,Time,1}, % Exercise different cancel code path
906                        {state_timeout,Time,1},
907			{next_event,internal,1}]}
908	      end,
909	  state1 =>
910	      fun
911		  (internal, 1, Data) ->
912		      %% Verify that a state change cancels timeout 1
913		      {next_state, state2, Data,
914		       [{timeout,0,2},
915			{state_timeout,0,2},
916			{next_event,internal,2}]}
917	      end,
918	  state2 =>
919	      fun
920		  (internal, 2, Data) ->
921		      %% Verify that {state_timeout,0,_}
922		      %% comes after next_event and that
923		      %% {timeout,0,_} is cancelled by
924		      %% pending {state_timeout,0,_}
925		      {keep_state, {ok,2,Data},
926		       [{timeout,0,3}]};
927		  (state_timeout, 2, {ok,2,Data}) ->
928		      %% Verify that timeout 0's are processed
929		      %% in order
930		      {keep_state, {ok,3,Data},
931		       [{timeout,0,4},{state_timeout,0,5}]};
932		  (timeout, 4, {ok,3,Data}) ->
933		      %% Verify that timeout 0 is cancelled by
934		      %% a state_timeout 0 event and that
935		      %% state_timeout 0 can be restarted
936		      {keep_state, {ok,4,Data},
937		       [{state_timeout,0,6},{timeout,0,7}]};
938		  (state_timeout, 6, {ok,4,{Time,From}}) ->
939		      {next_state, state3, 6,
940		       [{reply,From,ok},
941			{state_timeout,Time,8}]}
942	      end,
943	  state3 =>
944	      fun
945		  (info, message_to_self, 6) ->
946		      {keep_state, 7};
947		  ({call,From}, check, 7) ->
948		      {keep_state, From};
949		  (state_timeout, 8, From) ->
950		      {stop_and_reply, normal,
951		       {reply,From,ok}}
952	      end},
953
954    {ok,STM} =
955        gen_statem:start_link(
956          ?MODULE, {map_statem,Machine,[]}, [{debug,[trace]}]),
957    TRef = erlang:start_timer(1000, self(), kull),
958    ok = gen_statem:call(STM, {go,500}),
959    ok = gen_statem:call(STM, check),
960    receive
961	{timeout,TRef,kull} ->
962	    ct:fail(late_timeout)
963    after 0 ->
964	    receive
965		{timeout,TRef,kull} ->
966		    ok
967	    after 1000 ->
968		    ct:fail(no_check_timeout)
969	    end
970    end,
971    receive
972	{'EXIT',STM,normal} ->
973	    ok
974    after 500 ->
975	    ct:fail(did_not_stop)
976    end,
977
978    verify_empty_msgq().
979
980
981
982timeout_cancel_and_update(_Config) ->
983    process_flag(trap_exit, true),
984    %%
985    Machine =
986	#{init =>
987	      fun () ->
988		      {ok,start,0}
989	      end,
990	  start =>
991	      fun
992		  ({call,From}, test, 0)  ->
993		      self() ! message_to_self,
994		      {next_state, state1, From,
995		       %% Verify that internal events goes before external
996		       [{state_timeout,17,1},
997			{next_event,internal,1}]}
998	      end,
999	  state1 =>
1000	      fun
1001		  (internal, 1, _) ->
1002                      {keep_state_and_data,
1003                       [{state_timeout,cancel},
1004                        {{timeout,a},17,1}]};
1005                  (info, message_to_self, _) ->
1006                      {keep_state_and_data,
1007                       [{{timeout,a},update,a}]};
1008                  ({timeout,a}, a, Data) ->
1009                      {next_state,state2,Data,
1010                       [{state_timeout,17,2},
1011                        {next_event,internal,2}]}
1012              end,
1013	  state2 =>
1014	      fun
1015		  (internal, 2, _) ->
1016                      receive after 50 -> ok end,
1017                      %% Now state_timeout 17 should have triggered
1018                      {keep_state_and_data,
1019                       [{state_timeout,update,b},
1020                        {timeout,17,2}]};
1021                  (state_timeout, b, From) ->
1022                      {next_state,state3,3,
1023                       [{reply,From,ok},
1024                        17000]}
1025	      end,
1026          state3 =>
1027              fun
1028                  ({call,From}, stop, 3) ->
1029                      {stop_and_reply, normal,
1030                       [{reply,From,ok}]}
1031              end
1032         },
1033    %%
1034    {ok,STM} =
1035        gen_statem:start_link(
1036          ?MODULE, {map_statem,Machine,[]}, [{debug,[trace]}]),
1037    ok = gen_statem:call(STM, test),
1038    {status, STM, {module,gen_statem}, Info} = sys:get_status(STM),
1039    ct:log("Status info: ~p~n", [Info]),
1040    {_,Timeouts} = dig_data_tuple(Info),
1041    {_, {1,[{timeout,17000}]}} = lists:keyfind("Time-outs", 1, Timeouts),
1042    %%
1043    ok = gen_statem:call(STM, stop),
1044    receive
1045	{'EXIT',STM,normal} ->
1046	    ok
1047    after 500 ->
1048	    ct:fail(did_not_stop)
1049    end,
1050    %%
1051    verify_empty_msgq().
1052
1053dig_data_tuple([{data,_} = DataTuple|_]) -> DataTuple;
1054dig_data_tuple([H|T]) when is_list(H) ->
1055    case dig_data_tuple(H) of
1056        false -> dig_data_tuple(T);
1057        DataTuple -> DataTuple
1058    end;
1059dig_data_tuple([_|T]) -> dig_data_tuple(T);
1060dig_data_tuple([]) -> false.
1061
1062
1063
1064%% Test that all event types can be sent with {next_event,EventType,_}
1065event_types(_Config) ->
1066    process_flag(trap_exit, true),
1067
1068    Machine =
1069	%% Abusing the internal format of From...
1070	#{init =>
1071	      fun () ->
1072		      {ok, start1, undefined,
1073		       [{next_event,internal,0}]}
1074	      end,
1075	  start1 =>
1076	      fun (internal, 0, undefined) ->
1077		      {next_state, start2, undefined}
1078	      end,
1079	  start2 =>
1080	      fun ({call,_} = Call, Req, undefined) ->
1081		      {next_state, state1, undefined,
1082		       [{next_event,internal,1},
1083			{next_event,state_timeout,2},
1084			{next_event,timeout,3},
1085			{next_event,info,4},
1086			{next_event,cast,5},
1087			{next_event,{timeout,6}, 6},
1088			{next_event,Call,Req}]}
1089	      end,
1090	  state1 =>
1091	      fun (internal, 1, undefined) ->
1092		      {next_state, state2, undefined}
1093	      end,
1094	  state2 =>
1095	      fun (state_timeout, 2, undefined) ->
1096		      {next_state, state3, undefined}
1097	      end,
1098	  state3 =>
1099	      fun (timeout, 3, undefined) ->
1100		      {next_state, state4, undefined}
1101	      end,
1102	  state4 =>
1103	      fun (info, 4, undefined) ->
1104		      {next_state, state5, undefined}
1105	      end,
1106	  state5 =>
1107	      fun (cast, 5, undefined) ->
1108		      {next_state, state6, undefined}
1109	      end,
1110	  state6 =>
1111	      fun ({timeout,6}, 6, undefined) ->
1112		      {next_state, state7, undefined}
1113	      end,
1114	  state7 =>
1115	      fun ({call,From}, stop, undefined) ->
1116		      {stop_and_reply, shutdown,
1117		       [{reply,From,stopped}]}
1118	      end},
1119    {ok,STM} =
1120	gen_statem:start_link(
1121	  ?MODULE, {map_statem,Machine,[]}, [{debug,[trace]}]),
1122
1123    stopped = gen_statem:call(STM, stop),
1124    receive
1125	{'EXIT',STM,shutdown} ->
1126	    ok
1127    after 500 ->
1128	    ct:fail(did_not_stop)
1129    end,
1130
1131    {noproc,_} =
1132	?EXPECT_FAILURE(gen_statem:call(STM, hej), Reason),
1133    case flush() of
1134	[] ->
1135	    ok;
1136	Other2 ->
1137	    ct:fail({unexpected,Other2})
1138    end.
1139
1140
1141
1142generic_timers(_Config) ->
1143    process_flag(trap_exit, true),
1144
1145    Machine =
1146	%% Abusing the internal format of From...
1147	#{init =>
1148	      fun () ->
1149		      {ok, start, undefined}
1150	      end,
1151	  start =>
1152	      fun ({call,_} = Call, Req, undefined) ->
1153		      {next_state, state1, undefined,
1154		       [{{timeout,a},1500,1},
1155			{state_timeout,1500,1},
1156			{{timeout,b},1000,1},
1157			{next_event,Call,Req}]}
1158	      end,
1159	  state1 =>
1160	      fun ({call,_} = Call, Req, undefined) ->
1161		      T = erlang:monotonic_time(millisecond) + 500,
1162		      {next_state, state2, undefined,
1163		       [{{timeout,c},T,2,{abs,true}},
1164			{{timeout,d},0,2,[{abs,false}]},
1165			{timeout,0,2},
1166			{{timeout,b},infinity,2},
1167			{{timeout,a},1000,{Call,Req}}]}
1168	      end,
1169	  state2 =>
1170	      fun ({timeout,d}, 2, undefined) ->
1171		      {next_state, state3, undefined}
1172	      end,
1173	  state3 =>
1174	      fun ({timeout,c}, 2, undefined) ->
1175		      {next_state, state4, undefined}
1176	      end,
1177	  state4 =>
1178	      fun ({timeout,a}, {{call,From},stop}, undefined) ->
1179		      {stop_and_reply, shutdown,
1180		       [{reply,From,stopped}]}
1181	      end},
1182    {ok,STM} =
1183	gen_statem:start_link(
1184	  ?MODULE, {map_statem,Machine,[]}, [{debug,[trace]}]),
1185
1186    stopped = gen_statem:call(STM, stop),
1187    receive
1188	{'EXIT',STM,shutdown} ->
1189	    ok
1190    after 500 ->
1191	    ct:fail(did_not_stop)
1192    end,
1193
1194    {noproc,_} =
1195	?EXPECT_FAILURE(gen_statem:call(STM, hej), Reason),
1196    case flush() of
1197	[] ->
1198	    ok;
1199	Other2 ->
1200	    ct:fail({unexpected,Other2})
1201    end.
1202
1203
1204
1205sys1(Config) ->
1206    {ok,Pid} = gen_statem:start(?MODULE, start_arg(Config, []), []),
1207    {status, Pid, {module,gen_statem}, Info} = sys:get_status(Pid),
1208    ct:log("Status info: ~p~n", [Info]),
1209    sys:suspend(Pid),
1210    Parent = self(),
1211    Tag = make_ref(),
1212    Caller =
1213	spawn(
1214	  fun () ->
1215		  Parent ! {Tag,gen_statem:call(Pid, hej)}
1216	  end),
1217    receive
1218	{Tag,_} ->
1219	    ct:fail(should_be_suspended)
1220    after 3000 ->
1221	    exit(Caller, ok)
1222    end,
1223
1224    %% {timeout,_} =
1225    %% 	?EXPECT_FAILURE(gen_statem:call(Pid, hej), Reason),
1226    sys:resume(Pid),
1227    stop_it(Pid).
1228
1229code_change(_Config) ->
1230    {ok,Pid} =
1231	gen_statem:start(
1232	  ?MODULE, {callback_mode,state_functions,[]}, []),
1233    {idle,data} = sys:get_state(Pid),
1234    sys:suspend(Pid),
1235    Mode = handle_event_function,
1236    sys:change_code(Pid, ?MODULE, old_vsn, Mode),
1237    sys:resume(Pid),
1238    {idle,{old_vsn,data,Mode}} = sys:get_state(Pid),
1239    Mode = gen_statem:call(Pid, get_callback_mode),
1240    stop_it(Pid).
1241
1242call_format_status(Config) ->
1243    {ok,Pid} = gen_statem:start(?MODULE, start_arg(Config, []), []),
1244    Status = sys:get_status(Pid),
1245    {status,Pid,_Mod,[_PDict,running,_,_, Data]} = Status,
1246    [format_status_called|_] = lists:reverse(Data),
1247    stop_it(Pid),
1248
1249    %% check that format_status can handle a name being an atom (pid is
1250    %% already checked by the previous test)
1251    {ok, Pid2} =
1252	gen_statem:start(
1253	  {local, gstm}, ?MODULE, start_arg(Config, []), []),
1254    Status2 = sys:get_status(gstm),
1255    {status,Pid2,Mod,[_PDict2,running,_,_,Data2]} = Status2,
1256    [format_status_called|_] = lists:reverse(Data2),
1257    stop_it(Pid2),
1258
1259    %% check that format_status can handle a name being a term other than a
1260    %% pid or atom
1261    GlobalName1 = {global,"CallFormatStatus"},
1262    {ok,Pid3} =
1263	gen_statem:start(
1264	  GlobalName1, ?MODULE, start_arg(Config, []), []),
1265    Status3 = sys:get_status(GlobalName1),
1266    {status,Pid3,Mod,[_PDict3,running,_,_,Data3]} = Status3,
1267    [format_status_called|_] = lists:reverse(Data3),
1268    stop_it(Pid3),
1269    GlobalName2 = {global,{name, "term"}},
1270    {ok,Pid4} =
1271	gen_statem:start(
1272	  GlobalName2, ?MODULE, start_arg(Config, []), []),
1273    Status4 = sys:get_status(GlobalName2),
1274    {status,Pid4,Mod,[_PDict4,running,_,_, Data4]} = Status4,
1275    [format_status_called|_] = lists:reverse(Data4),
1276    stop_it(Pid4),
1277
1278    %% check that format_status can handle a name being a term other than a
1279    %% pid or atom
1280    dummy_via:reset(),
1281    ViaName1 = {via,dummy_via,"CallFormatStatus"},
1282    {ok,Pid5} = gen_statem:start(ViaName1, ?MODULE, start_arg(Config, []), []),
1283    Status5 = sys:get_status(ViaName1),
1284    {status,Pid5,Mod, [_PDict5,running,_,_, Data5]} = Status5,
1285    [format_status_called|_] = lists:reverse(Data5),
1286    stop_it(Pid5),
1287    ViaName2 = {via,dummy_via,{name,"term"}},
1288    {ok, Pid6} =
1289	gen_statem:start(
1290	  ViaName2, ?MODULE, start_arg(Config, []), []),
1291    Status6 = sys:get_status(ViaName2),
1292    {status,Pid6,Mod,[_PDict6,running,_,_,Data6]} = Status6,
1293    [format_status_called|_] = lists:reverse(Data6),
1294    stop_it(Pid6).
1295
1296
1297
1298error_format_status(Config) ->
1299    error_logger_forwarder:register(),
1300    OldFl = process_flag(trap_exit, true),
1301    Data = "called format_status",
1302    {ok,Pid} =
1303	gen_statem:start(
1304	  ?MODULE, start_arg(Config, {data,Data}), []),
1305    %% bad return value in the gen_statem loop
1306    {{{bad_return_from_state_function,badreturn},_},_} =
1307	?EXPECT_FAILURE(gen_statem:call(Pid, badreturn), Reason),
1308    receive
1309	{error,_,
1310	 {Pid,
1311	  "** State machine"++_,
1312	  [Pid,{{call,_},badreturn},
1313	   {formatted,idle,Data},
1314	   error,{bad_return_from_state_function,badreturn}|_]}} ->
1315	    ok;
1316	Other when is_tuple(Other), element(1, Other) =:= error ->
1317	    error_logger_forwarder:unregister(),
1318	    ct:fail({unexpected,Other})
1319    after 1000 ->
1320	    error_logger_forwarder:unregister(),
1321	    ct:fail(timeout)
1322    end,
1323    process_flag(trap_exit, OldFl),
1324    error_logger_forwarder:unregister(),
1325    receive
1326	%% Comes with SASL
1327	{error_report,_,{Pid,crash_report,_}} ->
1328	    ok
1329    after 500 ->
1330	    ok
1331    end,
1332    ok = verify_empty_msgq().
1333
1334terminate_crash_format(Config) ->
1335    error_logger_forwarder:register(),
1336    OldFl = process_flag(trap_exit, true),
1337    Data = crash_terminate,
1338    {ok,Pid} =
1339	gen_statem:start(
1340	  ?MODULE, start_arg(Config, {data,Data}), []),
1341    stop_it(Pid),
1342    Self = self(),
1343    receive
1344	{error,_GroupLeader,
1345	 {Pid,
1346	  "** State machine"++_,
1347	  [Pid,
1348	   {{call,{Self,_}},stop},
1349	   {formatted,idle,Data},
1350	   exit,{crash,terminate}|_]}} ->
1351	    ok;
1352	Other when is_tuple(Other), element(1, Other) =:= error ->
1353	    error_logger_forwarder:unregister(),
1354	    ct:fail({unexpected,Other})
1355    after 1000 ->
1356	    error_logger_forwarder:unregister(),
1357	    ct:fail(timeout)
1358    end,
1359    process_flag(trap_exit, OldFl),
1360    error_logger_forwarder:unregister(),
1361    receive
1362	%% Comes with SASL
1363	{error_report,_,{Pid,crash_report,_}} ->
1364	    ok
1365    after 500 ->
1366	    ok
1367    end,
1368    ok = verify_empty_msgq().
1369
1370
1371get_state(Config) ->
1372    State = self(),
1373    {ok,Pid} =
1374	gen_statem:start(
1375	  ?MODULE, start_arg(Config, {data,State}), []),
1376    {idle,State} = sys:get_state(Pid),
1377    {idle,State} = sys:get_state(Pid, 5000),
1378    stop_it(Pid),
1379
1380    %% check that get_state can handle a name being an atom (pid is
1381    %% already checked by the previous test)
1382    {ok,Pid2} =
1383	gen_statem:start(
1384	  {local,gstm}, ?MODULE, start_arg(Config, {data,State}), []),
1385    {idle,State} = sys:get_state(gstm),
1386    {idle,State} = sys:get_state(gstm, 5000),
1387    stop_it(Pid2),
1388
1389    %% check that get_state works when pid is sys suspended
1390    {ok,Pid3} =
1391	gen_statem:start(
1392	  ?MODULE, start_arg(Config, {data,State}), []),
1393    {idle,State} = sys:get_state(Pid3),
1394    ok = sys:suspend(Pid3),
1395    {idle,State} = sys:get_state(Pid3, 5000),
1396    ok = sys:resume(Pid3),
1397    stop_it(Pid3),
1398    ok = verify_empty_msgq().
1399
1400replace_state(Config) ->
1401    State = self(),
1402    {ok, Pid} =
1403	gen_statem:start(
1404	  ?MODULE, start_arg(Config, {data,State}), []),
1405    {idle,State} = sys:get_state(Pid),
1406    NState1 = "replaced",
1407    Replace1 = fun({StateName, _}) -> {StateName,NState1} end,
1408    {idle,NState1} = sys:replace_state(Pid, Replace1),
1409    {idle,NState1} = sys:get_state(Pid),
1410    NState2 = "replaced again",
1411    Replace2 = fun({idle, _}) -> {state0,NState2} end,
1412    {state0,NState2} = sys:replace_state(Pid, Replace2, 5000),
1413    {state0,NState2} = sys:get_state(Pid),
1414    %% verify no change in state if replace function crashes
1415    Replace3 = fun(_) -> error(fail) end,
1416    {callback_failed,
1417     {gen_statem,system_replace_state},{error,fail}} =
1418	?EXPECT_FAILURE(sys:replace_state(Pid, Replace3), Reason),
1419    {state0, NState2} = sys:get_state(Pid),
1420    %% verify state replaced if process sys suspended
1421    ok = sys:suspend(Pid),
1422    Suffix2 = " and again",
1423    NState3 = NState2 ++ Suffix2,
1424    Replace4 = fun({StateName, _}) -> {StateName, NState3} end,
1425    {state0,NState3} = sys:replace_state(Pid, Replace4),
1426    ok = sys:resume(Pid),
1427    {state0,NState3} = sys:get_state(Pid, 5000),
1428    stop_it(Pid),
1429    ok = verify_empty_msgq().
1430
1431%% Hibernation
1432hibernate(Config) ->
1433    OldFl = process_flag(trap_exit, true),
1434
1435    {ok,Pid0} =
1436	gen_statem:start_link(
1437	  ?MODULE, start_arg(Config, hiber_now), []),
1438    wait_erlang_hibernate(Pid0),
1439    stop_it(Pid0),
1440    receive
1441	{'EXIT',Pid0,normal} -> ok
1442    after 5000 ->
1443	    ct:fail(gen_statem_did_not_die)
1444    end,
1445
1446    {ok,Pid} =
1447	gen_statem:start_link(?MODULE, start_arg(Config, hiber), []),
1448    true = ({current_function,{erlang,hibernate,3}} =/=
1449		erlang:process_info(Pid,current_function)),
1450    hibernating = gen_statem:call(Pid, hibernate_sync),
1451    wait_erlang_hibernate(Pid),
1452    good_morning = gen_statem:call(Pid, wakeup_sync),
1453    is_not_in_erlang_hibernate(Pid),
1454    hibernating = gen_statem:call(Pid, hibernate_sync),
1455    wait_erlang_hibernate(Pid),
1456    please_just_five_more = gen_statem:call(Pid, snooze_sync),
1457    wait_erlang_hibernate(Pid),
1458    good_morning = gen_statem:call(Pid, wakeup_sync),
1459    is_not_in_erlang_hibernate(Pid),
1460    ok = gen_statem:cast(Pid, hibernate_async),
1461    wait_erlang_hibernate(Pid),
1462    ok = gen_statem:cast(Pid, wakeup_async),
1463    is_not_in_erlang_hibernate(Pid),
1464    ok = gen_statem:cast(Pid, hibernate_async),
1465    wait_erlang_hibernate(Pid),
1466    ok = gen_statem:cast(Pid, snooze_async),
1467    wait_erlang_hibernate(Pid),
1468    ok = gen_statem:cast(Pid, wakeup_async),
1469    is_not_in_erlang_hibernate(Pid),
1470
1471    Pid ! hibernate_later,
1472    true =
1473	({current_function,{erlang,hibernate,3}} =/=
1474	     erlang:process_info(Pid, current_function)),
1475    wait_erlang_hibernate(Pid),
1476
1477    'alive!' = gen_statem:call(Pid, 'alive?'),
1478    true =
1479	({current_function,{erlang,hibernate,3}} =/=
1480	     erlang:process_info(Pid, current_function)),
1481    Pid ! hibernate_now,
1482    wait_erlang_hibernate(Pid),
1483
1484    'alive!' = gen_statem:call(Pid, 'alive?'),
1485    true =
1486	({current_function,{erlang,hibernate,3}} =/=
1487	     erlang:process_info(Pid, current_function)),
1488
1489    hibernating = gen_statem:call(Pid, hibernate_sync),
1490    wait_erlang_hibernate(Pid),
1491    good_morning = gen_statem:call(Pid, wakeup_sync),
1492    is_not_in_erlang_hibernate(Pid),
1493    hibernating = gen_statem:call(Pid, hibernate_sync),
1494    wait_erlang_hibernate(Pid),
1495    please_just_five_more = gen_statem:call(Pid, snooze_sync),
1496    wait_erlang_hibernate(Pid),
1497    good_morning = gen_statem:call(Pid, wakeup_sync),
1498    is_not_in_erlang_hibernate(Pid),
1499    ok = gen_statem:cast(Pid, hibernate_async),
1500    wait_erlang_hibernate(Pid),
1501    ok  = gen_statem:cast(Pid, wakeup_async),
1502    is_not_in_erlang_hibernate(Pid),
1503    ok = gen_statem:cast(Pid, hibernate_async),
1504    wait_erlang_hibernate(Pid),
1505    ok = gen_statem:cast(Pid, snooze_async),
1506    wait_erlang_hibernate(Pid),
1507    ok = gen_statem:cast(Pid, wakeup_async),
1508    is_not_in_erlang_hibernate(Pid),
1509
1510    hibernating = gen_statem:call(Pid, hibernate_sync),
1511    wait_erlang_hibernate(Pid),
1512    sys:suspend(Pid),
1513    wait_erlang_hibernate(Pid),
1514    sys:resume(Pid),
1515    wait_erlang_hibernate(Pid),
1516    receive after 1000 -> ok end,
1517    wait_erlang_hibernate(Pid),
1518
1519    good_morning  = gen_statem:call(Pid, wakeup_sync),
1520    is_not_in_erlang_hibernate(Pid),
1521    stop_it(Pid),
1522    process_flag(trap_exit, OldFl),
1523    receive
1524	{'EXIT',Pid,normal} -> ok
1525    after 5000 ->
1526	    ct:fail(gen_statem_did_not_die)
1527    end,
1528    ok = verify_empty_msgq().
1529
1530%% Auto-hibernation timeout
1531auto_hibernate(Config) ->
1532    OldFl = process_flag(trap_exit, true),
1533    HibernateAfterTimeout = 1000,
1534
1535    {ok,Pid} =
1536        gen_statem:start_link(
1537            ?MODULE, start_arg(Config, []),
1538          [{hibernate_after, HibernateAfterTimeout}]),
1539    %% After init test
1540    is_not_in_erlang_hibernate(Pid),
1541    timer:sleep(HibernateAfterTimeout),
1542    wait_erlang_hibernate(Pid),
1543    %% After info test
1544    Pid ! {hping, self()},
1545    receive
1546        {Pid, hpong} ->
1547            ok
1548    after 1000 ->
1549        ct:fail(info)
1550    end,
1551    is_not_in_erlang_hibernate(Pid),
1552    timer:sleep(HibernateAfterTimeout),
1553    wait_erlang_hibernate(Pid),
1554    %% After cast test
1555    ok = gen_statem:cast(Pid, {hping, self()}),
1556    receive
1557        {Pid, hpong} ->
1558            ok
1559    after 1000 ->
1560        ct:fail(cast)
1561    end,
1562    is_not_in_erlang_hibernate(Pid),
1563    timer:sleep(HibernateAfterTimeout),
1564    wait_erlang_hibernate(Pid),
1565    %% After call test
1566    hpong = gen_statem:call(Pid, hping),
1567    is_not_in_erlang_hibernate(Pid),
1568    timer:sleep(HibernateAfterTimeout),
1569    wait_erlang_hibernate(Pid),
1570    %% Timer test 1
1571    TimerTimeout1 = HibernateAfterTimeout div 2,
1572    ok = gen_statem:call(Pid, {start_htimer, self(), TimerTimeout1}),
1573    is_not_in_erlang_hibernate(Pid),
1574    timer:sleep(TimerTimeout1),
1575    is_not_in_erlang_hibernate(Pid),
1576    receive
1577        {Pid, htimer_timeout} ->
1578            ok
1579    after 1000 ->
1580        ct:fail(timer1)
1581    end,
1582    is_not_in_erlang_hibernate(Pid),
1583    timer:sleep(HibernateAfterTimeout),
1584    wait_erlang_hibernate(Pid),
1585    %% Timer test 2
1586    TimerTimeout2 = HibernateAfterTimeout * 2,
1587    ok = gen_statem:call(Pid, {start_htimer, self(), TimerTimeout2}),
1588    is_not_in_erlang_hibernate(Pid),
1589    timer:sleep(HibernateAfterTimeout),
1590    wait_erlang_hibernate(Pid),
1591    receive
1592        {Pid, htimer_timeout} ->
1593            ok
1594    after TimerTimeout2 ->
1595        ct:fail(timer2)
1596    end,
1597    is_not_in_erlang_hibernate(Pid),
1598    timer:sleep(HibernateAfterTimeout),
1599    wait_erlang_hibernate(Pid),
1600    stop_it(Pid),
1601    process_flag(trap_exit, OldFl),
1602    receive
1603        {'EXIT',Pid,normal} -> ok
1604    after 5000 ->
1605        ct:fail(gen_statem_did_not_die)
1606    end,
1607    ok = verify_empty_msgq().
1608
1609
1610wait_erlang_hibernate(Pid) ->
1611    receive after 1 -> ok end,
1612    wait_erlang_hibernate_1(200, Pid).
1613
1614wait_erlang_hibernate_1(0, Pid) ->
1615    ct:log("~p\n", [erlang:process_info(Pid, current_function)]),
1616    ct:fail(should_be_in_erlang_hibernate_3);
1617wait_erlang_hibernate_1(N, Pid) ->
1618    {current_function,MFA} = erlang:process_info(Pid, current_function),
1619    case MFA of
1620	{erlang,hibernate,3} ->
1621	    ok;
1622	_ ->
1623	    receive after 10 -> ok end,
1624	    wait_erlang_hibernate_1(N-1, Pid)
1625    end.
1626
1627is_not_in_erlang_hibernate(Pid) ->
1628    receive after 1 -> ok end,
1629    is_not_in_erlang_hibernate_1(200, Pid).
1630
1631is_not_in_erlang_hibernate_1(0, _Pid) ->
1632    ct:fail(should_not_be_in_erlang_hibernate_3);
1633is_not_in_erlang_hibernate_1(N, Pid) ->
1634    {current_function,MFA} = erlang:process_info(Pid, current_function),
1635    case MFA of
1636 	{erlang,hibernate,3} ->
1637	    receive after 10 -> ok end,
1638	    is_not_in_erlang_hibernate_1(N-1, Pid);
1639 	_ ->
1640 	    ok
1641    end.
1642
1643
1644enter_loop(_Config) ->
1645    OldFlag = process_flag(trap_exit, true),
1646
1647    dummy_via:reset(),
1648
1649    %% Locally registered process + {local,Name}
1650    {ok,Pid1a} =
1651	proc_lib:start_link(
1652          ?MODULE, enter_loop, [local,local,[{debug,[{log,7}]}]]),
1653    yes = gen_statem:call(Pid1a, 'alive?'),
1654    stopped = gen_statem:call(Pid1a, stop),
1655    receive
1656	{'EXIT',Pid1a,normal} ->
1657	    ok
1658    after 5000 ->
1659	    ct:fail(gen_statem_did_not_die)
1660    end,
1661
1662    %% Unregistered process + {local,Name}
1663    {ok,Pid1b} =
1664	proc_lib:start_link(
1665          ?MODULE, enter_loop, [anon,local,[{debug,[log]}]]),
1666    receive
1667	{'EXIT',Pid1b,process_not_registered} ->
1668	    ok
1669    after 5000 ->
1670	    ct:fail(gen_statem_did_not_die)
1671    end,
1672
1673    %% Globally registered process + {global,Name}
1674    {ok,Pid2a} =
1675	proc_lib:start_link(?MODULE, enter_loop, [global,global]),
1676    yes = gen_statem:call(Pid2a, 'alive?'),
1677    stopped = gen_statem:call(Pid2a, stop),
1678    receive
1679	{'EXIT',Pid2a,normal} ->
1680	    ok
1681    after 5000 ->
1682	    ct:fail(gen_statem_did_not_die)
1683    end,
1684
1685    %% Unregistered process + {global,Name}
1686    {ok,Pid2b} =
1687	proc_lib:start_link(?MODULE, enter_loop, [anon,global]),
1688    receive
1689	{'EXIT',Pid2b,process_not_registered_globally} ->
1690	    ok
1691    after 5000 ->
1692	    ct:fail(gen_statem_did_not_die)
1693    end,
1694
1695    %% Unregistered process + no name
1696    {ok,Pid3} =
1697	proc_lib:start_link(?MODULE, enter_loop, [anon,anon]),
1698    yes = gen_statem:call(Pid3, 'alive?'),
1699    stopped = gen_statem:call(Pid3, stop),
1700    receive
1701	{'EXIT',Pid3,normal} ->
1702	    ok
1703    after 5000 ->
1704	    ct:fail(gen_statem_did_not_die)
1705    end,
1706
1707    %% Process not started using proc_lib
1708    Pid4 = spawn_link(gen_statem, enter_loop, [?MODULE,[],state0,[]]),
1709    receive
1710	{'EXIT',Pid4,process_was_not_started_by_proc_lib} ->
1711	    ok
1712    after 5000 ->
1713	    ct:fail(gen_statem_did_not_die)
1714    end,
1715
1716    %% Make sure I am the parent, ie that ordering a shutdown will
1717    %% result in the process terminating with Reason==shutdown
1718    {ok,Pid5} =
1719	proc_lib:start_link(?MODULE, enter_loop, [anon,anon]),
1720    yes = gen_statem:call(Pid5, 'alive?'),
1721    exit(Pid5, shutdown),
1722    receive
1723	{'EXIT',Pid5,shutdown} ->
1724	    ok
1725    after 5000 ->
1726	    ct:fail(gen_statem_did_not_die)
1727    end,
1728
1729    %% Make sure gen_statem:enter_loop does not accept {local,Name}
1730    %% when it's another process than the calling one which is
1731    %% registered under that name
1732    register(armitage, self()),
1733    {ok,Pid6a} =
1734	proc_lib:start_link(?MODULE, enter_loop, [anon,local]),
1735    receive
1736	{'EXIT',Pid6a,process_not_registered} ->
1737	    ok
1738    after 1000 ->
1739	    ct:fail(gen_statem_started)
1740    end,
1741    unregister(armitage),
1742
1743    %% Make sure gen_statem:enter_loop does not accept {global,Name}
1744    %% when it's another process than the calling one which is
1745    %% registered under that name
1746    global:register_name(armitage, self()),
1747    {ok,Pid6b} =
1748	proc_lib:start_link(?MODULE, enter_loop, [anon,global]),
1749    receive
1750	{'EXIT',Pid6b,process_not_registered_globally} ->
1751	    ok
1752    after 1000 ->
1753	    ct:fail(gen_statem_started)
1754    end,
1755    global:unregister_name(armitage),
1756
1757    dummy_via:register_name(armitage, self()),
1758    {ok,Pid6c} =
1759	proc_lib:start_link(?MODULE, enter_loop, [anon,via]),
1760    receive
1761	{'EXIT',Pid6c,{process_not_registered_via,dummy_via}} ->
1762	    ok
1763    after 1000 ->
1764	    ct:fail(
1765	      {gen_statem_started,
1766	       process_info(self(), messages)})
1767    end,
1768    dummy_via:unregister_name(armitage),
1769
1770    process_flag(trap_exit, OldFlag),
1771    ok = verify_empty_msgq().
1772
1773enter_loop(Reg1, Reg2) ->
1774    enter_loop(Reg1, Reg2, []).
1775%%
1776enter_loop(Reg1, Reg2, Opts) ->
1777    process_flag(trap_exit, true),
1778    case Reg1 of
1779	local -> register(armitage, self());
1780	global -> global:register_name(armitage, self());
1781	via -> dummy_via:register_name(armitage, self());
1782	anon -> ignore
1783    end,
1784    proc_lib:init_ack({ok, self()}),
1785    case Reg2 of
1786	local ->
1787	    gen_statem:enter_loop(
1788	      ?MODULE, Opts, state0, [], {local,armitage});
1789	global ->
1790	    gen_statem:enter_loop(
1791	      ?MODULE, Opts, state0, [], {global,armitage});
1792	via ->
1793	    gen_statem:enter_loop(
1794	      ?MODULE, Opts, state0, [], {via, dummy_via, armitage});
1795	anon ->
1796	    gen_statem:enter_loop(?MODULE, Opts, state0, [])
1797    end.
1798
1799undef_code_change(_Config) ->
1800    {ok, Statem} = gen_statem:start(oc_statem, [], [{debug, [trace]}]),
1801    {error, {'EXIT',
1802             {undef, [{oc_statem, code_change, [_, _, _, _], _}|_]}}}
1803        = fake_upgrade(Statem, oc_statem).
1804
1805fake_upgrade(Pid, Mod) ->
1806    sys:suspend(Pid),
1807    sys:replace_state(Pid, fun(State) -> {new, State} end),
1808    Ret = sys:change_code(Pid, Mod, old_vsn, []),
1809    ok = sys:resume(Pid),
1810    Ret.
1811
1812undef_terminate1(_Config) ->
1813    {ok, Statem} = gen_statem:start(oc_statem, [], [{debug,[trace]}]),
1814    MRef = monitor(process, Statem),
1815    ok = gen_statem:stop(Statem),
1816    verify_down(Statem, MRef, normal),
1817    ok.
1818
1819undef_terminate2(_Config) ->
1820    Reason = {error, test},
1821    {ok, Statem} = oc_statem:start([{debug,[trace]}]),
1822    MRef = monitor(process, Statem),
1823    ok = gen_statem:stop(Statem, Reason, infinity),
1824    verify_down(Statem, MRef, Reason).
1825
1826undef_in_terminate(_Config) ->
1827    Data =  {undef_in_terminate, {?MODULE, terminate}},
1828    {ok, Statem} =
1829        gen_statem:start(
1830          ?MODULE, {data, Data}, [{debug,[log]}]),
1831    try
1832        gen_statem:stop(Statem),
1833        ct:fail(should_crash)
1834    catch
1835        exit:{undef, [{?MODULE, terminate, _, _}|_]} ->
1836            ok
1837    end.
1838
1839verify_down(Statem, MRef, Reason) ->
1840    receive
1841        {'DOWN', MRef, process, Statem, Reason} ->
1842            ok
1843    after 5000 ->
1844        ct:fail(default_terminate_failed)
1845    end.
1846
1847
1848pop_too_many(_Config) ->
1849    _ = process_flag(trap_exit, true),
1850
1851    Machine =
1852	#{init =>
1853	      fun () ->
1854		      {ok,start,undefined}
1855	      end,
1856	  start =>
1857	      fun ({call, From}, {change_callback_module, _Module} = Action,
1858                   undefined = _Data) ->
1859		      {keep_state_and_data,
1860                       [Action,
1861                        {reply,From,ok}]};
1862                  ({call, From}, {verify, ?MODULE},
1863                   undefined = _Data) ->
1864		      {keep_state_and_data,
1865                       [{reply,From,ok}]};
1866                  ({call, From}, pop_callback_module = Action,
1867                   undefined = _Data) ->
1868		      {keep_state_and_data,
1869                       [Action,
1870                        {reply,From,ok}]}
1871	      end},
1872    {ok, STM} =
1873	gen_statem:start_link(
1874          ?MODULE,
1875          {map_statem, Machine, []},
1876          [{debug, [trace]}]),
1877
1878    ok = gen_statem:call(STM, {change_callback_module, oc_statem}),
1879    ok = gen_statem:call(STM, {push_callback_module, ?MODULE}),
1880    ok = gen_statem:call(STM, {verify, ?MODULE}),
1881    ok = gen_statem:call(STM, pop_callback_module),
1882    BadAction = {bad_action_from_state_function, pop_callback_module},
1883    {{BadAction, _},
1884     {gen_statem,call,[STM,pop_callback_module,infinity]}} =
1885        ?EXPECT_FAILURE(gen_statem:call(STM, pop_callback_module), Reason),
1886
1887    receive
1888        {'EXIT', STM, {BadAction, _}} ->
1889            ok;
1890        Other ->
1891            ct:fail({surprise, Other})
1892    end.
1893
1894
1895%% Test the order for multiple {next_event,T,C}
1896next_events(Config) ->
1897    {ok,Pid} = gen_statem:start(?MODULE, start_arg(Config, []), []),
1898    ok = gen_statem:cast(Pid, next_event),
1899    {state,next_events,[]} = gen_statem:call(Pid, get),
1900    ok = gen_statem:stop(Pid),
1901    false = erlang:is_process_alive(Pid),
1902    noproc =
1903	?EXPECT_FAILURE(gen_statem:stop(Pid), Reason).
1904
1905
1906%% Test report callback for Logger handler error_logger
1907format_log_1(_Config) ->
1908    FD = application:get_env(kernel, error_logger_format_depth),
1909    application:unset_env(kernel, error_logger_format_depth),
1910    Term = lists:seq(1,15),
1911    Name = self(),
1912    Reason = {bad_reply_action_from_state_function,[]},
1913    Report1 = simple_report(Name, Term, Reason),
1914    Report2 = elaborate_report(Name, Term, Reason),
1915
1916    {F1,A1} = gen_statem:format_log(Report1),
1917    ct:log("F1: ~ts~nA1: ~tp",[F1,A1]),
1918    FExpected1 = "** State machine ~tp terminating~n"
1919        "** When server state  = ~tp~n"
1920        "** Reason for termination = ~tp:~tp~n"
1921        "** Callback modules = ~tp~n"
1922        "** Callback mode = ~tp~n",
1923    FExpected1 = F1,
1924    [Name,Term,error,Reason,[?MODULE],state_functions] = A1,
1925
1926    {F3,A3} = gen_statem:format_log(Report2),
1927    ct:log("F3: ~ts~nA3: ~tp",[F3,A3]),
1928    FExpected3 = "** State machine ~tp terminating~n"
1929        "** Last event = ~tp~n"
1930        "** When server state  = ~tp~n"
1931        "** Reason for termination = ~tp:~tp~n"
1932        "** Callback modules = ~tp~n"
1933        "** Callback mode = ~tp~n"
1934        "** Queued = ~tp~n"
1935        "** Postponed = ~tp~n"
1936        "** Stacktrace =~n**  ~tp~n"
1937        "** Time-outs: ~tp~n"
1938        "** Log =~n**  ~tp~n"
1939        "** Client ~tp stacktrace~n"
1940        "** ~tp~n",
1941    FExpected3 = F3,
1942    Stacktrace = stacktrace(),
1943    [Name,Term,Term,error,Reason,[?MODULE],[state_functions,state_enter],[Term],
1944     [{internal,Term}],Stacktrace,{1,[{timeout,message}]},[Term],Name,[]] = A3,
1945
1946    Depth = 10,
1947    ok = application:set_env(kernel, error_logger_format_depth, Depth),
1948    Limited = [1,2,3,4,5,6,7,8,9,'...'],
1949    {F2,A2} = gen_statem:format_log(Report1),
1950    ct:log("F2: ~ts~nA2: ~tp",[F2,A2]),
1951    FExpected2 = "** State machine ~tP terminating~n"
1952        "** When server state  = ~tP~n"
1953        "** Reason for termination = ~tP:~tP~n"
1954        "** Callback modules = ~tP~n"
1955        "** Callback mode = ~tP~n",
1956    FExpected2 = F2,
1957    [Name,Depth,Limited,Depth,error,Depth,Reason,Depth,
1958     [?MODULE],Depth,state_functions,Depth] = A2,
1959
1960    {F4,A4} = gen_statem:format_log(Report2),
1961    ct:log("F4: ~ts~nA4: ~tp",[F4,A4]),
1962    FExpected4 = "** State machine ~tP terminating~n"
1963        "** Last event = ~tP~n"
1964        "** When server state  = ~tP~n"
1965        "** Reason for termination = ~tP:~tP~n"
1966        "** Callback modules = ~tP~n"
1967        "** Callback mode = ~tP~n"
1968        "** Queued = ~tP~n"
1969        "** Postponed = ~tP~n"
1970        "** Stacktrace =~n**  ~tP~n"
1971        "** Time-outs: ~tP~n"
1972        "** Log =~n**  ~tP~n"
1973        "** Client ~tP stacktrace~n"
1974        "** ~tP~n",
1975    FExpected4 = F4,
1976    LimitedPostponed = [{internal,[1,2,3,4,5,6,'...']}],
1977    LimitedStacktrace = io_lib:limit_term(Stacktrace, Depth),
1978    LimitedQueue = io_lib:limit_term([Term], Depth),
1979    [Name,Depth,Limited,Depth,Limited,Depth,error,Depth,Reason,Depth,
1980     [?MODULE],Depth,[state_functions,state_enter],Depth,LimitedQueue,Depth,
1981     LimitedPostponed,Depth,LimitedStacktrace,Depth,{1,[{timeout,message}]},
1982     Depth,[Limited],Depth,Name,Depth,[],Depth] = A4,
1983
1984    case FD of
1985        undefined ->
1986            application:unset_env(kernel, error_logger_format_depth);
1987        _ ->
1988            application:set_env(kernel, error_logger_format_depth, FD)
1989    end,
1990    ok.
1991
1992%% Test report callback for any Logger handler
1993format_log_2(_Config) ->
1994    format_log_2_simple(),
1995    format_log_2_elaborate(),
1996    ok.
1997
1998format_log_2_simple() ->
1999    FD = application:get_env(kernel, error_logger_format_depth),
2000    application:unset_env(kernel, error_logger_format_depth),
2001
2002    Term = lists:seq(1,15),
2003    Name = self(),
2004    NameStr = pid_to_list(Name),
2005    Reason = {bad_reply_action_from_state_function,[]},
2006    Report = simple_report(Name, Term, Reason),
2007
2008    FormatOpts1 = #{},
2009    Str1 = flatten_format_log(Report, FormatOpts1),
2010    L1 = length(Str1),
2011    Expected1 = "** State machine " ++ NameStr ++ " terminating\n"
2012        "** When server state  = [1,2,3,4,5,6,7,8,9,10,11,12,13,14,15]\n"
2013        "** Reason for termination = "
2014           "error:{bad_reply_action_from_state_function,[]}\n"
2015        "** Callback modules = ["?MODULE_STRING"]\n"
2016        "** Callback mode = state_functions\n",
2017    ct:log("Str1: ~ts", [Str1]),
2018    ct:log("length(Str1): ~p", [L1]),
2019    Expected1 = Str1,
2020
2021    Depth = 10,
2022    FormatOpts2 = #{depth=>Depth},
2023    Str2 = flatten_format_log(Report, FormatOpts2),
2024    L2 = length(Str2),
2025    Expected2 = "** State machine " ++ NameStr ++ " terminating\n"
2026        "** When server state  = [1,2,3,4,5,6,7,8,9|...]\n"
2027        "** Reason for termination = "
2028           "error:{bad_reply_action_from_state_function,[]}\n"
2029        "** Callback modules = ["?MODULE_STRING"]\n"
2030        "** Callback mode = state_functions\n",
2031    ct:log("Str2: ~ts", [Str2]),
2032    ct:log("length(Str2): ~p", [L2]),
2033    true = Expected2 =:= Str2,
2034
2035    FormatOpts3 = #{chars_limit=>200},
2036    Str3 = flatten_format_log(Report, FormatOpts3),
2037    L3 = length(Str3),
2038    Expected3 = "** State machine " ++ NameStr ++ " terminating\n"
2039        "** When server state  = [",
2040    ct:log("Str3: ~ts", [Str3]),
2041    ct:log("length(Str3): ~p", [L3]),
2042    true = lists:prefix(Expected3, Str3),
2043    true = L3 < L1,
2044
2045    FormatOpts4 = #{single_line=>true},
2046    Str4 = flatten_format_log(Report, FormatOpts4),
2047    L4 = length(Str4),
2048    Expected4 = "State machine " ++ NameStr ++ " terminating. "
2049        "Reason: {bad_reply_action_from_state_function,[]}. "
2050        "State: [1,2,3,4,5,6,7,8,9,10,11,12,13,14,15].",
2051    ct:log("Str4: ~ts", [Str4]),
2052    ct:log("length(Str4): ~p", [L4]),
2053    Expected4 = Str4,
2054
2055    FormatOpts5 = #{single_line=>true, depth=>Depth},
2056    Str5 = flatten_format_log(Report, FormatOpts5),
2057    L5 = length(Str5),
2058    Expected5 = "State machine " ++ NameStr ++ " terminating. "
2059        "Reason: {bad_reply_action_from_state_function,[]}. "
2060        "State: [1,2,3,4,5,6,7,8,9|...].",
2061    ct:log("Str5: ~ts", [Str5]),
2062    ct:log("length(Str5): ~p", [L5]),
2063    Expected5 = Str5,
2064
2065    FormatOpts6 = #{single_line=>true, chars_limit=>100},
2066    Str6 = flatten_format_log(Report, FormatOpts6),
2067    L6 = length(Str6),
2068    Expected6 = "State machine " ++ NameStr ++ " terminating. "
2069        "Reason: ",
2070    ct:log("Str6: ~ts", [Str6]),
2071    ct:log("length(Str6): ~p", [L6]),
2072    true = lists:prefix(Expected6, Str6),
2073    true = L6 < L4,
2074
2075    case FD of
2076        undefined ->
2077            application:unset_env(kernel, error_logger_format_depth);
2078        _ ->
2079            application:set_env(kernel, error_logger_format_depth, FD)
2080    end,
2081    ok.
2082
2083format_log_2_elaborate() ->
2084    FD = application:get_env(kernel, error_logger_format_depth),
2085    application:unset_env(kernel, error_logger_format_depth),
2086
2087    Term = lists:seq(1,15),
2088    Name = self(),
2089    NameStr = pid_to_list(Name),
2090    Reason = {bad_reply_action_from_state_function,[]},
2091    Report = elaborate_report(Name, Term, Reason),
2092    FormatOpts1 = #{},
2093    Str1 = flatten_format_log(Report, FormatOpts1),
2094    L1 = length(Str1),
2095    Expected1 = "** State machine " ++ NameStr ++ " terminating\n"
2096        "** Last event = [1,2,3,4,5,6,7,8,9,10,11,12,13,14,15]\n",
2097    ct:log("Str1: ~ts", [Str1]),
2098    ct:log("length(Str1): ~p", [L1]),
2099    true = lists:prefix(Expected1, Str1),
2100
2101    Depth = 10,
2102    FormatOpts2 = #{depth=>Depth},
2103    Str2 = flatten_format_log(Report, FormatOpts2),
2104    L2 = length(Str2),
2105    Expected2 = "** State machine " ++ NameStr ++ " terminating\n"
2106        "** Last event = [1,2,3,4,5,6,7,8,9|...]\n"
2107        "** When server state  = [1,2,3,4,5,6,7,8,9|...]\n"
2108        "** Reason for termination = "
2109           "error:{bad_reply_action_from_state_function,[]}\n"
2110        "** Callback modules = ["?MODULE_STRING"]\n"
2111        "** Callback mode = [state_functions,state_enter]\n"
2112        "** Queued = [[1,2,3,4,5,6,7,8|...]]\n"
2113        "** Postponed = [{internal,[1,2,3,4,5,6|...]}]\n"
2114        "** Stacktrace =\n"
2115        "**  [{m,f,1,[1,2,3,4|...]}]\n"
2116        "** Time-outs: {1,[{timeout,message}]}\n"
2117        "** Log =\n"
2118        "**  [[1,2,3,4,5,6,7,8|...]]\n"
2119        "** Client "++NameStr ++ " stacktrace\n"
2120        "** []\n",
2121    ct:log("Str2: ~ts", [Str2]),
2122    ct:log("length(Str2): ~p", [L2]),
2123    Expected2 = Str2,
2124
2125    FormatOpts3 = #{chars_limit=>300},
2126    Str3 = flatten_format_log(Report, FormatOpts3),
2127    L3 = length(Str3),
2128    Expected3 = "** State machine " ++ NameStr ++ " terminating\n"
2129        "** Last event = ",
2130    ct:log("Str3: ~ts", [Str3]),
2131    ct:log("length(Str3): ~p", [L3]),
2132    true = lists:prefix(Expected3, Str3),
2133    true = L3 < L1,
2134
2135    FormatOpts4 = #{single_line=>true},
2136    Str4 = flatten_format_log(Report, FormatOpts4),
2137    L4 = length(Str4),
2138    Expected4 = "State machine " ++ NameStr ++ " terminating. "
2139        "Reason: {bad_reply_action_from_state_function,[]}. "
2140        "Stack: [{m,f,1,[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15]}]. "
2141        "Last event: [1,2,3,4,5,6,7,8,9,10,11,12,13,14,15]. "
2142        "State: [1,2,3,4,5,6,7,8,9,10,11,12,13,14,15]. "
2143        "Log: [[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15]]. "
2144        "Client " ++ NameStr ++ " stacktrace: [].",
2145    ct:log("Str4: ~ts", [Str4]),
2146    ct:log("length(Str4): ~p", [L4]),
2147    Expected4 = Str4,
2148
2149    FormatOpts5 = #{single_line=>true, depth=>Depth},
2150    Str5 = flatten_format_log(Report, FormatOpts5),
2151    L5 = length(Str5),
2152    Expected5 = "State machine " ++ NameStr ++ " terminating. "
2153        "Reason: {bad_reply_action_from_state_function,[]}. "
2154        "Stack: [{m,f,1,[1,2,3,4|...]}]. "
2155        "Last event: [1,2,3,4,5,6,7,8,9|...]. "
2156        "State: [1,2,3,4,5,6,7,8,9|...]. "
2157        "Log: [[1,2,3,4,5,6,7,8|...]]. "
2158        "Client " ++ NameStr ++ " stacktrace: [].",
2159    ct:log("Str5: ~ts", [Str5]),
2160    ct:log("length(Str5): ~p", [L5]),
2161    Expected5 = Str5,
2162
2163    FormatOpts6 = #{single_line=>true, chars_limit=>300},
2164    Str6 = flatten_format_log(Report, FormatOpts6),
2165    L6 = length(Str6),
2166    Expected6 = "State machine " ++ NameStr ++ " terminating. "
2167        "Reason:",
2168    ct:log("Str6: ~ts", [Str6]),
2169    ct:log("length(Str6): ~p", [L6]),
2170    true = lists:prefix(Expected6, Str6),
2171    true = L6 < L4,
2172
2173    case FD of
2174        undefined ->
2175            application:unset_env(kernel, error_logger_format_depth);
2176        _ ->
2177            application:set_env(kernel, error_logger_format_depth, FD)
2178    end,
2179    ok.
2180
2181simple_report(Name, Term, Reason) ->
2182    #{label=>{gen_statem,terminate},
2183      name=>Name,
2184      queue=>[],
2185      postponed=>[],
2186      modules=>[?MODULE],
2187      callback_mode=>state_functions,
2188      state_enter=>false,
2189      state=>Term,
2190      timeouts=>{0,[]},
2191      log=>[],
2192      reason=>{error,Reason,[]},
2193      client_info=>undefined}.
2194
2195elaborate_report(Name, Term, Reason) ->
2196    #{label=>{gen_statem,terminate},
2197      name=>Name,
2198      queue=>[Term,Term],
2199      postponed=>[{internal,Term}],
2200      modules=>[?MODULE],
2201      callback_mode=>state_functions,
2202      state_enter=>true,
2203      state=>Term,
2204      timeouts=>{1,[{timeout,message}]},
2205      log=>[Term],
2206      reason=>{error,Reason,stacktrace()},
2207      client_info=>{self(),{self(),[]}}}.
2208
2209stacktrace() ->
2210    [{m,f,1,lists:seq(1, 15)}].
2211
2212flatten_format_log(Report, Format) ->
2213    lists:flatten(gen_statem:format_log(Report, Format)).
2214
2215reply_by_alias_with_payload(Config) when is_list(Config) ->
2216    %% "Payload" version of tag not used yet, but make sure
2217    %% gen_statem:reply/2 works with it...
2218    %%
2219    %% Whitebox...
2220    Reply = make_ref(),
2221    Alias = alias(),
2222    Tag = [[alias|Alias], "payload"],
2223    spawn_link(fun () ->
2224                       gen_statem:reply({undefined, Tag},
2225                                        Reply)
2226               end),
2227    receive
2228        {[[alias|Alias]|_] = Tag, Reply} ->
2229            ok
2230    end.
2231
2232%%
2233%% Functionality check
2234%%
2235
2236wfor(Msg) ->
2237    receive
2238	Msg -> ok
2239    after 5000 ->
2240	    error(timeout)
2241    end.
2242
2243
2244stop_it(STM) ->
2245    stopped = gen_statem:call(STM, stop),
2246    check_stopped(STM).
2247
2248
2249check_stopped(STM) ->
2250    Call = there_you_are,
2251    {_,{gen_statem,call,[_,Call,infinity]}} =
2252	?EXPECT_FAILURE(gen_statem:call(STM, Call), Reason),
2253    ok.
2254
2255
2256do_func_test(STM) ->
2257    ok = gen_statem:cast(STM, {'alive?',self()}),
2258    wfor(yes),
2259    ok = do_connect(STM),
2260    ok = gen_statem:cast(STM, {'alive?',self()}),
2261    wfor(yes),
2262    test_server:do_times(3, ?MODULE, do_msg, [STM]),
2263    ok = gen_statem:cast(STM, {'alive?',self()}),
2264    wfor(yes),
2265    ok = do_disconnect(STM),
2266    ok = gen_statem:cast(STM, {'alive?',self()}),
2267    P0 = gen_statem:send_request(STM, 'alive?'),
2268    timeout = gen_statem:wait_response(P0, 0),
2269    wfor(yes),
2270    {reply, yes} = gen_statem:wait_response(P0, infinity),
2271    _ = flush(),
2272    P1 = gen_statem:send_request(STM, 'alive?'),
2273    receive Msg ->
2274            no_reply = gen_statem:check_response(Msg, P0),
2275            {reply, yes} = gen_statem:check_response(Msg, P1)
2276    after 1000 -> exit(timeout)
2277    end,
2278    ok.
2279
2280
2281do_connect(STM) ->
2282    check_state(STM, idle),
2283    gen_statem:cast(STM, {connect,self()}),
2284    wfor(accept),
2285    check_state(STM, wfor_conf),
2286    Tag = make_ref(),
2287    gen_statem:cast(STM, {ping,self(),Tag}),
2288    gen_statem:cast(STM, confirm),
2289    wfor({pong,Tag}),
2290    check_state(STM, connected),
2291    ok.
2292
2293do_msg(STM) ->
2294    check_state(STM, connected),
2295    R = make_ref(),
2296    ok = gen_statem:cast(STM, {msg,self(),R}),
2297    wfor({ack,R}).
2298
2299
2300do_disconnect(STM) ->
2301    ok = gen_statem:cast(STM, disconnect),
2302    check_state(STM, idle).
2303
2304check_state(STM, State) ->
2305    case gen_statem:call(STM, get) of
2306	{state, State, _} -> ok
2307    end.
2308
2309do_sync_func_test(STM) ->
2310    yes = gen_statem:call(STM, 'alive?'),
2311    ok = do_sync_connect(STM),
2312    yes = gen_statem:call(STM, 'alive?'),
2313    test_server:do_times(3, ?MODULE, do_sync_msg, [STM]),
2314    yes = gen_statem:call(STM, 'alive?'),
2315    ok = do_sync_disconnect(STM),
2316    yes = gen_statem:call(STM, 'alive?'),
2317    check_state(STM, idle),
2318    ok = gen_statem:call(STM, {timeout,200}),
2319    yes = gen_statem:call(STM, 'alive?'),
2320    check_state(STM, idle),
2321    ok.
2322
2323
2324do_sync_connect(STM) ->
2325    check_state(STM, idle),
2326    accept = gen_statem:call(STM, connect),
2327    check_state(STM, wfor_conf),
2328    Tag = make_ref(),
2329    gen_statem:cast(STM, {ping,self(),Tag}),
2330    yes = gen_statem:call(STM, confirm),
2331    wfor({pong,Tag}),
2332    check_state(STM, connected),
2333    ok.
2334
2335do_sync_msg(STM) ->
2336    check_state(STM, connected),
2337    R = make_ref(),
2338    {ack,R} = gen_statem:call(STM, {msg,R}),
2339    ok.
2340
2341do_sync_disconnect(STM) ->
2342    yes = gen_statem:call(STM, disconnect),
2343    check_state(STM, idle).
2344
2345
2346verify_empty_msgq() ->
2347    [] = flush(),
2348    ok.
2349
2350start_arg(Config, Arg) ->
2351    case lists:keyfind(callback_mode, 1, Config) of
2352	{_,CallbackMode} ->
2353	    {callback_mode,CallbackMode,Arg};
2354	false ->
2355	    Arg
2356    end.
2357
2358%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2359%%
2360%% The State Machine
2361%%
2362%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2363
2364init(ignore) ->
2365    ignore;
2366init(stop) ->
2367    {stop,stopped};
2368init(stop_shutdown) ->
2369    {stop,shutdown};
2370init(sleep) ->
2371    ct:sleep(1000),
2372    init_sup({ok,idle,data});
2373init(hiber) ->
2374    init_sup({ok,hiber_idle,[]});
2375init(hiber_now) ->
2376    init_sup({ok,hiber_idle,[],[hibernate]});
2377init({data, Data}) ->
2378    init_sup({ok,idle,Data});
2379init({callback_mode,CallbackMode,Arg}) ->
2380    ets:new(?MODULE, [named_table,private]),
2381    ets:insert(?MODULE, {callback_mode,CallbackMode}),
2382    init(Arg);
2383init({map_statem,#{init := Init}=Machine,Modes}) ->
2384    ets:new(?MODULE, [named_table,private]),
2385    ets:insert(?MODULE, {callback_mode,[handle_event_function|Modes]}),
2386    case Init() of
2387	{ok,State,Data,Ops} ->
2388	    init_sup({ok,State,[Data|Machine],Ops});
2389	{ok,State,Data} ->
2390	    init_sup({ok,State,[Data|Machine]});
2391	Other ->
2392	    init_sup(Other)
2393    end;
2394init([]) ->
2395    init_sup({ok,idle,data}).
2396
2397%% Supervise state machine parent i.e the test case, and if it dies
2398%% (fails due to some reason), kill the state machine,
2399%% just to not leak resources (process, name, ETS table, etc...)
2400%%
2401init_sup(Result) ->
2402    Parent = gen:get_parent(),
2403    Statem = self(),
2404    _Supervisor =
2405        spawn(
2406          fun () ->
2407                  StatemRef = monitor(process, Statem),
2408                  ParentRef = monitor(process, Parent),
2409                  receive
2410                      {'DOWN', StatemRef, _, _, Reason} ->
2411                          exit(Reason);
2412                      {'DOWN', ParentRef, _, _, _} ->
2413                          exit(Statem, kill)
2414                  end
2415          end),
2416    Result.
2417
2418callback_mode() ->
2419    try ets:lookup(?MODULE, callback_mode) of
2420	[{callback_mode,CallbackMode}] ->
2421	    CallbackMode
2422    catch
2423	error:badarg ->
2424	    state_functions
2425    end.
2426
2427terminate(_, _State, crash_terminate) ->
2428    exit({crash,terminate});
2429terminate(_, _State, {undef_in_terminate, {Mod, Fun}}) ->
2430    Mod:Fun(),
2431    ok;
2432terminate({From,stopped}, State, _Data) ->
2433    From ! {self(),{stopped,State}},
2434    ok;
2435terminate(_Reason, _State, _Data) ->
2436    ok.
2437
2438
2439%% State functions
2440
2441idle(info, {hping,Pid}, _Data) ->
2442    Pid ! {self(), hpong},
2443    keep_state_and_data;
2444idle(cast, {hping,Pid}, Data) ->
2445    Pid ! {self(), hpong},
2446    {keep_state, Data};
2447idle({call, From}, hping, _Data) ->
2448    {keep_state_and_data, [{reply, From, hpong}]};
2449idle({call, From}, {start_htimer, Pid, Timeout}, _Data) ->
2450    {keep_state_and_data, [{reply, From, ok}, {timeout, Timeout, {htimer, Pid}}]};
2451idle(timeout, {htimer, Pid}, _Data) ->
2452    Pid ! {self(), htimer_timeout},
2453    keep_state_and_data;
2454idle(cast, {connect,Pid}, Data) ->
2455    Pid ! accept,
2456    {next_state,wfor_conf,Data,infinity}; % NoOp timeout just to test API
2457idle({call,From}, connect, Data) ->
2458    gen_statem:reply(From, accept),
2459    {next_state,wfor_conf,Data,infinity}; % NoOp timeout just to test API
2460idle({call,_From}, badreturn, _Data) ->
2461    badreturn;
2462idle({call,_From}, badaction, Data) ->
2463    {keep_state, Data, [badaction]};
2464idle({call,_From}, {badtimeout,BadTimeout}, Data) ->
2465    {keep_state, Data, BadTimeout};
2466idle({call,From}, {delayed_answer,T}, Data) ->
2467    receive
2468    after T ->
2469	    gen_statem:reply({reply,From,delayed}),
2470	    throw({keep_state,Data})
2471    end;
2472idle({call,From}, {timeout,Time}, _Data) ->
2473    AbsTime = erlang:monotonic_time(millisecond) + Time,
2474    {next_state,timeout,{From,Time},
2475     {timeout,AbsTime,idle,[{abs,true}]}};
2476idle(cast, next_event, _Data) ->
2477    {next_state,next_events,[a,b,c],
2478     [{next_event,internal,a},
2479      {next_event,internal,b},
2480      {next_event,internal,c}]};
2481idle(Type, Content, Data) ->
2482    case handle_common_events(Type, Content, idle, Data) of
2483	undefined ->
2484	    case Type of
2485		{call,From} ->
2486		    throw({keep_state,Data,[{reply,From,'eh?'}]});
2487		_ ->
2488		    throw(
2489		      {stop,{unexpected,idle,Type,Content}})
2490	    end;
2491	Result ->
2492	    Result
2493    end.
2494
2495timeout(timeout, idle, {From,Time}) ->
2496    TRef = erlang:start_timer(Time, self(), ok),
2497    {keep_state,{From,TRef},0}; % Immediate timeout 0
2498timeout(timeout, 0, {From,TRef}) ->
2499    {next_state,timeout2,{From,TRef},
2500     [{timeout,1,should_be_cancelled},
2501      postpone]}; % Should cancel state timeout
2502timeout(_, _, _) ->
2503    keep_state_and_data.
2504
2505timeout2(timeout, 0, _) ->
2506    keep_state_and_data;
2507timeout2(timeout, Reason, _) ->
2508    {stop,Reason};
2509timeout2(info, {timeout,TRef,Result}, {From,TRef}) ->
2510    gen_statem:reply([{reply,From,Result}]),
2511    {next_state,idle,state};
2512timeout2(_, _, _) ->
2513    {keep_state_and_data,[]}.
2514
2515wfor_conf({call,From}, confirm, Data) ->
2516    {next_state,connected,Data,
2517     {reply,From,yes}};
2518wfor_conf(cast, {ping,_,_}, _) ->
2519    {keep_state_and_data,[postpone]};
2520wfor_conf(cast, confirm, Data) ->
2521    {next_state,connected,Data};
2522wfor_conf(Type, Content, Data) ->
2523    case handle_common_events(Type, Content, wfor_conf, Data) of
2524	undefined ->
2525	    case Type of
2526		{call,From} ->
2527		    {next_state,idle,Data,
2528		     [{reply,From,'eh?'}]};
2529		_ ->
2530		    throw(keep_state_and_data)
2531	    end;
2532	Result ->
2533	    Result
2534    end.
2535
2536connected({call,From}, {msg,Ref}, Data) ->
2537    {keep_state,Data,
2538     {reply,From,{ack,Ref}}};
2539connected(cast, {msg,From,Ref}, Data) ->
2540    From ! {ack,Ref},
2541    {keep_state,Data};
2542connected({call,From}, disconnect, Data) ->
2543    {next_state,idle,Data,
2544     [{reply,From,yes}]};
2545connected(cast, disconnect, Data) ->
2546    {next_state,idle,Data};
2547connected(cast, {ping,Pid,Tag}, Data) ->
2548    Pid ! {pong,Tag},
2549    {keep_state,Data};
2550connected(Type, Content, Data) ->
2551    case handle_common_events(Type, Content, connected, Data) of
2552	undefined ->
2553	    case Type of
2554		{call,From} ->
2555		    {keep_state,Data,
2556		     [{reply,From,'eh?'}]};
2557		_ ->
2558		    {keep_state,Data}
2559	    end;
2560	Result ->
2561	    Result
2562    end.
2563
2564state0({call,From}, stop, Data) ->
2565    {stop_and_reply,normal,[{reply,From,stopped}],Data};
2566state0(Type, Content, Data) ->
2567    case handle_common_events(Type, Content, state0, Data) of
2568	undefined ->
2569	    {keep_state,Data};
2570	Result ->
2571	    Result
2572    end.
2573
2574hiber_idle({call,From}, 'alive?', Data) ->
2575    {keep_state,Data,
2576     [{reply,From,'alive!'}]};
2577hiber_idle({call,From}, hibernate_sync, Data) ->
2578    {next_state,hiber_wakeup,Data,
2579     [{reply,From,hibernating},
2580      hibernate]};
2581hiber_idle(info, hibernate_later, _) ->
2582    Tref = erlang:start_timer(1000, self(), hibernate),
2583    {keep_state,Tref};
2584hiber_idle(info, hibernate_now, Data) ->
2585    {keep_state,Data,
2586     [hibernate]};
2587hiber_idle(info, {timeout,Tref,hibernate}, Tref) ->
2588    {keep_state,[],
2589     [hibernate]};
2590hiber_idle(cast, hibernate_async, Data) ->
2591    {next_state,hiber_wakeup,Data,
2592     [hibernate]};
2593hiber_idle(Type, Content, Data) ->
2594    case handle_common_events(Type, Content, hiber_idle, Data) of
2595	undefined ->
2596	    {keep_state,Data};
2597	Result ->
2598	    Result
2599    end.
2600
2601hiber_wakeup({call,From}, wakeup_sync, Data) ->
2602    {next_state,hiber_idle,Data,
2603     [{reply,From,good_morning}]};
2604hiber_wakeup({call,From}, snooze_sync, Data) ->
2605    {keep_state,Data,
2606     [{reply,From,please_just_five_more},
2607      hibernate]};
2608hiber_wakeup(cast, wakeup_async, Data) ->
2609    {next_state,hiber_idle,Data};
2610hiber_wakeup(cast, snooze_async, Data) ->
2611    {keep_state,Data,
2612     [hibernate]};
2613hiber_wakeup(Type, Content, Data) ->
2614    case handle_common_events(Type, Content, hiber_wakeup, Data) of
2615	undefined ->
2616	    {keep_state,Data};
2617	Result ->
2618	    Result
2619    end.
2620
2621next_events(internal, Msg, [Msg|Msgs]) ->
2622    {keep_state,Msgs};
2623next_events(Type, Content, Data) ->
2624    case handle_common_events(Type, Content, next_events, Data) of
2625	undefined ->
2626	    {keep_state,Data};
2627	Result ->
2628	    Result
2629    end.
2630
2631
2632handle_common_events({call,From}, get_callback_mode, _, _) ->
2633    {keep_state_and_data,{reply,From,state_functions}};
2634handle_common_events({call,From}, get, State, Data) ->
2635    {keep_state,Data,
2636     [{reply,From,{state,State,Data}}]};
2637handle_common_events(cast, {get,Pid}, State, Data) ->
2638    Pid ! {state,State,Data},
2639    {keep_state,Data};
2640handle_common_events({call,From}, stop, _, Data) ->
2641    {stop_and_reply,normal,[{reply,From,stopped}],Data};
2642handle_common_events(cast, stop, _, _) ->
2643    stop;
2644handle_common_events({call,From}, {stop,Reason}, _, Data) ->
2645    {stop_and_reply,Reason,{reply,From,stopped},Data};
2646handle_common_events(cast, {stop,Reason}, _, _) ->
2647    {stop,Reason};
2648handle_common_events({call,From}, 'alive?', _, Data) ->
2649    {keep_state,Data,
2650     [{reply,From,yes}]};
2651handle_common_events(cast, {'alive?',Pid}, _, Data) ->
2652    Pid ! yes,
2653    {keep_state,Data};
2654handle_common_events(_, _, _, _) ->
2655    undefined.
2656
2657handle_event({call,From}, get_callback_mode, _, _) ->
2658    {keep_state_and_data,{reply,From,handle_event_function}};
2659%% Wrapper state machine that uses a map state machine spec
2660handle_event(
2661  Type, Event, State, [Data|Machine])
2662  when is_map(Machine) ->
2663    #{State := HandleEvent} = Machine,
2664    case
2665	try HandleEvent(Type, Event, Data) of
2666	    Result ->
2667		Result
2668	catch
2669	    Result ->
2670		Result
2671	end of
2672	{stop,Reason,NewData} ->
2673	    {stop,Reason,[NewData|Machine]};
2674	{next_state,NewState,NewData} ->
2675	    {next_state,NewState,[NewData|Machine]};
2676	{next_state,NewState,NewData,Ops} ->
2677	    {next_state,NewState,[NewData|Machine],Ops};
2678	{keep_state,NewData} ->
2679	    {keep_state,[NewData|Machine]};
2680	{keep_state,NewData,Ops} ->
2681	    {keep_state,[NewData|Machine],Ops};
2682	{repeat_state,NewData} ->
2683	    {repeat_state,[NewData|Machine]};
2684	{repeat_state,NewData,Ops} ->
2685	    {repeat_state,[NewData|Machine],Ops};
2686	Other ->
2687	    Other
2688    end;
2689%%
2690%% Dispatcher to test callback_mode handle_event_function
2691%%
2692%% Wrap the state in a 1 element list just to test non-atom
2693%% states.  Note that the state from init/1 is not wrapped
2694%% so both atom and non-atom states are tested.
2695handle_event(Type, Event, State, Data) ->
2696    StateName = unwrap_state(State),
2697    try ?MODULE:StateName(Type, Event, Data) of
2698	Result ->
2699	    wrap_result(Result)
2700    catch
2701	throw:Result:Stacktrace ->
2702	    erlang:raise(
2703	      throw, wrap_result(Result), Stacktrace)
2704    end.
2705
2706unwrap_state([State]) ->
2707    State;
2708unwrap_state(State) ->
2709    State.
2710
2711wrap_result(Result) ->
2712    case Result of
2713	{next_state,NewState,NewData} ->
2714	    {next_state,[NewState],NewData};
2715	{next_state,NewState,NewData,StateOps} ->
2716	    {next_state,[NewState],NewData,StateOps};
2717	Other ->
2718	    Other
2719    end.
2720
2721
2722
2723code_change(OldVsn, State, Data, CallbackMode) ->
2724    io:format(
2725      "code_change(~p, ~p, ~p, ~p)~n", [OldVsn,State,Data,CallbackMode]),
2726    ets:insert(?MODULE, {callback_mode,CallbackMode}),
2727    io:format(
2728      "code_change(~p, ~p, ~p, ~p)~n", [OldVsn,State,Data,CallbackMode]),
2729    {ok,State,{OldVsn,Data,CallbackMode}}.
2730
2731format_status(terminate, [_Pdict,State,Data]) ->
2732    {formatted,State,Data};
2733format_status(normal, [_Pdict,_State,_Data]) ->
2734    [format_status_called].
2735
2736flush() ->
2737    receive
2738	Msg ->
2739	    [Msg|flush()]
2740    after 500 ->
2741	    []
2742    end.
2743