~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to erts/emulator/test/trace_call_time_SUITE.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2011. All Rights Reserved.
 
5
%%
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%%
 
17
%% %CopyrightEnd%
 
18
%%
 
19
 
 
20
%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
21
%%%
 
22
%%% Define to run outside of test server
 
23
%%%
 
24
%%% -define(STANDALONE,1).
 
25
%%%
 
26
%%%
 
27
%%% Define for debug output
 
28
%%%
 
29
%%% -define(debug,1).
 
30
 
 
31
-module(trace_call_time_SUITE).
 
32
 
 
33
%% Exported end user tests
 
34
 
 
35
-export([seq/3, seq_r/3]).
 
36
-export([loaded/1, a_function/1, a_called_function/1, dec/1, nif_dec/1]).
 
37
 
 
38
-define(US_ERROR, 10000).
 
39
-define(R_ERROR, 0.8).
 
40
-define(SINGLE_CALL_US_TIME, 10).
 
41
 
 
42
%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
43
%% Result examination macros
 
44
 
 
45
-define(CT(P,MFA),{trace,P,call,MFA}).
 
46
-define(CTT(P, MFA),{trace_ts,P,call,MFA,{_,_,_}}).
 
47
-define(RF(P,MFA,V),{trace,P,return_from,MFA,V}).
 
48
-define(RFT(P,MFA,V),{trace_ts,P,return_from,MFA,V,{_,_,_}}).
 
49
-define(RT(P,MFA),{trace,P,return_to,MFA}).
 
50
-define(RTT(P,MFA),{trace_ts,P,return_to,MFA,{_,_,_}}).
 
51
 
 
52
-ifdef(debug).
 
53
-define(dbgformat(A,B),io:format(A,B)).
 
54
-else.
 
55
-define(dbgformat(A,B),noop).
 
56
-endif.
 
57
 
 
58
%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
59
 
 
60
-include_lib("test_server/include/test_server.hrl").
 
61
 
 
62
%% When run in test server.
 
63
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 
64
         init_per_group/2,end_per_group/2, 
 
65
         init_per_testcase/2, end_per_testcase/2, not_run/1]).
 
66
-export([basic/1, on_and_off/1, info/1,
 
67
         pause_and_restart/1, scheduling/1, called_function/1, combo/1, 
 
68
         bif/1, nif/1]).
 
69
 
 
70
init_per_testcase(_Case, Config) ->
 
71
    ?line Dog=test_server:timetrap(test_server:seconds(400)),
 
72
    erlang:trace_pattern({'_','_','_'}, false, [local,meta,call_time,call_count]),
 
73
    erlang:trace_pattern(on_load, false, [local,meta,call_time,call_count]),
 
74
    timer:now_diff(now(),now()),
 
75
    [{watchdog, Dog}|Config].
 
76
 
 
77
end_per_testcase(_Case, Config) ->
 
78
    erlang:trace_pattern({'_','_','_'}, false, [local,meta,call_time,call_count]),
 
79
    erlang:trace_pattern(on_load, false, [local,meta,call_time,call_count]),
 
80
    erlang:trace(all, false, [all]),
 
81
    Dog=?config(watchdog, Config),
 
82
    test_server:timetrap_cancel(Dog),
 
83
    ok.
 
84
 
 
85
suite() -> [{ct_hooks,[ts_install_cth]}].
 
86
 
 
87
all() -> 
 
88
    case test_server:is_native(trace_call_time_SUITE) of
 
89
        true -> [not_run];
 
90
        false ->
 
91
            [basic, on_and_off, info, pause_and_restart, scheduling,
 
92
             combo, bif, nif, called_function]
 
93
    end.
 
94
 
 
95
groups() -> 
 
96
    [].
 
97
 
 
98
init_per_suite(Config) ->
 
99
    Config.
 
100
 
 
101
end_per_suite(_Config) ->
 
102
    ok.
 
103
 
 
104
init_per_group(_GroupName, Config) ->
 
105
    Config.
 
106
 
 
107
end_per_group(_GroupName, Config) ->
 
108
    Config.
 
109
 
 
110
 
 
111
not_run(Config) when is_list(Config) ->
 
112
    {skipped,"Native code"}.
 
113
 
 
114
basic(suite) ->
 
115
    [];
 
116
basic(doc) ->
 
117
    ["Tests basic call count trace"];
 
118
basic(Config) when is_list(Config) ->
 
119
    ?line P = erlang:trace_pattern({'_','_','_'}, false, [call_time]),
 
120
    ?line M = 1000,
 
121
    %%
 
122
    ?line 1 = erlang:trace_pattern({?MODULE,seq,  '_'}, true, [call_time]),
 
123
    ?line 2 = erlang:trace_pattern({?MODULE,seq_r,'_'}, true, [call_time]),
 
124
    ?line Pid = setup(),
 
125
    ?line {L,  T1} = execute(Pid, fun() -> seq(1, M, fun(X) -> (X+1) end) end),
 
126
    ?line ok = check_trace_info({?MODULE, seq,   3}, [{Pid, M, 0, 0}], T1),
 
127
    ?line ok = check_trace_info({?MODULE, seq_r, 3}, [], none),
 
128
 
 
129
    ?line {Lr, T2} = execute(Pid, fun() -> seq_r(1, M, fun(X) -> (X+1) end) end),
 
130
    ?line ok = check_trace_info({?MODULE, seq,   3}, [{Pid, M, 0, 0}], T1),
 
131
    ?line ok = check_trace_info({?MODULE, seq_r, 3}, [{Pid, 1, 0, 0}], T2/M),
 
132
    ?line ok = check_trace_info({?MODULE, seq_r, 4}, [{Pid, M, 0, 0}], T2),
 
133
    ?line L = lists:reverse(Lr),
 
134
 
 
135
    %%
 
136
    ?line P = erlang:trace_pattern({'_','_','_'}, false, [call_time]),
 
137
    ?line Pid ! quit,
 
138
    ok.
 
139
 
 
140
%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
141
 
 
142
 
 
143
on_and_off(suite) ->
 
144
    [];
 
145
on_and_off(doc) ->
 
146
    ["Tests turning trace parameters on and off"];
 
147
on_and_off(Config) when is_list(Config) ->
 
148
    ?line P = erlang:trace_pattern({'_','_','_'}, false, [call_time]),
 
149
    ?line M = 100,
 
150
    %%
 
151
    ?line 1 = erlang:trace_pattern({?MODULE,seq,'_'}, true, [call_time]),
 
152
    ?line Pid = setup(),
 
153
    ?line {L, T1} = execute(Pid, {?MODULE, seq, [1, M, fun(X) -> X+1 end]}),
 
154
    ?line ok = check_trace_info({?MODULE, seq, 3}, [{Pid, M, 0, 0}], T1),
 
155
 
 
156
    ?line N = erlang:trace_pattern({?MODULE,'_','_'}, true, [call_time]),
 
157
    ?line {L, T2} = execute(Pid, fun() -> seq(1, M, fun(X) -> X+1 end) end),
 
158
    ?line ok = check_trace_info({?MODULE, seq, 3}, [{Pid, M, 0, 0}], T2),
 
159
 
 
160
    ?line P = erlang:trace_pattern({'_','_','_'}, true, [call_time]),
 
161
    ?line {L, T3} = execute(Pid, fun() -> seq(1, M, fun(X) -> X+1 end) end),
 
162
    ?line ok = check_trace_info({?MODULE, seq, 3}, [{Pid, M, 0, 0}], T3),
 
163
 
 
164
    ?line 1 = erlang:trace_pattern({?MODULE,seq,'_'}, false, [call_time]),
 
165
    ?line ok = check_trace_info({?MODULE, seq, 3}, false, none),
 
166
    ?line {L, _T4} = execute(Pid, fun() -> seq(1, M, fun(X) -> X+1 end) end),
 
167
    ?line ok = check_trace_info({?MODULE, seq, 3}, false, none),
 
168
    ?line ok = check_trace_info({?MODULE, seq_r, 4}, [], none),
 
169
    ?line {Lr, T5} = execute(Pid, fun() -> seq_r(1, M, fun(X) -> X+1 end) end),
 
170
    ?line ok = check_trace_info({?MODULE, seq_r, 4}, [{Pid,M,0,0}], T5),
 
171
 
 
172
    ?line N = erlang:trace_pattern({?MODULE,'_','_'}, false, [call_time]),
 
173
    ?line ok = check_trace_info({?MODULE, seq_r, 4}, false, none),
 
174
    ?line {Lr, _T6} = execute(Pid, fun() -> seq_r(1, M, fun(X) -> X+1 end) end),
 
175
    ?line ok = check_trace_info({?MODULE, seq_r, 4}, false, none),
 
176
    ?line L = lists:reverse(Lr),
 
177
    %%
 
178
    ?line Pid ! quit,
 
179
    ?line P = erlang:trace_pattern({'_','_','_'}, false, [call_time]),
 
180
    ok.
 
181
 
 
182
%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
183
 
 
184
info(suite) ->
 
185
    [];
 
186
info(doc) ->
 
187
    ["Tests the trace_info BIF"];
 
188
info(Config) when is_list(Config) ->
 
189
    ?line P = erlang:trace_pattern({'_','_','_'}, false, [call_time]),
 
190
    %%
 
191
    ?line 1 = erlang:trace_pattern({?MODULE,seq,3}, true, [call_time]),
 
192
    ?line {call_time,[]} = erlang:trace_info({?MODULE,seq,3}, call_time),
 
193
    ?line 1 = erlang:trace_pattern({?MODULE,seq,'_'}, pause, [call_time]),
 
194
    ?line {call_time,[]} = erlang:trace_info({?MODULE,seq,3}, call_time),
 
195
    ?line {all,[_|_]=L} = erlang:trace_info({?MODULE,seq,3}, all),
 
196
    ?line {value,{call_time,[]}} = lists:keysearch(call_time, 1, L),
 
197
    ?line 1 = erlang:trace_pattern({?MODULE,seq,'_'}, restart, [call_time]),
 
198
    ?line {call_time,[]} = erlang:trace_info({?MODULE,seq,3}, call_time),
 
199
    ?line 1 = erlang:trace_pattern({?MODULE,seq,'_'}, false, [call_time]),
 
200
    ?line {call_time,false} = erlang:trace_info({?MODULE,seq,3}, call_time),
 
201
    ?line {all,false} = erlang:trace_info({?MODULE,seq,3}, all),
 
202
    %%
 
203
    ?line P = erlang:trace_pattern({'_','_','_'}, false, [call_time]),
 
204
    ok.
 
205
 
 
206
%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
207
 
 
208
pause_and_restart(suite) ->
 
209
    [];
 
210
pause_and_restart(doc) ->
 
211
    ["Tests pausing and restarting call time counters"];
 
212
pause_and_restart(Config) when is_list(Config) ->
 
213
    ?line P = erlang:trace_pattern({'_','_','_'}, false, [call_time]),
 
214
    ?line M = 100,
 
215
    ?line Pid = setup(),
 
216
    %%
 
217
    ?line 1 = erlang:trace_pattern({?MODULE,seq,'_'}, true, [call_time]),
 
218
    ?line ok = check_trace_info({?MODULE, seq, 3}, [], none),
 
219
    ?line {L, T1} = execute(Pid, fun() -> seq(1, M, fun(X) -> X+1 end) end),
 
220
    ?line ok = check_trace_info({?MODULE, seq, 3}, [{Pid,M,0,0}], T1),
 
221
    ?line 1 = erlang:trace_pattern({?MODULE,seq,'_'}, pause, [call_time]),
 
222
    ?line ok = check_trace_info({?MODULE, seq, 3}, [{Pid,M,0,0}], T1),
 
223
    ?line {L, T2} = execute(Pid, fun() -> seq(1, M, fun(X) -> X+1 end) end),
 
224
    ?line ok = check_trace_info({?MODULE, seq, 3}, [{Pid,M,0,0}], T2),
 
225
    ?line 1 = erlang:trace_pattern({?MODULE,seq,'_'}, restart, [call_time]),
 
226
    ?line ok = check_trace_info({?MODULE, seq, 3}, [], none),
 
227
    ?line {L, T3} = execute(Pid, fun() -> seq(1, M, fun(X) -> X+1 end) end),
 
228
    ?line ok = check_trace_info({?MODULE, seq, 3}, [{Pid,M,0,0}], T3),
 
229
    %%
 
230
    ?line Pid ! quit,
 
231
    ?line P = erlang:trace_pattern({'_','_','_'}, false, [call_time]),
 
232
    ok.
 
233
 
 
234
%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
235
 
 
236
scheduling(suite) ->
 
237
    [];
 
238
scheduling(doc) ->
 
239
    ["Tests in/out scheduling of call time counters"];
 
240
scheduling(Config) when is_list(Config) ->
 
241
    ?line P  = erlang:trace_pattern({'_','_','_'}, false, [call_time]),
 
242
    ?line M  = 1000000,
 
243
    ?line Np = erlang:system_info(schedulers_online),
 
244
    ?line F  = 12,
 
245
 
 
246
    %% setup load processes
 
247
    %% (single, no internal calls)
 
248
 
 
249
    ?line erlang:trace_pattern({?MODULE,loaded,1}, true, [call_time]),
 
250
 
 
251
    ?line Pids     = [setup() || _ <- lists:seq(1, F*Np)],
 
252
    ?line {_Ls,T1} = execute(Pids, {?MODULE,loaded,[M]}),
 
253
    ?line [Pid ! quit || Pid <- Pids],
 
254
 
 
255
    %% logic dictates that each process will get ~ 1/F of the schedulers time
 
256
 
 
257
    ?line {call_time, CT} = erlang:trace_info({?MODULE,loaded,1}, call_time),
 
258
 
 
259
    ?line lists:foreach(fun (Pid) ->
 
260
            ?line ok = case check_process_time(lists:keysearch(Pid, 1, CT), M, F, T1) of
 
261
                schedule_time_error ->
 
262
                    test_server:comment("Warning: Failed time ratio"),
 
263
                    ok;
 
264
                Other -> Other
 
265
            end
 
266
        end, Pids),
 
267
    ?line P  = erlang:trace_pattern({'_','_','_'}, false, [call_time]),
 
268
    ok.
 
269
 
 
270
%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
271
 
 
272
combo(suite) ->
 
273
    [];
 
274
combo(doc) ->
 
275
    ["Tests combining local call trace and meta trace with call time trace"];
 
276
combo(Config) when is_list(Config) ->
 
277
    ?line Self = self(),
 
278
    ?line Nbc = 3,
 
279
    ?line MetaMs = [{'_',[],[{return_trace}]}],
 
280
    ?line Flags = lists:sort([call, return_to]),
 
281
    ?line LocalTracer = spawn_link(fun () -> relay_n(5 + Nbc + 3, Self) end),
 
282
    ?line MetaTracer = spawn_link(fun () -> relay_n(9 + Nbc + 3, Self) end),
 
283
    ?line 2 = erlang:trace_pattern({?MODULE,seq_r,'_'}, [], [local]),
 
284
    ?line 2 = erlang:trace_pattern({?MODULE,seq_r,'_'}, true, [call_time]),
 
285
    ?line 2 = erlang:trace_pattern({?MODULE,seq_r,'_'}, MetaMs, [{meta,MetaTracer}]),
 
286
    ?line 2 = erlang:trace_pattern({?MODULE,seq_r,'_'}, true, [call_count]),
 
287
 
 
288
    % bifs
 
289
    ?line 2 = erlang:trace_pattern({erlang, term_to_binary, '_'}, [], [local]),
 
290
    ?line 2 = erlang:trace_pattern({erlang, term_to_binary, '_'}, true, [call_time]),
 
291
    ?line 2 = erlang:trace_pattern({erlang, term_to_binary, '_'}, MetaMs, [{meta,MetaTracer}]),
 
292
    %% not implemented
 
293
    %?line 2 = erlang:trace_pattern({erlang, term_to_binary, '_'}, true, [call_count]),
 
294
 
 
295
    ?line 1 = erlang:trace(Self, true, [{tracer,LocalTracer} | Flags]),
 
296
    %%
 
297
    ?line {traced,local} =
 
298
        erlang:trace_info({?MODULE,seq_r,3}, traced),
 
299
    ?line {match_spec,[]} =
 
300
        erlang:trace_info({?MODULE,seq_r,3}, match_spec),
 
301
    ?line {meta,MetaTracer} =
 
302
        erlang:trace_info({?MODULE,seq_r,3}, meta),
 
303
    ?line {meta_match_spec,MetaMs} =
 
304
        erlang:trace_info({?MODULE,seq_r,3}, meta_match_spec),
 
305
    ?line ok = check_trace_info({?MODULE, seq_r, 3}, [], none),
 
306
 
 
307
    %% check empty trace_info for ?MODULE:seq_r/3
 
308
    ?line {all,[_|_]=TraceInfo}     = erlang:trace_info({?MODULE,seq_r,3}, all),
 
309
    ?line {value,{traced,local}}    = lists:keysearch(traced, 1, TraceInfo),
 
310
    ?line {value,{match_spec,[]}}   = lists:keysearch(match_spec, 1, TraceInfo),
 
311
    ?line {value,{meta,MetaTracer}} = lists:keysearch(meta, 1, TraceInfo),
 
312
    ?line {value,{meta_match_spec,MetaMs}} = lists:keysearch(meta_match_spec, 1, TraceInfo),
 
313
    ?line {value,{call_count,0}} = lists:keysearch(call_count, 1, TraceInfo),
 
314
    ?line {value,{call_time,[]}} = lists:keysearch(call_time, 1, TraceInfo),
 
315
 
 
316
    %% check empty trace_info for erlang:term_to_binary/1
 
317
    ?line {all, [_|_] = TraceInfoBif} = erlang:trace_info({erlang, term_to_binary, 1}, all),
 
318
    ?line {value,{traced,local}}     = lists:keysearch(traced, 1, TraceInfoBif),
 
319
    ?line {value,{match_spec,[]}}    = lists:keysearch(match_spec, 1, TraceInfoBif),
 
320
    ?line {value,{meta, MetaTracer}}  = lists:keysearch(meta, 1, TraceInfoBif),
 
321
    ?line {value,{meta_match_spec,MetaMs}} = lists:keysearch(meta_match_spec, 1, TraceInfoBif),
 
322
    %% not implemented
 
323
    ?line {value,{call_count,false}} = lists:keysearch(call_count, 1, TraceInfoBif),
 
324
    %?line {value,{call_count,0}} = lists:keysearch(call_count, 1, TraceInfoBif),
 
325
    ?line {value,{call_time,[]}} = lists:keysearch(call_time, 1, TraceInfoBif),
 
326
 
 
327
    %%
 
328
    ?line [3,2,1] = seq_r(1, 3, fun(X) -> X+1 end),
 
329
    ?line T0 = now(),
 
330
    ?line with_bif(Nbc),
 
331
    ?line T1 = now(),
 
332
    ?line TimeB = timer:now_diff(T1,T0),
 
333
    %%
 
334
 
 
335
    ?line List = collect(100),
 
336
    ?line {MetaR, LocalR} =
 
337
        lists:foldl(
 
338
          fun ({P,X}, {M,L}) when P == MetaTracer ->
 
339
                  {[X|M],L};
 
340
              ({P,X}, {M,L}) when P == LocalTracer ->
 
341
                  {M,[X|L]}
 
342
          end,
 
343
          {[],[]},
 
344
          List),
 
345
    ?line Meta = lists:reverse(MetaR),
 
346
    ?line Local = lists:reverse(LocalR),
 
347
 
 
348
    ?line [?CTT(Self,{?MODULE,seq_r,[1,3,_]}),
 
349
           ?CTT(Self,{?MODULE,seq_r,[1,3,_,[]]}),
 
350
           ?CTT(Self,{?MODULE,seq_r,[2,3,_,[1]]}),
 
351
           ?CTT(Self,{?MODULE,seq_r,[3,3,_,[2,1]]}),
 
352
           ?RFT(Self,{?MODULE,seq_r,4},[3,2,1]),
 
353
           ?RFT(Self,{?MODULE,seq_r,4},[3,2,1]),
 
354
           ?RFT(Self,{?MODULE,seq_r,4},[3,2,1]),
 
355
           ?RFT(Self,{?MODULE,seq_r,3},[3,2,1]),
 
356
           ?CTT(Self,{erlang,term_to_binary,[3]}), % bif
 
357
           ?RFT(Self,{erlang,term_to_binary,1},<<131,97,3>>),
 
358
           ?CTT(Self,{erlang,term_to_binary,[2]}),
 
359
           ?RFT(Self,{erlang,term_to_binary,1},<<131,97,2>>)
 
360
        ] = Meta,
 
361
 
 
362
    ?line [?CT(Self,{?MODULE,seq_r,[1,3,_]}),
 
363
           ?CT(Self,{?MODULE,seq_r,[1,3,_,[]]}),
 
364
           ?CT(Self,{?MODULE,seq_r,[2,3,_,[1]]}),
 
365
           ?CT(Self,{?MODULE,seq_r,[3,3,_,[2,1]]}),
 
366
           ?RT(Self,{?MODULE,combo,1}),
 
367
           ?CT(Self,{erlang,term_to_binary,[3]}), % bif
 
368
           ?RT(Self,{?MODULE,with_bif,1}),
 
369
           ?CT(Self,{erlang,term_to_binary,[2]}),
 
370
           ?RT(Self,{?MODULE,with_bif,1})
 
371
        ] = Local,
 
372
 
 
373
    ?line ok = check_trace_info({?MODULE, seq_r, 3}, [{Self,1,0,0}], 1),
 
374
    ?line ok = check_trace_info({?MODULE, seq_r, 4}, [{Self,3,0,0}], 1),
 
375
    ?line ok = check_trace_info({?MODULE, seq_r, 3}, [{Self,1,0,0}], 1),
 
376
    ?line ok = check_trace_info({?MODULE, seq_r, 4}, [{Self,3,0,0}], 1),
 
377
    ?line ok = check_trace_info({erlang, term_to_binary, 1}, [{self(), Nbc - 1, 0, 0}], TimeB),
 
378
    %%
 
379
    ?line erlang:trace_pattern({'_','_','_'}, false, [local,meta,call_time]),
 
380
    ?line erlang:trace_pattern(on_load, false, [local,meta,call_time]),
 
381
    ?line erlang:trace(all, false, [all]),
 
382
    ok.
 
383
 
 
384
%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
385
 
 
386
bif(suite) ->
 
387
    [];
 
388
bif(doc) ->
 
389
    ["Tests tracing of bifs"];
 
390
bif(Config) when is_list(Config) ->
 
391
    ?line P = erlang:trace_pattern({'_','_','_'}, false, [call_time]),
 
392
    ?line M = 1000000,
 
393
    %%
 
394
    ?line 2 = erlang:trace_pattern({erlang, binary_to_term, '_'}, true, [call_time]),
 
395
    ?line 2 = erlang:trace_pattern({erlang, term_to_binary, '_'}, true, [call_time]),
 
396
    ?line Pid = setup(),
 
397
    ?line {L, T1} = execute(Pid, fun() -> with_bif(M) end),
 
398
 
 
399
    ?line ok = check_trace_info({erlang, binary_to_term, 1}, [{Pid, M - 1, 0, 0}], T1/2),
 
400
    ?line ok = check_trace_info({erlang, term_to_binary, 1}, [{Pid, M - 1, 0, 0}], T1/2),
 
401
 
 
402
    % disable term2binary
 
403
 
 
404
    ?line 2 = erlang:trace_pattern({erlang, term_to_binary, '_'}, false, [call_time]),
 
405
 
 
406
    ?line {L, T2} = execute(Pid, fun() -> with_bif(M) end),
 
407
 
 
408
    ?line ok = check_trace_info({erlang, binary_to_term, 1}, [{Pid, M*2 - 2, 0, 0}], T1/2 + T2),
 
409
    ?line ok = check_trace_info({erlang, term_to_binary, 1}, false, none),
 
410
 
 
411
    %%
 
412
    ?line P = erlang:trace_pattern({'_','_','_'}, false, [call_time]),
 
413
    ?line Pid ! quit,
 
414
    ok.
 
415
 
 
416
%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
417
 
 
418
nif(suite) ->
 
419
    [];
 
420
nif(doc) ->
 
421
    ["Tests tracing of nifs"];
 
422
nif(Config) when is_list(Config) ->
 
423
    load_nif(Config),
 
424
    ?line P = erlang:trace_pattern({'_','_','_'}, false, [call_time]),
 
425
    ?line M = 1000000,
 
426
    %%
 
427
    ?line 1 = erlang:trace_pattern({?MODULE, nif_dec,  '_'}, true, [call_time]),
 
428
    ?line 1 = erlang:trace_pattern({?MODULE, with_nif, '_'}, true, [call_time]),
 
429
    ?line Pid = setup(),
 
430
    ?line {_, T1} = execute(Pid, fun() -> with_nif(M) end),
 
431
 
 
432
    % the nif is called M - 1 times, the last time the function with 'with_nif'
 
433
    % returns ok and does not call the nif.
 
434
    ?line ok = check_trace_info({?MODULE, nif_dec,  1}, [{Pid, M-1, 0, 0}], T1/5*4),
 
435
    ?line ok = check_trace_info({?MODULE, with_nif, 1}, [{Pid, M, 0, 0}], T1/5),
 
436
 
 
437
    %%
 
438
    ?line P = erlang:trace_pattern({'_','_','_'}, false, [call_time]),
 
439
    ?line Pid ! quit,
 
440
    ok.
 
441
 
 
442
%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
443
 
 
444
called_function(suite) ->
 
445
    [];
 
446
called_function(doc) ->
 
447
    ["Tests combining nested function calls and that the time accumulates to the right function"];
 
448
called_function(Config) when is_list(Config) ->
 
449
    ?line P = erlang:trace_pattern({'_','_','_'}, false, [call_time]),
 
450
    ?line M = 2100,
 
451
    ?line Pid = setup(),
 
452
    %%
 
453
    ?line 1 = erlang:trace_pattern({?MODULE,a_function,'_'}, true, [call_time]),
 
454
    ?line {L, T1} = execute(Pid, {?MODULE, a_function, [M]}),
 
455
    ?line ok = check_trace_info({?MODULE, a_function, 1}, [{Pid, M, 0, 0}], T1),
 
456
 
 
457
    ?line 1 = erlang:trace_pattern({?MODULE,a_called_function,'_'}, true, [call_time]),
 
458
    ?line {L, T2} = execute(Pid, {?MODULE, a_function, [M]}),
 
459
    ?line ok = check_trace_info({?MODULE, a_function, 1}, [{Pid, M+M, 0, 0}], T1 + M*?SINGLE_CALL_US_TIME),
 
460
    ?line ok = check_trace_info({?MODULE, a_called_function, 1}, [{Pid, M, 0, 0}], T2),
 
461
 
 
462
 
 
463
    ?line 1 = erlang:trace_pattern({?MODULE,dec,'_'}, true, [call_time]),
 
464
    ?line {L, T3} = execute(Pid, {?MODULE, a_function, [M]}),
 
465
    ?line ok = check_trace_info({?MODULE, a_function, 1}, [{Pid, M+M+M, 0, 0}], T1 + (M+M)*?SINGLE_CALL_US_TIME),
 
466
    ?line ok = check_trace_info({?MODULE, a_called_function, 1}, [{Pid, M+M, 0, 0}], T2 + M*?SINGLE_CALL_US_TIME ),
 
467
    ?line ok = check_trace_info({?MODULE, dec, 1}, [{Pid, M, 0, 0}], T3),
 
468
 
 
469
    ?line Pid ! quit,
 
470
    ?line P = erlang:trace_pattern({'_','_','_'}, false, [call_time]),
 
471
    ok.
 
472
 
 
473
%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
474
%%% The Tests
 
475
%%%
 
476
 
 
477
%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
478
%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
479
%% Local helpers
 
480
 
 
481
 
 
482
load_nif(Config) ->
 
483
    ?line Path = ?config(data_dir, Config),
 
484
    ?line ok = erlang:load_nif(filename:join(Path,"trace_nif"), 0).
 
485
 
 
486
 
 
487
%% Stack recursive seq
 
488
seq(Stop, Stop, Succ) when is_function(Succ) ->
 
489
    [Stop];
 
490
seq(Start, Stop, Succ) when is_function(Succ) ->
 
491
    [Start | seq(Succ(Start), Stop, Succ)].
 
492
 
 
493
 
 
494
a_function(1) -> a_called_function(1);
 
495
a_function(N) when N > 1 -> a_function(a_called_function(N)).
 
496
 
 
497
a_called_function(N) -> dec(N).
 
498
 
 
499
with_bif(1) -> ok;
 
500
with_bif(N) ->
 
501
    with_bif(erlang:binary_to_term(erlang:term_to_binary(N)) - 1).
 
502
 
 
503
with_nif(0) -> error;
 
504
with_nif(1) -> ok;
 
505
with_nif(N) ->
 
506
    with_nif(?MODULE:nif_dec(N)).
 
507
 
 
508
 
 
509
nif_dec(_) -> 0.
 
510
 
 
511
dec(N) ->
 
512
    loaded(10000),
 
513
    N - 1.
 
514
 
 
515
loaded(N) when N > 1 -> loaded(N - 1);
 
516
loaded(_) -> 5.
 
517
 
 
518
 
 
519
%% Tail recursive seq, result list is reversed
 
520
seq_r(Start, Stop, Succ) when is_function(Succ) ->
 
521
    seq_r(Start, Stop, Succ, []).
 
522
 
 
523
seq_r(Stop, Stop, _, R) ->
 
524
    [Stop | R];
 
525
seq_r(Start, Stop, Succ, R) ->
 
526
    seq_r(Succ(Start), Stop, Succ, [Start | R]).
 
527
 
 
528
% Check call time tracing data and print mismatches
 
529
check_trace_info(Mfa, [{Pid, C,_,_}] = Expect, Time) ->
 
530
    case erlang:trace_info(Mfa, call_time) of
 
531
        % Time tests are somewhat problematic. We want to know if Time (EXPECTED_TIME) and S*1000000 + Us (ACTUAL_TIME)
 
532
        % is the same.
 
533
        % If the ratio EXPECTED_TIME/ACTUAL_TIME is ~ 1 or if EXPECTED_TIME - ACTUAL_TIME is near zero, the test is ok.
 
534
        {call_time,[{Pid,C,S,Us}]} when S >= 0, Us >= 0,  abs(1 - Time/(S*1000000 + Us)) < ?R_ERROR; abs(Time - S*1000000 - Us) < ?US_ERROR ->
 
535
            ok;
 
536
        {call_time,[{Pid,C,S,Us}]} ->
 
537
            Sum = S*1000000 + Us,
 
538
            io:format("Expected ~p -> {call_time, ~p (Time ~p us)}~n - got ~w s. ~w us. = ~w us. - ~w -> delta ~w (ratio ~.2f, should be 1.0)~n",
 
539
                [Mfa, Expect, Time, S, Us, Sum, Time, Sum - Time, Time/Sum]),
 
540
            time_error;
 
541
        Other ->
 
542
            io:format("Expected ~p -> {call_time, ~p (Time ~p us)}~n - got ~p~n", [ Mfa, Expect, Time, Other]),
 
543
            time_count_error
 
544
    end;
 
545
check_trace_info(Mfa, Expect, _) ->
 
546
    case erlang:trace_info(Mfa, call_time) of
 
547
        {call_time, Expect} ->
 
548
            ok;
 
549
        Other ->
 
550
            io:format("Expected ~p -> {call_time, ~p}~n - got ~p~n", [Mfa, Expect, Other]),
 
551
            result_not_expected_error
 
552
    end.
 
553
 
 
554
 
 
555
%check process time
 
556
check_process_time({value,{Pid, M, S, Us}}, M, F, Time) ->
 
557
    ?line Sum = S*1000000 + Us,
 
558
    if
 
559
        abs(1 - (F/(Time/Sum))) < ?R_ERROR ->
 
560
            ok;
 
561
        true ->
 
562
            io:format("- Pid ~p, Got ratio ~.2f, expected ratio ~w~n", [Pid, Time/Sum,F]),
 
563
            schedule_time_error
 
564
    end;
 
565
check_process_time(Other, M, _, _) ->
 
566
    io:format(" - Got ~p, expected count ~w~n", [Other, M]),
 
567
    error.
 
568
 
 
569
 
 
570
 
 
571
%% Message relay process
 
572
relay_n(0, _) ->
 
573
    ok;
 
574
relay_n(N, Dest) ->
 
575
    receive Msg ->
 
576
            Dest ! {self(), Msg},
 
577
            relay_n(N-1, Dest)
 
578
    end.
 
579
 
 
580
 
 
581
 
 
582
%% Collect received messages
 
583
collect(Time) ->
 
584
    Ref = erlang:start_timer(Time, self(), done),
 
585
    L = lists:reverse(collect([], Ref)),
 
586
    ?dbgformat("Got: ~p~n",[L]),
 
587
    L.
 
588
 
 
589
collect(A, 0) ->
 
590
    receive
 
591
        Mess ->
 
592
            collect([Mess | A], 0)
 
593
    after 0 ->
 
594
            A
 
595
    end;
 
596
collect(A, Ref) ->
 
597
    receive
 
598
        {timeout, Ref, done} ->
 
599
            collect(A, 0);
 
600
        Mess ->
 
601
            collect([Mess | A], Ref)
 
602
    end.
 
603
 
 
604
setup() ->
 
605
    Pid = spawn_link(fun() -> loop() end),
 
606
    ?line 1 = erlang:trace(Pid, true, [call]),
 
607
    Pid.
 
608
 
 
609
execute(Pids, Mfa) when is_list(Pids) ->
 
610
    T0 = now(),
 
611
    [P  ! {self(), execute, Mfa} || P <- Pids],
 
612
    As = [receive {P, answer, Answer} -> Answer end || P <- Pids],
 
613
    T1 = now(),
 
614
    {As, timer:now_diff(T1,T0)};
 
615
execute(P, Mfa) ->
 
616
    T0 = now(),
 
617
    P  ! {self(), execute, Mfa},
 
618
    A  = receive {P, answer, Answer} -> Answer end,
 
619
    T1 = now(),
 
620
    {A, timer:now_diff(T1,T0)}.
 
621
 
 
622
 
 
623
 
 
624
loop() ->
 
625
    receive
 
626
        quit ->
 
627
            ok;
 
628
        {Pid, execute, Fun } when is_function(Fun) ->
 
629
            Pid ! {self(), answer, erlang:apply(Fun, [])},
 
630
            loop();
 
631
        {Pid, execute, {M, F, A}} ->
 
632
            Pid ! {self(), answer, erlang:apply(M, F, A)},
 
633
            loop()
 
634
    end.