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

« back to all changes in this revision

Viewing changes to lib/snmp/test/snmp_manager_test.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
1
%% 
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2003-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2003-2010. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%% 
19
19
 
31
31
%% Include files
32
32
%%----------------------------------------------------------------------
33
33
 
34
 
-include("test_server.hrl").
 
34
-include_lib("test_server/include/test_server.hrl").
35
35
-include("snmp_test_lib.hrl").
36
36
-include("snmp_test_data/Test2.hrl").
37
37
 
43
43
%% External exports
44
44
%%----------------------------------------------------------------------
45
45
-export([
46
 
         all/1, 
47
 
         init_per_testcase/2, fin_per_testcase/2,
 
46
        all/0,groups/0,init_per_group/2,end_per_group/2, 
 
47
         init_per_testcase/2, end_per_testcase/2,
48
48
 
49
 
         start_and_stop_tests/1,
 
49
        
50
50
         simple_start_and_stop1/1,
51
51
         simple_start_and_stop2/1,
52
52
         simple_start_and_monitor_crash1/1,
54
54
         notify_started01/1,
55
55
         notify_started02/1,
56
56
 
57
 
         user_tests/1,
 
57
        
58
58
         register_user1/1,
59
59
         
60
 
         agent_tests/1,
 
60
        
61
61
         register_agent1/1,
62
62
         register_agent2/1,
63
63
 
64
 
         misc_tests/1,
 
64
        
65
65
         info/1,
66
66
         
67
 
         request_tests/1, 
 
67
         
68
68
 
69
 
         get_tests/1,
 
69
        
70
70
         simple_sync_get1/1, 
71
71
         simple_sync_get2/1, 
72
72
         simple_async_get1/1, 
73
73
         simple_async_get2/1, 
74
74
 
75
 
         get_next_tests/1,
 
75
        
76
76
         simple_sync_get_next1/1, 
77
77
         simple_sync_get_next2/1, 
78
78
         simple_async_get_next1/1, 
79
79
         simple_async_get_next2/1, 
80
80
 
81
 
         set_tests/1, 
 
81
         
82
82
         simple_sync_set1/1, 
83
83
         simple_sync_set2/1, 
84
84
         simple_async_set1/1, 
85
85
         simple_async_set2/1, 
86
86
 
87
 
         bulk_tests/1, 
 
87
         
88
88
         simple_sync_get_bulk1/1, 
89
89
         simple_sync_get_bulk2/1, 
90
90
         simple_async_get_bulk1/1, 
91
91
         simple_async_get_bulk2/1, 
92
92
 
93
 
         misc_request_tests/1, 
 
93
         
94
94
         misc_async1/1, 
95
95
         misc_async2/1, 
96
96
 
97
97
         discovery/1,
98
98
 
99
 
         event_tests/1, 
 
99
         
100
100
         
101
101
         trap1/1,
102
102
         trap2/1,
109
109
 
110
110
         report/1,
111
111
 
112
 
         tickets/1,
113
 
         otp8015/1,
114
 
         otp8015_1/1
 
112
        
 
113
        
 
114
         otp8015_1/1, 
 
115
        
 
116
         otp8395_1/1
115
117
 
116
118
        ]).
117
119
 
240
242
         simple_async_set2, 
241
243
         simple_sync_get_bulk2, 
242
244
         simple_async_get_bulk2,
243
 
         misc_async2
 
245
         misc_async2,
 
246
         otp8395_1
244
247
        ],
245
 
    Cases = [
246
 
             trap1,
247
 
             trap2,
248
 
             inform1,
249
 
             inform2,
250
 
             inform3,
251
 
             inform4,
252
 
             inform_swarm,
253
 
             report
254
 
            ] ++ OldApiCases ++ NewApiCases,
 
248
    Cases = 
 
249
        [
 
250
         trap1,
 
251
         trap2,
 
252
         inform1,
 
253
         inform2,
 
254
         inform3,
 
255
         inform4,
 
256
         inform_swarm,
 
257
         report
 
258
        ] ++ 
 
259
        OldApiCases ++ 
 
260
        NewApiCases,
255
261
    case lists:member(Case, Cases) of
256
262
        true ->
257
263
            NoAutoInformCases = [inform1, inform2, inform3, inform_swarm], 
265
271
                                    {agent_verbosity,              info}, 
266
272
                                    {agent_net_if_verbosity,       info}],
267
273
                            Verb ++ Config;
 
274
                        Case =:= otp8395_1 ->
 
275
                            [{manager_atl_seqno, true} | Config];
268
276
                        true ->
269
277
                            Config
270
278
                    end,
281
289
            Config
282
290
    end.
283
291
 
284
 
fin_per_testcase(Case, Config) when is_list(Config) ->
 
292
end_per_testcase(Case, Config) when is_list(Config) ->
285
293
    ?DBG("fin [~w] Nodes [1]: ~p", [Case, erlang:nodes()]),
286
294
    Dog    = ?config(watchdog, Config),
287
295
    ?WD_STOP(Dog),
288
296
    Conf1  = lists:keydelete(watchdog, 1, Config),
289
 
    Conf2  = fin_per_testcase2(Case, Conf1),
 
297
    Conf2  = end_per_testcase2(Case, Conf1),
290
298
    ?DBG("fin [~w] Nodes [2]: ~p", [Case, erlang:nodes()]),
291
299
    %%     TopDir = ?config(top_dir, Conf2),
292
300
    %%     ?DEL_DIR(TopDir),
293
301
    Conf2.
294
302
 
295
 
fin_per_testcase2(Case, Config) ->
 
303
end_per_testcase2(Case, Config) ->
296
304
    OldApiCases = 
297
305
        [
298
306
         simple_sync_get1, 
315
323
         simple_async_set2, 
316
324
         simple_sync_get_bulk2, 
317
325
         simple_async_get_bulk2,
318
 
         misc_async2
 
326
         misc_async2,
 
327
         otp8395_1
319
328
        ],
320
 
    Cases = [
321
 
             trap1,
322
 
             trap2,
323
 
             inform1,
324
 
             inform2,
325
 
             inform3,
326
 
             inform4,
327
 
             inform_swarm,
328
 
             report
329
 
            ] ++ OldApiCases ++ NewApiCases,
 
329
    Cases = 
 
330
        [
 
331
         trap1,
 
332
         trap2,
 
333
         inform1,
 
334
         inform2,
 
335
         inform3,
 
336
         inform4,
 
337
         inform_swarm,
 
338
         report
 
339
        ] ++ 
 
340
        OldApiCases ++ 
 
341
        NewApiCases,
330
342
    case lists:member(Case, Cases) of
331
343
        true ->
332
344
            Conf1 = case lists:member(Case, NewApiCases) of
347
359
%% Test case definitions
348
360
%%======================================================================
349
361
 
350
 
all(suite) ->
351
 
    [
352
 
     start_and_stop_tests,
353
 
     misc_tests,
354
 
     user_tests,
355
 
     agent_tests,
356
 
     request_tests,
357
 
     event_tests, 
358
 
     discovery,
359
 
     tickets
360
 
    ].
361
 
 
362
 
start_and_stop_tests(suite) ->
363
 
    [
364
 
     simple_start_and_stop1,
365
 
     simple_start_and_stop2,
366
 
     simple_start_and_monitor_crash1,
367
 
     simple_start_and_monitor_crash2,
368
 
     notify_started01,
369
 
     notify_started02
370
 
    ].
371
 
 
372
 
misc_tests(suite) ->
373
 
    [
374
 
     info
375
 
    ].
376
 
 
377
 
user_tests(suite) ->
378
 
    [
379
 
     register_user1
380
 
    ].
381
 
 
382
 
agent_tests(suite) ->
383
 
    [
384
 
     register_agent1, 
385
 
     register_agent2
386
 
    ].
387
 
 
388
 
request_tests(suite) ->
389
 
    [
390
 
     get_tests,
391
 
     get_next_tests,
392
 
     set_tests,
393
 
     bulk_tests,
394
 
     misc_request_tests
395
 
    ].
396
 
 
397
 
get_tests(suite) ->
398
 
    [
399
 
     simple_sync_get1,
400
 
     simple_sync_get2,
401
 
     simple_async_get1,
402
 
     simple_async_get2
403
 
    ].
404
 
 
405
 
get_next_tests(suite) ->
406
 
    [
407
 
     simple_sync_get_next1,
408
 
     simple_sync_get_next2,
409
 
     simple_async_get_next1,
410
 
     simple_async_get_next2
411
 
    ].
412
 
 
413
 
set_tests(suite) ->
414
 
    [
415
 
     simple_sync_set1,
416
 
     simple_sync_set2,
417
 
     simple_async_set1,
418
 
     simple_async_set2
419
 
    ].
420
 
 
421
 
bulk_tests(suite) ->
422
 
    [
423
 
     simple_sync_get_bulk1,
424
 
     simple_sync_get_bulk2,
425
 
     simple_async_get_bulk1,
426
 
     simple_async_get_bulk2
427
 
    ].
428
 
 
429
 
misc_request_tests(suite) ->
430
 
    [
431
 
     misc_async1,
432
 
     misc_async2
433
 
    ].
434
 
 
435
 
event_tests(suite) ->
436
 
    [
437
 
     trap1,
438
 
     trap2,
439
 
     inform1,
440
 
     inform2,
441
 
     inform3,
442
 
     inform4,
443
 
     inform_swarm,
444
 
     report
445
 
    ].
446
 
 
447
 
tickets(suite) ->
448
 
    [
449
 
     otp8015
450
 
    ].
451
 
 
452
 
otp8015(suite) ->
453
 
    [
454
 
     otp8015_1
455
 
    ].
 
362
all() -> 
 
363
[{group, start_and_stop_tests}, {group, misc_tests},
 
364
 {group, user_tests}, {group, agent_tests},
 
365
 {group, request_tests}, {group, event_tests}, discovery,
 
366
 {group, tickets}].
 
367
 
 
368
groups() -> 
 
369
    [{start_and_stop_tests, [],
 
370
  [simple_start_and_stop1, simple_start_and_stop2,
 
371
   simple_start_and_monitor_crash1,
 
372
   simple_start_and_monitor_crash2, notify_started01,
 
373
   notify_started02]},
 
374
 {misc_tests, [], [info]},
 
375
 {user_tests, [], [register_user1]},
 
376
 {agent_tests, [], [register_agent1, register_agent2]},
 
377
 {request_tests, [],
 
378
  [{group, get_tests}, {group, get_next_tests},
 
379
   {group, set_tests}, {group, bulk_tests},
 
380
   {group, misc_request_tests}]},
 
381
 {get_tests, [],
 
382
  [simple_sync_get1, simple_sync_get2, simple_async_get1,
 
383
   simple_async_get2]},
 
384
 {get_next_tests, [],
 
385
  [simple_sync_get_next1, simple_sync_get_next2,
 
386
   simple_async_get_next1, simple_async_get_next2]},
 
387
 {set_tests, [],
 
388
  [simple_sync_set1, simple_sync_set2, simple_async_set1,
 
389
   simple_async_set2]},
 
390
 {bulk_tests, [],
 
391
  [simple_sync_get_bulk1, simple_sync_get_bulk2,
 
392
   simple_async_get_bulk1, simple_async_get_bulk2]},
 
393
 {misc_request_tests, [], [misc_async1, misc_async2]},
 
394
 {event_tests, [],
 
395
  [trap1, trap2, inform1, inform2, inform3, inform4,
 
396
   inform_swarm, report]},
 
397
 {tickets, [], [{group, otp8015}, {group, otp8395}]},
 
398
 {otp8015, [], [otp8015_1]}, {otp8395, [], [otp8395_1]}].
 
399
 
 
400
init_per_group(_GroupName, Config) ->
 
401
        Config.
 
402
 
 
403
end_per_group(_GroupName, Config) ->
 
404
        Config.
 
405
 
 
406
 
 
407
 
 
408
 
 
409
 
 
410
 
 
411
 
 
412
 
 
413
 
 
414
 
 
415
 
 
416
 
 
417
 
 
418
 
 
419
 
456
420
 
457
421
 
458
422
%%======================================================================
777
741
notify_started02(Config) when is_list(Config) ->
778
742
    process_flag(trap_exit, true),
779
743
    put(tname,ns02),
 
744
 
 
745
    %% <CONDITIONAL-SKIP>
 
746
    %% The point of this is to catch machines running 
 
747
    %% SLES9 (2.6.5)
 
748
    LinuxVersionVerify = 
 
749
        fun() ->
 
750
                case os:cmd("uname -m") of
 
751
                    "i686" ++ _ ->
 
752
%%                      io:format("found an i686 machine, "
 
753
%%                                "now check version~n", []),
 
754
                        case os:version() of
 
755
                            {2, 6, Rev} when Rev >= 16 ->
 
756
                                true;
 
757
                            {2, Min, _} when Min > 6 ->
 
758
                                true;
 
759
                            {Maj, _, _} when Maj > 2 ->
 
760
                                true;
 
761
                            _ ->
 
762
                                false
 
763
                        end;
 
764
                    _ ->
 
765
                        true
 
766
                end
 
767
        end,
 
768
    Skippable = [{unix, [{linux, LinuxVersionVerify}]}],
 
769
    Condition = fun() -> ?OS_BASED_SKIP(Skippable) end,
 
770
    ?NON_PC_TC_MAYBE_SKIP(Config, Condition),
 
771
    %% </CONDITIONAL-SKIP>
 
772
 
780
773
    p("starting with Config: ~n~p", [Config]),
781
774
 
782
775
    ConfDir = ?config(manager_conf_dir, Config),
1372
1365
simple_sync_get2(Config) when is_list(Config) ->
1373
1366
    process_flag(trap_exit, true),
1374
1367
    put(tname, ssg2),
 
1368
    do_simple_get(Config).
 
1369
 
 
1370
do_simple_get(Config) ->
1375
1371
    p("starting with Config: ~p~n", [Config]),
1376
1372
 
1377
1373
    Node       = ?config(manager_node, Config),
1386
1382
    Oids2 = [[sysObjectID, 0], [sysDescr, 0], [sysUpTime, 0]],
1387
1383
    ?line ok = do_simple_get(Node, TargetName, Oids2),
1388
1384
    ok.
1389
 
 
 
1385
    
1390
1386
do_simple_get(Node, TargetName, Oids) ->
1391
1387
    ?line {ok, Reply, Rem} = mgr_user_sync_get(Node, TargetName, Oids),
1392
1388
 
4438
4434
 
4439
4435
 
4440
4436
%%======================================================================
 
4437
 
 
4438
otp8395_1(doc) -> ["OTP-8395:1 - simple get with ATL sequence numbering."];
 
4439
otp8395_1(suite) -> [];
 
4440
otp8395_1(Config) when is_list(Config) ->
 
4441
    process_flag(trap_exit, true),
 
4442
    put(tname, otp8395_1),
 
4443
    do_simple_get(Config).
 
4444
 
 
4445
 
 
4446
%%======================================================================
4441
4447
%% async snmp utility functions
4442
4448
%%======================================================================
4443
4449
 
5063
5069
    ServerVerbosity    = get_opt(manager_server_verbosity,     Conf0, trace),
5064
5070
    NetIfVerbosity     = get_opt(manager_net_if_verbosity,     Conf0, trace),
5065
5071
 
 
5072
    AtlSeqNo           = get_opt(manager_atl_seqno,            Conf0, false),
 
5073
 
5066
5074
    Env = [{versions,                     Vsns},
5067
5075
           {inform_request_behaviour,     IRB},
5068
5076
           {audit_trail_log, [{type,      read_write},
5069
5077
                              {dir,       AtlDir},
5070
5078
                              {size,      {10240, 10}},
5071
 
                              {repair,    true}]},
 
5079
                              {repair,    true},
 
5080
                              {seqno,     AtlSeqNo}]},
5072
5081
           {config,          [{dir,       ConfDir}, 
5073
5082
                              {db_dir,    DbDir}, 
5074
5083
                              {verbosity, ConfigVerbosity}]},