~ubuntu-branches/ubuntu/karmic/erlang/karmic-security

« back to all changes in this revision

Viewing changes to lib/percept/test/percept_SUITE.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:
27
27
-export([
28
28
        profile/1,
29
29
        analyze/1,
 
30
        analyze_dist/1,
30
31
        webserver/1
31
32
        ]).
32
33
 
33
34
%% Default timetrap timeout (set in init_per_testcase)
34
 
-define(default_timeout, ?t:minutes(1)).
 
35
-define(default_timeout, ?t:minutes(2)).
35
36
 
36
37
init_per_suite(Config) when is_list(Config) ->
37
38
    Config.
50
51
 
51
52
all(suite) ->
52
53
    % Test cases
53
 
    [   
54
 
        webserver,
 
54
    [   webserver,
55
55
        profile,
56
 
        analyze
57
 
    ].
 
56
        analyze,
 
57
        analyze_dist].
58
58
 
59
59
%%----------------------------------------------------------------------
60
60
%% Tests
86
86
analyze(suite) ->
87
87
    [];
88
88
analyze(doc) ->
89
 
    ["Percept profile test."];
 
89
    ["Percept analyze test."];
90
90
analyze(Config) when is_list(Config) ->
 
91
    Begin = processes(),
91
92
    Path = ?config(data_dir, Config),
92
93
    File = filename:join([Path,"profile_test.dat"]),
93
 
    ?line ok = percept:analyze(File),
94
 
    
 
94
    T0 = erlang:now(),
 
95
    ?line ok = percept:analyze(File),
 
96
    T1 = erlang:now(),
 
97
    Secs = timer:now_diff(T1,T0)/1000000,
 
98
    io:format("percept:analyze/1 took ~.2f s.~n", [Secs]),
 
99
    ?line {stopped, _} = percept_db:stop(),
 
100
    print_remainers(remainers(Begin, processes())),
 
101
    ok.
 
102
 
 
103
analyze_dist(suite) ->
 
104
    [];
 
105
analyze_dist(doc) ->
 
106
    ["Percept analyze distribution test."];
 
107
analyze_dist(Config) when is_list(Config) ->
 
108
    Begin = processes(),
 
109
    Path = ?config(data_dir, Config),
 
110
    File = filename:join([Path,"ipc-dist.dat"]),
 
111
    T0 = erlang:now(),
 
112
    ?line ok = percept:analyze(File),
 
113
    T1 = erlang:now(),
 
114
    Secs = timer:now_diff(T1,T0)/1000000,
 
115
    io:format("percept:analyze/1 took ~.2f s.~n", [Secs]),
 
116
    ?line {stopped, _} = percept_db:stop(),
 
117
    print_remainers(remainers(Begin, processes())),
95
118
    ok.
96
119
 
97
120
%%----------------------------------------------------------------------
101
124
%%----------------------------------------------------------------------
102
125
%% Auxiliary
103
126
%%----------------------------------------------------------------------
 
127
 
 
128
print_remainers([])   -> ok;
 
129
print_remainers([Pid|Pids]) ->
 
130
    io:format("[Pid ~p] [Entry ~p] [Name ~p]~n", [
 
131
        Pid,
 
132
        erlang:process_info(Pid, initial_call),
 
133
        erlang:process_info(Pid, registered_name)
 
134
    ]),
 
135
    print_remainers(Pids).
 
136
 
 
137
remainers(Begin, End) -> remainers(Begin, End, []).
 
138
remainers(_, [], Out) -> lists:reverse(Out);
 
139
remainers(Begin, [Pid|End], Out) ->
 
140
    case lists:member(Pid, Begin) of
 
141
        true  -> remainers(Begin, End, Out);
 
142
        false -> remainers(Begin, End, [Pid|Out])
 
143
    end.
 
144
 
 
145
 
 
146
 
 
147
    
 
148
 
 
149