~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/percept/src/percept_db.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
40
40
%%
41
41
%%==========================================================================
42
42
 
43
 
-type(activity_option() :: 
44
 
        {'ts_min', timestamp()} | 
45
 
        {'ts_max', timestamp()} |
46
 
        {'ts_exact', bool()} |
47
 
        {'mfa', true_mfa()} |
48
 
        {'state', state()} |
49
 
        {'id', 'all' | 'procs' | 'ports' | pid() | port()}).
50
 
 
51
 
-type(scheduler_option() :: 
52
 
        {'ts_min', timestamp()} | 
53
 
        {'ts_max', timestamp()} |
54
 
        {'ts_exact', bool()} |
55
 
        {'id', scheduler_id()}).
56
 
        
57
 
-type(system_option() ::
58
 
        'start_ts' | 'stop_ts').
59
 
 
60
 
-type(information_option() ::
61
 
        'all' | 'procs' | 'ports' |
62
 
        pid() | port()).
63
 
 
64
43
%% @type activity_option() = 
65
44
%%      {ts_min, timestamp()} | 
66
45
%%      {ts_max, timestamp()} | 
194
173
    
195
174
    % System warnings
196
175
    ets:new(pdb_warnings, [named_table, private, {keypos, 1}, ordered_set]),
 
176
    put(debug, 0),
197
177
    loop_percept_db().
198
178
 
199
179
loop_percept_db() ->
200
180
    receive
201
181
        {insert, Trace} ->
202
 
            insert_trace(Trace),
 
182
            insert_trace(clean_trace(Trace)),
203
183
            loop_percept_db();
204
184
        {select, Pid, Query} ->
205
185
            Pid ! select_query(Query),
224
204
%%
225
205
%%==========================================================================
226
206
 
 
207
%% cleans trace messages from external pids
 
208
 
 
209
clean_trace(Trace) when is_tuple(Trace) -> list_to_tuple(clean_trace(tuple_to_list(Trace)));
 
210
clean_trace(Trace) when is_list(Trace) -> clean_list(Trace, []);
 
211
clean_trace(Trace) when is_pid(Trace) ->
 
212
    PidStr = pid_to_list(Trace),
 
213
    [_,P2,P3p] = string:tokens(PidStr,"."),
 
214
    P3 = lists:sublist(P3p, 1, length(P3p) - 1),
 
215
    erlang:list_to_pid("<0." ++ P2 ++ "." ++ P3 ++ ">");
 
216
clean_trace(Trace) -> Trace.
 
217
 
 
218
clean_list([], Out) -> lists:reverse(Out);
 
219
clean_list([Element|Trace], Out) ->
 
220
    clean_list(Trace, [clean_trace(Element)|Out]).
 
221
 
 
222
 
227
223
insert_trace(Trace) ->
228
224
    case Trace of
229
225
        {profile_start, Ts} ->
236
232
        %%% ---------------------------------------------
237
233
        {profile, Id, State, Mfa, TS} when is_pid(Id) ->
238
234
            % Update runnable count in activity and db
 
235
            
239
236
            case check_activity_consistency(Id, State) of
240
237
                invalid_state -> 
241
 
                    io:format("insert_trace, bad_state: ~p~n", [Trace]),
242
238
                    ignored;
243
239
                ok ->
244
240
                    Rc = get_runnable_count(procs, State),
245
 
            
246
241
                    % Update registered procs
247
242
                    % insert proc activity
248
243
                    update_activity(#activity{
258
253
        {profile, Id, State, Mfa, TS} when is_port(Id) ->
259
254
            case check_activity_consistency(Id, State) of
260
255
                invalid_state -> 
261
 
                    io:format("insert_trace, bad_state: ~p~n", [Trace]),
262
256
                    ignored;
263
257
                ok ->
264
258
                    % Update runnable count in activity and db
288
282
        %%% erlang:trace, option: procs
289
283
        %%% ---------------------------
290
284
        {trace_ts, Parent, spawn, Pid, Mfa, TS} ->
291
 
            % Update registered procs
292
 
 
 
285
            InformativeMfa = mfa2informative(Mfa),
293
286
            % Update id_information
294
 
            update_information(#information{id = Pid, start = TS, parent = Parent, entry = Mfa}),
 
287
            update_information(#information{id = Pid, start = TS, parent = Parent, entry = InformativeMfa}),
295
288
            update_information_child(Parent, Pid),
296
 
 
297
289
            ok;
298
290
        {trace_ts, Pid, exit, _Reason, TS} ->
299
291
            % Update registered procs
310
302
            % Update id_information
311
303
            update_information(#information{id = Pid, name = Name}),
312
304
            ok;
 
305
        {trace_ts, _Pid, unregister, _Name, _Ts} -> 
 
306
            % Not implemented
 
307
            ok;
313
308
        {trace_ts, Pid, getting_unlinked, _Id, _Ts} when is_pid(Pid) ->
314
309
            % Update id_information
315
310
            ok;
339
334
            io:format("insert_trace, unhandled: ~p~n", [Unhandled])
340
335
    end.
341
336
 
 
337
mfa2informative({erlang, apply, [M, F, Args]})  -> mfa2informative({M, F,Args});
 
338
mfa2informative({erlang, apply, [Fun, Args]}) ->
 
339
    FunInfo = erlang:fun_info(Fun), 
 
340
    M = case proplists:get_value(module, FunInfo, undefined) of
 
341
            []        -> undefined_fun_module;
 
342
            undefined -> undefined_fun_module;
 
343
            Module    -> Module
 
344
        end,
 
345
    F = case proplists:get_value(name, FunInfo, undefined) of
 
346
            []        -> undefined_fun_function;
 
347
            undefined -> undefined_fun_function;
 
348
            Function  -> Function
 
349
        end,
 
350
    mfa2informative({M, F, Args});
 
351
mfa2informative(Mfa) -> Mfa.
 
352
 
342
353
%% consolidate_db() -> bool()
343
354
%% Purpose:
344
355
%%      Check start/stop time
345
356
%%      Activity consistency
346
357
 
347
358
consolidate_db() ->
 
359
    io:format("Consolidating...~n"),
348
360
    % Check start/stop timestamps
349
361
    case select_query({system, start_ts}) of
350
362
        undefined ->
358
370
            update_system_stop_ts(Max);
359
371
        _ -> ok
360
372
    end,
 
373
    consolidate_runnability(),
361
374
    ok.
362
375
 
 
376
consolidate_runnability() ->
 
377
    put({runnable, procs}, undefined),
 
378
    put({runnable, ports}, undefined),
 
379
    consolidate_runnability_loop(ets:first(pdb_activity)).
 
380
 
 
381
consolidate_runnability_loop('$end_of_table') -> ok;
 
382
consolidate_runnability_loop(Key) ->
 
383
    case ets:lookup(pdb_activity, Key) of
 
384
        [#activity{id = Id, state = State } = A] when is_pid(Id) ->
 
385
            Rc = get_runnable_count(procs, State),
 
386
            ets:insert(pdb_activity, A#activity{ runnable_count = Rc});
 
387
        [#activity{id = Id, state = State } = A] when is_port(Id) ->
 
388
            Rc = get_runnable_count(ports, State),
 
389
            ets:insert(pdb_activity, A#activity{ runnable_count = Rc});
 
390
        _ -> throw(consolidate)
 
391
    end,
 
392
    consolidate_runnability_loop(ets:next(pdb_activity, Key)).
 
393
 
363
394
list_all_ts() ->
364
395
    ATs = [ Act#activity.timestamp || 
365
396
        Act <- select_query({activity, []})],
390
421
%%      during the profile duration.
391
422
 
392
423
get_runnable_count(Type, State) ->
393
 
    case get({runnable, Type}) of 
394
 
        undefined when State == active -> 
 
424
    case {get({runnable, Type}), State} of 
 
425
        {undefined, active} -> 
395
426
            put({runnable, Type}, 1),
396
427
            1;
397
 
        N when State == active ->
 
428
        {N, active} ->
398
429
            put({runnable, Type}, N + 1),
399
430
            N + 1;
400
 
        N when State == inactive ->
 
431
        {N, inactive} ->
401
432
            put({runnable, Type}, N - 1),
402
433
            N - 1;
403
434
        Unhandled ->
411
442
            io:format("check_activity_consistency, state flow invalid.~n"),
412
443
            invalid_state;
413
444
        undefined when State == inactive -> 
414
 
            io:format("check_activity_consistency, invalid start state: ~p.~n",[State]),
415
445
            invalid_state;
416
446
        _ ->
417
447
            put({previous_state, Id}, State),
520
550
                true ->
521
551
                    case catch select_query_activity_exact_ts(Options) of
522
552
                        {'EXIT', Reason} ->
523
 
                            io:format("select_query_activity, error: ~p~n", [Reason]),
 
553
                            io:format(" - select_query_activity [ catch! ]: ~p~n", [Reason]),
524
554
                            [];
525
555
                        Match ->
526
556
                            Match
529
559
                    MS = activity_ms(Options),
530
560
                    case catch ets:select(pdb_activity, MS) of
531
561
                        {'EXIT', Reason} ->
532
 
                            io:format("select_query_activity, error: ~p~n", [Reason]),
 
562
                            io:format(" - select_query_activity [ catch! ]: ~p~n", [Reason]),
533
563
                            [];
534
564
                        Match ->
535
565
                            Match
541
571
    end.
542
572
 
543
573
select_query_activity_exact_ts(Options) ->
544
 
    TsMinMember = lists:keymember(ts_min, 1, Options),
545
 
    TsMaxMember = lists:keymember(ts_max, 1, Options),
546
 
    if 
547
 
        TsMinMember == true , TsMaxMember == true ->
548
 
            % Extract timestamps            
549
 
            {value, {ts_min, TsMin}} = lists:keysearch(ts_min, 1, Options),
550
 
            {value, {ts_max, TsMax}} = lists:keysearch(ts_max, 1, Options),
551
 
            
 
574
    case { proplists:get_value(ts_min, Options, undefined), proplists:get_value(ts_max, Options, undefined) } of
 
575
        {undefined, undefined} -> [];
 
576
        {undefined, _        } -> [];
 
577
        {_        , undefined} -> [];
 
578
        {TsMin    , TsMax    } ->
552
579
            % Remove unwanted options
553
 
            Opts = lists:filter(
554
 
                fun(Opt) ->
555
 
                    case Opt of
556
 
                        {ts_min, _ } -> false;
557
 
                        {ts_max, _ } -> false;
558
 
                        {ts_exact, _ } -> false;
559
 
                        _ -> true
560
 
                    end
561
 
                end, Options),
 
580
            Opts = lists_filter([ts_exact], Options),
562
581
            Ms = activity_ms(Opts),
563
 
            Activities = ets:select(pdb_activity, Ms),
564
 
            filter_activities_exact_ts(Activities, TsMin,TsMax);
565
 
        true ->
566
 
            io:format("select_query_activity, error: exact needs ts_min and ts_max~n"),
567
 
            []
568
 
    end.
569
 
 
570
 
filter_activities_exact_ts(Activities, TsMin, TsMax) ->
571
 
    filter_activities_exact_ts_pre(Activities, {undefined, TsMin, TsMax}, []).
572
 
 
573
 
filter_activities_exact_ts_pre([], _, Out) ->
574
 
    lists:reverse(Out);
575
 
filter_activities_exact_ts_pre([A | As], {PreA, TsMin, TsMax}, Out) ->
576
 
    if 
577
 
        A#activity.timestamp < TsMin ->
578
 
            filter_activities_exact_ts_pre(As, {A,TsMin, TsMax}, Out);
579
 
        PreA == undefined ->
580
 
            filter_activities_exact_ts_end(As, {A,TsMin, TsMax}, [ A | Out]);
581
 
        true ->
582
 
            B = PreA#activity{timestamp = TsMin},
583
 
            filter_activities_exact_ts_end(As, {A,TsMin, TsMax}, [A,B])
584
 
    end.
585
 
filter_activities_exact_ts_end([],_, Out) ->
586
 
    lists:reverse(Out);
587
 
filter_activities_exact_ts_end([A | As], {_PreA, TsMin, TsMax}, Out) ->
588
 
    if
589
 
        A#activity.timestamp > TsMin , A#activity.timestamp < TsMax ->
590
 
            filter_activities_exact_ts_end(As, {A,TsMin, TsMax}, [A | Out]);
591
 
        A#activity.timestamp >= TsMax ->
592
 
            B = A#activity{timestamp = TsMax},
593
 
            filter_activities_exact_ts_end([], {A,TsMin, TsMax}, [B | Out]);
594
 
        true ->
595
 
            io:format("filter_activities_exact_ts_pro, error: range problems~n"),
596
 
            []
597
 
    end.
 
582
            case ets:select(pdb_activity, Ms) of
 
583
                % no entries within interval
 
584
                [] -> 
 
585
                    Opts2 = lists_filter([ts_max, ts_min], Opts) ++ [{ts_min, TsMax}],
 
586
                    Ms2   = activity_ms(Opts2),
 
587
                    case ets:select(pdb_activity, Ms2, 1) of
 
588
                        '$end_of_table' -> [];
 
589
                        {[E], _}  -> 
 
590
                            [PrevAct] = ets:lookup(pdb_activity, ets:prev(pdb_activity, E#activity.timestamp)),
 
591
                            [PrevAct#activity{ timestamp = TsMin} , E] 
 
592
                    end;
 
593
                Acts ->
 
594
                    [Head| _] = Acts,
 
595
                    if
 
596
                        Head#activity.timestamp == TsMin -> Acts;
 
597
                        true ->
 
598
                            PrevTs = ets:prev(pdb_activity, Head#activity.timestamp),
 
599
                            case ets:lookup(pdb_activity, PrevTs) of
 
600
                                [] -> Acts;
 
601
                                [PrevAct] -> [PrevAct#activity{timestamp = TsMin}|Acts]
 
602
                            end
 
603
                    end
 
604
            end
 
605
    end.
 
606
 
 
607
lists_filter([], Options) -> Options;
 
608
lists_filter([D|Ds], Options) ->
 
609
    lists_filter(Ds, lists:filter(
 
610
        fun ({Pred, _}) ->
 
611
            if 
 
612
                Pred == D -> false;
 
613
                true      -> true
 
614
            end
 
615
        end, Options)).
598
616
 
599
617
% Options:
600
618
% {ts_min, timestamp()}