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