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

« back to all changes in this revision

Viewing changes to lib/tools/test/fprof_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 2001-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
-module(fprof_SUITE).
 
20
 
 
21
-include_lib("test_server/include/test_server.hrl").
 
22
 
 
23
%% Test server framework exports
 
24
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 
25
         init_per_group/2,end_per_group/2, not_run/1]).
 
26
 
 
27
%% Test suites
 
28
-export([stack_seq/1, tail_seq/1, create_file_slow/1, spawn_simple/1,
 
29
         imm_tail_seq/1, imm_create_file_slow/1, imm_compile/1,
 
30
         cpu_create_file_slow/1]).
 
31
 
 
32
%% Other exports
 
33
-export([create_file_slow/2]).
 
34
 
 
35
 
 
36
%% Debug exports
 
37
-export([parse/1, verify/2]).
 
38
-export([spawn_simple_test/3]).
 
39
 
 
40
 
 
41
-define(line_trace,true).
 
42
 
 
43
%-define(debug,true).
 
44
-ifdef(debug).
 
45
-define(dbg(Str,Args), io:format(Str,Args)).
 
46
-else.
 
47
-define(dbg(Str,Args), ok).
 
48
-endif.
 
49
 
 
50
 
 
51
 
 
52
%%%---------------------------------------------------------------------
 
53
%%% Test suites
 
54
%%%---------------------------------------------------------------------
 
55
 
 
56
 
 
57
 
 
58
suite() -> [{ct_hooks,[ts_install_cth]}].
 
59
 
 
60
all() -> 
 
61
    case test_server:is_native(fprof_SUITE) of
 
62
        true -> [not_run];
 
63
        false ->
 
64
            [stack_seq, tail_seq, create_file_slow, spawn_simple,
 
65
             imm_tail_seq, imm_create_file_slow, imm_compile,
 
66
             cpu_create_file_slow]
 
67
    end.
 
68
 
 
69
groups() -> 
 
70
    [].
 
71
 
 
72
init_per_suite(Config) ->
 
73
    Config.
 
74
 
 
75
end_per_suite(_Config) ->
 
76
    ok.
 
77
 
 
78
init_per_group(_GroupName, Config) ->
 
79
    Config.
 
80
 
 
81
end_per_group(_GroupName, Config) ->
 
82
    Config.
 
83
 
 
84
 
 
85
not_run(Config) when is_list(Config) ->
 
86
    {skipped, "Native code"}.
 
87
 
 
88
%%%---------------------------------------------------------------------
 
89
 
 
90
stack_seq(doc) ->
 
91
    ["Tests a stack recursive variant of lists:seq/3"];
 
92
stack_seq(suite) ->
 
93
    [];
 
94
stack_seq(Config) when is_list(Config) ->
 
95
    ?line Timetrap = ?t:timetrap(?t:seconds(20)),
 
96
    ?line PrivDir = ?config(priv_dir, Config),
 
97
    ?line TraceFile = 
 
98
        filename:join(PrivDir, ?MODULE_STRING"_stack_seq.trace"),
 
99
    ?line AnalysisFile = 
 
100
        filename:join(PrivDir, ?MODULE_STRING"_stack_seq.analysis"),
 
101
    ?line Start = 1,
 
102
    ?line Stop = 1000,
 
103
    ?line Succ = fun (X) -> X + 1 end,
 
104
    ?line ok = fprof:stop(kill),
 
105
    %%
 
106
    ?line TS0 = erlang:now(),
 
107
    ?line R0 = fprof:apply(fun seq/3, [Start, Stop, Succ], [{file, TraceFile}]),
 
108
    ?line TS1 = erlang:now(),
 
109
    ?line R = seq(Start, Stop, Succ),
 
110
    ?line TS2 = erlang:now(),
 
111
    ?line ok = fprof:profile(file, TraceFile),
 
112
    ?line ok = fprof:analyse(),
 
113
    ?line ok = fprof:analyse(dest, AnalysisFile),
 
114
    ?line ok = fprof:stop(),
 
115
    ?line R = R0,
 
116
    %%
 
117
    ?line {ok, [T, P]} = parse(AnalysisFile),
 
118
    ?line io:format("~p~n~n~p~n", [P, ets:tab2list(T)]),
 
119
    ?line ok = (catch verify(T, P)),
 
120
    ?line Proc = pid_to_list(self()),
 
121
    ?line case P of
 
122
              [{analysis_options, _},
 
123
               [{totals, _, Acc, _}],
 
124
               [{Proc, _, undefined, _} | _]] ->
 
125
                  ok
 
126
          end,
 
127
    %%
 
128
    ?line check_own_and_acc(TraceFile,AnalysisFile),
 
129
    %%
 
130
    ?line ets:delete(T),
 
131
    ?line file:delete(TraceFile),
 
132
    ?line file:delete(AnalysisFile),
 
133
    ?line ?t:timetrap_cancel(Timetrap),
 
134
    ?line Acc1 = ts_sub(TS1, TS0),
 
135
    ?line Acc2 = ts_sub(TS2, TS1),
 
136
    ?line io:format("ts:~w, fprof:~w, bare:~w.~n", [Acc, Acc1, Acc2]),
 
137
    {comment, io_lib:format("~p times slower", [Acc1/Acc2])}.
 
138
 
 
139
%%%---------------------------------------------------------------------
 
140
 
 
141
tail_seq(doc) ->
 
142
    ["Tests a tail recursive variant of lists:seq/3"];
 
143
tail_seq(suite) ->
 
144
    [];
 
145
tail_seq(Config) when is_list(Config) ->
 
146
    ?line Timetrap = ?t:timetrap(?t:seconds(10)),
 
147
    ?line PrivDir = ?config(priv_dir, Config),
 
148
    ?line TraceFile = 
 
149
        filename:join(PrivDir, ?MODULE_STRING"_tail_seq.trace"),
 
150
    ?line AnalysisFile = 
 
151
        filename:join(PrivDir, ?MODULE_STRING"_tail_seq.analysis"),
 
152
    ?line Start = 1,
 
153
    ?line Stop = 1000,
 
154
    ?line Succ = fun (X) -> X + 1 end,
 
155
    ?line ok = fprof:stop(kill),
 
156
    %%
 
157
    ?line TS0 = erlang:now(),
 
158
    ?line R = seq_r(Start, Stop, Succ),
 
159
    ?line TS1 = erlang:now(),
 
160
    %%
 
161
    ?line R1 = fprof:apply(fun seq_r/3, [Start, Stop, Succ], 
 
162
                          [{file, TraceFile}]),
 
163
    ?line TS2 = erlang:now(),
 
164
    ?line ok = fprof:profile([{file,TraceFile}]),
 
165
    ?line ok = fprof:analyse(),
 
166
    ?line ok = fprof:analyse(dest, AnalysisFile),
 
167
    ?line ok = fprof:stop(),
 
168
    ?line R = R1,
 
169
    %%
 
170
    ?line {ok, [T, P]} = parse(AnalysisFile),
 
171
    ?line io:format("~p~n~n~p~n", [P, ets:tab2list(T)]),
 
172
    ?line ok = verify(T, P),
 
173
    ?line Proc = pid_to_list(self()),
 
174
    ?line case P of
 
175
              [{analysis_options, _},
 
176
               [{totals, _, Acc, _}],
 
177
               [{Proc, _, undefined, _} | _]] ->
 
178
                  ok
 
179
          end,
 
180
    %%
 
181
    ?line check_own_and_acc(TraceFile,AnalysisFile),
 
182
    %%
 
183
    ?line ets:delete(T),
 
184
    ?line file:delete(TraceFile),
 
185
    ?line file:delete(AnalysisFile),
 
186
    ?line ?t:timetrap_cancel(Timetrap),
 
187
    ?line Acc1 = ts_sub(TS1, TS0),
 
188
    ?line Acc2 = ts_sub(TS2, TS1),
 
189
    ?line io:format("ts:~w, fprof:~w, bare:~w.~n", [Acc, Acc2, Acc1]),
 
190
    {comment, io_lib:format("~p times slower", [Acc2/Acc1])}.
 
191
 
 
192
%%%---------------------------------------------------------------------
 
193
 
 
194
create_file_slow(doc) ->
 
195
    ["Tests the create_file_slow benchmark"];
 
196
create_file_slow(suite) ->
 
197
    [];
 
198
create_file_slow(Config) when is_list(Config) ->
 
199
    ?line Timetrap = ?t:timetrap(?t:seconds(40)),
 
200
    ?line PrivDir = ?config(priv_dir, Config),
 
201
    ?line TraceFile = 
 
202
        filename:join(PrivDir, ?MODULE_STRING"_create_file_slow.trace"),
 
203
    ?line AnalysisFile = 
 
204
        filename:join(PrivDir, ?MODULE_STRING"_create_file_slow.analysis"),
 
205
    ?line DataFile = 
 
206
        filename:join(PrivDir, ?MODULE_STRING"_create_file_slow.data"),
 
207
    ?line ok = fprof:stop(kill),
 
208
    %%
 
209
    ?line TS0 = erlang:now(),
 
210
    ?line ok = create_file_slow(DataFile, 1024),
 
211
    ?line TS1 = erlang:now(),
 
212
    %%
 
213
    ?line ok = file:delete(DataFile),
 
214
    ?line TS2 = erlang:now(),
 
215
    ?line ok = fprof:apply(?MODULE, create_file_slow, [DataFile, 1024], 
 
216
                           [{file, TraceFile}]),
 
217
    ?line TS3 = erlang:now(),
 
218
    ?line ok = fprof:profile(file, TraceFile),
 
219
    ?line ok = fprof:analyse(),
 
220
    ?line ok = fprof:analyse(dest, AnalysisFile),
 
221
    ?line ok = fprof:stop(),
 
222
    %%
 
223
    ?line {ok, [T, P]} = parse(AnalysisFile),
 
224
    ?line io:format("~p~n~n~p~n", [P, ets:tab2list(T)]),
 
225
    ?line ok = verify(T, P),
 
226
    ?line Proc = pid_to_list(self()),
 
227
    ?line case P of
 
228
              [{analysis_options, _},
 
229
               [{totals, _, Acc, _}],
 
230
               [{Proc, _, undefined, _} | _]] ->
 
231
                  ok
 
232
          end,
 
233
    %%
 
234
    ?line check_own_and_acc(TraceFile,AnalysisFile),
 
235
    %%
 
236
    ?line ets:delete(T),
 
237
    ?line file:delete(DataFile),
 
238
    ?line file:delete(TraceFile),
 
239
    ?line file:delete(AnalysisFile),
 
240
    ?line ?t:timetrap_cancel(Timetrap),
 
241
    ?line Acc1 = ts_sub(TS1, TS0),
 
242
    ?line Acc3 = ts_sub(TS3, TS2),
 
243
    ?line io:format("ts:~w, fprof:~w, bare:~w.~n", [Acc, Acc3, Acc1]),
 
244
    {comment, io_lib:format("~p times slower", [Acc3/Acc1])}.
 
245
 
 
246
 
 
247
 
 
248
%%%---------------------------------------------------------------------
 
249
 
 
250
spawn_simple(doc) ->
 
251
    ["Tests process spawn"];
 
252
spawn_simple(suite) ->
 
253
    [];
 
254
spawn_simple(Config) when is_list(Config) ->
 
255
    ?line Timetrap = ?t:timetrap(?t:seconds(30)),
 
256
    ?line PrivDir = ?config(priv_dir, Config),
 
257
    ?line TraceFile = 
 
258
        filename:join(PrivDir, ?MODULE_STRING"_spawn_simple.trace"),
 
259
    ?line AnalysisFile = 
 
260
        filename:join(PrivDir, ?MODULE_STRING"_spawn_simple.analysis"),
 
261
    ?line Start = 1,
 
262
    ?line Stop = 1000,
 
263
    ?line Succ = fun (X) -> X + 1 end,
 
264
    ?line ok = fprof:stop(kill),
 
265
    %%
 
266
    ?line TS0 = erlang:now(),
 
267
    ?line {{_, R1}, {_, R2}} = spawn_simple_test(Start, Stop, Succ),
 
268
    ?line TS1 = erlang:now(),
 
269
    %%
 
270
    ?line ok = fprof:trace(start, TraceFile),
 
271
    ?line {{P1, R3}, {P2, R4}} = spawn_simple_test(Start, Stop, Succ),
 
272
    ?line ok = fprof:trace(stop),
 
273
    ?line TS2 = erlang:now(),
 
274
    ?line ok = fprof:profile(file, TraceFile),
 
275
    ?line ok = fprof:analyse(),
 
276
    ?line ok = fprof:analyse(dest, AnalysisFile),
 
277
    ?line ok = fprof:stop(),
 
278
    ?line R1 = R3,
 
279
    ?line R2 = R4,
 
280
    %%
 
281
    ?line {ok, [T, P]} = parse(AnalysisFile),
 
282
    ?line io:format("~p~n~n~p~n", [P, ets:tab2list(T)]),
 
283
    ?line ok = verify(T, P),
 
284
    ?line Proc1 = pid_to_list(P1),
 
285
    ?line Proc2 = pid_to_list(P2),
 
286
    ?line Proc0 = pid_to_list(self()),
 
287
    ?line io:format("~p~n ~p ~p ~p~n", [P, Proc0, Proc1, Proc2]),
 
288
    ?line [{analysis_options, _}, [{totals, _, Acc, _}] | Procs] = P,
 
289
    ?line [[{Proc0, _, undefined, _} | _]] = 
 
290
        lists:filter(fun ([Pt | _]) when element(1, Pt) == Proc0 -> true;
 
291
                         (_) -> false
 
292
                     end, Procs),
 
293
    ?line [[{Proc1, _, undefined, _},
 
294
            {spawned_by, Proc0},
 
295
            {spawned_as, {erlang, apply, ["#Fun"++_, []]}},
 
296
            {initial_calls, [{erlang, apply, 2}, 
 
297
                             {?MODULE, '-spawn_simple_test/3-fun-0-', 4}]} 
 
298
            | _]] = 
 
299
        lists:filter(fun ([Pt | _]) when element(1, Pt) == Proc1 -> true;
 
300
                         (_) -> false
 
301
                     end, Procs),
 
302
    ?line [[{Proc2, _, undefined, _},
 
303
            {spawned_by, Proc0},
 
304
            {spawned_as, {erlang, apply, ["#Fun"++_, []]}},
 
305
            {initial_calls, [{erlang, apply, 2}, 
 
306
                             {?MODULE, '-spawn_simple_test/3-fun-1-', 4}]} 
 
307
            | _]] = 
 
308
        lists:filter(fun ([Pt | _]) when element(1, Pt) == Proc2 -> true;
 
309
                         (_) -> false
 
310
                     end, Procs),
 
311
    ?line 3 = length(Procs),
 
312
    ?line R1 = lists:reverse(R2),
 
313
    %%
 
314
    ?line check_own_and_acc(TraceFile,AnalysisFile),
 
315
    %%
 
316
    ?line ets:delete(T),
 
317
    ?line file:delete(TraceFile),
 
318
    ?line file:delete(AnalysisFile),
 
319
    ?line ?t:timetrap_cancel(Timetrap),
 
320
    ?line Acc1 = ts_sub(TS1, TS0),
 
321
    ?line Acc2 = ts_sub(TS2, TS1),
 
322
    ?line io:format("ts:~w, fprof:~w, bare:~w.~n", [Acc, Acc2, Acc1]),
 
323
    {comment, io_lib:format("~p times slower", [Acc2/Acc1])}.
 
324
 
 
325
 
 
326
spawn_simple_test(Start, Stop, Succ) ->
 
327
    Parent = self(),
 
328
    Seq = 
 
329
        spawn_link(
 
330
          fun () ->
 
331
                  Parent ! {self(), seq(Start, Stop, Succ)}
 
332
          end),
 
333
    SeqR = 
 
334
        spawn_link(
 
335
          fun () ->
 
336
                  Parent ! {self(), seq_r(Start, Stop, Succ)}
 
337
          end),
 
338
    receive {Seq, SeqResult} ->
 
339
            receive {SeqR, SeqRResult} ->
 
340
                    {{Seq, SeqResult}, {SeqR, SeqRResult}}
 
341
            end
 
342
    end.
 
343
 
 
344
 
 
345
 
 
346
%%%---------------------------------------------------------------------
 
347
 
 
348
imm_tail_seq(doc) ->
 
349
    ["Tests a tail recursive variant of lists:seq/3 ",
 
350
     "with immediate trace to profile"];
 
351
imm_tail_seq(suite) ->
 
352
    [];
 
353
imm_tail_seq(Config) when is_list(Config) ->
 
354
    ?line Timetrap = ?t:timetrap(?t:seconds(10)),
 
355
    ?line PrivDir = ?config(priv_dir, Config),
 
356
    ?line AnalysisFile = 
 
357
        filename:join(PrivDir, ?MODULE_STRING"_imm_tail_seq.analysis"),
 
358
    ?line Start = 1,
 
359
    ?line Stop = 1000,
 
360
    ?line Succ = fun (X) -> X + 1 end,
 
361
    ?line ok = fprof:stop(kill),
 
362
    ?line catch eprof:stop(),
 
363
    %%
 
364
    ?line TS0 = erlang:now(),
 
365
    ?line R0 = seq_r(Start, Stop, Succ),
 
366
    ?line TS1 = erlang:now(),
 
367
    %%
 
368
    ?line profiling = eprof:start_profiling([self()]),
 
369
    ?line TS2 = erlang:now(),
 
370
    ?line R2 = seq_r(Start, Stop, Succ),
 
371
    ?line TS3 = erlang:now(),
 
372
    ?line profiling_stopped = eprof:stop_profiling(),
 
373
    ?line R2 = R0,
 
374
    %%
 
375
    ?line eprof:analyze(),
 
376
    ?line stopped = eprof:stop(),
 
377
    %%
 
378
    ?line {ok, Tracer} = fprof:profile(start),
 
379
    ?line ok = fprof:trace([start, {tracer, Tracer}]),
 
380
    ?line TS4 = erlang:now(),
 
381
    ?line R4 = seq_r(Start, Stop, Succ),
 
382
    ?line TS5 = erlang:now(),
 
383
    ?line ok = fprof:trace(stop),
 
384
    ?line ok = fprof:analyse(),
 
385
    ?line ok = fprof:analyse(dest, AnalysisFile),
 
386
    ?line ok = fprof:stop(),
 
387
    ?line R4 = R0,
 
388
    %%
 
389
    ?line {ok, [T, P]} = parse(AnalysisFile),
 
390
    ?line io:format("~p~n~n~p~n", [P, ets:tab2list(T)]),
 
391
    ?line ok = verify(T, P),
 
392
    ?line Proc = pid_to_list(self()),
 
393
    ?line case P of
 
394
              [{analysis_options, _},
 
395
               [{totals, _, Acc, _}],
 
396
               [{Proc, _, undefined, _} | _]] ->
 
397
                  ok
 
398
          end,
 
399
    %%
 
400
    ?line ets:delete(T),
 
401
    ?line file:delete(AnalysisFile),
 
402
    ?line ?t:timetrap_cancel(Timetrap),
 
403
    ?line Acc1 = ts_sub(TS1, TS0),
 
404
    ?line Acc3 = ts_sub(TS3, TS2),
 
405
    ?line Acc5 = ts_sub(TS5, TS4),
 
406
    ?line io:format("~p (plain), ~p (eprof), ~p (fprof), ~p (cpu)~n", 
 
407
                    [Acc1/1000, Acc3/1000, Acc5/1000, Acc/1000]),
 
408
    {comment, io_lib:format("~p/~p (fprof/eprof) times slower", 
 
409
                            [Acc5/Acc1, Acc3/Acc1])}.
 
410
 
 
411
%%%---------------------------------------------------------------------
 
412
 
 
413
imm_create_file_slow(doc) ->
 
414
    ["Tests a tail recursive variant of lists:seq/3 ",
 
415
     "with immediate trace to profile"];
 
416
imm_create_file_slow(suite) ->
 
417
    [];
 
418
imm_create_file_slow(Config) when is_list(Config) ->
 
419
    ?line Timetrap = ?t:timetrap(?t:seconds(60)),
 
420
    ?line PrivDir = ?config(priv_dir, Config),
 
421
    ?line DataFile = 
 
422
        filename:join(PrivDir, ?MODULE_STRING"_imm_create_file_slow.data"),
 
423
    ?line AnalysisFile = 
 
424
        filename:join(PrivDir, ?MODULE_STRING"_imm_create_file_slow.analysis"),
 
425
    ?line ok = fprof:stop(kill),
 
426
    %%
 
427
    ?line TS0 = erlang:now(),
 
428
    ?line ok = create_file_slow(DataFile, 1024),
 
429
    ?line TS1 = erlang:now(),
 
430
    ?line ok = file:delete(DataFile),
 
431
    %%
 
432
    ?line {ok, Tracer} = fprof:profile(start),
 
433
    ?line TS2 = erlang:now(),
 
434
    ?line ok = fprof:apply(?MODULE, create_file_slow, [DataFile, 1024], 
 
435
                          [{tracer, Tracer}, continue]),
 
436
    ?line TS3 = erlang:now(),
 
437
    ?line ok = fprof:profile(stop),
 
438
    ?line ok = fprof:analyse(),
 
439
    ?line ok = fprof:analyse(dest, AnalysisFile),
 
440
    ?line ok = fprof:stop(),
 
441
    %%
 
442
    ?line {ok, [T, P]} = parse(AnalysisFile),
 
443
    ?line io:format("~p~n~n~p~n", [P, ets:tab2list(T)]),
 
444
    ?line ok = verify(T, P),
 
445
    ?line Proc = pid_to_list(self()),
 
446
    ?line case P of
 
447
              [{analysis_options, _},
 
448
               [{totals, _, Acc, _}],
 
449
               [{Proc, _, undefined, _} | _]] ->
 
450
                  ok
 
451
          end,
 
452
    %%
 
453
    ?line ets:delete(T),
 
454
    ?line file:delete(DataFile),
 
455
    ?line file:delete(AnalysisFile),
 
456
    ?line ?t:timetrap_cancel(Timetrap),
 
457
    ?line Acc1 = ts_sub(TS1, TS0),
 
458
    ?line Acc3 = ts_sub(TS3, TS2),
 
459
    ?line io:format("ts:~w, fprof:~w, bare:~w.~n", [Acc, Acc3, Acc1]),
 
460
    {comment, io_lib:format("~p times slower", [Acc3/Acc1])}.
 
461
 
 
462
%%%---------------------------------------------------------------------
 
463
 
 
464
imm_compile(doc) ->
 
465
    ["Tests to compile a small source file ",
 
466
     "with immediate trace to profile"];
 
467
imm_compile(suite) ->
 
468
    [];
 
469
imm_compile(Config) when is_list(Config) ->
 
470
    ?line Timetrap = ?t:timetrap(?t:minutes(20)),
 
471
    ?line DataDir = ?config(data_dir, Config),
 
472
    ?line SourceFile = filename:join(DataDir, "foo.erl"),
 
473
    ?line PrivDir = ?config(priv_dir, Config),
 
474
    ?line AnalysisFile = 
 
475
        filename:join(PrivDir, ?MODULE_STRING"_imm_compile.analysis"),
 
476
    ?line ok = fprof:stop(kill),
 
477
    ?line catch eprof:stop(),
 
478
    %%
 
479
    ?line {ok, foo, _} = compile:file(SourceFile, [binary]),
 
480
    ?line TS0 = erlang:now(),
 
481
    ?line {ok, foo, _} = compile:file(SourceFile, [binary]),
 
482
    ?line TS1 = erlang:now(),
 
483
    %%
 
484
    ?line profiling = eprof:start_profiling([self()]),
 
485
    ?line TS2 = erlang:now(),
 
486
    ?line {ok, foo, _} = compile:file(SourceFile, [binary]),
 
487
    ?line TS3 = erlang:now(),
 
488
    ?line profiling_stopped = eprof:stop_profiling(),
 
489
    %%
 
490
    ?line eprof:analyze(),
 
491
    ?line stopped = eprof:stop(),
 
492
    %%
 
493
    ?line {ok, Tracer} = fprof:profile(start),
 
494
    ?line ok = fprof:trace([start, {tracer, Tracer}]),
 
495
    ?line TS4 = erlang:now(),
 
496
    ?line {ok, foo, _} = compile:file(SourceFile, [binary]),
 
497
    ?line TS5 = erlang:now(),
 
498
    ?line ok = fprof:trace(stop),
 
499
    %%
 
500
    ?line io:format("Analysing...~n"),
 
501
    ?line ok = fprof:analyse(dest, AnalysisFile),
 
502
    ?line ok = fprof:stop(),
 
503
    %%
 
504
    ?line {ok, [T, P]} = parse(AnalysisFile),
 
505
    ?line io:format("~p~n", [P]),
 
506
    ?line Acc1 = ts_sub(TS1, TS0),
 
507
    ?line Acc3 = ts_sub(TS3, TS2),
 
508
    ?line Acc5 = ts_sub(TS5, TS4),
 
509
    ?line io:format("Verifying...~n"),
 
510
    ?line ok = verify(T, P),
 
511
    ?line case P of
 
512
              [{analysis_options, _},
 
513
               [{totals, _, Acc, _}] | _] ->
 
514
                  ok
 
515
          end,
 
516
    %%
 
517
    ?line ets:delete(T),
 
518
    ?line file:delete(AnalysisFile),
 
519
    ?line ?t:timetrap_cancel(Timetrap),
 
520
    ?line io:format("~p (plain), ~p (eprof), ~p (fprof), ~p(cpu)~n", 
 
521
                    [Acc1/1000, Acc3/1000, Acc5/1000, Acc/1000]),
 
522
    {comment, io_lib:format("~p/~p (fprof/eprof) times slower", 
 
523
                            [Acc5/Acc1, Acc3/Acc1])}.
 
524
 
 
525
%%%---------------------------------------------------------------------
 
526
 
 
527
cpu_create_file_slow(doc) ->
 
528
    ["Tests the create_file_slow benchmark using cpu_time"];
 
529
cpu_create_file_slow(suite) ->
 
530
    [];
 
531
cpu_create_file_slow(Config) when is_list(Config) ->
 
532
    ?line Timetrap = ?t:timetrap(?t:seconds(40)),
 
533
    ?line PrivDir = ?config(priv_dir, Config),
 
534
    ?line TraceFile = 
 
535
        filename:join(PrivDir, ?MODULE_STRING"_cpu_create_file_slow.trace"),
 
536
    ?line AnalysisFile = 
 
537
        filename:join(PrivDir, ?MODULE_STRING"_cpu_create_file_slow.analysis"),
 
538
    ?line DataFile = 
 
539
        filename:join(PrivDir, ?MODULE_STRING"_cpu_create_file_slow.data"),
 
540
    ?line ok = fprof:stop(kill),
 
541
    %%
 
542
    ?line TS0 = erlang:now(),
 
543
    ?line Result = (catch fprof:apply(?MODULE, create_file_slow, 
 
544
                                      [DataFile, 1024], 
 
545
                                      [{file, TraceFile}, cpu_time])),
 
546
    ?line TS1 = erlang:now(),
 
547
    ?line TestResult = 
 
548
        case Result of 
 
549
            ok ->
 
550
                ?line ok = fprof:profile(file, TraceFile),
 
551
                ?line ok = fprof:analyse(),
 
552
                ?line ok = fprof:analyse(dest, AnalysisFile),
 
553
                ?line ok = fprof:stop(),
 
554
                %%
 
555
                ?line {ok, [T, P]} = parse(AnalysisFile),
 
556
                ?line io:format("~p~n~n~p~n", [P, ets:tab2list(T)]),
 
557
                ?line ok = verify(T, P),
 
558
                ?line Proc = pid_to_list(self()),
 
559
                ?line case P of
 
560
                          [{analysis_options, _},
 
561
                           [{totals, _, Acc, _}],
 
562
                           [{Proc, _, undefined, _} | _]] ->
 
563
                              ok
 
564
                      end,
 
565
                %%
 
566
                ?line check_own_and_acc(TraceFile,AnalysisFile),
 
567
                %%
 
568
                ?line ets:delete(T),
 
569
                ?line file:delete(DataFile),
 
570
                ?line file:delete(TraceFile),
 
571
                ?line file:delete(AnalysisFile),
 
572
                ?line Acc1 = ts_sub(TS1, TS0),
 
573
                ?line io:format("cpu_ts:~w, fprof:~w~n", [Acc, Acc1]),
 
574
                {comment, io_lib:format("~p% cpu utilization", 
 
575
                                        [100*Acc/Acc1])};
 
576
            {'EXIT', not_supported} -> 
 
577
                case {os:type(), os:version()} of
 
578
                    {{unix, sunos}, {Major, Minor, _}}
 
579
                    when Major >= 5, Minor >= 7 ->
 
580
                        test_server:fail(Result);
 
581
                    _ ->
 
582
                        {skipped, "not_supported"}
 
583
                end;
 
584
            _ ->
 
585
                test_server:fail(Result)
 
586
        end,
 
587
    ?line ?t:timetrap_cancel(Timetrap),
 
588
    TestResult.
 
589
 
 
590
 
 
591
 
 
592
%%%---------------------------------------------------------------------
 
593
%%% Functions to test
 
594
%%%---------------------------------------------------------------------
 
595
 
 
596
 
 
597
 
 
598
%% Stack recursive seq
 
599
seq(Stop, Stop, Succ) when is_function(Succ) ->
 
600
    [Stop];
 
601
seq(Start, Stop, Succ) when is_function(Succ) ->
 
602
    [Start | seq(Succ(Start), Stop, Succ)].
 
603
 
 
604
 
 
605
 
 
606
%% Tail recursive seq, result list is reversed
 
607
seq_r(Start, Stop, Succ) when is_function(Succ) ->
 
608
    seq_r(Start, Stop, Succ, []).
 
609
 
 
610
seq_r(Stop, Stop, _, R) ->
 
611
    [Stop | R];
 
612
seq_r(Start, Stop, Succ, R) ->
 
613
    seq_r(Succ(Start), Stop, Succ, [Start | R]).
 
614
 
 
615
 
 
616
 
 
617
create_file_slow(Name, N) when is_integer(N), N >= 0 ->
 
618
    {ok, FD} = 
 
619
        file:open(Name, [raw, write, delayed_write, binary]),
 
620
    if N > 256 ->
 
621
            ok = file:write(FD, 
 
622
                            lists:map(fun (X) -> <<X:32/unsigned>> end,
 
623
                            lists:seq(0, 255))),
 
624
            ok = create_file_slow(FD, 256, N);
 
625
       true ->
 
626
            ok = create_file_slow(FD, 0, N)
 
627
    end,
 
628
    ok = file:close(FD).
 
629
 
 
630
create_file_slow(_FD, M, M) ->
 
631
    ok;
 
632
create_file_slow(FD, M, N) ->
 
633
    ok = file:write(FD, <<M:32/unsigned>>),
 
634
    create_file_slow(FD, M+1, N).
 
635
 
 
636
 
 
637
 
 
638
%%%---------------------------------------------------------------------
 
639
%%% Profile verification functions
 
640
%%%---------------------------------------------------------------------
 
641
 
 
642
 
 
643
 
 
644
verify(Tab, [{analysis_options, _},
 
645
             [{totals, Cnt, Acc, Own} | _] | Processes]) ->
 
646
    Processes_1 = 
 
647
        lists:map(
 
648
          fun ([{Proc, Cnt_P, undefined, Own_P} | _]) ->
 
649
                  case sum_process(Tab, Proc) of
 
650
                      {Proc, Cnt_P, Acc_P, Own_P} = Clocks 
 
651
                      when Acc_P >= Own_P ->
 
652
                          Clocks;
 
653
                      Weird ->
 
654
                          throw({error, [?MODULE, ?LINE, Weird]})
 
655
                  end
 
656
          end,
 
657
          Processes),
 
658
    case lists:foldl(
 
659
           fun ({_, Cnt_P2, Acc_P2, Own_P2}, 
 
660
                {totals, Cnt_T, Acc_T, Own_T}) ->
 
661
                   {totals, Cnt_P2+Cnt_T, Acc_P2+Acc_T, Own_P2+Own_T}
 
662
           end,
 
663
           {totals, 0, 0, 0},
 
664
           Processes_1) of
 
665
        {totals, Cnt, Acc_T, Own} when Acc_T >= Acc ->
 
666
            ok;
 
667
        Weird ->
 
668
            throw({error, [?MODULE, ?LINE, Weird]})
 
669
    end.
 
670
          
 
671
 
 
672
 
 
673
sum_process(Tab, Proc) ->
 
674
    ets_select_fold(
 
675
      Tab, [{{{Proc, '_'}, '_'}, [], ['$_']}], 100,
 
676
      fun ({{P, MFA}, {Callers, {MFA, Cnt, Acc, Own}, Called}},
 
677
           {P, Cnt_P, Acc_P, Own_P}) when P == Proc ->
 
678
              ok = verify_callers(Tab, Proc, MFA, Callers),
 
679
              ok = verify_called(Tab, Proc, MFA, Called),
 
680
              {P, Cnt+Cnt_P, Acc+Acc_P, Own+Own_P};
 
681
          (Weird, Clocks) ->
 
682
              throw({error, [?MODULE, ?LINE, Weird, Clocks]})
 
683
      end,
 
684
      {Proc, 0, 0, 0}).
 
685
 
 
686
verify_callers(_, _, _, []) ->
 
687
    ok;
 
688
verify_callers(Tab, Proc, MFA, [{Caller, Cnt, Acc, Own} | Tail]) ->
 
689
    Id = {Proc, Caller},
 
690
    case ets:lookup(Tab, Id) of
 
691
        [{Id, {_, {Caller, _, _, _}, Called}}] ->
 
692
            case lists:keysearch(MFA, 1, Called) of
 
693
                {value, {MFA, Cnt, Acc, Own}} ->
 
694
                    verify_callers(Tab, Proc, MFA, Tail);
 
695
                false ->
 
696
                    throw({error, [?MODULE, ?LINE, MFA, Id]})
 
697
            end;
 
698
        Weird ->
 
699
            throw({error, [?MODULE, ?LINE, Weird]})
 
700
    end.
 
701
              
 
702
verify_called(_, _, _, []) ->
 
703
    ok;
 
704
verify_called(Tab, Proc, MFA, [{Called, Cnt, Acc, Own} | Tail]) ->
 
705
    Id = {Proc, Called},
 
706
    case ets:lookup(Tab, Id) of
 
707
        [{Id, {Callers, {Called, _, _, _}, _}}] ->
 
708
            case lists:keysearch(MFA, 1, Callers) of
 
709
                {value, {MFA, Cnt, Acc, Own}} ->
 
710
                    verify_called(Tab, Proc, MFA, Tail);
 
711
                false ->
 
712
                    throw({error, [?MODULE, ?LINE, MFA, Id]})
 
713
            end;
 
714
        Weird ->
 
715
            throw({error, [?MODULE, ?LINE, Weird]})
 
716
    end.
 
717
 
 
718
 
 
719
 
 
720
%% Parse a analysis file and return an Ets table with all function entries, 
 
721
%% and a list of process entries. Checks the concistency of the function
 
722
%% entries when they are read.
 
723
parse(Filename) ->
 
724
    case file:open(Filename, [read]) of
 
725
        {ok, FD} ->
 
726
            Result = parse_stream(FD),
 
727
            file:close(FD),
 
728
            Result;
 
729
        Error ->
 
730
            Error
 
731
    end.
 
732
 
 
733
parse_stream(FD) ->
 
734
    Tab = ets:new(fprof_SUITE, []),
 
735
    parse_stream(FD, Tab, [], void).
 
736
 
 
737
parse_stream(FD, Tab, R, Proc) ->
 
738
    case catch io:read(FD, '') of
 
739
        {'EXIT', _} ->
 
740
            {error, [?MODULE, ?LINE]};
 
741
        {ok, Term} ->
 
742
            case parse_term(Term) of
 
743
                {ok, {analysis_options, _} = Term_1}
 
744
                when Proc == void ->
 
745
                    parse_stream(FD, Tab, [Term_1 | R], analysis_options);
 
746
                {ok, [{totals, _, _, _} | _] = Term_1}
 
747
                when Proc == analysis_options ->
 
748
                    parse_stream(FD, Tab, [Term_1 | R], totals);
 
749
                {ok, [{P, _, _, _} | _] = Term_1} ->
 
750
                    parse_stream(FD, Tab, [Term_1 | R], P);
 
751
                {ok, {_Callers, {MFA, _, _, _}, _Called} = Term_1} 
 
752
                when Proc == totals; is_list(Proc) ->
 
753
                    ets:insert(Tab, {{Proc, MFA}, Term_1}),
 
754
                    parse_stream(FD, Tab, R, Proc);
 
755
                {ok, Term_1} ->
 
756
                    {error, [?MODULE, ?LINE, Term_1]};
 
757
                E ->
 
758
                    E
 
759
            end;
 
760
        eof ->
 
761
            {ok, [Tab, lists:reverse(R)]};
 
762
        Error ->
 
763
            Error
 
764
    end.
 
765
 
 
766
parse_term({Callers, Func, Called})
 
767
  when is_list(Callers), is_list(Called) ->
 
768
    Callers_1 = lists:map(fun parse_clocks/1, Callers),
 
769
    Func_1 = parse_clocks(Func),
 
770
    Called_1 = lists:map(fun parse_clocks/1, Called),
 
771
    Result = {Callers_1, Func_1, Called_1},
 
772
    case chk_invariant(Result) of
 
773
        ok ->
 
774
            {ok, Result};
 
775
        Error ->
 
776
            Error
 
777
    end;
 
778
parse_term([{_, _, _, _} = Clocks | Tail]) ->
 
779
    {ok, [parse_clocks(Clocks) | Tail]};
 
780
parse_term(Term) ->
 
781
    {ok, Term}.
 
782
 
 
783
parse_clocks({MFA, Cnt, undefined, Own}) ->
 
784
    {MFA, Cnt, undefined, round(Own*1000)};
 
785
parse_clocks({MFA, Cnt, Acc, Own}) ->
 
786
    {MFA, Cnt, round(Acc*1000), round(Own*1000)};
 
787
parse_clocks(Clocks) ->
 
788
    Clocks.
 
789
 
 
790
 
 
791
 
 
792
chk_invariant({Callers, {MFA, Cnt, Acc, Own}, Called} = Term) ->
 
793
    {_, Callers_Cnt, Callers_Acc, Callers_Own} = Callers_Sum = sum(Callers),
 
794
%    {_, Called_Cnt, Called_Acc, Called_Own} = Called_Sum = sum(Called),
 
795
    case {MFA, 
 
796
          lists:keymember(suspend, 1, Callers),
 
797
          lists:keymember(garbage_collect, 1, Callers),
 
798
          Called} of
 
799
        {suspend, false, _, []} ->
 
800
            ok;
 
801
        {suspend, _, _, _} = Weird ->
 
802
            {error, [?MODULE, ?LINE, Weird, Term]};
 
803
        {garbage_collect, false, false, []} ->
 
804
            ok;
 
805
        {garbage_collect, false, false, [{suspend, _, _, _}]} ->
 
806
            ok;
 
807
        {garbage_collect, _, _, _} = Weird ->
 
808
            {error, [?MODULE, ?LINE, Weird, Term]};
 
809
        {undefined, false, false, _} 
 
810
        when Callers == [], Cnt == 0, Acc == 0, Own == 0 ->
 
811
            ok;
 
812
        {undefined, _, _, _} = Weird ->
 
813
            {error, [?MODULE, ?LINE, Weird, Term]};
 
814
        {_, _, _, _} ->
 
815
            case chk_self_call(Term) of
 
816
                true when Callers_Cnt /= Cnt; Callers_Acc /= Acc; 
 
817
                          Callers_Own /= Own ->
 
818
                    {error, [?MODULE, ?LINE, Callers_Sum, Term]};
 
819
%               true when Called_Acc + Own /= Acc ->
 
820
%                   io:format("WARNING: ~p:~p, ~p, ~p.~n",
 
821
%                             [?MODULE, ?LINE, Term, Called_Sum]),
 
822
%                   {error, [?MODULE, ?LINE, Term, Called_Sum]};
 
823
%                   ok;
 
824
                true ->
 
825
                    ok;
 
826
                false ->
 
827
                    {error, [?MODULE, ?LINE, Term]}
 
828
            end
 
829
    end.
 
830
 
 
831
ts_sub({A, B, C}, {A0, B0, C0}) ->
 
832
    ((A - A0)*1000000000000 + (B - B0))*1000000 + C - C0.
 
833
 
 
834
sum(Funcs) ->
 
835
    {sum, _Cnt, _Acc, _Own} = 
 
836
        lists:foldl(
 
837
          fun ({_, C1, A1, O1}, {sum, C2, A2, O2}) ->
 
838
                  {sum, C1+C2, A1+A2, O1+O2}
 
839
          end,
 
840
          {sum, 0, 0, 0},
 
841
          Funcs).
 
842
 
 
843
chk_self_call({Callers, {MFA, _Cnt, _Acc, _Own}, Called}) ->
 
844
    case lists:keysearch(MFA, 1, Callers) of
 
845
        false ->
 
846
            true;
 
847
        {value, {MFA, C, 0, O}} ->
 
848
            case lists:keysearch(MFA, 1, Called) of
 
849
                false ->
 
850
                    false;
 
851
                {value, {MFA, C, 0, O}} ->
 
852
                    true;
 
853
                {value, _} ->
 
854
                    false
 
855
            end;
 
856
        {value, _} ->
 
857
            false
 
858
    end.
 
859
 
 
860
 
 
861
 
 
862
%%%---------------------------------------------------------------------
 
863
%%% Fairly generic support functions
 
864
%%%---------------------------------------------------------------------
 
865
 
 
866
 
 
867
ets_select_fold(Table, MatchSpec, Limit, Fun, Acc) ->
 
868
    ets:safe_fixtable(Table, true),
 
869
    ets_select_fold_1(ets:select(Table, MatchSpec, Limit), Fun, Acc).
 
870
 
 
871
ets_select_fold_1('$end_of_table', _, Acc) ->
 
872
    Acc;
 
873
ets_select_fold_1({Matches, Continuation}, Fun, Acc) ->
 
874
    ets_select_fold_1(ets:select(Continuation), 
 
875
                      Fun, 
 
876
                      lists:foldl(Fun, Acc, Matches)).
 
877
 
 
878
 
 
879
 
 
880
% ets_select_foreach(Table, MatchSpec, Limit, Fun) ->
 
881
%     ets:safe_fixtable(Table, true),
 
882
%     ets_select_foreach_1(ets:select(Table, MatchSpec, Limit), Fun).
 
883
 
 
884
% ets_select_foreach_1('$end_of_table', _) ->
 
885
%     ok;
 
886
% ets_select_foreach_1({Matches, Continuation}, Fun) ->
 
887
%     lists:foreach(Fun, Matches),
 
888
%     ets_select_foreach_1(ets:select(Continuation), Fun).
 
889
 
 
890
 
 
891
%%%---------------------------------------------------------------------
 
892
%%% Simple smulation of fprof used for checking own and acc times for
 
893
%%% each function.
 
894
%%% The function 'undefined' is ignored
 
895
%%%---------------------------------------------------------------------
 
896
 
 
897
%% check_own_and_acc_traced(TraceFile, AnalysisFile) ->
 
898
%%     check_own_and_acc(TraceFile, AnalysisFile, fun handle_trace_traced/2).
 
899
 
 
900
check_own_and_acc(TraceFile, AnalysisFile) ->
 
901
    check_own_and_acc(TraceFile, AnalysisFile, fun handle_trace/2).
 
902
 
 
903
check_own_and_acc(TraceFile, AnalysisFile, HandlerFun) ->
 
904
    dbg:trace_client(file,TraceFile,{HandlerFun,{init,self()}}),
 
905
    receive {result,Result} -> 
 
906
            compare(Result,get_own_and_acc_from_analysis(AnalysisFile))
 
907
    end.
 
908
 
 
909
%% handle_trace_traced(Trace, Msg) ->
 
910
%%     io:format("handle_trace_traced(~p, ~p).", [Trace, Msg]),
 
911
%%     handle_trace(Trace, Msg).
 
912
 
 
913
handle_trace(Trace,{init,Parent}) ->
 
914
    ?dbg("~p",[start]),
 
915
    ets:new(fprof_verify_tab,[named_table]),
 
916
    handle_trace(Trace,Parent);
 
917
handle_trace({trace_ts,Pid,in,MFA,TS},P) ->
 
918
    ?dbg("~p",[{{in,Pid,MFA},get(Pid)}]),
 
919
    case get(Pid) of
 
920
        [suspend|[suspend|_]=NewStack] ->
 
921
            T = ts_sub(TS,get({Pid,last_ts})),
 
922
            update_acc(Pid,NewStack,T),
 
923
            put(Pid,NewStack);
 
924
        [suspend|NewStack] = Stack ->
 
925
            T = ts_sub(TS,get({Pid,last_ts})),
 
926
            update_acc(Pid,Stack,T),
 
927
            put(Pid,NewStack);
 
928
        [] ->
 
929
            put(Pid,[MFA]),
 
930
            insert(Pid,MFA);
 
931
        undefined ->
 
932
            put(first_ts,TS),
 
933
            put(Pid,[MFA]),
 
934
            insert(Pid,MFA)
 
935
    end,
 
936
    put({Pid,last_ts},TS),
 
937
    P;
 
938
handle_trace({trace_ts,Pid,out,_MfaOrZero,TS},P) ->
 
939
    ?dbg("~p",[{{out,Pid,_MfaOrZero},get(Pid)}]),
 
940
    T = ts_sub(TS,get({Pid,last_ts})),
 
941
    case get(Pid) of
 
942
        [suspend|S] = Stack ->
 
943
            update_acc(Pid,S,T),
 
944
            put(Pid,[suspend|Stack]);
 
945
        [MFA|_] = Stack ->
 
946
            insert(Pid,suspend),
 
947
            update_own(Pid,MFA,T),
 
948
            update_acc(Pid,Stack,T),
 
949
            put(Pid,[suspend|Stack]);
 
950
        [] ->
 
951
            insert(Pid,suspend),
 
952
            put(Pid,[suspend])
 
953
    end,
 
954
    put({Pid,last_ts},TS),
 
955
    P;
 
956
handle_trace({trace_ts,Pid,call,MFA,{cp,Caller},TS},P) ->
 
957
    ?dbg("~p",[{{call,Pid,MFA},get(Pid)}]),
 
958
    T = ts_sub(TS,get({Pid,last_ts})),
 
959
    case get(Pid) of
 
960
        [MFA|_] = Stack ->
 
961
            %% recursive
 
962
            update_own(Pid,MFA,T),
 
963
            update_acc(Pid,Stack,T);
 
964
        [CallingMFA|_] = Stack when Caller==undefined ->
 
965
            insert(Pid,MFA),
 
966
            update_own(Pid,CallingMFA,T),
 
967
            update_acc(Pid,Stack,T),
 
968
            put(Pid,[MFA|Stack]);
 
969
        [] when Caller==undefined ->
 
970
            insert(Pid,MFA),
 
971
            insert(Pid,MFA),
 
972
            put(Pid,[MFA]);
 
973
         Stack0 ->
 
974
            Stack = [CallingMFA|_] = insert_caller(Caller,Stack0,[]),
 
975
            insert(Pid,MFA),
 
976
            insert(Pid,Caller),
 
977
            update_own(Pid,CallingMFA,T),
 
978
            update_acc(Pid,Stack,T),
 
979
            put(Pid,[MFA|Stack])
 
980
    end,
 
981
    put({Pid,last_ts},TS),
 
982
    P;
 
983
handle_trace({trace_ts,Pid,return_to,MFA,TS},P) ->
 
984
    ?dbg("~p",[{{return_to,Pid,MFA},get(Pid)}]),
 
985
    T = ts_sub(TS,get({Pid,last_ts})),
 
986
    case get(Pid) of
 
987
        [MFA|_] = Stack ->
 
988
            %% recursive
 
989
            update_own(Pid,MFA,T),
 
990
            update_acc(Pid,Stack,T),
 
991
            put(Pid,Stack);
 
992
        [ReturnFromMFA,MFA|RestOfStack] = Stack ->
 
993
            update_own(Pid,ReturnFromMFA,T),
 
994
            update_acc(Pid,Stack,T),
 
995
            put(Pid,[MFA|RestOfStack]);
 
996
        [ReturnFromMFA|RestOfStack] = Stack ->
 
997
            update_own(Pid,ReturnFromMFA,T),
 
998
            update_acc(Pid,Stack,T),
 
999
            case find_return_to(MFA,RestOfStack) of
 
1000
                [] when MFA==undefined -> 
 
1001
                    put(Pid,[]);
 
1002
                [] -> 
 
1003
                    insert(Pid,MFA),
 
1004
                    put(Pid,[MFA]);
 
1005
                NewStack ->
 
1006
                    put(Pid,NewStack)
 
1007
            end
 
1008
    end,
 
1009
    put({Pid,last_ts},TS),
 
1010
    P;
 
1011
handle_trace({trace_ts,Pid,gc_start,_,TS},P) ->
 
1012
    ?dbg("~p",[{{gc_start,Pid},get(Pid)}]),
 
1013
    case get(Pid) of
 
1014
        [suspend|_] = Stack ->
 
1015
            T = ts_sub(TS,get({Pid,last_ts})),
 
1016
            insert(Pid,garbage_collect),
 
1017
            update_acc(Pid,Stack,T),
 
1018
            put(Pid,[garbage_collect|Stack]);
 
1019
        [CallingMFA|_] = Stack ->
 
1020
            T = ts_sub(TS,get({Pid,last_ts})),
 
1021
            insert(Pid,garbage_collect),
 
1022
            update_own(Pid,CallingMFA,T),
 
1023
            update_acc(Pid,Stack,T),
 
1024
            put(Pid,[garbage_collect|Stack]);
 
1025
        undefined ->
 
1026
            put(first_ts,TS),
 
1027
            put(Pid,[garbage_collect]),
 
1028
            insert(Pid,garbage_collect)
 
1029
    end,
 
1030
    put({Pid,last_ts},TS),
 
1031
    P;
 
1032
handle_trace({trace_ts,Pid,gc_end,_,TS},P) ->
 
1033
    ?dbg("~p",[{{gc_end,Pid},get(Pid)}]),
 
1034
    T = ts_sub(TS,get({Pid,last_ts})),
 
1035
    case get(Pid) of
 
1036
        [garbage_collect|RestOfStack] = Stack ->
 
1037
            update_own(Pid,garbage_collect,T),
 
1038
            update_acc(Pid,Stack,T),
 
1039
            put(Pid,RestOfStack)
 
1040
    end,
 
1041
    put({Pid,last_ts},TS),
 
1042
    P;
 
1043
handle_trace({trace_ts,Pid,spawn,NewPid,{M,F,Args},TS},P) ->
 
1044
    MFA = {M,F,length(Args)},
 
1045
    ?dbg("~p",[{{spawn,Pid,NewPid,MFA},get(Pid)}]),
 
1046
    T = ts_sub(TS,get({Pid,last_ts})),
 
1047
    put({NewPid,last_ts},TS),
 
1048
    put(NewPid,[suspend,MFA]),
 
1049
    insert(NewPid,suspend),
 
1050
    insert(NewPid,MFA),
 
1051
    case get(Pid) of
 
1052
        [SpawningMFA|_] = Stack ->
 
1053
            update_own(Pid,SpawningMFA,T),
 
1054
            update_acc(Pid,Stack,T)
 
1055
    end,
 
1056
    put({Pid,last_ts},TS),
 
1057
    P;
 
1058
handle_trace({trace_ts,Pid,exit,_Reason,TS},P) ->
 
1059
    ?dbg("~p",[{{exit,Pid,_Reason},get(Pid)}]),
 
1060
    T = ts_sub(TS,get({Pid,last_ts})),
 
1061
    case get(Pid) of
 
1062
        [DyingMFA|_] = Stack ->
 
1063
            update_own(Pid,DyingMFA,T),
 
1064
            update_acc(Pid,Stack,T),
 
1065
            put(Pid,[]);
 
1066
        [] ->
 
1067
            ok
 
1068
    end,
 
1069
    put({Pid,last_ts},TS),
 
1070
    P;
 
1071
handle_trace({trace_ts,_,Link,_,_},P) 
 
1072
  when Link==link;
 
1073
       Link==unlink;
 
1074
       Link==getting_linked;
 
1075
       Link==getting_unlinked ->
 
1076
    P;
 
1077
handle_trace(end_of_trace,P) ->
 
1078
    ?dbg("~p",['end']),
 
1079
    Result = ets:tab2list(fprof_verify_tab),
 
1080
    {TotOwn,ProcOwns} = get_proc_owns(Result,[],0),
 
1081
    TotAcc = ts_sub(get_last_ts(),get(first_ts)),
 
1082
    P ! {result,[{totals,TotAcc,TotOwn}|ProcOwns]++Result},
 
1083
    P;
 
1084
handle_trace(Other,_P) ->
 
1085
    exit({unexpected,Other}).
 
1086
 
 
1087
find_return_to(MFA,[MFA|_]=Stack) ->
 
1088
    Stack;
 
1089
find_return_to(MFA,[_|Stack]) ->
 
1090
    find_return_to(MFA,Stack);
 
1091
find_return_to(_MFA,[]) ->
 
1092
    [].
 
1093
 
 
1094
insert_caller(MFA,[MFA|Rest],Result) ->
 
1095
    lists:reverse(Result)++[MFA|Rest];
 
1096
insert_caller(MFA,[Other|Rest],Result) ->
 
1097
    insert_caller(MFA,Rest,[Other|Result]);
 
1098
insert_caller(MFA,[],Result) ->
 
1099
    lists:reverse([MFA|Result]).
 
1100
 
 
1101
insert(Pid,MFA) ->
 
1102
    case ets:member(fprof_verify_tab,{Pid,MFA}) of
 
1103
        false ->
 
1104
            ets:insert(fprof_verify_tab,{{Pid,MFA},0,0});
 
1105
        true ->
 
1106
            ok
 
1107
    end.
 
1108
 
 
1109
update_own(Pid,MFA,T) ->
 
1110
    ets:update_counter(fprof_verify_tab,{Pid,MFA},{3,T}).
 
1111
 
 
1112
update_acc(Pid,[MFA|Rest],T) ->
 
1113
    case lists:member(MFA,Rest) of
 
1114
        true -> 
 
1115
            %% Only charge one time for recursive functions
 
1116
            ok;
 
1117
        false -> 
 
1118
            ets:update_counter(fprof_verify_tab,{Pid,MFA},{2,T})
 
1119
    end,
 
1120
    update_acc(Pid,Rest,T);
 
1121
update_acc(_Pid,[],_T) ->
 
1122
    ok.
 
1123
 
 
1124
 
 
1125
get_last_ts() ->
 
1126
    get_last_ts(get(),{0,0,0}).
 
1127
get_last_ts([{{_,last_ts},TS}|Rest],Last) when TS>Last ->
 
1128
    get_last_ts(Rest,TS);
 
1129
get_last_ts([_|Rest],Last) ->
 
1130
    get_last_ts(Rest,Last);
 
1131
get_last_ts([],Last) ->
 
1132
    Last.
 
1133
 
 
1134
get_proc_owns([{{Pid,_MFA},_Acc,Own}|Rest],Result,Sum) ->
 
1135
    NewResult = 
 
1136
        case lists:keysearch(Pid,1,Result) of
 
1137
            {value,{Pid,undefined,PidOwn}} ->
 
1138
                lists:keyreplace(Pid,1,Result,{Pid,undefined,PidOwn+Own});
 
1139
            false ->
 
1140
                [{Pid,undefined,Own}|Result]
 
1141
    end,
 
1142
    get_proc_owns(Rest,NewResult,Sum+Own);
 
1143
get_proc_owns([],Result,Sum) ->
 
1144
    {Sum,Result}.
 
1145
    
 
1146
 
 
1147
compare([X|Rest],FprofResult) ->
 
1148
    FprofResult1 = 
 
1149
        case lists:member(X,FprofResult) of
 
1150
            true ->
 
1151
                ?dbg("~p",[X]),
 
1152
                lists:delete(X,FprofResult);
 
1153
            false -> 
 
1154
                case lists:keysearch(element(1,X),1,FprofResult) of
 
1155
                    {value,Fprof} ->
 
1156
                        put(compare_error,true),
 
1157
                        io:format("Error: Different values\n"
 
1158
                                  "Fprof:     ~p\n"
 
1159
                                  "Simulator: ~p",[Fprof,X]),
 
1160
                        lists:delete(Fprof,FprofResult);
 
1161
                    false ->
 
1162
                        put(compare_error,true),
 
1163
                        io:format("Error: Missing in fprof: ~p",[X]),
 
1164
                        FprofResult
 
1165
                end
 
1166
        end,
 
1167
    compare(Rest,FprofResult1);
 
1168
compare([],Rest) ->
 
1169
    case {remove_undefined(Rest,[]),get(compare_error)} of
 
1170
        {[],undefined} -> ok;
 
1171
        {Error,_} ->
 
1172
            case Error of
 
1173
                [] -> ok;
 
1174
                _ -> io:format("\nMissing in simulator results:\n~p\n",[Error])
 
1175
            end,
 
1176
            ?t:fail({error,mismatch_between_simulator_and_fprof})
 
1177
    end.
 
1178
    
 
1179
remove_undefined([{{_Pid,undefined},_,_}|Rest],Result) ->
 
1180
    remove_undefined(Rest,Result);
 
1181
remove_undefined([X|Rest],Result) ->
 
1182
    remove_undefined(Rest,[X|Result]);
 
1183
remove_undefined([],Result) ->
 
1184
    Result.
 
1185
    
 
1186
get_own_and_acc_from_analysis(Log) ->
 
1187
    case file:consult(Log) of
 
1188
        {ok,[_Options,[{totals,_,TotAcc,TotOwn}]|Rest]} ->
 
1189
            get_own_and_acc(undefined,Rest,
 
1190
                            [{totals,m1000(TotAcc),m1000(TotOwn)}]);
 
1191
        Error ->
 
1192
            exit({error,{cant_open,Log,Error}})
 
1193
    end.
 
1194
 
 
1195
get_own_and_acc(_,[[{PidStr,_,Acc,Own}|_]|Rest],Result) ->
 
1196
    Pid = list_to_pid(PidStr),
 
1197
    get_own_and_acc(Pid,Rest,[{Pid,m1000(Acc),m1000(Own)}|Result]);
 
1198
get_own_and_acc(Pid,[{_Callers,{MFA,_,Acc,Own},_Called}|Rest],Result) ->
 
1199
    get_own_and_acc(Pid,Rest,[{{Pid,MFA},m1000(Acc),m1000(Own)}|Result]);
 
1200
get_own_and_acc(_,[],Result) ->
 
1201
    lists:reverse(Result).
 
1202
 
 
1203
m1000(undefined) ->
 
1204
    undefined;
 
1205
m1000(X) ->
 
1206
    round(X*1000).
 
1207