1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 1999-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%%% Purpose : Tests the new call_trace BIF.
21
22-module(call_trace_SUITE).
23
24-export([all/0, suite/0,
25         init_per_testcase/2,end_per_testcase/2,
26         process_specs/1,basic/1,flags/1,errors/1,pam/1,change_pam/1,
27         return_trace/1,exception_trace/1,on_load/1,deep_exception/1,
28         upgrade/1,
29         exception_nocatch/1,bit_syntax/1]).
30
31%% Helper functions.
32
33-export([bar/0,foo/0,foo/1,foo/2,expect/1,worker_foo/1,pam_foo/2,nasty/0,
34         id/1,deep/3,deep_1/3,deep_2/2,deep_3/2,deep_4/1,deep_5/1,
35         bs_sum_a/2,bs_sum_b/2]).
36
37%% Debug
38-export([abbr/1,abbr/2]).
39
40-include_lib("common_test/include/ct.hrl").
41
42-define(P, 20).
43
44suite() ->
45    [{ct_hooks,[ts_install_cth]},
46     {timetrap, {minutes, 2}}].
47
48all() ->
49    [process_specs, basic, flags, pam, change_pam,
50     upgrade,
51     return_trace, exception_trace, deep_exception,
52     exception_nocatch, bit_syntax, errors, on_load].
53
54init_per_testcase(Func, Config) when is_atom(Func), is_list(Config) ->
55    Config.
56
57end_per_testcase(_Func, _Config) ->
58    %% Reloading the module will clear all trace patterns, and
59    %% in a debug-compiled emulator run assertions of the counters
60    %% for the number of traced exported functions in this module.
61
62    c:l(?MODULE).
63
64%% Tests 'all', 'new', and 'existing' for specifying processes.
65process_specs(Config) when is_list(Config) ->
66    Tracer = start_tracer(),
67    {flags,[call]} = trace_info(self(), flags),
68    {tracer,Tracer} = trace_info(self(), tracer),
69    trace_func({?MODULE,worker_foo,1}, []),
70
71    %% Test the 'new' and 'new_processes' flags.
72
73    New = fun(Flag) ->
74                  {Work1A,Work1B} = start_and_trace(Flag, [1,2,3], A1B={3,2,1}),
75                  {flags,[]} = trace_info(Work1A, flags),
76                  {tracer,[]} = trace_info(Work1A, tracer),
77                  {tracer,Tracer} = trace_info(Work1B, tracer),
78                  {flags,[call]} = trace_info(Work1B, flags),
79                  expect({trace,Work1B,call,{?MODULE,worker_foo,[A1B]}}),
80                  unlink(Work1B),
81                  Mref = erlang:monitor(process, Work1B),
82                  exit(Work1B, kill),
83                  receive
84                      {'DOWN',Mref,_,_,_} -> ok
85                  end,
86                  undefined = trace_info(Work1B, flags),
87                  {flags,[]} = trace_info(Flag, flags),
88                  {tracer,[]} = trace_info(Flag, tracer)
89          end,
90    New(new),
91    New(new_processes),
92
93    %% Test the 'existing' and 'existing_processes' flags.
94    Existing =
95        fun(Flag) ->
96                {Work2A,_Work2B} = start_and_trace(Flag, A2A=[5,6,7], [7,6,5]),
97                expect({trace,Work2A,call,{?MODULE,worker_foo,[A2A]}})
98        end,
99    Existing(existing),
100    Existing(existing_processes),
101
102    %% Test the 'all' and 'processes' flags.
103    All =
104        fun(Flag) ->
105                   {Work3A,Work3B} = start_and_trace(Flag, A3A=[12,13], A3B=[13,12]),
106                   expect({trace,Work3A,call,{?MODULE,worker_foo,[A3A]}}),
107                   expect({trace,Work3B,call,{?MODULE,worker_foo,[A3B]}})
108        end,
109    All(all),
110    All(processes),
111
112    ok.
113
114start_and_trace(Flag, A1, A2) ->
115    W1 = start_worker(),
116    trace_pid(Flag, true, [call]),
117    W2 = start_worker(),
118    call_worker(W1, A1),
119    call_worker(W2, A2),
120    case Flag of
121        new ->
122            {flags,[call]} = trace_info(new, flags),
123            {tracer,_} = trace_info(new, tracer);
124        _Other ->
125            ok
126    end,
127    trace_pid(Flag, false, [call]),
128    {W1,W2}.
129
130start_worker() ->
131    spawn(fun worker_loop/0).
132
133call_worker(Pid, Arg) ->
134    Pid ! {self(),{call,Arg}},
135    receive
136        {result,Res} -> Res
137    after 5000 ->
138              ct:fail(no_answer_from_worker)
139    end.
140
141worker_loop() ->
142    receive
143        {From,{call,Arg}} ->
144            From ! {result,?MODULE:worker_foo(Arg)},
145            worker_loop();
146        Other ->
147            exit({unexpected_message,Other})
148    end.
149
150worker_foo(_Arg) ->
151    ok.
152
153%% Basic test of the call tracing (we trace one process).
154basic(_Config) ->
155    start_tracer(),
156    trace_info(self(), flags),
157    trace_info(self(), tracer),
158    0 = trace_func({?MODULE,no_such_function,0}, []),
159    {traced,undefined} =
160    trace_info({?MODULE,no_such_function,0}, traced),
161    {match_spec, undefined} =
162    trace_info({?MODULE,no_such_function,0}, match_spec),
163
164    %% Trace some functions...
165
166    trace_func({lists,'_','_'}, []),
167
168    %% Make sure that tracing the same functions more than once
169    %% does not cause any problems.
170    3 = trace_func({?MODULE,foo,'_'}, true),
171    3 = trace_func({?MODULE,foo,'_'}, true),
172    1 = trace_func({?MODULE,bar,0}, true),
173    1 = trace_func({?MODULE,bar,0}, true),
174    {traced,global} = trace_info({?MODULE,bar,0}, traced),
175    1 = trace_func({erlang,list_to_integer,1}, true),
176    {traced,global} = trace_info({erlang,list_to_integer,1}, traced),
177
178    %% ... and call them...
179
180    AList = [x,y,z],
181    true = lists:member(y, AList),
182    foo0 = ?MODULE:foo(),
183    4 = ?MODULE:foo(3),
184    11 = ?MODULE:foo(7, 4),
185    ok = ?MODULE:bar(),
186    42 = list_to_integer(non_literal("42")),
187
188    %% ... make sure the we got trace messages (but not for ?MODULE:expect/1).
189
190    Self = self(),
191    ?MODULE:expect({trace,Self,call,{lists,member,[y,AList]}}),
192    ?MODULE:expect({trace,Self,call,{?MODULE,foo,[]}}),
193    ?MODULE:expect({trace,Self,call,{?MODULE,foo,[3]}}),
194    ?MODULE:expect({trace,Self,call,{?MODULE,foo,[7,4]}}),
195    ?MODULE:expect({trace,Self,call,{?MODULE,bar,[]}}),
196    ?MODULE:expect({trace,Self,call,{erlang,list_to_integer,["42"]}}),
197
198    %% Turn off trace for this module and call functions...
199
200    trace_func({?MODULE,'_','_'}, false),
201    {traced,false} = trace_info({?MODULE,bar,0}, traced),
202    foo0 = ?MODULE:foo(),
203    4 = ?MODULE:foo(3),
204    11 = ?MODULE:foo(7, 4),
205    ok = ?MODULE:bar(),
206    [1,2,3,4,5,6,7,8,9,10] = lists:seq(1, 10),
207    777 = list_to_integer(non_literal("777")),
208
209    %% ... turn on all trace messages...
210
211    trace_func({'_','_','_'}, false),
212    [b,a] = lists:reverse([a,b]),
213
214    %% Read out the remaining trace messages.
215
216    ?MODULE:expect({trace,Self,call,{lists,seq,[1,10]}}),
217    ?MODULE:expect({trace,Self,call,{erlang,list_to_integer,["777"]}}),
218    receive
219        Any ->
220            ct:fail({unexpected_message,Any})
221    after 1 ->
222              ok
223    end,
224
225    %% Turn on and then off tracing on all external functions.
226    %% This might cause the emulator to crasch later if it doesn't
227    %% restore all export entries properly.
228
229    AllFuncs = trace_func({'_','_','_'}, true),
230    io:format("AllFuncs = ~p", [AllFuncs]),
231    %% Make sure that a traced, exported function can still be found.
232    true = erlang:function_exported(error_handler, undefined_function, 3),
233    AllFuncs = trace_func({'_','_','_'}, false),
234    erlang:trace_delivered(all),
235    receive
236        {trace_delivered,_,_} -> ok
237    end,
238    c:flush(),					% Print the traces messages.
239    c:flush(),					% Print the traces messages.
240
241    {traced,false} = trace_info({erlang,list_to_integer,1}, traced),
242
243    ok.
244
245non_literal(X) -> X.
246
247bar() ->
248    ok.
249
250foo() -> foo0.
251foo(X) -> X+1.
252foo(X, Y) -> X+Y.
253
254
255%% Note that the semantics that this test case verifies
256%% are not explicitly specified in the docs (what I could find in R15B).
257%% This test case was written to verify that we do not change
258%% any behaviour with the introduction of "block-free" upgrade in R16.
259%% In short: Do not refer to this test case as an authority of how it must work.
260
261%% Test tracing on module being upgraded
262upgrade(Config) when is_list(Config) ->
263    V1 = compile_version(my_upgrade_test, 1, Config),
264    V2 = compile_version(my_upgrade_test, 2, Config),
265    start_tracer(),
266    upgrade_do(V1, V2, false),
267    upgrade_do(V1, V2, true).
268
269upgrade_do(V1, V2, TraceLocalVersion) ->
270    {module,my_upgrade_test} = erlang:load_module(my_upgrade_test, V1),
271
272
273    %% Test that trace is cleared after load_module
274
275    trace_func({my_upgrade_test,'_','_'}, [], [global]),
276    case TraceLocalVersion of
277        true -> trace_func({my_upgrade_test,local_version,0}, [], [local]);
278        _ -> ok
279    end,
280    1 = my_upgrade_test:version(),
281    1 = my_upgrade_test:do_local(),
282    1 = my_upgrade_test:do_real_local(),
283    put('F1_exp', my_upgrade_test:make_fun_exp()),
284    put('F1_loc', my_upgrade_test:make_fun_local()),
285    1 = (get('F1_exp'))(),
286    1 = (get('F1_loc'))(),
287
288    Self = self(),
289    expect({trace,Self,call,{my_upgrade_test,version,[]}}),
290    expect({trace,Self,call,{my_upgrade_test,do_local,[]}}),
291    expect({trace,Self,call,{my_upgrade_test,do_real_local,[]}}),
292    case TraceLocalVersion of
293        true -> expect({trace,Self,call,{my_upgrade_test,local_version,[]}});
294        _ -> ok
295    end,
296    expect({trace,Self,call,{my_upgrade_test,make_fun_exp,[]}}),
297    expect({trace,Self,call,{my_upgrade_test,make_fun_local,[]}}),
298    expect({trace,Self,call,{my_upgrade_test,version,[]}}), % F1_exp
299    case TraceLocalVersion of
300        true -> expect({trace,Self,call,{my_upgrade_test,local_version,[]}}); % F1_loc
301        _ -> ok
302    end,
303
304    {module,my_upgrade_test} = erlang:load_module(my_upgrade_test, V2),
305    2 = my_upgrade_test:version(),
306    put('F2_exp', my_upgrade_test:make_fun_exp()),
307    put('F2_loc', my_upgrade_test:make_fun_local()),
308    2 = (get('F1_exp'))(),
309    1 = (get('F1_loc'))(),
310    2 = (get('F2_exp'))(),
311    2 = (get('F2_loc'))(),
312    expect(),
313
314    put('F1_exp', undefined),
315    put('F1_loc', undefined),
316    erlang:garbage_collect(),
317    erlang:purge_module(my_upgrade_test),
318
319    % Test that trace is cleared after delete_module
320
321    trace_func({my_upgrade_test,'_','_'}, [], [global]),
322    case TraceLocalVersion of
323        true -> trace_func({my_upgrade_test,local_version,0}, [], [local]);
324        _ -> ok
325    end,
326    2 = my_upgrade_test:version(),
327    2 = my_upgrade_test:do_local(),
328    2 = my_upgrade_test:do_real_local(),
329    2 = (get('F2_exp'))(),
330    2 = (get('F2_loc'))(),
331
332    expect({trace,Self,call,{my_upgrade_test,version,[]}}),
333    expect({trace,Self,call,{my_upgrade_test,do_local,[]}}),
334    expect({trace,Self,call,{my_upgrade_test,do_real_local,[]}}),
335    case TraceLocalVersion of
336        true -> expect({trace,Self,call,{my_upgrade_test,local_version,[]}});
337        _ -> ok
338    end,
339    expect({trace,Self,call,{my_upgrade_test,version,[]}}), % F2_exp
340    case TraceLocalVersion of
341        true -> expect({trace,Self,call,{my_upgrade_test,local_version,[]}}); % F2_loc
342        _ -> ok
343    end,
344
345    true = erlang:delete_module(my_upgrade_test),
346    {'EXIT',{undef,_}} = (catch my_upgrade_test:version()),
347    {'EXIT',{undef,_}} = (catch ((get('F2_exp'))())),
348    2 = (get('F2_loc'))(),
349    expect(),
350
351    put('F2_exp', undefined),
352    put('F2_loc', undefined),
353    erlang:garbage_collect(),
354    erlang:purge_module(my_upgrade_test),
355    ok.
356
357compile_version(Module, Version, Config) ->
358    Data = proplists:get_value(data_dir, Config),
359    File = filename:join(Data, atom_to_list(Module)),
360    {ok,Module,Bin} = compile:file(File, [{d,'VERSION',Version},
361                                          binary,report]),
362    Bin.
363
364
365
366%% Test flags (arity, timestamp) for call_trace/3.
367%% Also, test the '{tracer,Pid}' option.
368flags(_Config) ->
369    Tracer = start_tracer_loop(),
370    trace_pid(self(), true, [call,{tracer,Tracer}]),
371
372    %% Trace some functions...
373
374    trace_func({filename,'_','_'}, true),
375
376    %% ... and call them...
377
378    Self = self(),
379    filename:absname("nisse"),
380    ?MODULE:expect({trace,Self,call,{filename,absname,["nisse"]}}),
381    trace_pid(Self, true, [call,arity]),
382    filename:absname("kalle"),
383    filename:absname("kalle", "/root"),
384    ?MODULE:expect({trace,Self,call,{filename,absname,1}}),
385    ?MODULE:expect({trace,Self,call,{filename,absname,2}}),
386    trace_info(Self, flags),
387
388    %% Timestamp + arity.
389
390    flag_test(fun() ->
391                      trace_pid(Self, true, [timestamp]),
392                      "dum" = filename:basename("/abcd/dum"),
393                      Ts = expect({trace_ts,Self,call,{filename,basename,1},ts}),
394                      trace_info(Self, flags),
395                      Ts
396              end),
397
398    %% Timestamp.
399
400    AnArg = "/abcd/hejsan",
401    flag_test(fun() ->
402                      trace_pid(Self, false, [arity]),
403                      "hejsan" = filename:basename(AnArg),
404                      Ts = expect({trace_ts,Self,call,
405                                   {filename,basename,[AnArg]},ts}),
406                      trace_info(Self, flags),
407                      Ts
408              end),
409
410    %% All flags turned off.
411
412    trace_pid(Self, false, [timestamp]),
413    AnotherArg = filename:join(AnArg, "hoppsan"),
414    "hoppsan" = filename:basename(AnotherArg),
415    expect({trace,Self,call,{filename,join,[AnArg,"hoppsan"]}}),
416    expect({trace,Self,call,{filename,basename,[AnotherArg]}}),
417    trace_info(Self, flags),
418
419    ok.
420
421flag_test(Test) ->
422    Now = now(),
423    Ts = Test(),
424    case timer:now_diff(Ts, Now) of
425        Time when Time < 5*1000000 ->
426            %% Reasonable short time.
427            ok;
428        _Diff ->
429            %% Too large difference.
430            ct:fail("Now = ~p, Ts = ~p", [Now, Ts])
431    end,
432    flag_test_cpu_timestamp(Test).
433
434flag_test_cpu_timestamp(Test) ->
435    try erlang:trace(all, true, [cpu_timestamp]) of
436        _ ->
437            io:format("CPU timestamps"),
438            Ts = Test(),
439            erlang:trace(all, false, [cpu_timestamp]),
440            Origin = {0,0,0},
441            Hour = 3600*1000000,
442            case timer:now_diff(Ts, Origin) of
443                Diff when Diff < 4*Hour ->
444                    %% In the worst case, CPU timestamps count from when this
445                    %% Erlang emulator was started. The above test is a conservative
446                    %% test that all CPU timestamps should pass.
447                    ok;
448                _Time ->
449                    ct:fail("Strange CPU timestamp: ~p", [Ts])
450            end,
451            io:format("Turned off CPU timestamps")
452    catch
453        error:badarg -> ok
454    end.
455
456%% Test bad arguments for trace/3 and trace_pattern/3.
457errors(Config) when is_list(Config) ->
458    expect_badarg_pid(aaa, true, []),
459    expect_badarg_pid({pid,dum}, false, []),
460    expect_badarg_func({'_','_',1}, []),
461    expect_badarg_func({'_',gosh,1}, []),
462    expect_badarg_func({xxx,'_',2}, []),
463    expect_badarg_func({xxx,yyy,b}, glurp),
464    ok.
465
466expect_badarg_pid(What, How, Flags) ->
467    case catch erlang:trace(What, How, Flags) of
468        {'EXIT',{badarg,Where}} ->
469            io:format("trace(~p, ~p, ~p) ->\n  {'EXIT',{badarg,~p}}",
470                      [What,How,Flags,Where]),
471            ok;
472        Other ->
473            io:format("trace(~p, ~p, ~p) -> ~p",
474                      [What,How,Flags,Other]),
475            ct:fail({unexpected,Other})
476    end.
477
478expect_badarg_func(MFA, Pattern) ->
479    case catch erlang:trace_pattern(MFA, Pattern) of
480        {'EXIT',{badarg,Where}} ->
481            io:format("trace_pattern(~p, ~p) ->\n  {'EXIT',{badarg,~p}}",
482                      [MFA,Pattern,Where]),
483            ok;
484        Other ->
485            io:format("trace_pattern(~p, ~p) -> ~p",
486                      [MFA, Pattern, Other]),
487            ct:fail({unexpected,Other})
488    end.
489
490%% Basic test of PAM.
491pam(Config) when is_list(Config) ->
492    start_tracer(),
493    Self = self(),
494
495    %% Build the match program.
496    Prog1 = {[{a,tuple},'$1'],[],[]},
497    Prog2 = {[{a,bigger,tuple},'$1'],[],[{message,'$1'}]},
498    MatchProg = [Prog1,Prog2],
499    pam_trace(MatchProg),
500
501    %% Do some calls.
502    ?MODULE:pam_foo(not_a_tuple, [a,b]),
503    ?MODULE:pam_foo({a,tuple}, [a,list]),
504    ?MODULE:pam_foo([this,one,will,'not',match], dummy_arg),
505    LongList = lists:seq(1,10),
506    ?MODULE:pam_foo({a,bigger,tuple}, LongList),
507
508    %% Check that we get the correct trace messages.
509    expect({trace,Self,call,{?MODULE,pam_foo,[{a,tuple},[a,list]]}}),
510    expect({trace,Self,call,
511            {?MODULE,pam_foo,[{a,bigger,tuple},LongList]},
512            LongList}),
513
514    trace_func({?MODULE,pam_foo,'_'}, false),
515    ok.
516
517pam_trace(Prog) ->
518    1 = trace_func({?MODULE,pam_foo,'_'}, Prog),
519    {match_spec,Prog} = trace_info({?MODULE,pam_foo,2}, match_spec),
520    ok.
521
522pam_foo(A, B) ->
523    {ok,A,B}.
524
525
526%% Test changing PAM programs for a function.
527change_pam(_Config) ->
528    start_tracer(),
529    Self = self(),
530
531    %% Install the first match program.
532    %% Test using timestamp at the same time.
533
534    trace_pid(Self, true, [call,arity,timestamp]),
535    Prog1 = [{['$1','$2'],[],[{message,'$1'}]}],
536    change_pam_trace(Prog1),
537    [x,y] = lists:append(id([x]), id([y])),
538    {heap_size,_} = erlang:process_info(Self, heap_size),
539    expect({trace_ts,Self,call,{lists,append,2},[x],ts}),
540    expect({trace_ts,Self,call,{erlang,process_info,2},Self,ts}),
541
542    %% Install a new PAM program.
543
544    Prog2 = [{['$1','$2'],[],[{message,'$2'}]}],
545    change_pam_trace(Prog2),
546    [xx,yy] = lists:append(id([xx]), id([yy])),
547    {current_function,_} = erlang:process_info(Self, current_function),
548    expect({trace_ts,Self,call,{lists,append,2},[yy],ts}),
549    expect({trace_ts,Self,call,{erlang,process_info,2},current_function,ts}),
550
551    1 = trace_func({lists,append,2}, false),
552    1 = trace_func({erlang,process_info,2}, false),
553    {match_spec,false} = trace_info({lists,append,2}, match_spec),
554    {match_spec,false} = trace_info({erlang,process_info,2}, match_spec),
555
556    ok.
557
558change_pam_trace(Prog) ->
559    1 = trace_func({lists,append,2}, Prog),
560    1 = trace_func({erlang,process_info,2}, Prog),
561    {match_spec,Prog} = trace_info({lists,append,2}, match_spec),
562    {match_spec,Prog} = trace_info({erlang,process_info,2}, match_spec),
563    ok.
564
565return_trace(_Config) ->
566    X = {save,me},
567    start_tracer(),
568    Self = self(),
569
570    %% Test call and return trace and timestamp.
571
572    trace_pid(Self, true, [call,timestamp]),
573    Stupid = {pointless,tuple},
574    Prog1 = [{['$1','$2'],[],[{return_trace},{message,{Stupid}}]}],
575    1 = trace_func({lists,append,2}, Prog1),
576    1 = trace_func({erlang,process_info,2}, Prog1),
577    {match_spec,Prog1} = trace_info({lists,append,2}, match_spec),
578    {match_spec,Prog1} = trace_info({erlang,process_info,2}, match_spec),
579
580    [x,y] = lists:append(id([x]), id([y])),
581    Current = {current_function,{?MODULE,return_trace,1}},
582    Current = erlang:process_info(Self, current_function),
583    expect({trace_ts,Self,call,{lists,append,[[x],[y]]},Stupid,ts}),
584    expect({trace_ts,Self,return_from,{lists,append,2},[x,y],ts}),
585    expect({trace_ts,Self,call,{erlang,process_info,[Self,current_function]},
586            Stupid,ts}),
587    expect({trace_ts,Self,return_from,{erlang,process_info,2},Current,ts}),
588
589    %% Try catch/exit.
590
591    1 = trace_func({?MODULE,nasty,0}, [{[],[],[{return_trace},{message,false}]}]),
592    {'EXIT',good_bye} = (catch ?MODULE:nasty()),
593    1 = trace_func({?MODULE,nasty,0}, false),
594
595    %% Turn off trace.
596
597    1 = trace_func({lists,append,2}, false),
598    1 = trace_func({erlang,process_info,2}, false),
599    {match_spec,false} = trace_info({lists,append,2}, match_spec),
600    {match_spec,false} = trace_info({erlang,process_info,2}, match_spec),
601
602    %% No timestamp, no trace message for call.
603
604    trace_pid(Self, false, [timestamp]),
605    Prog2 = [{['$1','$2'],[],[{return_trace},{message,false}]},
606             {['$1'],[],[{return_trace},{message,false}]}],
607    1 = trace_func({lists,seq,2}, Prog2),
608    1 = trace_func({erlang,atom_to_list,1}, Prog2),
609    {match_spec,Prog2} = trace_info({lists,seq,2}, match_spec),
610    {match_spec,Prog2} = trace_info({erlang,atom_to_list,1}, match_spec),
611
612    lists:seq(2, 7),
613    _ = atom_to_list(non_literal(nisse)),
614    expect({trace,Self,return_from,{lists,seq,2},[2,3,4,5,6,7]}),
615    expect({trace,Self,return_from,{erlang,atom_to_list,1},"nisse"}),
616
617    %% Turn off trace.
618
619    1 = trace_func({lists,seq,2}, false),
620    1 = trace_func({erlang,atom_to_list,1}, false),
621    {match_spec,false} = trace_info({lists,seq,2}, match_spec),
622    {match_spec,false} = trace_info({erlang,atom_to_list,1}, match_spec),
623
624    {save,me} = X,
625
626    ok.
627
628nasty() ->
629    exit(good_bye).
630
631exception_trace(_Config) ->
632    X = {save,me},
633    start_tracer(),
634    Self = self(),
635
636    %% Test call and return trace and timestamp.
637
638    trace_pid(Self, true, [call,timestamp]),
639    Stupid = {pointless,tuple},
640    Prog1 = [{['$1','$2'],[],[{exception_trace},{message,{Stupid}}]}],
641    1 = trace_func({lists,append,2}, Prog1),
642    1 = trace_func({erlang,process_info,2}, Prog1),
643    {match_spec,Prog1} = trace_info({lists,append,2}, match_spec),
644    {match_spec,Prog1} =
645    trace_info({erlang,process_info,2}, match_spec),
646
647    [x,y] = lists:append(id([x]), id([y])),
648    Current = {current_function,{?MODULE,exception_trace,1}},
649    Current = erlang:process_info(Self, current_function),
650    expect({trace_ts,Self,call,{lists,append,[[x],[y]]},Stupid,ts}),
651    expect({trace_ts,Self,return_from,{lists,append,2},[x,y],ts}),
652    expect({trace_ts,Self,call,{erlang,process_info,
653                                [Self,current_function]},
654            Stupid,ts}),
655    expect({trace_ts,Self,return_from,
656            {erlang,process_info,2},Current,ts}),
657
658    %% Try catch/exit.
659
660    1 = trace_func({?MODULE,nasty,0},
661                   [{[],[],[{exception_trace},{message,false}]}]),
662    {'EXIT',good_bye} = (catch ?MODULE:nasty()),
663    expect({trace_ts,Self,exception_from,
664            {?MODULE,nasty,0},{exit,good_bye},ts}),
665    1 = trace_func({?MODULE,nasty,0}, false),
666
667    %% Turn off trace.
668
669    1 = trace_func({lists,append,2}, false),
670    1 = trace_func({erlang,process_info,2}, false),
671    {match_spec,false} = trace_info({lists,append,2}, match_spec),
672    {match_spec,false} =
673    trace_info({erlang,process_info,2}, match_spec),
674
675    %% No timestamp, no trace message for call.
676
677    trace_pid(Self, false, [timestamp]),
678    Prog2 = [{['$1','$2'],[],[{exception_trace},{message,false}]},
679             {['$1'],[],[{exception_trace},{message,false}]}],
680    1 = trace_func({lists,seq,2}, Prog2),
681    1 = trace_func({erlang,atom_to_list,1}, Prog2),
682    {match_spec,Prog2} = trace_info({lists,seq,2}, match_spec),
683    {match_spec,Prog2} =
684    trace_info({erlang,atom_to_list,1}, match_spec),
685
686    lists:seq(2, 7),
687    _ = atom_to_list(non_literal(nisse)),
688    expect({trace,Self,return_from,{lists,seq,2},[2,3,4,5,6,7]}),
689    expect({trace,Self,return_from,{erlang,atom_to_list,1},"nisse"}),
690
691    %% Turn off trace.
692
693    1 = trace_func({lists,seq,2}, false),
694    1 = trace_func({erlang,atom_to_list,1}, false),
695    {match_spec,false} = trace_info({lists,seq,2}, match_spec),
696    {match_spec,false} =
697    trace_info({erlang,atom_to_list,1}, match_spec),
698
699    expect(),
700    {save,me} = X,
701    ok.
702
703%% Test the on_load argument for trace_pattern/3.
704on_load(Config) when is_list(Config) ->
705    0 = erlang:trace_pattern(on_load, []),
706    {traced,global} = erlang:trace_info(on_load, traced),
707    {match_spec,[]} = erlang:trace_info(on_load, match_spec),
708
709    0 = erlang:trace_pattern(on_load, true, [local]),
710    {traced,local} = erlang:trace_info(on_load, traced),
711    {match_spec,[]} = erlang:trace_info(on_load, match_spec),
712
713    0 = erlang:trace_pattern(on_load, false, [local]),
714    {traced,false} = erlang:trace_info(on_load, traced),
715    {match_spec,false} = erlang:trace_info(on_load, match_spec),
716
717    Pam1 = [{[],[],[{message,false}]}],
718    0 = erlang:trace_pattern(on_load, Pam1),
719    {traced,global} = erlang:trace_info(on_load, traced),
720    {match_spec,Pam1} = erlang:trace_info(on_load, match_spec),
721
722    0 = erlang:trace_pattern(on_load, true, [local]),
723    0 = erlang:trace_pattern(on_load, false, [local]),
724
725    ok.
726
727
728
729%% Test the new exception trace.
730deep_exception(Config) when is_list(Config) ->
731    deep_exception().
732
733deep_exception() ->
734    start_tracer(),
735    Self = self(),
736    N = 200000,
737    LongImproperList = seq(1, N-1, N),
738
739    Prog = [{'_',[],[{exception_trace}]}],
740    %%    1 = trace_pid(Self, true, [call]),
741    1 = trace_func({?MODULE,deep,'_'}, Prog),
742    1 = trace_func({?MODULE,deep_1,'_'}, Prog),
743    1 = trace_func({?MODULE,deep_2,'_'}, Prog),
744    1 = trace_func({?MODULE,deep_3,'_'}, Prog),
745    1 = trace_func({?MODULE,deep_4,'_'}, Prog),
746    1 = trace_func({?MODULE,deep_5,'_'}, Prog),
747    1 = trace_func({?MODULE,id,'_'}, Prog),
748    1 = trace_func({erlang,'++','_'}, Prog),
749    1 = trace_func({erlang,exit,1}, Prog),
750    1 = trace_func({erlang,throw,1}, Prog),
751    3 = trace_func({erlang,error,'_'}, Prog),
752    1 = trace_func({lists,reverse,2}, Prog),
753
754    deep_exception(?LINE, exit, [paprika], 1,
755                   [{trace,Self,call,{erlang,exit,[paprika]}},
756                    {trace,Self,exception_from,{erlang,exit,1},
757                     {exit,paprika}}],
758                   exception_from, {exit,paprika}),
759    deep_exception(?LINE, throw, [3.14], 2,
760                   [{trace,Self,call,{erlang,throw,[3.14]}},
761                    {trace,Self,exception_from,{erlang,throw,1},
762                     {throw,3.14}}],
763                   exception_from, {throw,3.14}),
764    deep_exception(?LINE, error, [{paprika}], 3,
765                   [{trace,Self,call,{erlang,error,[{paprika}]}},
766                    {trace,Self,exception_from,{erlang,error,1},
767                     {error,{paprika}}}],
768                   exception_from, {error,{paprika}}),
769    deep_exception(?LINE, error, ["{paprika}",[]], 3,
770                   [{trace,Self,call,{erlang,error,["{paprika}",[]]}},
771                    {trace,Self,exception_from,{erlang,error,2},
772                     {error,"{paprika}"}}],
773                   exception_from, {error,"{paprika}"}),
774    deep_exception(?LINE, id, [broccoli], 4, [],
775                   return_from, broccoli),
776    deep_exception(
777      ?LINE, append, [1,2], 5,
778      [{trace,Self,call,{erlang,'++',[1,2]}},
779       {trace,Self,exception_from,{erlang,'++',2},{error,badarg}}],
780      exception_from, {error,badarg}),
781    deep_exception(?LINE, '=', [1,2], 6, [],
782                   exception_from, {error,{badmatch,2}}),
783    %%
784    io:format("== Subtest: ~w", [?LINE]),
785    try lists:reverse(LongImproperList, []) of
786        R1 -> ct:fail({returned,abbr(R1)})
787    catch error:badarg -> ok
788    end,
789    expect(fun ({trace,S,call,{lists,reverse,[L1,L2]}}, Traps)
790                 when is_list(L1), is_list(L2), S == Self ->
791                   %% Each trapping call to reverse/2 must have a corresponding
792                   %% exception_from
793                   {next, Traps + 1};
794               ({trace,S,exception_from,
795                 {lists,reverse,2},{error,badarg}}, Traps)
796                 when S == Self, Traps > 1 ->
797                   {next, Traps - 1};
798               ({trace,S,exception_from,
799                 {lists,reverse,2},{error,badarg}}, 1)
800                 when S == Self ->
801                   expected;
802               ('_', _Traps) ->
803                   {trace,Self,exception_from,
804                    {lists,reverse,2},{error,badarg}};
805               (_, _Traps) ->
806                   {unexpected,
807                    {trace,Self,exception_from,
808                     {lists,reverse,2},{error,badarg}}}
809           end, 0),
810    deep_exception(?LINE, deep_5, [1,2], 7,
811                   [{trace,Self,call,{erlang,error,[undef]}},
812                    {trace,Self,exception_from,{erlang,error,1},
813                     {error,undef}}],
814                   exception_from, {error,undef}),
815    deep_exception(?LINE, deep_5, [undef], 8,
816                   [{trace,Self,call,{?MODULE,deep_5,[undef]}},
817                    {trace,Self,exception_from,{?MODULE,deep_5,1},
818                     {error,function_clause}}],
819                   exception_from, {error,function_clause}),
820
821    %% Apply
822    %%
823    deep_exception(?LINE, apply, [erlang,error,[[mo|rot]]], 1,
824                   [{trace,Self,call,{erlang,error,[[mo|rot]]}},
825                    {trace,Self,exception_from,{erlang,error,1},
826                     {error,[mo|rot]}}],
827                   exception_from, {error,[mo|rot]}),
828    deep_exception(?LINE, apply, [erlang,error,[[mo|"rot"],[]]], 1,
829                   [{trace,Self,call,{erlang,error,[[mo|"rot"],[]]}},
830                    {trace,Self,exception_from,{erlang,error,2},
831                     {error,[mo|"rot"]}}],
832                   exception_from, {error,[mo|"rot"]}),
833    Morot = make_ref(),
834    deep_exception(?LINE, apply, [erlang,throw,[Morot]], 3,
835                   [{trace,Self,call,{erlang,throw,[Morot]}},
836                    {trace,Self,exception_from,{erlang,throw,1},
837                     {throw,Morot}}],
838                   exception_from, {throw,Morot}),
839    deep_exception(?LINE, apply, [erlang,exit,[["morot"|Morot]]], 2,
840                   [{trace,Self,call,{erlang,exit,[["morot"|Morot]]}},
841                    {trace,Self,exception_from,{erlang,exit,1},
842                     {exit,["morot"|Morot]}}],
843                   exception_from, {exit,["morot"|Morot]}),
844    deep_exception(
845      ?LINE, apply, [?MODULE,id,[spenat]], 4,
846      [{trace,Self,call,{?MODULE,id,[spenat]}},
847       {trace,Self,return_from,{?MODULE,id,1},spenat}],
848      return_from, spenat),
849    deep_exception(
850      ?LINE, apply, [erlang,'++',[1,2]], 5,
851      [{trace,Self,call,{erlang,'++',[1,2]}},
852       {trace,Self,exception_from,{erlang,'++',2},{error,badarg}}],
853      exception_from, {error,badarg}),
854    io:format("== Subtest: ~w", [?LINE]),
855    try apply(lists, reverse, [LongImproperList, []]) of
856        R2 -> ct:fail({returned,abbr(R2)})
857    catch error:badarg -> ok
858    end,
859    expect(fun ({trace,S,call,{lists,reverse,[L1,L2]}}, Traps)
860                 when is_list(L1), is_list(L2), S == Self ->
861                   %% Each trapping call to reverse/2 must have a corresponding
862                   %% exception_from
863                   {next, Traps + 1};
864               ({trace,S,exception_from,
865                 {lists,reverse,2},{error,badarg}}, Traps)
866                 when S == Self, Traps > 1 ->
867                   {next, Traps - 1};
868               ({trace,S,exception_from,
869                 {lists,reverse,2},{error,badarg}}, 1)
870                 when S == Self ->
871                   expected;
872               ('_', _Traps) ->
873                   {trace,Self,exception_from,
874                    {lists,reverse,2},{error,badarg}};
875               (_, _Traps) ->
876                   {unexpected,
877                    {trace,Self,exception_from,
878                     {lists,reverse,2},{error,badarg}}}
879           end, 0),
880    deep_exception(?LINE, apply, [?MODULE,deep_5,[1,2]], 7,
881                   [{trace,Self,call,{erlang,error,[undef]}},
882                    {trace,Self,exception_from,{erlang,error,1},
883                     {error,undef}}],
884                   exception_from, {error,undef}),
885    deep_exception(?LINE, apply, [?MODULE,deep_5,[undef]], 8,
886                   [{trace,Self,call,{?MODULE,deep_5,[undef]}},
887                    {trace,Self,exception_from,{?MODULE,deep_5,1},
888                     {error,function_clause}}],
889                   exception_from, {error,function_clause}),
890    %% Apply of fun
891    %%
892    deep_exception(?LINE, apply,
893                   [fun () ->
894                            erlang:error([{"palsternacka",3.14},17])
895                    end, []], 1,
896                   [{trace,Self,call,
897                     {erlang,error,[[{"palsternacka",3.14},17]]}},
898                    {trace,Self,exception_from,{erlang,error,1},
899                     {error,[{"palsternacka",3.14},17]}}],
900                   exception_from, {error,[{"palsternacka",3.14},17]}),
901    deep_exception(?LINE, apply,
902                   [fun () ->
903                            erlang:error(["palsternacka",17], [])
904                    end, []], 1,
905                   [{trace,Self,call,
906                     {erlang,error,[["palsternacka",17],[]]}},
907                    {trace,Self,exception_from,{erlang,error,2},
908                     {error,["palsternacka",17]}}],
909                   exception_from, {error,["palsternacka",17]}),
910    deep_exception(?LINE, apply,
911                   [fun () -> erlang:throw(Self) end, []], 2,
912                   [{trace,Self,call,{erlang,throw,[Self]}},
913                    {trace,Self,exception_from,{erlang,throw,1},
914                     {throw,Self}}],
915                   exception_from, {throw,Self}),
916    deep_exception(?LINE, apply,
917                   [fun () ->
918                            erlang:exit({1,2,3,4,[5,palsternacka]})
919                    end, []], 3,
920                   [{trace,Self,call,
921                     {erlang,exit,[{1,2,3,4,[5,palsternacka]}]}},
922                    {trace,Self,exception_from,{erlang,exit,1},
923                     {exit,{1,2,3,4,[5,palsternacka]}}}],
924                   exception_from, {exit,{1,2,3,4,[5,palsternacka]}}),
925    deep_exception(?LINE, apply,
926                   [fun () -> ?MODULE:id(bladsallad) end, []], 4,
927                   [{trace,Self,call,{?MODULE,id,[bladsallad]}},
928                    {trace,Self,return_from,{?MODULE,id,1},bladsallad}],
929                   return_from, bladsallad),
930    deep_exception(?LINE, apply,
931                   [fun (A, B) -> A ++ B end, [1,2]], 5,
932                   [{trace,Self,call,{erlang,'++',[1,2]}},
933                    {trace,Self,exception_from,
934                     {erlang,'++',2},{error,badarg}}],
935                   exception_from, {error,badarg}),
936    deep_exception(?LINE, apply, [fun (A, B) -> A = B end, [1,2]], 6,
937                   [],
938                   exception_from, {error,{badmatch,2}}),
939    io:format("== Subtest: ~w", [?LINE]),
940    try apply(fun() -> lists:reverse(LongImproperList, []) end, []) of
941        R3 -> ct:fail({returned,abbr(R3)})
942    catch error:badarg -> ok
943    end,
944    expect(fun ({trace,S,call,{lists,reverse,[L1,L2]}}, Traps)
945                 when is_list(L1), is_list(L2), S == Self ->
946                   %% Each trapping call to reverse/2 must have a corresponding
947                   %% exception_from
948                   {next, Traps + 1};
949               ({trace,S,exception_from,
950                 {lists,reverse,2},{error,badarg}}, Traps)
951                 when S == Self, Traps > 1 ->
952                   {next, Traps - 1};
953               ({trace,S,exception_from,
954                 {lists,reverse,2},{error,badarg}}, 1)
955                 when S == Self ->
956                   expected;
957               ('_', _Traps) ->
958                   {trace,Self,exception_from,
959                    {lists,reverse,2},{error,badarg}};
960               (_, _Traps) ->
961                   {unexpected,
962                    {trace,Self,exception_from,
963                     {lists,reverse,2},{error,badarg}}}
964           end, 0),
965    deep_exception(?LINE, apply,
966                   [fun () -> ?MODULE:deep_5(1,2) end, []], 7,
967                   [{trace,Self,call,{erlang,error,[undef]}},
968                    {trace,Self,exception_from,{erlang,error,1},
969                     {error,undef}}],
970                   exception_from, {error,undef}),
971    deep_exception(?LINE, apply,
972                   [fun () -> ?MODULE:deep_5(undef) end, []], 8,
973                   [{trace,Self,call,{?MODULE,deep_5,[undef]}},
974                    {trace,Self,exception_from,{?MODULE,deep_5,1},
975                     {error,function_clause}}],
976                   exception_from, {error,function_clause}),
977
978    trace_func({?MODULE,'_','_'}, false),
979    trace_func({erlang,'_','_'}, false),
980    trace_func({lists,'_','_'}, false),
981    expect(),
982    ok.
983
984
985deep_exception(Line, B, Q, N, Extra, Tag, R) ->
986    Self = self(),
987    io:format("== Subtest: ~w", [Line]),
988    Result = ?MODULE:deep(N, B, Q),
989    Result = deep_expect(Self, B, Q, N, Extra, Tag, R).
990
991deep_expect(Self, B, Q, N, Extra, Tag, R) ->
992    expect({trace,Self,call,{?MODULE,deep,[N,B,Q]}}),
993    Result = deep_expect_N(Self, B, Q, N, Extra, Tag, R),
994    expect({trace,Self,return_from,{?MODULE,deep,3},Result}),
995    Result.
996
997deep_expect_N(Self, B, Q, N, Extra, Tag, R) ->
998    deep_expect_N(Self, B, Q, N, Extra, Tag, R, N).
999
1000deep_expect_N(Self, B, Q, N, Extra, Tag, R, J) when J > 0 ->
1001    expect({trace,Self,call,{?MODULE,deep_1,[J,B,Q]}}),
1002    deep_expect_N(Self, B, Q, N, Extra, Tag, R, J-1);
1003deep_expect_N(Self, B, Q, N, Extra, Tag, R, 0) ->
1004    expect({trace,Self,call,{?MODULE,deep_2,[B,Q]}}),
1005    expect({trace,Self,call,{?MODULE,deep_3,[B,Q]}}),
1006    expect({trace,Self,return_from,{?MODULE,deep_3,2},{B,Q}}),
1007    expect({trace,Self,call,{?MODULE,deep_4,[{B,Q}]}}),
1008    expect({trace,Self,call,{?MODULE,id,[{B,Q}]}}),
1009    expect({trace,Self,return_from,{?MODULE,id,1},{B,Q}}),
1010    deep_expect_Extra(Self, N, Extra, Tag, R),
1011    expect({trace,Self,Tag,{?MODULE,deep_4,1},R}),
1012    expect({trace,Self,Tag,{?MODULE,deep_2,2},R}),
1013    deep_expect_N(Self, N, Tag, R).
1014
1015deep_expect_Extra(Self, N, [E|Es], Tag, R) ->
1016    expect(E),
1017    deep_expect_Extra(Self, N, Es, Tag, R);
1018deep_expect_Extra(_Self, _N, [], _Tag, _R) ->
1019    ok.
1020
1021deep_expect_N(Self, N, Tag, R) when N > 0 ->
1022    expect({trace,Self,Tag,{?MODULE,deep_1,3},R}),
1023    deep_expect_N(Self, N-1, Tag, R);
1024deep_expect_N(_Self, 0, return_from, R) ->
1025    {value,R};
1026deep_expect_N(_Self, 0, exception_from, R) ->
1027    R.
1028
1029
1030
1031%% Test the new exception trace.
1032exception_nocatch(Config) when is_list(Config) ->
1033    exception_nocatch().
1034
1035exception_nocatch() ->
1036    Deep4LocThrow = get_deep_4_loc({throw,[42]}),
1037    Deep4LocError = get_deep_4_loc({error,[42]}),
1038    Deep4LocBadmatch = get_deep_4_loc({'=',[a,b]}),
1039
1040    Prog = [{'_',[],[{exception_trace}]}],
1041    1 = erlang:trace_pattern({?MODULE,deep_1,'_'}, Prog),
1042    1 = erlang:trace_pattern({?MODULE,deep_2,'_'}, Prog),
1043    1 = erlang:trace_pattern({?MODULE,deep_3,'_'}, Prog),
1044    1 = erlang:trace_pattern({?MODULE,deep_4,'_'}, Prog),
1045    1 = erlang:trace_pattern({?MODULE,deep_5,'_'}, Prog),
1046    1 = erlang:trace_pattern({?MODULE,id,'_'}, Prog),
1047    1 = erlang:trace_pattern({erlang,exit,1}, Prog),
1048    1 = erlang:trace_pattern({erlang,throw,1}, Prog),
1049    3 = erlang:trace_pattern({erlang,error,'_'}, Prog),
1050    Q1 = {make_ref(),Prog},
1051    T1 =
1052    exception_nocatch(?LINE, exit, [Q1], 3,
1053                      [{trace,t1,call,{erlang,exit,[Q1]}},
1054                       {trace,t1,exception_from,{erlang,exit,1},
1055                        {exit,Q1}}],
1056                      exception_from, {exit,Q1}),
1057    expect({trace,T1,exit,Q1}),
1058    Q2 = {cake,14.125},
1059    T2 =
1060    exception_nocatch(?LINE, throw, [Q2], 2,
1061                      [{trace,t2,call,{erlang,throw,[Q2]}},
1062                       {trace,t2,exception_from,{erlang,throw,1},
1063                        {error,{nocatch,Q2}}}],
1064                      exception_from, {error,{nocatch,Q2}}),
1065    expect({trace,T2,exit,{{nocatch,Q2},[{?MODULE,deep_4,1,
1066                                          Deep4LocThrow}]}}),
1067    Q3 = {dump,[dump,{dump}]},
1068    T3 =
1069    exception_nocatch(?LINE, error, [Q3], 4,
1070                      [{trace,t3,call,{erlang,error,[Q3]}},
1071                       {trace,t3,exception_from,{erlang,error,1},
1072                        {error,Q3}}],
1073                      exception_from, {error,Q3}),
1074    expect({trace,T3,exit,{Q3,[{?MODULE,deep_4,1,Deep4LocError}]}}),
1075    T4 =
1076    exception_nocatch(?LINE, '=', [17,4711], 5, [],
1077                      exception_from, {error,{badmatch,4711}}),
1078    expect({trace,T4,exit,{{badmatch,4711},
1079                           [{?MODULE,deep_4,1,Deep4LocBadmatch}]}}),
1080    %%
1081    erlang:trace_pattern({?MODULE,'_','_'}, false),
1082    erlang:trace_pattern({erlang,'_','_'}, false),
1083    expect(),
1084    ok.
1085
1086get_deep_4_loc(Arg) ->
1087    try
1088        deep_4(Arg),
1089        ct:fail(should_not_return_to_here)
1090    catch
1091        _:_:Stk ->
1092            [{?MODULE,deep_4,1,Loc0}|_] = Stk,
1093            Loc0
1094    end.
1095
1096exception_nocatch(Line, B, Q, N, Extra, Tag, R) ->
1097    io:format("== Subtest: ~w", [Line]),
1098    Go = make_ref(),
1099    Tracee =
1100    spawn(fun () ->
1101                  receive
1102                      Go ->
1103                          deep_1(N, B, Q)
1104                  end
1105          end),
1106    1 = erlang:trace(Tracee, true, [call,return_to,procs]),
1107    Tracee ! Go,
1108    deep_expect_N(Tracee, B, Q, N-1,
1109                  [setelement(2, T, Tracee) || T <- Extra], Tag, R),
1110    Tracee.
1111
1112%% Make sure that code that uses the optimized bit syntax matching
1113%% can be traced without crashing the emulator. (Actually, it seems
1114%% that we can't trigger the bug using external call trace, but we
1115%% will keep the test case anyway.)
1116
1117bit_syntax(Config) when is_list(Config) ->
1118    start_tracer(),
1119    1 = trace_func({?MODULE,bs_sum_a,'_'}, []),
1120    1 = trace_func({?MODULE,bs_sum_b,'_'}, []),
1121
1122    6 = call_bs_sum_a(<<1,2,3>>),
1123    10 = call_bs_sum_b(<<1,2,3,4>>),
1124
1125    trace_func({?MODULE,'_','_'}, false),
1126    erlang:trace_delivered(all),
1127    receive
1128        {trace_delivered,_,_} -> ok
1129    end,
1130
1131    Self = self(),
1132    expect({trace,Self,call,{?MODULE,bs_sum_a,[<<2,3>>,1]}}),
1133    expect({trace,Self,call,{?MODULE,bs_sum_b,[1,<<2,3,4>>]}}),
1134
1135    ok.
1136
1137call_bs_sum_a(<<H,T/binary>>) ->
1138    ?MODULE:bs_sum_a(T, H).
1139
1140call_bs_sum_b(<<H,T/binary>>) ->
1141    ?MODULE:bs_sum_b(H, T).
1142
1143bs_sum_a(<<H,T/binary>>, Acc) -> bs_sum_a(T, H+Acc);
1144bs_sum_a(<<>>, Acc) -> Acc.
1145
1146bs_sum_b(Acc, <<H,T/binary>>) -> bs_sum_b(H+Acc, T);
1147bs_sum_b(Acc, <<>>) -> Acc.
1148
1149
1150
1151
1152%%% Help functions.
1153
1154expect() ->
1155    case flush() of
1156        [] -> ok;
1157        Msgs ->
1158            ct:fail({unexpected,abbr(Msgs)})
1159    end.
1160
1161expect({trace_ts,Pid,Type,MFA,Term,ts}=Message) ->
1162    receive
1163        M ->
1164            case M of
1165                {trace_ts,Pid,Type,MFA,Term,Ts}=MessageTs ->
1166                    ok = io:format("Expected and got ~p", [abbr(MessageTs)]),
1167                    Ts;
1168                _ ->
1169                    io:format("Expected ~p; got ~p", [abbr(Message),abbr(M)]),
1170                    ct:fail({unexpected,abbr([M|flush()])})
1171            end
1172    after 5000 ->
1173              io:format("Expected ~p; got nothing", [abbr(Message)]),
1174              ct:fail(no_trace_message)
1175    end;
1176expect({trace_ts,Pid,Type,MFA,ts}=Message) ->
1177    receive
1178        M ->
1179            case M of
1180                {trace_ts,Pid,Type,MFA,Ts} ->
1181                    ok = io:format("Expected and got ~p", [abbr(M)]),
1182                    Ts;
1183                _ ->
1184                    io:format("Expected ~p; got ~p", [abbr(Message),abbr(M)]),
1185                    ct:fail({unexpected,abbr([M|flush()])})
1186            end
1187    after 5000 ->
1188              io:format("Expected ~p; got nothing", [abbr(Message)]),
1189              ct:fail(no_trace_message)
1190    end;
1191expect(Validator) when is_function(Validator) ->
1192    receive
1193        M ->
1194            case Validator(M) of
1195                expected ->
1196                    ok = io:format("Expected and got ~p", [abbr(M)]);
1197                next ->
1198                    ok = io:format("Expected and got ~p", [abbr(M)]),
1199                    expect(Validator);
1200                {unexpected,Message} ->
1201                    io:format("Expected ~p; got ~p", [abbr(Message),abbr(M)]),
1202                    ct:fail({unexpected,abbr([M|flush()])})
1203            end
1204    after 5000 ->
1205              io:format("Expected ~p; got nothing", [abbr(Validator('_'))]),
1206              ct:fail(no_trace_message)
1207    end;
1208expect(Message) ->
1209    receive
1210        M ->
1211            case M of
1212                Message ->
1213                    ok = io:format("Expected and got ~p", [abbr(Message)]);
1214                Other ->
1215                    io:format("Expected ~p; got ~p",
1216                              [abbr(Message),abbr(Other)]),
1217                    ct:fail({unexpected,abbr([Other|flush()])})
1218            end
1219    after 5000 ->
1220              io:format("Expected ~p; got nothing", [abbr(Message)]),
1221              ct:fail(no_trace_message)
1222    end.
1223
1224expect(Validator, State0) when is_function(Validator) ->
1225    receive
1226        M ->
1227            case Validator(M, State0) of
1228                expected ->
1229                    ok = io:format("Expected and got ~p", [abbr(M)]);
1230                {next, State} ->
1231                    ok = io:format("Expected and got ~p", [abbr(M)]),
1232                    expect(Validator, State);
1233                {unexpected,Message} ->
1234                    io:format("Expected ~p; got ~p", [abbr(Message),abbr(M)]),
1235                    ct:fail({unexpected,abbr([M|flush()])})
1236            end
1237    after 5000 ->
1238              io:format("Expected ~p; got nothing", [abbr(Validator('_'))]),
1239              ct:fail(no_trace_message)
1240    end.
1241
1242trace_info(What, Key) ->
1243    get(tracer) ! {apply,self(),{erlang,trace_info,[What,Key]}},
1244    Res = receive
1245              {apply_result,Result} -> Result
1246          end,
1247    ok = io:format("erlang:trace_info(~p, ~p) -> ~p",
1248                   [What,Key,Res]),
1249    Res.
1250
1251trace_func(MFA, MatchSpec) ->
1252    trace_func(MFA, MatchSpec, []).
1253trace_func(MFA, MatchSpec, Flags) ->
1254    get(tracer) ! {apply,self(),{erlang,trace_pattern,[MFA, MatchSpec, Flags]}},
1255    Res = receive
1256              {apply_result,Result} -> Result
1257          end,
1258    ok = io:format("trace_pattern(~p, ~p, ~p) -> ~p", [MFA,MatchSpec,Flags,Res]),
1259    Res.
1260
1261trace_pid(Pid, On, Flags) ->
1262    get(tracer) ! {apply,self(),{erlang,trace,[Pid,On,Flags]}},
1263    Res = receive
1264              {apply_result,Result} -> Result
1265          end,
1266    ok = io:format("trace(~p, ~p, ~p) -> ~p", [Pid,On,Flags,Res]),
1267    Res.
1268
1269start_tracer() ->
1270    Self = self(),
1271    put(tracer, spawn(fun() -> tracer(Self) end)),
1272    get(tracer).
1273
1274start_tracer_loop() ->
1275    Self = self(),
1276    put(tracer, spawn(fun() -> tracer_loop(Self) end)),
1277    get(tracer).
1278
1279tracer(RelayTo) ->
1280    erlang:trace(RelayTo, true, [call]),
1281    tracer_loop(RelayTo).
1282
1283tracer_loop(RelayTo) ->
1284    receive
1285        {apply,From,{M,F,A}} ->
1286            From ! {apply_result,apply(M, F, A)},
1287            tracer_loop(RelayTo);
1288        Msg ->
1289            RelayTo ! Msg,
1290            tracer_loop(RelayTo)
1291    end.
1292
1293id(I) -> I.
1294
1295deep(N, Class, Reason) ->
1296    try ?MODULE:deep_1(N, Class, Reason) of
1297        Value -> {value,Value}
1298    catch C:R -> {C,R}
1299    end.
1300
1301deep_1(1, Class, Reason) ->
1302    ?MODULE:deep_2(Class, Reason);
1303deep_1(N, Class, Reason) when is_integer(N), N > 1 ->
1304    ?MODULE:deep_1(N-1, Class, Reason).
1305
1306deep_2(Class, Reason) ->
1307    ?MODULE:deep_4(?MODULE:deep_3(Class, Reason)).
1308
1309deep_3(Class, Reason) ->
1310    {Class,Reason}.
1311
1312deep_4(CR) ->
1313    case ?MODULE:id(CR) of
1314        {exit,[Reason]} ->
1315            erlang:exit(Reason);
1316        {throw,[Reason]} ->
1317            erlang:throw(Reason);
1318        {error,[Reason,Arglist]} ->
1319            erlang:error(Reason, Arglist);
1320        {error,[Reason]} ->
1321            erlang:error(Reason);
1322        {id,[Reason]} ->
1323            Reason;
1324        {reverse,[A,B]} ->
1325            lists:reverse(A, B);
1326        {append,[A,B]} ->
1327            A ++ B;
1328        {apply,[Fun,Args]} ->
1329            erlang:apply(Fun, Args);
1330        {apply,[M,F,Args]} ->
1331            erlang:apply(M, F, Args);
1332        {deep_5,[A,B]} ->
1333            ?MODULE:deep_5(A, B);
1334        {deep_5,[A]} ->
1335            ?MODULE:deep_5(A);
1336        {'=',[A,B]} ->
1337            A = B
1338    end.
1339
1340deep_5(A) when is_integer(A) ->
1341    A.
1342
1343flush() ->
1344    receive X ->
1345                [X|flush()]
1346    after 1000 ->
1347              []
1348    end.
1349
1350%% Abbreviate large complex terms
1351abbr(Term) ->
1352    abbr(Term, 20).
1353%%
1354abbr(Tuple, N) when is_tuple(Tuple) ->
1355    abbr_tuple(Tuple, 1, N, []);
1356abbr(List, N) when is_list(List) ->
1357    abbr_list(List, N, []);
1358abbr(Term, _) -> Term.
1359%%
1360abbr_tuple(_, _, 0, R) ->
1361    list_to_tuple(reverse(R, ['...']));
1362abbr_tuple(Tuple, J, N, R) when J =< size(Tuple) ->
1363    M = N-1,
1364    abbr_tuple(Tuple, J+1, M, [abbr(element(J, Tuple), M)|R]);
1365abbr_tuple(_, _, _, R) ->
1366    list_to_tuple(reverse(R)).
1367%%
1368abbr_list(_, 0, R) ->
1369    case io_lib:printable_list(R) of
1370        true ->
1371            reverse(R, "...");
1372        false ->
1373            reverse(R, '...')
1374    end;
1375abbr_list([H|T], N, R) ->
1376    M = N-1,
1377    abbr_list(T, M, [abbr(H, M)|R]);
1378abbr_list(T, _, R) ->
1379    reverse(R, T).
1380
1381%% Lean and mean list functions
1382
1383%% Do not build garbage
1384seq(M, N, R) when M =< N ->
1385    seq(M, N-1, [N|R]);
1386seq(_, _, R) -> R.
1387
1388%% lists:reverse cannot be called since it is traced
1389reverse(L) ->
1390    reverse(L, []).
1391%%
1392reverse([], R) -> R;
1393reverse([H|T], R) ->
1394    reverse(T, [H|R]).
1395