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

« back to all changes in this revision

Viewing changes to lib/snmp/test/snmp_test_server.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:
1
1
%%<copyright>
2
 
%% <year>2003-2007</year>
 
2
%% <year>2003-2008</year>
3
3
%% <holder>Ericsson AB, All Rights Reserved</holder>
4
4
%%</copyright>
5
5
%%<legalnotice>
25
25
 
26
26
-compile(export_all).
27
27
 
 
28
-export([
 
29
         run/1, run/2,
 
30
 
 
31
         error/3,
 
32
         skip/3,
 
33
         fatal_skip/3,
 
34
 
 
35
         init_per_testcase/2,
 
36
         fin_per_testcase/2
 
37
        ]).
 
38
 
28
39
-include("snmp_test_lib.hrl").
29
40
 
 
41
-define(GLOBAL_LOGGER, snmp_global_logger).
 
42
-define(TEST_CASE_SUP, snmp_test_case_supervisor).
 
43
 
30
44
-define(d(F,A),d(F,A,?LINE)).
31
45
 
 
46
-ifndef(snmp_priv_dir).
 
47
-define(snmp_priv_dir, "run-" ++ timestamp()).
 
48
-endif.
 
49
 
32
50
 
33
51
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
34
52
%% Evaluates a test case or test suite
37
55
%%     {Mod, Fun, ExpectedRes, ActualRes}
38
56
%%----------------------------------------------------------------------
39
57
 
40
 
t(Case) ->
41
 
    io:format("~n", []),
42
 
    ?d("t(~p) -> entry", [Case]),
43
 
    Res = t(Case, default_config()),
44
 
    display_result(Res),
45
 
    Res;
46
 
t([Mod, Fun]) when atom(Mod), atom(Fun) ->
47
 
    ?d("t([~w,~w]:1) -> entry", [Mod, Fun]),
48
 
    Res = t({Mod, Fun}, default_config()),
49
 
    display_result(Res),
50
 
    ?d("t(~p,~p) -> Res:~n~p", [Mod, Fun, Res]),
 
58
run([Mod, Fun]) when is_atom(Mod) andalso is_atom(Fun) ->
 
59
    Res = run({Mod, Fun}, default_config(Mod)),
 
60
    display_result(Res),
 
61
    Res;
 
62
run({Mod, _Fun} = Case) when is_atom(Mod) ->
 
63
    io:format("~n", []),
 
64
    Res = run(Case, default_config(Mod)),
 
65
    display_result(Res),
 
66
    Res;
 
67
run(Mod) when is_atom(Mod) ->
 
68
    io:format("~n", []),
 
69
    Res = run(Mod, default_config(Mod)),
 
70
    display_result(Res),
 
71
    Res;
 
72
run([Mod]) when is_atom(Mod) ->
 
73
    io:format("~n", []),
 
74
    Res = run(Mod, default_config(Mod)),
 
75
    display_result(Res),
51
76
    Res.
52
77
    
53
78
 
54
 
t({Mod, Fun}, Config) when atom(Mod), atom(Fun), list(Config) ->
55
 
    ?d("t(~p,~p) -> entry", [Mod, Fun]),
 
79
run({Mod, Fun}, Config) when is_atom(Mod) andalso 
 
80
                             is_atom(Fun) andalso 
 
81
                             is_list(Config) ->
 
82
    ?d("run(~p,~p) -> entry", [Mod, Fun]),
56
83
    case (catch apply(Mod, Fun, [suite])) of
57
84
        [] ->
58
85
            io:format("~n~n*** Eval: ~p ***************~n", 
64
91
                    [Other]
65
92
            end;
66
93
 
67
 
        Cases when list(Cases) ->
 
94
        Cases when is_list(Cases) ->
68
95
            io:format("~n*** Expand: ~p ...~n", [{Mod, Fun}]),
69
 
            Map = fun(Case) when atom(Case)-> {Mod, Case};
 
96
            Map = fun(Case) when is_atom(Case) -> {Mod, Case};
70
97
                     (Case) -> Case
71
98
                  end,
72
 
            t(lists:map(Map, Cases), Config);
 
99
            run(lists:map(Map, Cases), Config);
73
100
 
74
 
        {req, _, SubCases} when list(SubCases) ->
 
101
        {conf, InitSuite, Cases, FinishSuite} when is_atom(InitSuite) andalso 
 
102
                                                   is_list(Cases) andalso 
 
103
                                                   is_atom(FinishSuite) ->
 
104
            ?d("run -> conf: "
 
105
               "~n   InitSuite:   ~p"
 
106
               "~n   Cases:       ~p"
 
107
               "~n   FinishSuite: ~p", [InitSuite, Cases, FinishSuite]),
 
108
            do_suite(Mod, InitSuite, Cases, FinishSuite, Config);
 
109
                    
 
110
        {req, _, SubCases} when is_list(SubCases) ->
 
111
            ?d("run -> req: "
 
112
               "~n   SubCases: ~p", [SubCases]),
75
113
            do_subcases(Mod, Fun, SubCases, Config, []);
76
114
                    
77
115
        {req, _, Conf} ->
 
116
            ?d("run -> req: "
 
117
               "~n   Conf: ~p", [Conf]),
78
118
            do_subcases(Mod, Fun, [Conf], Config, []);
79
119
                    
80
120
        {'EXIT', {undef, _}} ->
85
125
            io:format("~n*** Ignoring:   ~p: ~p~n", [{Mod, Fun}, Error]),
86
126
            [{failed, {Mod, Fun}, Error}]
87
127
    end;
88
 
t(Mod, Config) when atom(Mod), list(Config) ->
89
 
    ?d("t(~p) -> entry whith"
90
 
        "~n   Config: ~p", [Mod, Config]),
91
 
    t({Mod, all}, Config);
92
 
t(Cases, Config) when list(Cases), list(Config) ->
93
 
    ?d("t -> entry whith"
94
 
        "~n   Cases:  ~p"
95
 
        "~n   Config: ~p", [Cases, Config]),
96
 
    Errors = [t(Case, Config) || Case <- Cases],
97
 
    ?d("t -> Errors: ~n~p", [Errors]),
 
128
 
 
129
run(Mod, Config) when is_atom(Mod) andalso is_list(Config) ->
 
130
    run({Mod, all}, Config);
 
131
 
 
132
run(Cases, Config) when is_list(Cases) andalso is_list(Config) ->
 
133
    Errors = [run(Case, Config) || Case <- Cases],
98
134
    lists:append(Errors);
99
 
t(Bad, Config) ->
100
 
    ?d("t -> entry with"
101
 
        "~n   Bad:    ~p"
102
 
        "~n   Config: ~p", [Bad, Config]),
 
135
 
 
136
run(Bad, _Config) ->
103
137
    [{badarg, Bad, ok}].
104
138
 
105
139
 
106
 
do_case(M,F,C) ->
107
 
    io:format("~n~n*** Eval: ~p ***************~n", [{M, F}]),
108
 
    case eval(M, F, C) of
109
 
        {ok, _, _} ->
110
 
            [];
111
 
        Other ->
112
 
            [Other]
 
140
do_suite(Mod, Init, Cases, Finish, Config0) ->
 
141
    ?d("do_suite -> entry with"
 
142
       "~n   Mod:     ~p"
 
143
       "~n   Init:    ~p"
 
144
       "~n   Cases:   ~p"
 
145
       "~n   Finish:  ~p"
 
146
       "~n   Config0: ~p", [Mod, Init, Cases, Finish, Config0]),
 
147
    case (catch apply(Mod, Init, [Config0])) of
 
148
        Config when is_list(Config) ->
 
149
            io:format("~n*** Expand: ~p ...~n", [Mod]),
 
150
            Map = fun(Case) when is_atom(Case) -> {Mod, Case};
 
151
                     (Case) -> Case
 
152
                  end,
 
153
            Res = run(lists:map(Map, Cases), Config),
 
154
            (catch apply(Mod, Finish, [Config])),
 
155
            Res;
 
156
 
 
157
        {'EXIT', {skipped, Reason}} ->
 
158
            io:format(" => skipping: ~p~n", [Reason]),
 
159
            SkippedCases = 
 
160
                [{skipped, {Mod, Case}, suite_init_skipped} || Case <- Cases],
 
161
            lists:flatten([[{skipped, {Mod, Init}, Reason}],
 
162
                           SkippedCases, 
 
163
                           [{skipped, {Mod, Finish}, suite_init_skipped}]]);
 
164
 
 
165
        Error ->
 
166
            io:format(" => init (~p) failed: ~n~p~n", [Init, Error]),
 
167
            InitResult = 
 
168
                [{failed, {Mod, Init}, Error}],
 
169
            SkippedCases = 
 
170
                [{skipped, {Mod, Case}, suite_init_failed} || Case <- Cases],
 
171
            FinResult = 
 
172
                case (catch apply(Mod, Finish, [Config0])) of
 
173
                    ok ->
 
174
                        [];
 
175
                    FinConfig when is_list(FinConfig) ->
 
176
                        [];
 
177
                    FinError ->
 
178
                        [{failed, {Mod, Finish}, FinError}]
 
179
                end,
 
180
            lists:flatten([InitResult, SkippedCases, FinResult])
 
181
 
113
182
    end.
114
 
    
 
183
 
115
184
 
116
185
do_subcases(_Mod, _Fun, [], _Config, Acc) ->
117
 
    ?d("t -> do_subcases([]) -> entry with"
118
 
        "~n   Acc: ~p", [Acc]),
119
186
    lists:flatten(lists:reverse(Acc));
120
 
do_subcases(Mod, Fun, [{conf, Init, Cases, Finish}|SubCases], Config, Acc) ->
121
 
    ?d("t -> do_subcases(conf) -> entry with"
122
 
        "~n   Init:   ~p"
123
 
        "~n   Cases:  ~p"
124
 
        "~n   Finish: ~p", [Init, Cases, Finish]),
 
187
do_subcases(Mod, Fun, [{conf, Init, Cases, Finish}|SubCases], Config, Acc) 
 
188
  when is_atom(Init) andalso is_list(Cases) andalso is_atom(Finish) ->
125
189
    R = case (catch apply(Mod, Init, [Config])) of
126
 
            Conf when list(Conf) ->
 
190
            Conf when is_list(Conf) ->
127
191
                io:format("~n*** Expand: ~p ...~n", [{Mod, Fun}]),
128
 
                Map = fun(Case) when atom(Case) -> {Mod, Case};
 
192
                Map = fun(Case) when is_atom(Case) -> {Mod, Case};
129
193
                         (Case) -> Case
130
194
                      end,
131
 
                Res = t(lists:map(Map, Cases), Conf),
 
195
                Res = run(lists:map(Map, Cases), Conf),
132
196
                (catch apply(Mod, Finish, [Conf])),
133
197
                Res;
134
198
            
141
205
                (catch apply(Mod, Finish, [Config])),
142
206
                [{failed, {Mod, Fun}, Error}]
143
207
        end,
144
 
    ?d("t -> do_subcases(conf):"
145
 
        "~n   R: ~p", [R]),
146
208
    do_subcases(Mod, Fun, SubCases, Config, [R|Acc]);
147
209
do_subcases(Mod, Fun, [SubCase|SubCases], Config, Acc) when atom(SubCase) ->
148
 
    ?d("t -> do_subcases(~p)", [SubCase]),
149
210
    R = do_case(Mod, SubCase, Config),
150
211
    do_subcases(Mod, Fun, SubCases,Config, [R|Acc]).
151
212
 
152
213
 
 
214
do_case(M, F, C) ->
 
215
    io:format("~n~n*** Eval: ~p ***************~n", [{M, F}]),
 
216
    case eval(M, F, C) of
 
217
        {ok, _, _} ->
 
218
            [];
 
219
        Other ->
 
220
            [Other]
 
221
    end.
 
222
 
153
223
 
154
224
eval(Mod, Fun, Config) ->
155
 
    ?d("eval -> entry with"
156
 
        "~n   Mod: ~p"
157
 
        "~n   Fun: ~p", [Mod, Fun]),
158
 
    global:register_name(inets_test_case_sup, self()),
159
 
    Flag = process_flag(trap_exit, true),
 
225
    Flag    = process_flag(trap_exit, true),
 
226
    global:register_name(?TEST_CASE_SUP, self()),
160
227
    Config2 = Mod:init_per_testcase(Fun, Config),
161
 
    Pid = spawn_link(?MODULE, do_eval, [self(), Mod, Fun, Config2]),
162
 
    R = wait_for_evaluator(Pid, Mod, Fun, Config2, []),
 
228
    Self    = self(), 
 
229
    Eval    = fun() -> do_eval(Self, Mod, Fun, Config2) end,
 
230
    Pid     = spawn_link(Eval),
 
231
    R       = wait_for_evaluator(Pid, Mod, Fun, Config2, []),
163
232
    Mod:fin_per_testcase(Fun, Config2),
164
 
    global:unregister_name(inets_test_case_sup),
 
233
    global:unregister_name(?TEST_CASE_SUP),
165
234
    process_flag(trap_exit, Flag),
166
 
    ?d("eval -> exit with:"
167
 
        "~n   R: ~p", [R]),
168
235
    R.
169
236
 
170
237
wait_for_evaluator(Pid, Mod, Fun, Config, Errors) ->
173
240
        {'EXIT', _Watchdog, watchdog_timeout} ->
174
241
            io:format("*** ~s WATCHDOG TIMEOUT~n", [Pre]), 
175
242
            exit(Pid, kill),
176
 
            {failed, {Mod,Fun}, watchdog_timeout};
177
 
        {done, Pid, ok} when Errors == [] ->
 
243
            {failed, {Mod, Fun}, watchdog_timeout};
 
244
        {done, Pid, ok} when Errors =:= [] ->
178
245
            io:format("*** ~s OK~n", [Pre]),
179
246
            {ok, {Mod, Fun}, Errors};
180
 
        {done, Pid, {ok, _}} when Errors == [] ->
 
247
        {done, Pid, {ok, _}} when Errors =:= [] ->
181
248
            io:format("*** ~s OK~n", [Pre]),
182
249
            {ok, {Mod, Fun}, Errors};
183
250
        {done, Pid, Fail} ->
184
251
            io:format("*** ~s FAILED~n~p~n", [Pre, Fail]),
185
 
            {failed, {Mod,Fun}, Fail};
 
252
            {failed, {Mod, Fun}, Fail};
186
253
        {'EXIT', Pid, {skipped, Reason}} -> 
187
254
            io:format("*** ~s SKIPPED~n~p~n", [Pre, Reason]),
188
255
            {skipped, {Mod, Fun}, Errors};
195
262
   end.
196
263
 
197
264
do_eval(ReplyTo, Mod, Fun, Config) ->
198
 
    ?d("do_eval -> entry with"
199
 
        "~n   ReplyTo: ~p"
200
 
        "~n   Mod:     ~p"
201
 
        "~n   Fun:     ~p"
202
 
        "~n   Config:  ~p"
203
 
        "~nat"
204
 
        "~n   ~p", [ReplyTo, Mod, Fun, Config, erlang:now()]),
205
265
    case (catch apply(Mod, Fun, [Config])) of
206
266
        {'EXIT', {skipped, Reason}} ->
207
267
            ReplyTo ! {'EXIT', self(), {skipped, Reason}};
208
268
        Other ->
209
 
            ?d("do_eval -> entry with"
210
 
                "~n   Other: ~p", [Other]),
211
269
            ReplyTo ! {done, self(), Other}
212
270
    end,
213
 
    ?d("do_eval -> case ~p completed at ~p", [Fun, erlang:now()]),
214
271
    unlink(ReplyTo),
215
272
    exit(shutdown).
216
273
 
218
275
display_result([]) ->    
219
276
    io:format("TEST OK~n", []);
220
277
 
221
 
display_result(Errors) when list(Errors) ->
 
278
display_result(Errors) when is_list(Errors) ->
222
279
    Nyi     = [MF || {nyi, MF, _} <- Errors],
223
280
    Skipped = [{MF, Reason} || {skipped, MF, Reason} <- Errors],
224
281
    Crashed = [{MF, Reason} || {crashed, MF, Reason} <- Errors],
269
326
%% Stores the result in the process dictionary if mismatch
270
327
 
271
328
error(Actual, Mod, Line) ->
272
 
    global:send(inets_global_logger, {failed, Mod, Line}),
 
329
    global:send(?GLOBAL_LOGGER, {failed, Mod, Line}),
273
330
    log("<ERROR> Bad result: ~p~n", [Actual], Mod, Line),
274
 
    case global:whereis_name(inets_test_case_sup) of
 
331
    case global:whereis_name(?TEST_CASE_SUP) of
275
332
        undefined -> 
276
333
            ignore;
277
334
        Pid -> 
284
341
    exit({skipped, {Actual, Mod, Line}}).
285
342
 
286
343
fatal_skip(Actual, Mod, Line) ->
287
 
    ?d("fatal_skip -> entry with"
288
 
      "~n   Actual: ~p"
289
 
      "~n   Mod:    ~p"
290
 
      "~n   Line:  ~p", [Actual, Mod, Line]),
291
344
    error(Actual, Mod, Line),
292
 
    
293
345
    exit(shutdown).
294
346
 
295
347
 
296
348
log(Format, Args, Mod, Line) ->
297
 
    case global:whereis_name(inets_global_logger) of
 
349
    case global:whereis_name(?GLOBAL_LOGGER) of
298
350
        undefined ->
299
351
            io:format(user, "~p(~p): " ++ Format, [Mod, Line] ++ Args);
300
352
        Pid ->
305
357
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
306
358
%% Test server callbacks
307
359
 
308
 
init_per_testcase(Case, Config) ->
309
 
    ?d("init_per_testcase(~p) -> entry", [Case]),
310
 
    global:register_name(megaco_global_logger, group_leader()),
 
360
init_per_testcase(_Case, Config) ->
 
361
    global:register_name(?GLOBAL_LOGGER, group_leader()),
311
362
    Config.
312
363
 
313
 
fin_per_testcase(Case, Config) ->
314
 
    ?d("fin_per_testcase(~p) -> entry", [Case]),
315
 
    global:unregister_name(megaco_global_logger),
 
364
fin_per_testcase(_Case, _Config) ->
 
365
    global:unregister_name(?GLOBAL_LOGGER),
316
366
    ok.
317
367
 
318
368
 
319
369
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
320
370
%% Internal utility functions
321
371
 
322
 
default_config() ->
323
 
    [{nodes, default_nodes()}].
324
 
 
325
 
default_nodes() ->    
326
 
    mk_nodes(2, []).
327
 
 
328
 
mk_nodes(0, Nodes) ->
329
 
    Nodes;
330
 
mk_nodes(N, []) ->
331
 
    mk_nodes(N - 1, [node()]);
332
 
mk_nodes(N, Nodes) when N > 0 ->
333
 
    Head = hd(Nodes),
334
 
    [Name, Host] = node_to_name_and_host(Head),
335
 
    Nodes ++ [mk_node(I, Name, Host) || I <- lists:seq(1, N)].
336
 
 
337
 
mk_node(N, Name, Host) ->
338
 
    list_to_atom(lists:concat([Name ++ integer_to_list(N) ++ "@" ++ Host])).
339
 
    
340
 
%% Returns [Name, Host]    
341
 
node_to_name_and_host(Node) ->
342
 
    string:tokens(atom_to_list(Node), [$@]).
343
 
 
344
 
start_nodes([Node | Nodes], File, Line) ->
345
 
    case net_adm:ping(Node) of
346
 
        pong ->
347
 
            start_nodes(Nodes, File, Line);
348
 
        pang ->
349
 
            [Name, Host] = node_to_name_and_host(Node),
350
 
            Args = [],
351
 
            
352
 
            case ?STARTL_NODE(Host, Name, Args) of
353
 
                {ok, NewNode} when NewNode == Node ->
354
 
                    start_nodes(Nodes, File, Line);
355
 
                Other ->
356
 
                    fatal_skip({cannot_start_node, Node, Other}, File, Line)
357
 
            end
358
 
    end;
359
 
start_nodes([], File, Line) ->
360
 
    ok.
 
372
default_config(Mod) ->
 
373
    PrivDir0 = ?snmp_priv_dir,
 
374
    case filename:pathtype(PrivDir0) of
 
375
        absolute ->
 
376
            ok;
 
377
        _ ->
 
378
            case file:make_dir(Mod) of
 
379
                ok ->
 
380
                    ok;
 
381
                {error, eexist} ->
 
382
                    ok
 
383
            end,
 
384
            PrivDir = filename:join(Mod, PrivDir0), 
 
385
            case file:make_dir(PrivDir) of
 
386
                ok ->
 
387
                    ok;
 
388
                {error, eexist} ->
 
389
                    ok;
 
390
                Error ->
 
391
                    ?FAIL({failed_creating_subsuite_top_dir, Error})
 
392
            end,
 
393
            [{priv_dir, PrivDir}]
 
394
    end.
361
395
 
362
396
 
363
397
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
364
398
 
365
399
d(F, A, L) ->
366
 
    %% d(true, F, A, L).
367
 
    d(get(dbg), F, A, L).
 
400
    d(true, F, A, L).
 
401
    %% d(get(dbg), F, A, L).
368
402
 
369
403
d(true, F, A, L) ->
370
 
    io:format("STS:~p:~p " ++ F ++ "~n", [self(),L|A]);
 
404
    io:format("STS[~w] ~p " ++ F ++ "~n", [L,self()|A]);
371
405
d(_, _, _, _) ->
372
406
    ok.
373
407
 
 
408
timestamp() ->
 
409
    {Date, Time}     = calendar:now_to_datetime( now() ),
 
410
    {YYYY, MM, DD}   = Date,
 
411
    {Hour, Min, Sec} = Time,
 
412
    FormatDate =
 
413
        io_lib:format("~.4w-~.2.0w-~.2.0w_~.2.0w.~.2.0w.~.2.0w",
 
414
                      [YYYY,MM,DD,Hour,Min,Sec]),
 
415
    lists:flatten(FormatDate).
 
416