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

« back to all changes in this revision

Viewing changes to lib/tools/src/lcnt.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 2010. 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
-module(lcnt).
 
21
-behaviour(gen_server).
 
22
-author("Björn-Egil Dahlberg").
 
23
 
 
24
%% gen_server callbacks
 
25
-export([
 
26
        init/1,
 
27
        handle_call/3,
 
28
        handle_cast/2,
 
29
        handle_info/2,
 
30
        terminate/2,
 
31
        code_change/3
 
32
        ]).
 
33
 
 
34
%% start/stop
 
35
-export([
 
36
        start/0,
 
37
        stop/0
 
38
        ]).
 
39
 
 
40
%% erts_debug:lock_counters api
 
41
-export([
 
42
        rt_collect/0,
 
43
        rt_collect/1,
 
44
        rt_clear/0,
 
45
        rt_clear/1,
 
46
        rt_opt/1,
 
47
        rt_opt/2
 
48
    ]).
 
49
 
 
50
 
 
51
%% gen_server call api
 
52
-export([
 
53
        raw/0,
 
54
        collect/0,
 
55
        collect/1,
 
56
        clear/0,
 
57
        clear/1,
 
58
        conflicts/0,
 
59
        conflicts/1,
 
60
        locations/0,
 
61
        locations/1,
 
62
        inspect/1,
 
63
        inspect/2,
 
64
        information/0,
 
65
        swap_pid_keys/0,
 
66
        % set options
 
67
        set/1,
 
68
        set/2,
 
69
 
 
70
        load/1,
 
71
        save/1
 
72
        ]).
 
73
 
 
74
%% convenience
 
75
-export([
 
76
        apply/3,
 
77
        apply/2,
 
78
        apply/1,
 
79
        all_conflicts/0,
 
80
        all_conflicts/1,
 
81
        pid/2, pid/3,
 
82
        port/1, port/2
 
83
    ]).
 
84
 
 
85
-define(version, "1.0").
 
86
 
 
87
-record(state, {
 
88
        locks      = [],
 
89
        duration   = 0
 
90
    }).
 
91
 
 
92
 
 
93
-record(stats, {
 
94
        file,
 
95
        line,
 
96
        tries,
 
97
        colls,
 
98
        time,     % us
 
99
        nt        % #timings collected
 
100
    }).
 
101
 
 
102
-record(lock, {
 
103
        name,
 
104
        id,
 
105
        type,
 
106
        stats = []
 
107
    }).
 
108
 
 
109
-record(print, {
 
110
        name,
 
111
        id,
 
112
        type,
 
113
        entry,
 
114
        tries,
 
115
        colls,
 
116
        cr,     % collision ratio
 
117
        time,
 
118
        dtr     % time duration ratio
 
119
    }).
 
120
 
 
121
 
 
122
 
 
123
%% -------------------------------------------------------------------- %%
 
124
%%
 
125
%% start/stop/init
 
126
%%
 
127
%% -------------------------------------------------------------------- %%
 
128
 
 
129
start()  -> gen_server:start({local, ?MODULE}, ?MODULE, [], []).
 
130
stop()   -> gen_server:cast(?MODULE, stop).
 
131
init([]) -> {ok, #state{ locks = [], duration = 0 } }.
 
132
 
 
133
%% -------------------------------------------------------------------- %%
 
134
%%
 
135
%% API erts_debug:lock_counters
 
136
%%
 
137
%% -------------------------------------------------------------------- %%
 
138
 
 
139
rt_collect() ->
 
140
    erts_debug:lock_counters(info).
 
141
 
 
142
rt_collect(Node) ->
 
143
    rpc:call(Node, erts_debug, lock_counters, [info]).
 
144
 
 
145
rt_clear() ->
 
146
    erts_debug:lock_counters(clear).
 
147
 
 
148
rt_clear(Node) ->
 
149
    rpc:call(Node, erts_debug, lock_counters, [clear]).
 
150
 
 
151
rt_opt({Type, Opt}) ->
 
152
    erts_debug:lock_counters({Type, Opt}).
 
153
 
 
154
rt_opt(Node, {Type, Opt}) ->
 
155
    rpc:call(Node, erts_debug, lock_counters, [{Type, Opt}]).
 
156
 
 
157
%% -------------------------------------------------------------------- %%
 
158
%%
 
159
%% API implementation
 
160
%%
 
161
%% -------------------------------------------------------------------- %%
 
162
 
 
163
clear()              -> rt_clear().
 
164
clear(Node)          -> rt_clear(Node).
 
165
collect()            -> call({collect, rt_collect()}).
 
166
collect(Node)        -> call({collect, rt_collect(Node)}).
 
167
 
 
168
locations()          -> call({locations,[]}).
 
169
locations(Opts)      -> call({locations, Opts}).
 
170
conflicts()          -> call({conflicts, []}).
 
171
conflicts(Opts)      -> call({conflicts, Opts}).
 
172
inspect(Lock)        -> call({inspect, Lock, []}).
 
173
inspect(Lock, Opts)  -> call({inspect, Lock, Opts}).
 
174
information()        -> call(information).
 
175
swap_pid_keys()      -> call(swap_pid_keys).
 
176
raw()                -> call(raw).
 
177
set(Option, Value)   -> call({set, Option, Value}).
 
178
set({Option, Value}) -> call({set, Option, Value}).
 
179
save(Filename)       -> call({save, Filename}).
 
180
load(Filename)       -> start(), call({load, Filename}).
 
181
 
 
182
call(Msg) -> gen_server:call(?MODULE, Msg, infinity).
 
183
 
 
184
%% -------------------------------------------------------------------- %%
 
185
%%
 
186
%% convenience implementation
 
187
%%
 
188
%% -------------------------------------------------------------------- %%
 
189
 
 
190
apply(M,F,As) when is_atom(M), is_atom(F), is_list(As) ->
 
191
    lcnt:start(),
 
192
    Opt = lcnt:rt_opt({copy_save, true}),
 
193
    lcnt:clear(),
 
194
    Res = erlang:apply(M,F,As),
 
195
    lcnt:collect(),
 
196
    lcnt:rt_opt({copy_save, Opt}),
 
197
    Res.
 
198
 
 
199
apply(Fun) when is_function(Fun) ->
 
200
    lcnt:apply(Fun, []).
 
201
 
 
202
apply(Fun, As) when is_function(Fun) ->
 
203
    lcnt:start(),
 
204
    Opt = lcnt:rt_opt({copy_save, true}),
 
205
    lcnt:clear(),
 
206
    Res = erlang:apply(Fun, As),
 
207
    lcnt:collect(),
 
208
    lcnt:rt_opt({copy_save, Opt}),
 
209
    Res.
 
210
 
 
211
all_conflicts() -> all_conflicts(time).
 
212
all_conflicts(Sort) ->
 
213
    conflicts([{max_locks, none}, {thresholds, []},{combine,false}, {sort, Sort}, {reverse, true}]).
 
214
 
 
215
pid(Id, Serial) -> pid(node(), Id, Serial).
 
216
pid(Node, Id, Serial) when is_atom(Node) ->
 
217
    Header   = <<131,103,100>>,
 
218
    String   = atom_to_list(Node),
 
219
    L        = length(String),
 
220
    binary_to_term(list_to_binary([Header, bytes16(L), String, bytes32(Id), bytes32(Serial),0])).
 
221
 
 
222
port(Id) -> port(node(), Id).
 
223
port(Node, Id ) when is_atom(Node) ->
 
224
    Header   = <<131,102,100>>,
 
225
    String   = atom_to_list(Node),
 
226
    L        = length(String),
 
227
    binary_to_term(list_to_binary([Header, bytes16(L), String, bytes32(Id), 0])).
 
228
 
 
229
%% -------------------------------------------------------------------- %%
 
230
%%
 
231
%% handle_call
 
232
%%
 
233
%% -------------------------------------------------------------------- %%
 
234
 
 
235
% printing
 
236
 
 
237
handle_call({conflicts, InOpts}, _From, #state{ locks = Locks } = State) when is_list(InOpts) ->
 
238
    Default = [
 
239
        {sort,       time},
 
240
        {reverse,    false},
 
241
        {print,      [name,id,tries,colls,ratio,time,duration]},
 
242
        {max_locks,  20},
 
243
        {combine,    true},
 
244
        {thresholds, [{tries, 0}, {colls, 0}, {time, 0}] },
 
245
        {locations,  false}],
 
246
 
 
247
    Opts       = options(InOpts, Default),
 
248
    Flocks     = filter_locks_type(Locks, proplists:get_value(type, Opts)),
 
249
    Combos     = combine_classes(Flocks, proplists:get_value(combine, Opts)),
 
250
    Printables = locks2print(Combos, State#state.duration),
 
251
    Filtered   = filter_print(Printables, Opts),
 
252
 
 
253
    print_lock_information(Filtered, proplists:get_value(print, Opts)),
 
254
 
 
255
    {reply, ok, State};
 
256
 
 
257
handle_call(information, _From, State) ->
 
258
    print_state_information(State),
 
259
    {reply, ok, State};
 
260
 
 
261
handle_call({locations, InOpts}, _From, #state{ locks = Locks } = State) when is_list(InOpts) ->
 
262
    Default = [
 
263
        {sort,       time},
 
264
        {reverse,    false},
 
265
        {print,      [name,entry,tries,colls,ratio,time,duration]},
 
266
        {max_locks,  20},
 
267
        {combine,    true},
 
268
        {thresholds, [{tries, 0}, {colls, 0}, {time, 0}] },
 
269
        {locations,  true}],
 
270
 
 
271
    Opts = options(InOpts, Default),
 
272
    Printables = filter_print([#print{
 
273
            name  = string_names(Names),
 
274
            entry = term2string("~p:~p", [Stats#stats.file, Stats#stats.line]),
 
275
            colls = Stats#stats.colls,
 
276
            tries = Stats#stats.tries,
 
277
            cr    = percent(Stats#stats.colls, Stats#stats.tries),
 
278
            time  = Stats#stats.time,
 
279
            dtr   = percent(Stats#stats.time, State#state.duration)
 
280
        } || {Stats, Names} <- combine_locations(Locks) ], Opts),
 
281
 
 
282
    print_lock_information(Printables, proplists:get_value(print, Opts)),
 
283
 
 
284
    {reply, ok, State};
 
285
 
 
286
handle_call({inspect, Lockname, InOpts}, _From, #state{ duration = Duration, locks = Locks } = State) when is_list(InOpts) ->
 
287
    Default = [
 
288
        {sort,       time},
 
289
        {reverse,    false},
 
290
        {print,      [name,id,tries,colls,ratio,time,duration]},
 
291
        {max_locks,  20},
 
292
        {combine,    false},
 
293
        {thresholds, [] },
 
294
        {locations,  false}],
 
295
 
 
296
    Opts      = options(InOpts, Default),
 
297
    Filtered  = filter_locks(Locks, Lockname),
 
298
    IDs       = case {proplists:get_value(full_id, Opts), proplists:get_value(combine, Opts)} of
 
299
        {true, true} -> locks_ids(Filtered);
 
300
        _            -> []
 
301
    end,
 
302
    Combos    =  combine_classes(Filtered, proplists:get_value(combine, Opts)),
 
303
    case proplists:get_value(locations, Opts) of
 
304
        true ->
 
305
            lists:foreach(fun
 
306
                    (#lock{ name = Name, id = Id, type = Type, stats =  Stats })  ->
 
307
                        IdString = case proplists:get_value(full_id, Opts) of
 
308
                            true -> term2string(proplists:get_value(Name, IDs, Id));
 
309
                            _    -> term2string(Id)
 
310
                        end,
 
311
                        Combined = [CStats || {CStats,_} <- combine_locations(Stats)],
 
312
                        case Combined of
 
313
                            [] ->
 
314
                                ok;
 
315
                            _  ->
 
316
                                %io:format("Combined ~p~n", [Combined]),
 
317
                                print("lock: " ++ term2string(Name)),
 
318
                                print("id:   " ++ IdString),
 
319
                                print("type: " ++ term2string(Type)),
 
320
                                Ps = stats2print(Combined, Duration),
 
321
                                Opts1 = options([{print, [entry, tries,colls,ratio,time,duration]},
 
322
                                        {thresholds, [{tries, -1}, {colls, -1}, {time, -1}]}], Opts),
 
323
                                print_lock_information(filter_print(Ps, Opts1), proplists:get_value(print, Opts1))
 
324
                        end
 
325
                   % (#lock{ name = Name, id = Id}) ->
 
326
                %       io:format("Empty lock ~p ~p~n", [Name, Id])
 
327
                end, Combos);
 
328
        _ ->
 
329
            Print1 = locks2print(Combos, Duration),
 
330
            Print2 = filter_print(Print1, Opts),
 
331
            print_lock_information(Print2, proplists:get_value(print, Opts))
 
332
    end,
 
333
    {reply, ok, State};
 
334
 
 
335
handle_call(raw, _From, #state{ locks = Locks} = State)->
 
336
    {reply, Locks, State};
 
337
 
 
338
% collecting
 
339
handle_call({collect, Data}, _From, State)->
 
340
    {reply, ok, data2state(Data, State)};
 
341
 
 
342
% manipulate
 
343
handle_call(swap_pid_keys, _From, #state{ locks = Locks } = State)->
 
344
    SwappedLocks = lists:map(fun
 
345
        (L) when L#lock.name =:= port_lock; L#lock.type =:= proclock ->
 
346
            L#lock{ id = L#lock.name, name = L#lock.id };
 
347
        (L) ->
 
348
            L
 
349
    end, Locks),
 
350
 
 
351
    {reply, ok, State#state{ locks = SwappedLocks}};
 
352
 
 
353
% settings
 
354
handle_call({set, data, Data}, _From, State)->
 
355
    {reply, ok, data2state(Data, State)};
 
356
 
 
357
handle_call({set, duration, Duration}, _From, State)->
 
358
    {reply, ok, State#state{ duration = Duration}};
 
359
 
 
360
% file operations
 
361
handle_call({load, Filename}, _From, State) ->
 
362
    case file:read_file(Filename) of
 
363
        {ok, Binary} ->
 
364
            case binary_to_term(Binary) of
 
365
                {?version, Statelist} ->
 
366
                    {reply, ok, list2state(Statelist)};
 
367
                {Version, _} ->
 
368
                    {reply, {error, {mismatch, Version, ?version}}, State}
 
369
            end;
 
370
        Error ->
 
371
            {reply, {error, Error}, State}
 
372
    end;
 
373
 
 
374
handle_call({save, Filename}, _From, State) ->
 
375
    Binary = term_to_binary({?version, state2list(State)}),
 
376
    case file:write_file(Filename, Binary) of
 
377
        ok ->
 
378
            {reply, ok, State};
 
379
        Error ->
 
380
            {reply, {error, Error}, State}
 
381
    end;
 
382
 
 
383
 
 
384
handle_call(Command, _From, State) ->
 
385
    {reply, {error, {undefined, Command}}, State}.
 
386
 
 
387
%% -------------------------------------------------------------------- %%
 
388
%%
 
389
%% handle_cast
 
390
%%
 
391
%% -------------------------------------------------------------------- %%
 
392
 
 
393
handle_cast(stop, State) ->
 
394
    {stop, normal, State};
 
395
handle_cast(_, State) ->
 
396
    {noreply, State}.
 
397
 
 
398
%% -------------------------------------------------------------------- %%
 
399
%%
 
400
%% handle_info
 
401
%%
 
402
%% -------------------------------------------------------------------- %%
 
403
 
 
404
handle_info(_Info, State) ->
 
405
    {noreply, State}.
 
406
 
 
407
%% -------------------------------------------------------------------- %%
 
408
%%
 
409
%% termination
 
410
%%
 
411
%% -------------------------------------------------------------------- %%
 
412
 
 
413
terminate(_Reason, _State) ->
 
414
    ok.
 
415
 
 
416
%% -------------------------------------------------------------------- %%
 
417
%%
 
418
%% code_change
 
419
%%
 
420
%% -------------------------------------------------------------------- %%
 
421
 
 
422
code_change(_OldVsn, State, _Extra) ->
 
423
    {ok, State}.
 
424
 
 
425
%% -------------------------------------------------------------------- %%
 
426
%%
 
427
%% AUX
 
428
%%
 
429
%% -------------------------------------------------------------------- %%
 
430
 
 
431
% summate
 
432
 
 
433
summate_locks(Locks) -> summate_locks(Locks, #stats{ tries = 0, colls = 0, time = 0, nt = 0}).
 
434
summate_locks([], Stats) -> Stats;
 
435
summate_locks([L|Ls], #stats{ tries = Tries, colls = Colls, time = Time, nt = Nt}) ->
 
436
    S = summate_stats(L#lock.stats),
 
437
    summate_locks(Ls, #stats{ tries = Tries + S#stats.tries, colls = Colls + S#stats.colls, time = Time + S#stats.time, nt = Nt + S#stats.nt}).
 
438
 
 
439
summate_stats(Stats) -> summate_stats(Stats, #stats{ tries = 0, colls = 0, time = 0, nt = 0}).
 
440
summate_stats([], Stats) -> Stats;
 
441
summate_stats([S|Ss], #stats{ tries = Tries, colls = Colls, time = Time, nt = Nt}) ->
 
442
    summate_stats(Ss, #stats{ tries = Tries + S#stats.tries, colls = Colls + S#stats.colls, time = Time + S#stats.time, nt = Nt + S#stats.nt}).
 
443
 
 
444
 
 
445
%% manipulators
 
446
filter_locks_type(Locks, undefined) -> Locks;
 
447
filter_locks_type(Locks, all) -> Locks;
 
448
filter_locks_type(Locks, Types) when is_list(Types) ->
 
449
    [ L || L <- Locks, lists:member(L#lock.type, Types)];
 
450
filter_locks_type(Locks, Type) ->
 
451
    [ L || L <- Locks, L#lock.type =:= Type].
 
452
 
 
453
filter_locks(Locks, {Lockname, Ids}) when is_list(Ids) ->
 
454
    [ L || L <- Locks, L#lock.name =:= Lockname, lists:member(L#lock.id, Ids)];
 
455
filter_locks(Locks, {Lockname, Id}) ->
 
456
    [ L || L <- Locks, L#lock.name =:= Lockname, L#lock.id =:= Id ];
 
457
filter_locks(Locks, Lockname) ->
 
458
    [ L || L <- Locks, L#lock.name =:= Lockname ].
 
459
% order of processing
 
460
% 2. cut thresholds
 
461
% 3. sort locks
 
462
% 4. max length of locks
 
463
 
 
464
filter_print(PLs, Opts) ->
 
465
    TLs = threshold_locks(PLs, proplists:get_value(thresholds, Opts, [])),
 
466
    SLs =      sort_locks(TLs, proplists:get_value(sort,       Opts, time)),
 
467
    CLs =       cut_locks(SLs, proplists:get_value(max_locks,  Opts, none)),
 
468
            reverse_locks(CLs, proplists:get_value(reverse,    Opts, false)).
 
469
 
 
470
sort_locks(Locks, Type)   -> lists:reverse(sort_locks0(Locks, Type)).
 
471
sort_locks0(Locks, name)  -> lists:keysort(#print.name, Locks);
 
472
sort_locks0(Locks, id)    -> lists:keysort(#print.id, Locks);
 
473
sort_locks0(Locks, type)  -> lists:keysort(#print.type, Locks);
 
474
sort_locks0(Locks, tries) -> lists:keysort(#print.tries, Locks);
 
475
sort_locks0(Locks, colls) -> lists:keysort(#print.colls, Locks);
 
476
sort_locks0(Locks, ratio) -> lists:keysort(#print.cr, Locks);
 
477
sort_locks0(Locks, time)  -> lists:keysort(#print.time, Locks);
 
478
sort_locks0(Locks, _)     -> sort_locks0(Locks, time).
 
479
 
 
480
% cut locks not above certain thresholds
 
481
threshold_locks(Locks, Thresholds) ->
 
482
    Tries = proplists:get_value(tries, Thresholds, -1),
 
483
    Colls = proplists:get_value(colls, Thresholds, -1),
 
484
    Time  = proplists:get_value(time,  Thresholds, -1),
 
485
    [ L || L <- Locks, L#print.tries > Tries, L#print.colls > Colls, L#print.time > Time].
 
486
 
 
487
cut_locks(Locks, N) when is_integer(N), N > 0 -> lists:sublist(Locks, N);
 
488
cut_locks(Locks, _) -> Locks.
 
489
 
 
490
%% reversal
 
491
reverse_locks(Locks, true) -> lists:reverse(Locks);
 
492
reverse_locks(Locks, _) -> Locks.
 
493
 
 
494
 
 
495
%%
 
496
string_names([]) -> "";
 
497
string_names(Names) -> string_names(Names, []).
 
498
string_names([Name], Strings) -> strings(lists:reverse([term2string(Name) | Strings]));
 
499
string_names([Name|Names],Strings) -> string_names(Names, [term2string(Name) ++ ","|Strings]).
 
500
 
 
501
%% combine_locations
 
502
%% In:
 
503
%%      Locations :: [#lock{}] | [#stats{}]
 
504
%% Out:
 
505
%%      [{{File,Line}, #stats{}, [Lockname]}]
 
506
 
 
507
 
 
508
combine_locations(Locations)    -> gb_trees:values(combine_locations(Locations, gb_trees:empty())).
 
509
combine_locations([], Tree) -> Tree;
 
510
combine_locations([S|_] = Stats, Tree) when is_record(S, stats) ->
 
511
    combine_locations(Stats, undefined, Tree);
 
512
combine_locations([#lock{ stats = Stats, name = Name}|Ls], Tree)  ->
 
513
    combine_locations(Ls, combine_locations(Stats, Name, Tree)).
 
514
 
 
515
combine_locations([], _, Tree) -> Tree;
 
516
combine_locations([S|Ss], Name, Tree) when is_record(S, stats)->
 
517
    Key  = {S#stats.file, S#stats.line},
 
518
    Tree1 = case gb_trees:lookup(Key, Tree) of
 
519
        none ->
 
520
            gb_trees:insert(Key, {S, [Name]}, Tree);
 
521
        {value, {C, Names}} ->
 
522
            NewNames = case lists:member(Name, Names) of
 
523
                true -> Names;
 
524
                _    -> [Name | Names]
 
525
            end,
 
526
            gb_trees:update(Key, {
 
527
                C#stats{
 
528
                    tries = C#stats.tries + S#stats.tries,
 
529
                    colls = C#stats.colls + S#stats.colls,
 
530
                    time  = C#stats.time  + S#stats.time,
 
531
                    nt    = C#stats.nt    + S#stats.nt
 
532
                }, NewNames}, Tree)
 
533
    end,
 
534
    combine_locations(Ss, Name, Tree1).
 
535
 
 
536
%% combines all statistics for a class (name) lock
 
537
%% id's are translated to #id's.
 
538
 
 
539
combine_classes(Locks, true) ->  combine_classes1(Locks, gb_trees:empty());
 
540
combine_classes(Locks, _) -> Locks.
 
541
 
 
542
combine_classes1([], Tree) ->  gb_trees:values(Tree);
 
543
combine_classes1([L|Ls], Tree) ->
 
544
    Key = L#lock.name,
 
545
    case gb_trees:lookup(Key, Tree) of
 
546
        none ->
 
547
            combine_classes1(Ls, gb_trees:insert(Key, L#lock{ id = 1 }, Tree));
 
548
        {value, C} ->
 
549
            combine_classes1(Ls, gb_trees:update(Key, C#lock{
 
550
                id    = C#lock.id    + 1,
 
551
                stats = L#lock.stats ++ C#lock.stats
 
552
            }, Tree))
 
553
    end.
 
554
 
 
555
locks_ids(Locks) -> locks_ids(Locks, []).
 
556
locks_ids([], Out) -> Out;
 
557
locks_ids([#lock{ name = Key } = L|Ls], Out) ->
 
558
    case proplists:get_value(Key, Out) of
 
559
        undefined ->
 
560
            locks_ids(Ls, [{Key, [L#lock.id] } | Out]);
 
561
        Ids ->
 
562
            locks_ids(Ls, [{Key, [L#lock.id | Ids] } | proplists:delete(Key,Out)])
 
563
    end.
 
564
 
 
565
stats2print(Stats, Duration) ->
 
566
    lists:map(fun
 
567
        (S) ->
 
568
            #print{
 
569
                entry = term2string("~p:~p", [S#stats.file, S#stats.line]),
 
570
                colls = S#stats.colls,
 
571
                tries = S#stats.tries,
 
572
                cr    = percent(S#stats.colls, S#stats.tries),
 
573
                time  = S#stats.time,
 
574
                dtr   = percent(S#stats.time,  Duration)
 
575
            }
 
576
        end, Stats).
 
577
 
 
578
locks2print(Locks, Duration) ->
 
579
    lists:map( fun
 
580
        (L) ->
 
581
            Tries = lists:sum([T || #stats{ tries = T} <- L#lock.stats]),
 
582
            Colls = lists:sum([C || #stats{ colls = C} <- L#lock.stats]),
 
583
            Time  = lists:sum([T || #stats{ time  = T} <- L#lock.stats]),
 
584
            Cr    = percent(Colls, Tries),
 
585
            Dtr   = percent(Time,  Duration),
 
586
            #print{
 
587
                name  = L#lock.name,
 
588
                id    = L#lock.id,
 
589
                type  = L#lock.type,
 
590
                tries = Tries,
 
591
                colls = Colls,
 
592
                cr    = Cr,
 
593
                time  = Time,
 
594
                dtr   = Dtr
 
595
            }
 
596
        end, Locks).
 
597
 
 
598
%% state making
 
599
 
 
600
data2state(Data, State) ->
 
601
    Duration = time2us(proplists:get_value(duration, Data)),
 
602
    Rawlocks = proplists:get_value(locks, Data),
 
603
    Locks    = locks2records(Rawlocks),
 
604
    State#state{
 
605
        duration = Duration,
 
606
        locks    = Locks
 
607
    }.
 
608
 
 
609
locks2records(Locks) -> locks2records(Locks, []).
 
610
locks2records([], Out) -> Out;
 
611
locks2records([{Name, Id, Type, Stats}|Locks], Out) ->
 
612
    Lock = #lock{
 
613
            name  = Name,
 
614
            id    = clean_id_creation(Id),
 
615
            type  = Type,
 
616
            stats = [ #stats{
 
617
                file  = File,
 
618
                line  = Line,
 
619
                tries = Tries,
 
620
                colls = Colls,
 
621
                time  = time2us({S, Ns}),
 
622
                nt    = N
 
623
            } || {{File, Line}, {Tries, Colls, {S, Ns, N}}} <- Stats] },
 
624
    locks2records(Locks, [Lock|Out]).
 
625
 
 
626
clean_id_creation(Id) when is_pid(Id) ->
 
627
    Bin = term_to_binary(Id),
 
628
    <<H:3/binary, L:16, Node:L/binary, Ids:8/binary, _Creation/binary>> = Bin,
 
629
    Bin2 = list_to_binary([H, bytes16(L), Node, Ids, 0]),
 
630
    binary_to_term(Bin2);
 
631
clean_id_creation(Id) when is_port(Id) ->
 
632
    Bin = term_to_binary(Id),
 
633
    <<H:3/binary, L:16, Node:L/binary, Ids:4/binary, _Creation/binary>> = Bin,
 
634
    Bin2 = list_to_binary([H, bytes16(L), Node, Ids, 0]),
 
635
    binary_to_term(Bin2);
 
636
clean_id_creation(Id) ->
 
637
    Id.
 
638
 
 
639
%% serializer
 
640
 
 
641
state_default(Field) -> proplists:get_value(Field, state2list(#state{})).
 
642
 
 
643
state2list(State) ->
 
644
    [_|Values] = tuple_to_list(State),
 
645
    lists:zipwith(fun
 
646
        (locks, Locks) -> {locks, [lock2list(Lock) || Lock <- Locks]};
 
647
        (X, Y) -> {X,Y}
 
648
    end, record_info(fields, state), Values).
 
649
 
 
650
list2state(List) -> list2state(record_info(fields, state), List, [state]).
 
651
list2state([], _, Out) -> list_to_tuple(lists:reverse(Out));
 
652
list2state([locks|Fs], List, Out) ->
 
653
    Locks = [ list2lock(Lock) || Lock <- proplists:get_value(locks, List, [])],
 
654
    list2state(Fs, List, [Locks|Out]);
 
655
list2state([F|Fs], List, Out) -> list2state(Fs, List, [proplists:get_value(F, List, state_default(F))|Out]).
 
656
 
 
657
lock_default(Field) -> proplists:get_value(Field, lock2list(#lock{})).
 
658
 
 
659
lock2list(Lock) ->
 
660
    [_|Values] = tuple_to_list(Lock),
 
661
    lists:zip(record_info(fields, lock), Values).
 
662
 
 
663
list2lock(List) -> list2lock(record_info(fields, lock), List, [lock]).
 
664
list2lock([], _, Out) -> list_to_tuple(lists:reverse(Out));
 
665
list2lock([F|Fs], List, Out) -> list2lock(Fs, List, [proplists:get_value(F, List, lock_default(F))|Out]).
 
666
 
 
667
%% printing
 
668
 
 
669
%% print_lock_information
 
670
%% In:
 
671
%%      Locks :: [#lock{}]
 
672
%%      Print :: [Type | {Type, integer()}]
 
673
%%
 
674
%% Out:
 
675
%%      ok
 
676
 
 
677
auto_print_width(Locks, Print) ->
 
678
    % iterate all lock entries to save all max length values
 
679
    % these are records, so we do a little tuple <-> list smashing
 
680
    R = lists:foldl(fun
 
681
        (L, Max) ->
 
682
                list_to_tuple(lists:reverse(lists:foldl(fun
 
683
                    ({print,print}, Out) -> [print|Out];
 
684
                    ({Str, Len}, Out)    -> [erlang:min(erlang:max(length(s(Str))+1,Len),80)|Out]
 
685
                end, [], lists:zip(tuple_to_list(L), tuple_to_list(Max)))))
 
686
        end, #print{ id = 4, type = 5, entry = 5, name = 6, tries = 8, colls = 13, cr = 16, time = 11, dtr = 14 },
 
687
        Locks),
 
688
    % Setup the offsets for later pruning
 
689
    Offsets = [
 
690
        {id, R#print.id},
 
691
        {name, R#print.name},
 
692
        {type, R#print.type},
 
693
        {entry, R#print.entry},
 
694
        {tries, R#print.tries},
 
695
        {colls, R#print.colls},
 
696
        {ratio, R#print.cr},
 
697
        {time, R#print.time},
 
698
        {duration, R#print.dtr}],
 
699
    % Prune offsets to only allow specified print options
 
700
    lists:foldr(fun
 
701
            ({Type, W}, Out) -> [{Type, W}|Out];
 
702
            (Type, Out)      -> [proplists:lookup(Type, Offsets)|Out]
 
703
        end, [], Print).
 
704
 
 
705
print_lock_information(Locks, Print) ->
 
706
    % remake Print to autosize entries
 
707
    AutoPrint = auto_print_width(Locks, Print),
 
708
 
 
709
    print_header(AutoPrint),
 
710
 
 
711
    lists:foreach(fun
 
712
        (L) ->
 
713
            print_lock(L, AutoPrint)
 
714
    end, Locks),
 
715
    ok.
 
716
 
 
717
print_header(Opts) ->
 
718
    Header = #print{
 
719
        name  = "lock",
 
720
        id    = "id",
 
721
        type  = "type",
 
722
        entry = "location",
 
723
        tries = "#tries",
 
724
        colls = "#collisions",
 
725
        cr    = "collisions [%]",
 
726
        time  = "time [us]",
 
727
        dtr   = "duration [%]"
 
728
    },
 
729
    Divider = #print{
 
730
        name  = lists:duplicate(1 + length(Header#print.name),  45),
 
731
        id    = lists:duplicate(1 + length(Header#print.id),    45),
 
732
        type  = lists:duplicate(1 + length(Header#print.type),  45),
 
733
        entry = lists:duplicate(1 + length(Header#print.entry), 45),
 
734
        tries = lists:duplicate(1 + length(Header#print.tries), 45),
 
735
        colls = lists:duplicate(1 + length(Header#print.colls), 45),
 
736
        cr    = lists:duplicate(1 + length(Header#print.cr),    45),
 
737
        time  = lists:duplicate(1 + length(Header#print.time),  45),
 
738
        dtr   = lists:duplicate(1 + length(Header#print.dtr),   45)
 
739
    },
 
740
    print_lock(Header, Opts),
 
741
    print_lock(Divider, Opts),
 
742
    ok.
 
743
 
 
744
 
 
745
print_lock(L, Opts) -> print_lock(L, Opts, []).
 
746
print_lock(_, [],  Formats) -> print(strings(lists:reverse(Formats)));
 
747
print_lock(L, [Opt|Opts], Formats) ->
 
748
    case Opt of
 
749
        id            -> print_lock(L, Opts, [{space, 25, s(L#print.id)   } | Formats]);
 
750
        {id, W}       -> print_lock(L, Opts, [{space,  W, s(L#print.id)   } | Formats]);
 
751
        type          -> print_lock(L, Opts, [{space, 18, s(L#print.type) } | Formats]);
 
752
        {type, W}     -> print_lock(L, Opts, [{space,  W, s(L#print.type) } | Formats]);
 
753
        entry         -> print_lock(L, Opts, [{space, 30, s(L#print.entry)} | Formats]);
 
754
        {entry, W}    -> print_lock(L, Opts, [{space,  W, s(L#print.entry)} | Formats]);
 
755
        name          -> print_lock(L, Opts, [{space, 22, s(L#print.name) } | Formats]);
 
756
        {name, W}     -> print_lock(L, Opts, [{space,  W, s(L#print.name) } | Formats]);
 
757
        tries         -> print_lock(L, Opts, [{space, 12, s(L#print.tries)} | Formats]);
 
758
        {tries, W}    -> print_lock(L, Opts, [{space,  W, s(L#print.tries)} | Formats]);
 
759
        colls         -> print_lock(L, Opts, [{space, 14, s(L#print.colls)} | Formats]);
 
760
        {colls, W}    -> print_lock(L, Opts, [{space,  W, s(L#print.colls)} | Formats]);
 
761
        ratio         -> print_lock(L, Opts, [{space, 20, s(L#print.cr)   } | Formats]);
 
762
        {ratio, W}    -> print_lock(L, Opts, [{space,  W, s(L#print.cr)   } | Formats]);
 
763
        time          -> print_lock(L, Opts, [{space, 15, s(L#print.time) } | Formats]);
 
764
        {time, W}     -> print_lock(L, Opts, [{space,  W, s(L#print.time) } | Formats]);
 
765
        duration      -> print_lock(L, Opts, [{space, 20, s(L#print.dtr)  } | Formats]);
 
766
        {duration, W} -> print_lock(L, Opts, [{space,  W, s(L#print.dtr)  } | Formats]);
 
767
        _             -> print_lock(L, Opts, Formats)
 
768
    end.
 
769
 
 
770
print_state_information(#state{ locks = Locks} = State) ->
 
771
    Stats = summate_locks(Locks),
 
772
    print("information:"),
 
773
    print(kv("#locks",          s(length(Locks)))),
 
774
    print(kv("duration",        s(State#state.duration) ++ " us" ++ " (" ++ s(State#state.duration/1000000) ++ " s)")),
 
775
    print("\nsummated stats:"),
 
776
    print(kv("#tries",          s(Stats#stats.tries))),
 
777
    print(kv("#colls",          s(Stats#stats.colls))),
 
778
    print(kv("wait time",       s(Stats#stats.time) ++ " us" ++ " ( " ++ s(Stats#stats.time/1000000) ++ " s)")),
 
779
    print(kv("percent of duration", s(Stats#stats.time/State#state.duration*100) ++ " %")),
 
780
    ok.
 
781
 
 
782
%% AUX
 
783
 
 
784
time2us({S, Ns}) -> round(S*1000000 + Ns/1000).
 
785
 
 
786
percent(_,0) -> 0.0;
 
787
percent(T,N) -> T/N*100.
 
788
 
 
789
options(Opts, Default) when is_list(Default) ->
 
790
    options1(proplists:unfold(Opts), Default).
 
791
options1([], Defaults) -> Defaults;
 
792
options1([{Key, Value}|Opts], Defaults) ->
 
793
    case proplists:get_value(Key, Defaults) of
 
794
        undefined -> options1(Opts, [{Key, Value} | Defaults]);
 
795
        _         -> options1(Opts, [{Key, Value} | proplists:delete(Key, Defaults)])
 
796
    end.
 
797
 
 
798
%%% AUX STRING FORMATTING
 
799
 
 
800
print(String) -> io:format("~s~n", [String]).
 
801
 
 
802
kv(Key, Value) -> kv(Key, Value, 20).
 
803
kv(Key, Value, Offset) -> term2string(term2string("~~~ps : ~~s", [Offset]),[Key, Value]).
 
804
 
 
805
s(T) when is_float(T) -> term2string("~.4f", [T]);
 
806
s(T) when is_list(T)  -> term2string("~s", [T]);
 
807
s(T)                  -> term2string(T).
 
808
 
 
809
strings(Strings) -> strings(Strings, []).
 
810
strings([], Out) -> Out;
 
811
strings([{space,  N,      S} | Ss], Out) -> strings(Ss, Out ++ term2string(term2string("~~~ps", [N]), [S]));
 
812
strings([{format, Format, S} | Ss], Out) -> strings(Ss, Out ++ term2string(Format, [S]));
 
813
strings([S|Ss], Out) -> strings(Ss, Out ++ term2string("~s", [S])).
 
814
 
 
815
 
 
816
term2string({M,F,A}) when is_atom(M), is_atom(F), is_integer(A) -> term2string("~p:~p/~p", [M,F,A]);
 
817
term2string(Term) when is_port(Term) ->
 
818
    %  ex #Port<6442.816>
 
819
    <<_:3/binary, L:16, Node:L/binary, Ids:32, _/binary>> = term_to_binary(Term),
 
820
    term2string("#Port<~s.~w>", [Node, Ids]);
 
821
term2string(Term) when is_pid(Term) ->
 
822
    %  ex <0.80.0>
 
823
    <<_:3/binary, L:16, Node:L/binary, Ids:32, Serial:32,  _/binary>> = term_to_binary(Term),
 
824
    term2string("<~s.~w.~w>", [Node, Ids, Serial]);
 
825
term2string(Term) -> term2string("~w", [Term]).
 
826
term2string(Format, Terms) -> lists:flatten(io_lib:format(Format, Terms)).
 
827
 
 
828
%%% AUD id binary
 
829
 
 
830
bytes16(Value) ->
 
831
    B0 =  Value band 255,
 
832
    B1 = (Value bsr 8) band 255,
 
833
    <<B1, B0>>.
 
834
 
 
835
bytes32(Value) ->
 
836
    B0 =  Value band 255,
 
837
    B1 = (Value bsr  8) band 255,
 
838
    B2 = (Value bsr 16) band 255,
 
839
    B3 = (Value bsr 24) band 255,
 
840
    <<B3, B2, B1, B0>>.