~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/snmp/test/snmp_test.erl

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%% ``The contents of this file are subject to the Erlang Public License,
2
 
%% Version 1.1, (the "License"); you may not use this file except in
3
 
%% compliance with the License. You should have received a copy of the
4
 
%% Erlang Public License along with this software. If not, it can be
5
 
%% retrieved via the world wide web at http://www.erlang.org/.
6
 
%% 
7
 
%% Software distributed under the License is distributed on an "AS IS"
8
 
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
9
 
%% the License for the specific language governing rights and limitations
10
 
%% under the License.
11
 
%% 
12
 
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
13
 
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
14
 
%% AB. All Rights Reserved.''
15
 
%% 
16
 
%%     $Id$
17
 
%%
18
 
-module(snmp_test).
19
 
 
20
 
%% TODO
21
 
%% * Test fault-tolerance (kill master etc)
22
 
%%
23
 
 
24
 
-compile(export_all).
25
 
 
26
 
-define(application, snmp).
27
 
 
28
 
-include_lib("kernel/include/file.hrl").
29
 
-include("test_server.hrl").
30
 
-include("snmp_test_lib.hrl").
31
 
-define(SNMP_USE_V3, true).
32
 
-include_lib("snmp/include/snmp_types.hrl").
33
 
 
34
 
 
35
 
-define(klas1, [1,3,6,1,2,1,7]).
36
 
-define(klas2, [1,3,6,1,2,1,9]).
37
 
-define(klas3, [1,3,6,1,2,1,8,1]).
38
 
-define(klas4, [1,3,6,1,2,1,8,4]).
39
 
-define(sa, [1,3,6,1,4,1,193,2]).
40
 
-define(system, [1,3,6,1,2,1,1]).
41
 
-define(snmp, [1,3,6,1,2,1,11]).
42
 
-define(snmpTraps, [1,3,6,1,6,3,1,1,5]).
43
 
-define(ericsson, [1,3,6,1,4,1,193]).
44
 
-define(testTrap, [1,3,6,1,2,1,15,0]).
45
 
-define(xDescr, [1,3,6,1,2,1,17,1]).
46
 
-define(xDescr2, [1,3,6,1,2,1,17,2]).
47
 
 
48
 
-define(active, 1).
49
 
-define(notInService, 2).
50
 
-define(notReady, 3).
51
 
-define(createAndGo, 4).
52
 
-define(createAndWait, 5).
53
 
-define(destroy, 6).
54
 
 
55
 
-define(TRAP_UDP, "5000").
56
 
 
57
 
-define(tooBigStr, "ffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffff").
58
 
 
59
 
-define(str(X), snmp_pdus:bits_to_str(X)).
60
 
 
61
 
-define(break(), begin io:format(user, "break at line ~w: pid: ~p\n",
62
 
                                 [?LINE, self()]),
63
 
                       receive cont -> ok end
64
 
                 end).
65
 
 
66
 
 
67
 
-import(snmp_mgr, [gn/1, g/1, s/1, gb/3]).
68
 
-define(v1_2(V1,V2),
69
 
               case get(vsn) of
70
 
                   v1 -> V1;
71
 
                   _ -> V2
72
 
               end).
73
 
                        
74
 
-define(v1_2_3(V1,V2,V3),
75
 
               case get(vsn) of
76
 
                   v1 -> V1;
77
 
                   v2 -> V2;
78
 
                   _ -> V3
79
 
               end).
80
 
                        
81
 
machine() ->
82
 
    from($@, atom_to_list(node())).
83
 
 
84
 
all(suite) -> {req,
85
 
               [mnesia, distribution,
86
 
                {local_slave_nodes, 2}, {time, 360}],
87
 
               [{conf, init_all, cases(), finish_all}]}.
88
 
 
89
 
init_per_testcase(Case, Config) when list(Config) ->
90
 
    Dog = ?t:timetrap(?t:minutes(6)),
91
 
    [{watchdog, Dog}|Config].
92
 
 
93
 
fin_per_testcase(Case, Config) when list(Config) ->
94
 
    Dog = ?config(watchdog, Config),
95
 
    ?t:timetrap_cancel(Dog),
96
 
    Config.
97
 
 
98
 
cases() ->
99
 
    case ?OSTYPE() of
100
 
        vxworks ->
101
 
            %% No crypto app, so skip v3 testcases
102
 
            [
103
 
             app_info, 
104
 
             test_v1, 
105
 
             test_v2, 
106
 
             test_v1_v2, 
107
 
             test_multi_threaded, 
108
 
             mib_storage, 
109
 
             tickets
110
 
            ];
111
 
        _Else ->
112
 
            %%              [mib_storage]
113
 
            [
114
 
             app_info, 
115
 
             test_v1, 
116
 
             test_v2, 
117
 
             test_v1_v2, 
118
 
             test_v3, 
119
 
             test_multi_threaded, 
120
 
             mib_storage, 
121
 
             test_compiler, 
122
 
             tickets
123
 
            ]
124
 
    end.
125
 
 
126
 
 
127
 
%%%-----------------------------------------------------------------
128
 
%%% The test case structure is as follows:
129
 
%%%
130
 
%%% init_all - starts mnesia, 
131
 
%%%      
132
 
%%%    init_v1 - starts agent
133
 
%%%       simple
134
 
%%%       big  - e.g. starts/stops subagent, load/unloads mibs
135
 
%%%       init_mul
136
 
%%%          mul_get
137
 
%%%          mul_set
138
 
%%%          <etc>
139
 
%%%       finish_mul
140
 
%%%       <etc>
141
 
%%%    finish_v1
142
 
%%%
143
 
%%%    init_v2 - starts agent
144
 
%%%    finish_v2
145
 
%%%      
146
 
%%%    init_bilingual - starts agent
147
 
%%%    finish_bilingual
148
 
%%%      
149
 
%%% finish_all
150
 
%%%
151
 
%%% There is still one problem with these testsuites.  If one test
152
 
%%% fails, it may not be possible to run some other cases, as it
153
 
%%% may have e.g. created some row or loaded some table, that it
154
 
%%% didn't undo (since it failed).
155
 
%%%-----------------------------------------------------------------
156
 
 
157
 
init_all(Config) when list(Config) ->
158
 
    ?LOG("init_all -> entry with"
159
 
         "~n   Config: ~p",[Config]),
160
 
 
161
 
    %% -- 
162
 
    %% Start nodes
163
 
    %% 
164
 
 
165
 
    ?line {ok, SaNode}  = start_node(snmp_sa),
166
 
    ?line {ok, MgrNode} = start_node(snmp_mgr),
167
 
 
168
 
 
169
 
    %% -- 
170
 
    %% Create necessary files
171
 
    %% 
172
 
 
173
 
    Dir = ?config(priv_dir, Config),
174
 
    ?DBG("init_all -> Dir ~p", [Dir]),
175
 
 
176
 
    DataDir = ?config(data_dir, Config),
177
 
    ?DBG("init_all -> DataDir ~p", [DataDir]),
178
 
 
179
 
    file:make_dir(MgrDir = filename:join(Dir, "mgr_dir/")),
180
 
    ?DBG("init_all -> MgrDir ~p", [MgrDir]),
181
 
 
182
 
    file:make_dir(AgentDir = filename:join(Dir, "agent_dir/")),
183
 
    ?DBG("init_all -> AgentDir ~p", [AgentDir]),
184
 
 
185
 
    file:make_dir(SaDir = filename:join(Dir, "sa_dir/")),
186
 
    ?DBG("init_all -> SaDir ~p", [SaDir]),
187
 
 
188
 
 
189
 
    %% -- 
190
 
    %% Start and initiate mnesia
191
 
    %% 
192
 
 
193
 
    ?DBG("init_all -> load application mnesia", []),
194
 
    ?line ok = application:load(mnesia),
195
 
 
196
 
    ?DBG("init_all -> load application mnesia on node ~p", [SaNode]),
197
 
    ?line ok = rpc:call(SaNode, application, load, [mnesia]),
198
 
    
199
 
    ?DBG("init_all -> application mnesia: set_env dir",[]),
200
 
    ?line application_controller:set_env(mnesia, dir, 
201
 
                                         filename:join(Dir, "Mnesia1")),
202
 
 
203
 
    ?DBG("init_all -> application mnesia: set_env dir on node ~p",[SaNode]),
204
 
    ?line rpc:call(SaNode, application_controller, set_env,
205
 
                   [mnesia, dir,  filename:join(Dir, "Mnesia2")]),
206
 
 
207
 
    ?DBG("init_all -> create mnesia schema",[]),
208
 
    ?line ok = mnesia:create_schema([SaNode, node()]),
209
 
    
210
 
    ?DBG("init_all -> start application mnesia",[]),
211
 
    ?line ok = application:start(mnesia),
212
 
 
213
 
    ?DBG("init_all -> start application mnesia on ~p",[SaNode]),
214
 
    ?line ok = rpc:call(SaNode, application, start, [mnesia]),
215
 
    {ok, Ip} = snmp_misc:ip(net_adm:localhost()),
216
 
    [{snmp_sa, SaNode}, {snmp_mgr, MgrNode}, {agent_dir, AgentDir ++ "/"},
217
 
     {mgr_dir, MgrDir ++ "/"},
218
 
     {sa_dir, SaDir ++ "/"}, {mib_dir, DataDir}, {ip, Ip} | Config].
219
 
 
220
 
finish_all(Config) when list(Config) ->
221
 
    SaNode = ?config(snmp_sa, Config),
222
 
    MgrNode = ?config(snmp_mgr, Config),
223
 
    stop_node(SaNode),
224
 
    stop_node(MgrNode),
225
 
    application:stop(mnesia).
226
 
 
227
 
start_v1_agent(Config) when list(Config) ->
228
 
    start_agent(Config, [v1]).
229
 
 
230
 
start_v1_agent(Config,Opts) when list(Config), list(Opts)  ->
231
 
    start_agent(Config, [v1], Opts).
232
 
 
233
 
start_v2_agent(Config) when list(Config) ->
234
 
    start_agent(Config, [v2]).
235
 
 
236
 
start_v3_agent(Config) when list(Config) ->
237
 
    start_agent(Config, [v3]).
238
 
 
239
 
start_bilingual_agent(Config) when list(Config) ->
240
 
    start_agent(Config, [v1,v2]).
241
 
 
242
 
start_multi_threaded_agent(Config) when list(Config) ->
243
 
    start_agent(Config, [v2], [{multi_threaded, true}]).
244
 
 
245
 
stop_agent(Config) when list(Config) ->
246
 
    ?LOG("stop_agent -> entry with"
247
 
         "~n   Config: ~p",[Config]),
248
 
 
249
 
    {Sup, Par} = ?config(snmp_sup, Config),
250
 
    ?DBG("stop_agent -> attempt to stop (sup) ~p",[Sup]),
251
 
    stop_sup(Sup, Par),
252
 
 
253
 
    {Sup2, Par2} = ?config(snmp_sub, Config),
254
 
    ?DBG("stop_agent -> attempt to stop (sub) ~p",[Sup2]),
255
 
    stop_sup(Sup2, Par2),
256
 
 
257
 
    ?DBG("stop_agent -> done - now cleanup config", []),
258
 
    C1 = lists:keydelete(snmp_sup, 1, Config),
259
 
    lists:keydelete(snmp_sub, 1, C1).
260
 
 
261
 
stop_sup(Pid, Parent) ->
262
 
    ?LOG("attempt to stop ~p with parent ~p", [Pid, Parent]),
263
 
    Ref = erlang:monitor(process, Pid),
264
 
    Pid ! {'EXIT', Parent, shutdown}, % usch
265
 
    await_stopped(Pid, Ref).
266
 
 
267
 
await_stopped(Pid, Ref) ->
268
 
    receive
269
 
        {'DOWN', Ref, process, Pid, Reason} ->
270
 
            ?DBG("received down message for ~p", [Pid]),
271
 
            ok
272
 
    after 10000 ->
273
 
            ?INF("await_stopped -> timeout for ~p",[Pid]),
274
 
            erlang:demonitor(Ref),
275
 
            ?FAIL({failed_stop,Pid})
276
 
    end.
277
 
 
278
 
 
279
 
start_agent(Config, Vsn) ->
280
 
    start_agent(Config, Vsn, []).
281
 
start_agent(Config, Vsn, Opts) -> 
282
 
    ?LOG("start_agent -> entry (~p) with"
283
 
        "~n   Config: ~p"
284
 
        "~n   Vsn:    ~p"
285
 
        "~n   Opts:   ~p",[node(), Config, Vsn, Opts]),
286
 
 
287
 
    ?line AgentDir = ?config(agent_dir, Config),
288
 
    ?line SaNode   = ?config(snmp_sa,   Config),
289
 
 
290
 
    ?DBG("start_agent -> start crypto app",[]),
291
 
    ?line Crypto = case os:type() of
292
 
                       vxworks ->
293
 
                           no_crypto;
294
 
                       _ ->
295
 
                           crypto:start()
296
 
                   end,
297
 
    ?DBG("start_agent -> crypto start result: ~n\t~p",[Crypto]),
298
 
 
299
 
    ?DBG("start_agent -> unload snmp",[]),
300
 
    ?line application:unload(snmp),
301
 
    ?DBG("start_agent -> load snmp",[]),
302
 
    ?line application:load(snmp),
303
 
    ?DBG("start_agent -> (env) set the proper version",[]),
304
 
    ?line lists:foreach(fun(V) -> 
305
 
                                application_controller:set_env(snmp,V,true),
306
 
                                ?DBG("start_agent -> set ~p true",[V])
307
 
                        end,
308
 
                        Vsn),
309
 
    ?line lists:foreach(fun(V) -> 
310
 
                                application_controller:set_env(snmp,V,false),
311
 
                                ?DBG("start_agent -> set ~p false",[V])
312
 
                        end,
313
 
                        [v1,v2,v3] -- Vsn),
314
 
 
315
 
    Args = [{supervisor_verbosity,     silence},
316
 
            {master_agent_verbosity,   log},
317
 
            {net_if_verbosity,         log},
318
 
            {mibserver_verbosity,      log},
319
 
            {symbolic_store_verbosity, silence},
320
 
            {name,{local,snmp_master_agent}},{snmp_vsn,Vsn}|Opts],
321
 
    process_flag(trap_exit,true),
322
 
 
323
 
    ?DBG("start_agent -> (supervisor) start master agent",[]),
324
 
    Sup = case (catch snmp_supervisor:start_master(AgentDir,AgentDir,Args)) of
325
 
              {ok,S} ->
326
 
                  ?DBG("start_agent -> started, Sup: ~p",[S]),
327
 
                  S;
328
 
              
329
 
%             {error, {already_started, Pid}} ->
330
 
%                 ?DBG("start_agent -> already started: ~p:~n~p",
331
 
%                     [Pid, process_info(Pid)]),
332
 
%                 exit({already_started,Pid});
333
 
              
334
 
              O ->
335
 
                  ?DBG("start_agent -> unknown result: ~p~n"
336
 
                         "\n when Crypto: ~p",[O,Crypto]),
337
 
                  %% Get info about the apps we depend on
338
 
                  CryptoInfo = {crypto_info,crypto_running(),Crypto},
339
 
                  MnesiaInfo = {mnesia_info,mnesia_running()},
340
 
                  exit({start_failed,O,[CryptoInfo,MnesiaInfo]})
341
 
          end,
342
 
 
343
 
%     ?DBG("start_agent -> set trace verbosity on master agent",[]),
344
 
%     ?line snmp:verbosity(snmp_master_agent,trace),
345
 
%     ?DBG("start_agent -> set trace verbosity on net if",[]),
346
 
%     ?line snmp:verbosity(snmp_net_if,trace),
347
 
%     ?DBG("start_agent -> set trace verbosity on mib server",[]),
348
 
%     ?line snmp:verbosity(snmp_mib,trace),
349
 
 
350
 
    ?DBG("start_agent -> unlink from supervisor",[]),
351
 
    ?line unlink(Sup),
352
 
    ?line SaDir = ?config(sa_dir, Config),
353
 
    ?DBG("start_agent -> (rpc) start sub on ~p",[SaNode]),
354
 
    ?line {ok, Sub} = rpc:call(SaNode, ?MODULE, start_sub, [SaDir]),
355
 
    ?DBG("start_agent -> done",[]),
356
 
    ?line [{snmp_sup, {Sup, self()}}, {snmp_sub, Sub} | Config].
357
 
 
358
 
 
359
 
%% Test if application is running
360
 
mnesia_running() -> app_running(mnesia).
361
 
crypto_running() -> app_running(crypto).
362
 
 
363
 
%% Test if the application 'App' is running
364
 
app_running(App) -> 
365
 
    Apps = application:which_applications(),
366
 
    lists:keymember(App,1,Apps).
367
 
 
368
 
 
369
 
start_sub(Dir) ->
370
 
    ?DBG("start_sub -> entry",[]),
371
 
    {ok, P} = snmp_supervisor:start_sub(Dir),
372
 
    unlink(P),
373
 
    {ok, {P, self()}}.
374
 
 
375
 
create_tables(SaNode) ->
376
 
    ?line {atomic, ok} = mnesia:create_table([{name, friendsTable2},
377
 
                                              {ram_copies, [SaNode]},
378
 
                                              {snmp, [{key, integer}]},
379
 
                                              {attributes, [a1,a2,a3]}]),
380
 
    ?line {atomic, ok} = mnesia:create_table([{name, kompissTable2},
381
 
                                              {ram_copies, [SaNode]},
382
 
                                              {snmp, [{key, integer}]},
383
 
                                              {attributes, [a1,a2,a3]}]),
384
 
    ?line {atomic, ok} = mnesia:create_table([{name, snmp_variables},
385
 
                                              {attributes, [a1,a2]}]).
386
 
 
387
 
delete_tables() ->
388
 
    mnesia:delete_table(friendsTable2),
389
 
    mnesia:delete_table(kompissTable2),
390
 
    mnesia:delete_table(snmp_variables).
391
 
 
392
 
%% Creation is done in runtime!
393
 
delete_mib_storage_mnesia_tables() ->
394
 
    mnesia:delete_table(snmp_mib_data),
395
 
    mnesia:delete_table(snmp_mib_tree),
396
 
    mnesia:delete_table(snmp_symbolic_store).
397
 
 
398
 
%%-----------------------------------------------------------------
399
 
%% A test case is always one of:
400
 
%%   - v1 specific case
401
 
%%   - v2 specific case
402
 
%%   - v1 and v2 case
403
 
%% All v1 specific cases are prefixed with v1_, and all v2 with
404
 
%% v2_.  E.g. v1_trap/v2_trap.
405
 
%%
406
 
%% All other cases are shared. However, the testserver uses the name
407
 
%% of the case to generate a file for that case.  The same case cannot
408
 
%% be used in different configurations in the same suite.  Therefore
409
 
%% all these functions exists in two variants, the base function
410
 
%% <base>, and a second version <base>_2.  There may be several
411
 
%% versions as well, <base>_N.
412
 
%%-----------------------------------------------------------------
413
 
mib_storage(suite) -> [
414
 
                       mib_storage_ets, 
415
 
                       mib_storage_dets, 
416
 
                       mib_storage_mnesia,
417
 
                       mib_storage_size_check_ets,
418
 
                       mib_storage_size_check_dets,
419
 
                       mib_storage_size_check_mnesia,
420
 
                       mib_storage_varm_dets,
421
 
                       mib_storage_varm_mnesia
422
 
                      ].
423
 
 
424
 
mib_storage_ets(suite) -> {req, [], {conf, init_mib_storage_ets, 
425
 
                                     mib_storage_ets_cases(), 
426
 
                                     finish_mib_storage_ets}}.
427
 
 
428
 
mib_storage_dets(suite) -> {req, [], {conf, init_mib_storage_dets, 
429
 
                                     mib_storage_dets_cases(), 
430
 
                                     finish_mib_storage_dets}}.
431
 
 
432
 
mib_storage_mnesia(suite) -> {req, [], {conf, init_mib_storage_mnesia, 
433
 
                                        mib_storage_mnesia_cases(), 
434
 
                                        finish_mib_storage_mnesia}}.
435
 
 
436
 
mib_storage_size_check_ets(suite) -> 
437
 
    {req, [], {conf, 
438
 
               init_size_check_mse, 
439
 
               mse_size_check_cases(), 
440
 
               finish_size_check_mse}}.
441
 
 
442
 
mib_storage_size_check_dets(suite) -> 
443
 
    {req, [], {conf, 
444
 
               init_size_check_msd, 
445
 
               msd_size_check_cases(), 
446
 
               finish_size_check_msd}}.
447
 
 
448
 
mib_storage_size_check_mnesia(suite) -> 
449
 
    {req, [], {conf, 
450
 
               init_size_check_msm, 
451
 
               msm_size_check_cases(), 
452
 
               finish_size_check_msm}}.
453
 
 
454
 
mib_storage_varm_dets(suite) -> 
455
 
    {req, [], {conf, 
456
 
               init_varm_mib_storage_dets, 
457
 
               varm_mib_storage_dets_cases(), 
458
 
               finish_varm_mib_storage_dets}}.
459
 
 
460
 
mib_storage_varm_mnesia(suite) -> 
461
 
    {req, [], {conf, 
462
 
               init_varm_mib_storage_mnesia, 
463
 
               varm_mib_storage_mnesia_cases(), 
464
 
               finish_varm_mib_storage_mnesia}}.
465
 
 
466
 
mib_storage_ets_cases() ->
467
 
    [mse_simple, 
468
 
     mse_v1_processing, 
469
 
     mse_big, 
470
 
     mse_big2, 
471
 
     mse_loop_mib, 
472
 
     mse_api, 
473
 
     mse_sa_register, 
474
 
     mse_v1_trap, 
475
 
     mse_sa_error, 
476
 
     mse_next_across_sa, 
477
 
     mse_undo,
478
 
     mse_standard_mib, 
479
 
     mse_community_mib, 
480
 
     mse_framework_mib, 
481
 
     mse_target_mib, 
482
 
     mse_notification_mib, 
483
 
     mse_view_based_acm_mib, 
484
 
     mse_sparse_table].
485
 
 
486
 
mib_storage_dets_cases() ->
487
 
    [msd_simple, 
488
 
     msd_v1_processing, 
489
 
     msd_big, 
490
 
     msd_big2, 
491
 
     msd_loop_mib, 
492
 
     msd_api, 
493
 
     msd_sa_register, 
494
 
     msd_v1_trap, 
495
 
     msd_sa_error, 
496
 
     msd_next_across_sa, 
497
 
     msd_undo,
498
 
     msd_standard_mib,
499
 
     msd_community_mib, 
500
 
     msd_framework_mib, 
501
 
     msd_target_mib, 
502
 
     msd_notification_mib, 
503
 
     msd_view_based_acm_mib, 
504
 
     msd_sparse_table].
505
 
 
506
 
mib_storage_mnesia_cases() ->
507
 
    [msm_simple, 
508
 
     msm_v1_processing, 
509
 
     msm_big, 
510
 
     msm_big2, 
511
 
     msm_loop_mib, 
512
 
     msm_api, 
513
 
     msm_sa_register, 
514
 
     msm_v1_trap, 
515
 
     msm_sa_error, 
516
 
     msm_next_across_sa, 
517
 
     msm_undo,
518
 
     msm_standard_mib, 
519
 
     msm_community_mib, 
520
 
     msm_framework_mib, 
521
 
     msm_target_mib, 
522
 
     msm_notification_mib, 
523
 
     msm_view_based_acm_mib, 
524
 
     msm_sparse_table].
525
 
 
526
 
mse_size_check_cases() ->
527
 
    [mse_size_check].
528
 
 
529
 
msd_size_check_cases() ->
530
 
    [msd_size_check].
531
 
 
532
 
msm_size_check_cases() ->
533
 
    [msm_size_check].
534
 
 
535
 
varm_mib_storage_dets_cases() ->
536
 
    [msd_varm_mib_start].
537
 
 
538
 
varm_mib_storage_mnesia_cases() ->
539
 
    [msm_varm_mib_start].
540
 
 
541
 
init_mib_storage_ets(Config) when list(Config) ->
542
 
    ?LOG("init_mib_storage_ets -> entry", []),
543
 
    MibStorage = {mib_storage,ets},
544
 
    init_ms(Config, [MibStorage]).
545
 
 
546
 
init_mib_storage_dets(Config) when list(Config) ->
547
 
    ?LOG("init_mib_storage_ets -> entry", []),
548
 
    ?line AgentDir = ?GCONF(agent_dir, Config),
549
 
    MibStorage = {mib_storage,{dets,AgentDir}},
550
 
    init_ms(Config, [MibStorage]).
551
 
 
552
 
init_mib_storage_mnesia(Config) when list(Config) ->
553
 
    ?LOG("init_mib_storage_ets -> entry", []),
554
 
    MibStorage = {mib_storage,{mnesia,[]}},
555
 
    init_ms(Config, [MibStorage]).
556
 
 
557
 
init_ms(Config, Opts) when list(Config) ->
558
 
    ?LOG("init_mib_storage_ets -> entry", []),
559
 
    ?line SaNode   = ?GCONF(snmp_sa, Config),
560
 
    ?line create_tables(SaNode),
561
 
    ?line AgentDir = ?GCONF(agent_dir, Config),
562
 
    ?line MgrDir   = ?GCONF(mgr_dir, Config),
563
 
    ?line Ip       = ?GCONF(ip, Config),
564
 
    ?line config([1], MgrDir, AgentDir, tuple_to_list(Ip), tuple_to_list(Ip)),
565
 
    MasterAgentVerbosity = {master_agent_verbosity,   trace},
566
 
    MibsVerbosity        = {mibserver_verbosity,      trace},
567
 
    SymStoreVerbosity    = {symbolic_store_verbosity, trace},
568
 
    Opts1 = [MasterAgentVerbosity,MibsVerbosity,SymStoreVerbosity|Opts],
569
 
    [{vsn, v1} | start_v1_agent(Config,Opts1)].
570
 
 
571
 
init_size_check_mse(Config) when list(Config) ->
572
 
    MibStorage = {mib_storage, ets},
573
 
    init_size_check_ms(Config, [MibStorage]).
574
 
 
575
 
init_size_check_msd(Config) when list(Config) ->
576
 
    AgentDir   = ?GCONF(agent_dir, Config),
577
 
    MibStorage = {mib_storage, {dets, AgentDir}},
578
 
    init_size_check_ms(Config, [MibStorage]).
579
 
 
580
 
init_size_check_msm(Config) when list(Config) ->
581
 
    MibStorage = {mib_storage, {mnesia,[]}},
582
 
    init_size_check_ms(Config, [MibStorage]).
583
 
 
584
 
init_size_check_ms(Config, Opts) when list(Config) ->
585
 
    SaNode = ?GCONF(snmp_sa, Config),
586
 
    create_tables(SaNode),
587
 
    AgentDir = ?GCONF(agent_dir, Config),
588
 
    MgrDir = ?GCONF(mgr_dir, Config),
589
 
    Ip = ?GCONF(ip, Config),
590
 
    ?line ok = 
591
 
        config([3], MgrDir, AgentDir, tuple_to_list(Ip), tuple_to_list(Ip)),
592
 
    [{vsn, v3} | start_agent(Config, [v3], Opts)].
593
 
 
594
 
init_varm_mib_storage_dets(Config) when list(Config) ->
595
 
    ?LOG("init_varm_mib_storage_dets -> entry", []),
596
 
    ?line SaNode   = ?GCONF(snmp_sa, Config),
597
 
    ?line create_tables(SaNode),
598
 
    ?line AgentDir = ?GCONF(agent_dir, Config),
599
 
    ?line MgrDir   = ?GCONF(mgr_dir, Config),
600
 
    ?line Ip       = ?GCONF(ip, Config),
601
 
    ?line config([1], MgrDir, AgentDir, tuple_to_list(Ip), tuple_to_list(Ip)),
602
 
    MibStorage           = {mib_storage,{dets,AgentDir}},
603
 
    MasterAgentVerbosity = {master_agent_verbosity,   trace},
604
 
    MibsVerbosity        = {mibserver_verbosity,      trace},
605
 
    SymStoreVerbosity    = {symbolic_store_verbosity, trace},
606
 
    Opts = [MibStorage,MasterAgentVerbosity,MibsVerbosity,SymStoreVerbosity],
607
 
    [{vsn, v1}, {agent_opts,Opts} | Config].
608
 
 
609
 
init_varm_mib_storage_mnesia(Config) when list(Config) ->
610
 
    ?LOG("init_varm_mib_storage_mnesia -> entry", []),
611
 
    ?line SaNode   = ?GCONF(snmp_sa, Config),
612
 
    ?line create_tables(SaNode),
613
 
    ?line AgentDir = ?GCONF(agent_dir, Config),
614
 
    ?line MgrDir   = ?GCONF(mgr_dir, Config),
615
 
    ?line Ip       = ?GCONF(ip, Config),
616
 
    ?line config([1], MgrDir, AgentDir, tuple_to_list(Ip), tuple_to_list(Ip)),
617
 
    MibStorage           = {mib_storage,{mnesia,[]}},
618
 
    MasterAgentVerbosity = {master_agent_verbosity,   trace},
619
 
    MibsVerbosity        = {mibserver_verbosity,      trace},
620
 
    SymStoreVerbosity    = {symbolic_store_verbosity, trace},
621
 
    Opts = [MibStorage,MasterAgentVerbosity,MibsVerbosity,SymStoreVerbosity],
622
 
    [{vsn, v1}, {agent_opts,Opts} | Config].
623
 
 
624
 
finish_mib_storage_ets(Config) when list(Config) ->
625
 
    ?LOG("finish_mib_storage_ets -> entry", []),
626
 
    delete_tables(),
627
 
    C1 = stop_agent(Config),
628
 
    delete_files(C1),
629
 
    C2 = lists:keydelete(vsn, 1, C1),
630
 
    lists:keydelete(agent_opts, 1, C2).
631
 
 
632
 
finish_mib_storage_dets(Config) when list(Config) ->
633
 
    ?LOG("finish_mib_storage_dets -> entry", []),
634
 
    delete_tables(),
635
 
    C1 = stop_agent(Config),
636
 
    delete_files(C1),
637
 
    C2 = lists:keydelete(vsn, 1, C1),
638
 
    lists:keydelete(agent_opts, 1, C2).
639
 
 
640
 
finish_mib_storage_mnesia(Config) when list(Config) ->
641
 
    ?LOG("finish_mib_storage_mnesia -> entry", []),
642
 
    delete_tables(),
643
 
    delete_mib_storage_mnesia_tables(),
644
 
    C1 = stop_agent(Config),
645
 
    delete_files(C1),
646
 
    C2 = lists:keydelete(vsn, 1, C1),
647
 
    lists:keydelete(agent_opts, 1, C2).
648
 
 
649
 
finish_varm_mib_storage_dets(Config) when list(Config) ->
650
 
    ?LOG("finish_varm_mib_storage_dets -> entry", []),
651
 
    delete_tables(),
652
 
    %% C1 = stop_agent(Config), % In case something went wrong...
653
 
    delete_files(Config),
654
 
    C2 = lists:keydelete(vsn, 1, Config),
655
 
    lists:keydelete(agent_opts, 1, C2).
656
 
 
657
 
finish_varm_mib_storage_mnesia(Config) when list(Config) ->
658
 
    ?LOG("finish_varm_mib_storage_mnesia -> entry", []),
659
 
    delete_tables(),
660
 
    delete_mib_storage_mnesia_tables(),
661
 
    %% C1 = stop_agent(Config), % In case something went wrong...
662
 
    delete_files(Config),
663
 
    C2 = lists:keydelete(vsn, 1, Config),
664
 
    lists:keydelete(agent_opts, 1, C2).
665
 
 
666
 
finish_size_check_mse(Config) when list(Config) ->
667
 
    finish_size_check_ms(Config).
668
 
 
669
 
finish_size_check_msd(Config) when list(Config) ->
670
 
    finish_size_check_ms(Config).
671
 
 
672
 
finish_size_check_msm(Config) when list(Config) ->
673
 
    finish_size_check_ms(Config).
674
 
 
675
 
finish_size_check_ms(Config) when list(Config) ->
676
 
    delete_tables(),
677
 
    C1 = stop_agent(Config),
678
 
    delete_files(C1),
679
 
    C2 = lists:keydelete(vsn, 1, C1).
680
 
 
681
 
 
682
 
%% These are just interface functions to fool the test server
683
 
mse_simple(X)         -> simple(X).
684
 
mse_v1_processing(X)  -> v1_processing(X).
685
 
mse_big(X)            -> big(X).
686
 
mse_big2(X)           -> big2(X).
687
 
mse_loop_mib(X)       -> loop_mib(X).
688
 
mse_api(X)            -> api(X).
689
 
mse_sa_register(X)    -> sa_register(X).
690
 
mse_v1_trap(X)        -> v1_trap(X).
691
 
mse_sa_error(X)       -> sa_error(X).
692
 
mse_next_across_sa(X) -> next_across_sa(X).
693
 
mse_undo(X)           -> undo(X).
694
 
mse_standard_mib(X)   -> snmp_standard_mib(X).
695
 
mse_community_mib(X)  -> snmp_community_mib(X).
696
 
mse_framework_mib(X)  -> snmp_framework_mib(X).
697
 
mse_target_mib(X)         -> snmp_target_mib(X).
698
 
mse_notification_mib(X)   -> snmp_notification_mib(X).
699
 
mse_view_based_acm_mib(X) -> snmp_view_based_acm_mib(X).
700
 
mse_sparse_table(X)   -> sparse_table(X).
701
 
 
702
 
msd_simple(X)         -> simple(X).
703
 
msd_v1_processing(X)  -> v1_processing(X).
704
 
msd_big(X)            -> big(X).
705
 
msd_big2(X)           -> big2(X).
706
 
msd_loop_mib(X)       -> loop_mib(X).
707
 
msd_api(X)            -> api(X).
708
 
msd_sa_register(X)    -> sa_register(X).
709
 
msd_v1_trap(X)        -> v1_trap(X).
710
 
msd_sa_error(X)       -> sa_error(X).
711
 
msd_next_across_sa(X) -> next_across_sa(X).
712
 
msd_undo(X)           -> undo(X).
713
 
msd_standard_mib(X)   -> snmp_standard_mib(X).
714
 
msd_community_mib(X)  -> snmp_community_mib(X).
715
 
msd_framework_mib(X)  -> snmp_framework_mib(X).
716
 
msd_target_mib(X)         -> snmp_target_mib(X).
717
 
msd_notification_mib(X)   -> snmp_notification_mib(X).
718
 
msd_view_based_acm_mib(X) -> snmp_view_based_acm_mib(X).
719
 
msd_sparse_table(X)   -> sparse_table(X).
720
 
 
721
 
msm_simple(X)         -> simple(X).
722
 
msm_v1_processing(X)  -> v1_processing(X).
723
 
msm_big(X)            -> big(X).
724
 
msm_big2(X)           -> big2(X).
725
 
msm_loop_mib(X)       -> loop_mib(X).
726
 
msm_api(X)            -> api(X).
727
 
msm_sa_register(X)    -> sa_register(X).
728
 
msm_v1_trap(X)        -> v1_trap(X).
729
 
msm_sa_error(X)       -> sa_error(X).
730
 
msm_next_across_sa(X) -> next_across_sa(X).
731
 
msm_undo(X)           -> undo(X).
732
 
msm_standard_mib(X)   -> snmp_standard_mib(X).
733
 
msm_community_mib(X)  -> snmp_community_mib(X).
734
 
msm_framework_mib(X)  -> snmp_framework_mib(X).
735
 
msm_target_mib(X)         -> snmp_target_mib(X).
736
 
msm_notification_mib(X)   -> snmp_notification_mib(X).
737
 
msm_view_based_acm_mib(X) -> snmp_view_based_acm_mib(X).
738
 
msm_sparse_table(X)       -> sparse_table(X).
739
 
 
740
 
 
741
 
mse_size_check(X)     -> p("mse_size_check..."), ms_size_check(X).
742
 
msd_size_check(X)     -> p("msd_size_check..."), ms_size_check(X).
743
 
msm_size_check(X)     -> p("msm_size_check..."), ms_size_check(X).
744
 
 
745
 
msd_varm_mib_start(X) -> p("msd_varm_mib_start..."), varm_mib_start(X).
746
 
msm_varm_mib_start(X) -> p("msm_varm_mib_start..."), varm_mib_start(X).
747
 
 
748
 
ms_size_check(suite) -> [];
749
 
ms_size_check(Config) when list(Config) ->
750
 
    p("ms_size_check..."),
751
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
752
 
    ?LOG("mib server size check...", []),
753
 
 
754
 
    ?line load_master("Test2"),
755
 
    ?line load_master("TestTrap"),
756
 
    ?line load_master("TestTrapv2"),
757
 
    ?line load_master_std("OTP-SNMPEA-MIB"),
758
 
    ?line load_master_std("SNMP-COMMUNITY-MIB"),
759
 
    ?line load_master_std("SNMP-FRAMEWORK-MIB"),
760
 
    ?line load_master_std("SNMP-MPD-MIB"),
761
 
    ?line load_master_std("SNMP-NOTIFICATION-MIB"),
762
 
    ?line load_master_std("SNMP-TARGET-MIB"),
763
 
    ?line load_master_std("SNMP-USER-BASED-SM-MIB"),
764
 
    ?line load_master_std("SNMP-VIEW-BASED-ACM-MIB"),
765
 
    ?line load_master_std("SNMPv2-MIB"),
766
 
    ?line load_master_std("SNMPv2-TM"),
767
 
 
768
 
    ?SLEEP(2000),
769
 
 
770
 
    ?line display_memory_usage(),
771
 
 
772
 
    ?line unload_master("OTP-SNMPEA-MIB"),
773
 
    ?line unload_master("SNMP-COMMUNITY-MIB"),
774
 
    ?line unload_master("SNMP-FRAMEWORK-MIB"),
775
 
    ?line unload_master("SNMP-MPD-MIB"),
776
 
    ?line unload_master("SNMP-NOTIFICATION-MIB"),
777
 
    ?line unload_master("SNMP-TARGET-MIB"),
778
 
    ?line unload_master("SNMP-USER-BASED-SM-MIB"),
779
 
    ?line unload_master("SNMP-VIEW-BASED-ACM-MIB"),
780
 
    ?line unload_master("SNMPv2-MIB"),
781
 
    ?line unload_master("SNMPv2-TM"),
782
 
 
783
 
    ?line unload_master("TestTrapv2"),
784
 
    ?line unload_master("TestTrap"),
785
 
    ?line unload_master("Test2"),
786
 
 
787
 
    ok.
788
 
 
789
 
 
790
 
varm_mib_start(suite) -> [];
791
 
varm_mib_start(Config) when list(Config) ->
792
 
    p("varm_mib_start..."),
793
 
    ?LOG("varm_mib_start -> entry", []),
794
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
795
 
 
796
 
    %% Start the agent
797
 
    Opts = ?GCONF(agent_opts, Config),
798
 
    Config1 = start_v1_agent(Config, Opts),
799
 
 
800
 
    %% Sleep some in order for the agent to start properly
801
 
    ?DBG("varm_mib_start -> sleep some (before loading mobs)", []),
802
 
    ?SLEEP(5000),
803
 
 
804
 
    %% Load all the mibs
805
 
    HardwiredMibs = loaded_mibs(),
806
 
    ?DBG("varm_mib_start -> load all mibs", []),
807
 
    ?line load_master_std("SNMP-COMMUNITY-MIB"),
808
 
    ?line load_master_std("SNMP-FRAMEWORK-MIB"),
809
 
    ?line load_master_std("SNMP-TARGET-MIB"),
810
 
    ?line load_master_std("SNMP-NOTIFICATION-MIB"),
811
 
 
812
 
    %% Unload the hardwired mibs
813
 
    ?DBG("varm_mib_start -> sleep some (before unloading hardwired mibs)", []),
814
 
    ?SLEEP(1000),
815
 
    ?DBG("varm_mib_start -> unload (hardwired) mibs", []),
816
 
    ?line unload_mibs(HardwiredMibs),    %% unload hardwired
817
 
 
818
 
    ?DBG("varm_mib_start -> sleep some (before stopping agent)", []),
819
 
    ?SLEEP(1000),
820
 
 
821
 
    %% Stop the agent (without deleting the stored files)
822
 
    ?DBG("varm_mib_start -> stop the agent", []),
823
 
    Config2 = stop_agent(Config1),
824
 
 
825
 
    %% Sleep some in order for the agent to stop properly
826
 
    ?DBG("varm_mib_start -> sleep some (before re-starting the agent)", []),
827
 
    ?SLEEP(5000),
828
 
 
829
 
    %% Start the agent (again)
830
 
    ?DBG("varm_mib_start -> start the agent", []),
831
 
    Config3 = start_v1_agent(Config2, Opts),
832
 
 
833
 
    ?DBG("varm_mib_start -> sleep some (before starting tests)", []),
834
 
    ?SLEEP(5000),
835
 
 
836
 
    %% Perform the test(s)
837
 
    ?DBG("varm_mib_start -> perform the tests", []),
838
 
    try_test(snmp_community_mib),
839
 
    try_test(snmp_framework_mib),
840
 
    try_test(snmp_target_mib),
841
 
    try_test(snmp_notification_mib),
842
 
 
843
 
    %% Stop the agent (without deleting the stored files)
844
 
    ?DBG("varm_mib_start -> stop the agent", []),
845
 
    stop_agent(Config3),
846
 
    ok.
847
 
 
848
 
 
849
 
app_info(suite) -> [];
850
 
app_info(Config) when list(Config) ->
851
 
    SnmpDir   = app_dir(snmp),
852
 
    SslDir    = app_dir(ssl),
853
 
    CryptoDir = app_dir(crypto),
854
 
    Attr  = snmp:module_info(attributes),
855
 
    AppVsn = 
856
 
        case lists:keysearch(app_vsn, 1, Attr) of
857
 
            {value, {app_vsn, V}} ->
858
 
                V;
859
 
            false ->
860
 
                "undefined"
861
 
        end,
862
 
    io:format("Root dir: ~s~n"
863
 
              "SNMP:   Application dir: ~s~n"
864
 
              "        Application ver: ~s~n"
865
 
              "SSL:    Application dir: ~s~n"
866
 
              "CRYPTO: Application dir: ~s~n", 
867
 
              [code:root_dir(), SnmpDir, AppVsn, SslDir, CryptoDir]),
868
 
    ok.
869
 
 
870
 
app_dir(App) ->
871
 
    case code:lib_dir(App) of
872
 
        D when list(D) ->
873
 
            filename:basename(D);
874
 
        {error, _Reason} ->
875
 
            "undefined"
876
 
    end.
877
 
 
878
 
 
879
 
test_v1(suite) -> {req, [], {conf, init_v1, v1_cases(), finish_v1}}.
880
 
 
881
 
%v1_cases() -> [loop_mib];
882
 
v1_cases() ->
883
 
    [
884
 
     simple, 
885
 
     db_notify_client,
886
 
     v1_processing, 
887
 
     big, 
888
 
     big2, 
889
 
     loop_mib, 
890
 
     api, 
891
 
     subagent, 
892
 
     mnesia, 
893
 
     multiple_reqs,
894
 
     sa_register, 
895
 
     v1_trap, 
896
 
     sa_error, 
897
 
     next_across_sa, 
898
 
     undo, 
899
 
     reported_bugs,
900
 
     standard_mibs, 
901
 
     sparse_table, 
902
 
     cnt_64, 
903
 
     opaque,
904
 
     % opaque].
905
 
    
906
 
     change_target_addr_config
907
 
    ].  
908
 
 
909
 
init_v1(Config) when list(Config) ->
910
 
    ?line SaNode = ?config(snmp_sa, Config),
911
 
    ?line create_tables(SaNode),
912
 
    ?line AgentDir = ?config(agent_dir, Config),
913
 
    ?line MgrDir = ?config(mgr_dir, Config),
914
 
    ?line Ip = ?config(ip, Config),
915
 
    ?line config([1], MgrDir, AgentDir, tuple_to_list(Ip), tuple_to_list(Ip)),
916
 
    [{vsn, v1} | start_v1_agent(Config)].
917
 
 
918
 
finish_v1(Config) when list(Config) ->
919
 
    delete_tables(),
920
 
    C1 = stop_agent(Config),
921
 
    delete_files(C1),
922
 
    C2 = lists:keydelete(vsn, 1, C1).
923
 
 
924
 
test_v2(suite) -> {req, [], {conf, init_v2, v2_cases(), finish_v2}}.
925
 
 
926
 
%v2_cases() -> [loop_mib_2];
927
 
v2_cases() ->
928
 
    [simple_2, v2_processing, big_2, big2_2, loop_mib_2,
929
 
     api_2, subagent_2, mnesia_2,
930
 
     multiple_reqs_2, sa_register_2, v2_trap, v2_inform, sa_error_2,
931
 
     next_across_sa_2, undo_2, reported_bugs_2, standard_mibs_2,
932
 
     v2_types, implied, sparse_table_2, cnt_64_2, opaque_2, v2_caps].
933
 
 
934
 
init_v2(Config) when list(Config) ->
935
 
    SaNode = ?config(snmp_sa, Config),
936
 
    create_tables(SaNode),
937
 
    AgentDir = ?config(agent_dir, Config),
938
 
    MgrDir = ?config(mgr_dir, Config),
939
 
    Ip = ?config(ip, Config),
940
 
    config([2], MgrDir, AgentDir, tuple_to_list(Ip), tuple_to_list(Ip)),
941
 
    [{vsn, v2} | start_v2_agent(Config)].
942
 
 
943
 
finish_v2(Config) when list(Config) ->
944
 
    delete_tables(),
945
 
    C1 = stop_agent(Config),
946
 
    delete_files(C1),
947
 
    C2 = lists:keydelete(vsn, 1, C1).
948
 
 
949
 
test_v1_v2(suite) -> {req, [], {conf, init_v1_v2, v1_v2_cases(), finish_v1_v2}}.
950
 
 
951
 
v1_v2_cases() ->
952
 
    [simple_bi].
953
 
 
954
 
init_v1_v2(Config) when list(Config) ->
955
 
    SaNode = ?config(snmp_sa, Config),
956
 
    create_tables(SaNode),
957
 
    AgentDir = ?config(agent_dir, Config),
958
 
    MgrDir = ?config(mgr_dir, Config),
959
 
    Ip = ?config(ip, Config),
960
 
    config([1,2], MgrDir, AgentDir, tuple_to_list(Ip), tuple_to_list(Ip)),
961
 
    [{vsn, bilingual} | start_bilingual_agent(Config)].
962
 
 
963
 
finish_v1_v2(Config) when list(Config) ->
964
 
    delete_tables(),
965
 
    C1 = stop_agent(Config),
966
 
    delete_files(C1),
967
 
    C2 = lists:keydelete(vsn, 1, C1).
968
 
 
969
 
test_v3(suite) -> {req, [], {conf, init_v3, v3_cases(), finish_v3}}.
970
 
 
971
 
%v3_cases() -> [loop_mib_3];
972
 
v3_cases() ->
973
 
    [simple_3, v3_processing,
974
 
     big_3, big2_3, api_3, subagent_3, mnesia_3, loop_mib_3,
975
 
     multiple_reqs_3, sa_register_3, v3_trap, v3_inform, sa_error_3,
976
 
     next_across_sa_3, undo_3, reported_bugs_3, standard_mibs_3,
977
 
     v3_security,
978
 
     v2_types_3, implied_3, sparse_table_3, cnt_64_3, opaque_3, v2_caps_3].
979
 
 
980
 
init_v3(Config) when list(Config) ->
981
 
    SaNode = ?config(snmp_sa, Config),
982
 
    create_tables(SaNode),
983
 
    AgentDir = ?config(agent_dir, Config),
984
 
    MgrDir = ?config(mgr_dir, Config),
985
 
    Ip = ?config(ip, Config),
986
 
    ?line ok = config([3], MgrDir, AgentDir, tuple_to_list(Ip), tuple_to_list(Ip)),
987
 
    [{vsn, v3} | start_v3_agent(Config)].
988
 
 
989
 
finish_v3(Config) when list(Config) ->
990
 
    delete_tables(),
991
 
    C1 = stop_agent(Config),
992
 
    delete_files(C1),
993
 
    C2 = lists:keydelete(vsn, 1, C1).
994
 
 
995
 
test_multi_threaded(suite) -> {req, [], {conf, init_mt, mt_cases(), finish_mt}}.
996
 
 
997
 
mt_cases() ->
998
 
    [multi_threaded, mt_trap].
999
 
 
1000
 
init_mt(Config) when list(Config) ->
1001
 
    SaNode = ?config(snmp_sa, Config),
1002
 
    create_tables(SaNode),
1003
 
    AgentDir = ?config(agent_dir, Config),
1004
 
    MgrDir = ?config(mgr_dir, Config),
1005
 
    Ip = ?config(ip, Config),
1006
 
    ?line ok = config([2], MgrDir, AgentDir, tuple_to_list(Ip), tuple_to_list(Ip)),
1007
 
    [{vsn, v2} | start_multi_threaded_agent(Config)].
1008
 
 
1009
 
finish_mt(Config) when list(Config) ->
1010
 
    delete_tables(),
1011
 
    C1 = stop_agent(Config),
1012
 
    delete_files(C1),
1013
 
    C2 = lists:keydelete(vsn, 1, C1).
1014
 
 
1015
 
test_compiler(suite) -> 
1016
 
    {req, [], {conf, init_comp, comp_cases(), finish_comp}}.
1017
 
 
1018
 
comp_cases() ->
1019
 
    [comp_description, oid_conflicts].
1020
 
 
1021
 
init_comp(Config) when list(Config) ->
1022
 
    Config.
1023
 
 
1024
 
finish_comp(Config) when list(Config) ->
1025
 
    Config.
1026
 
 
1027
 
%% This one *must* be run first in each case.
1028
 
init_case(Config) when list(Config) ->
1029
 
    ?DBG("init_case -> entry with"
1030
 
           "~n   Config: ~p", [Config]),
1031
 
    SaNode = ?config(snmp_sa, Config),
1032
 
    MgrNode = ?config(snmp_mgr, Config),
1033
 
    MasterNode = node(),
1034
 
 
1035
 
    SaHost = from($@, atom_to_list(SaNode)),
1036
 
    MgrHost = from($@, atom_to_list(MgrNode)),
1037
 
    MasterHost = from($@, atom_to_list(MasterNode)),
1038
 
    {ok, MasterIP} =  snmp_misc:ip(MasterHost),
1039
 
    {ok, MIP} =  snmp_misc:ip(MgrHost),
1040
 
    {ok, SIP} =  snmp_misc:ip(SaHost),
1041
 
 
1042
 
 
1043
 
    put(mgr_node, MgrNode),
1044
 
    put(sa_node, SaNode),
1045
 
    put(master_node, MasterNode),
1046
 
    put(sa_host, SaHost),
1047
 
    put(mgr_host, MgrHost),
1048
 
    put(master_host, MasterHost),
1049
 
    put(mip , tuple_to_list(MIP)),
1050
 
    put(masterip , tuple_to_list(MasterIP)),
1051
 
    put(sip, tuple_to_list(SIP)),
1052
 
    
1053
 
    MibDir = ?config(mib_dir, Config),
1054
 
    put(mib_dir, MibDir),
1055
 
    StdM = filename:join(code:priv_dir(snmp), "mibs") ++ "/",
1056
 
    put(std_mib_dir, StdM),
1057
 
 
1058
 
    MgrDir = ?config(mgr_dir, Config),
1059
 
    put(mgr_dir, MgrDir),
1060
 
 
1061
 
    put(vsn, ?config(vsn, Config)),
1062
 
    ?DBG("init_case -> exit with"
1063
 
           "~n   SaNode:  ~p"
1064
 
           "~n   MgrNode: ~p"
1065
 
           "~n   MibDir:  ~p", [SaNode, MgrNode, MibDir]),
1066
 
    {SaNode, MgrNode, MibDir}.
1067
 
 
1068
 
load_master(Mib) ->
1069
 
    snmp:unload_mibs(snmp_master_agent, [Mib]), % Unload for safety
1070
 
    ok = snmp:load_mibs(snmp_master_agent, [get(mib_dir) ++ Mib]).
1071
 
 
1072
 
load_master_std(Mib) ->
1073
 
    snmp:unload_mibs(snmp_master_agent, [Mib]), % Unload for safety
1074
 
    ok = snmp:load_mibs(snmp_master_agent, [get(std_mib_dir) ++ Mib]).
1075
 
 
1076
 
unload_master(Mib) ->
1077
 
    ok = snmp:unload_mibs(snmp_master_agent, [Mib]).
1078
 
 
1079
 
loaded_mibs() ->
1080
 
    Info = snmp:info(snmp_master_agent),
1081
 
    {value, {loaded_mibs, Mibs}} = lists:keysearch(loaded_mibs, 1, Info),
1082
 
    [atom_to_list(Mib) || {Mib,_,_} <- Mibs].
1083
 
 
1084
 
unload_mibs(Mibs) ->
1085
 
    ok = snmp:unload_mibs(snmp_master_agent, Mibs).
1086
 
 
1087
 
start_subagent(SaNode, RegTree, Mib) ->
1088
 
    MA = whereis(snmp_master_agent),
1089
 
    MibDir = get(mib_dir),
1090
 
%     ?line XX = rpc:call(SaNode, snmp_supervisor, 
1091
 
%                       start_subagent, [MA, RegTree, [MibDir++Mib]]),
1092
 
%     ?DBG("start_subagent -> XX: ~p", [XX]),
1093
 
%     ?line {ok, SA} = XX,
1094
 
%     XX.
1095
 
    Mib1 = join(MibDir,Mib),
1096
 
    case rpc:call(SaNode, snmp_supervisor, 
1097
 
                  start_subagent, [MA, RegTree, [Mib1]]) of
1098
 
        {ok, SA} ->
1099
 
            {ok, SA};
1100
 
        Error ->
1101
 
            ?FAIL({subagent_start_failed, SaNode, Error, [MA, RegTree, Mib1]})
1102
 
    end.
1103
 
 
1104
 
stop_subagent(SA) ->
1105
 
    rpc:call(node(SA), snmp_supervisor, stop_subagent, [SA]).
1106
 
 
1107
 
%%-----------------------------------------------------------------
1108
 
%% This function takes care of the old OTP-SNMPEA-MIB.
1109
 
%% Unfortunately, the testcases were written to use the data in the
1110
 
%% internal tables, and these table are now obsolete and not used
1111
 
%% by the agent.  Therefore, we emulate them by using
1112
 
%% OLD-SNMPEA-MIB, which uses the default impl. of all tables.
1113
 
%%
1114
 
%% These two rows must exist in intCommunityTable
1115
 
%%    {[147,214,36,45], "public", 2, readWrite}.
1116
 
%%    {[147,214,36,45], "standard trap", 2, read}.
1117
 
%% (But with the manager's IP address)
1118
 
%%
1119
 
%%-----------------------------------------------------------------
1120
 
init_old() ->
1121
 
    snmp_local_db:table_create_row(intCommunityTable,
1122
 
                                   get(mip) ++ [6 | "public"],
1123
 
                                   {get(mip), "public", 2, 2}),
1124
 
    snmp_local_db:table_create_row(intCommunityTable,
1125
 
                                   get(mip) ++ [13 | "standard trap"],
1126
 
                                   {get(mip), "standard trap", 2, 1}),
1127
 
    snmp_local_db:variable_set(intAgentIpAddress, [127,0,0,1]).
1128
 
    
1129
 
                                    
1130
 
 
1131
 
simple(suite) -> [];
1132
 
simple(Config) when list(Config) ->
1133
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1134
 
    
1135
 
    try_test(simple_standard_test).
1136
 
 
1137
 
simple_2(X) -> simple(X).
1138
 
 
1139
 
simple_bi(suite) -> [];
1140
 
simple_bi(Config) when list(Config) ->
1141
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1142
 
 
1143
 
    put(vsn, v1), % First, try v1 manager
1144
 
    try_test(simple_standard_test),
1145
 
    
1146
 
    put(vsn, v2), % Then, try v2 manager
1147
 
    try_test(simple_standard_test).
1148
 
    
1149
 
simple_3(X) ->
1150
 
    simple(X).
1151
 
 
1152
 
big(suite) -> [];
1153
 
big(Config) when list(Config) ->
1154
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1155
 
 
1156
 
    p("Starting subagent..."),
1157
 
    ?line pong = net_adm:ping(SaNode),
1158
 
    
1159
 
    ?line {ok, SA} = start_subagent(SaNode, ?klas1, "Klas1"),
1160
 
    ?line load_master("OLD-SNMPEA-MIB"),
1161
 
    ?line init_old(),
1162
 
    try_test(big_test),
1163
 
    ?line stop_subagent(SA),
1164
 
    ?line unload_master("OLD-SNMPEA-MIB").
1165
 
 
1166
 
big_2(X) -> big(X).
1167
 
 
1168
 
big_3(X) -> big(X).
1169
 
 
1170
 
     
1171
 
big2(suite) -> [];
1172
 
big2(Config) when list(Config) ->
1173
 
    %% This is exactly the same tests as 'big', but with the
1174
 
    %% v2 equivalent of the mibs.
1175
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1176
 
 
1177
 
    p("Starting subagent..."),
1178
 
    ?line pong = net_adm:ping(SaNode),
1179
 
    
1180
 
    ?line {ok, SA} = start_subagent(SaNode, ?klas1, "Klas1-v2"),
1181
 
    ?line load_master("OLD-SNMPEA-MIB-v2"),
1182
 
    ?line init_old(),
1183
 
    try_test(big_test),
1184
 
    ?line stop_subagent(SA),
1185
 
    ?line unload_master("OLD-SNMPEA-MIB-v2").
1186
 
 
1187
 
big2_2(X) -> big2(X).
1188
 
 
1189
 
big2_3(X) -> big2(X).
1190
 
    
1191
 
 
1192
 
multi_threaded(suite) -> [];
1193
 
multi_threaded(Config) when list(Config) ->
1194
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1195
 
    
1196
 
    ?line load_master("Test1"),
1197
 
    try_test(multi_threaded_test),
1198
 
    ?line unload_master("Test1").
1199
 
 
1200
 
mt_trap(suite) -> [];
1201
 
mt_trap(Config) when list(Config) ->
1202
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1203
 
    MA = whereis(snmp_master_agent),
1204
 
    
1205
 
    ?line load_master("Test1"),
1206
 
    ?line load_master("TestTrapv2"),
1207
 
    try_test(mt_trap_test, [MA]),
1208
 
    ?line unload_master("TestTrapv2"),
1209
 
    ?line unload_master("Test1").
1210
 
 
1211
 
v2_types(suite) -> [];
1212
 
v2_types(Config) when list(Config) ->
1213
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1214
 
 
1215
 
    ?line load_master("Test1"),
1216
 
    try_test(types_v2_test),
1217
 
    ?line unload_master("Test1").
1218
 
 
1219
 
v2_types_3(X) -> v2_types(X).
1220
 
    
1221
 
 
1222
 
implied(suite) -> [];
1223
 
implied(Config) when list(Config) ->
1224
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1225
 
    MA = whereis(snmp_master_agent),
1226
 
 
1227
 
    ?line load_master("Test1"),
1228
 
    try_test(implied_test,[MA]),
1229
 
    ?line unload_master("Test1").
1230
 
 
1231
 
implied_3(X) -> implied(X).
1232
 
    
1233
 
 
1234
 
sparse_table(suite) -> [];
1235
 
sparse_table(Config) when list(Config) ->
1236
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1237
 
 
1238
 
    ?line load_master("Test1"),
1239
 
    try_test(sparse_table_test),
1240
 
    ?line unload_master("Test1").
1241
 
 
1242
 
sparse_table_2(X) -> sparse_table(X).
1243
 
 
1244
 
sparse_table_3(X) -> sparse_table(X).
1245
 
 
1246
 
cnt_64(suite) -> [];
1247
 
cnt_64(Config) when list(Config) ->
1248
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1249
 
    MA = whereis(snmp_master_agent),
1250
 
 
1251
 
    ?line load_master("Test1"),
1252
 
    try_test(cnt_64_test, [MA]),
1253
 
    ?line unload_master("Test1").
1254
 
 
1255
 
cnt_64_2(X) -> cnt_64(X).
1256
 
 
1257
 
cnt_64_3(X) -> cnt_64(X).
1258
 
 
1259
 
opaque(suite) -> [];
1260
 
opaque(Config) when list(Config) ->
1261
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1262
 
 
1263
 
    ?line load_master("Test1"),
1264
 
    try_test(opaque_test),
1265
 
    ?line unload_master("Test1").
1266
 
 
1267
 
opaque_2(X) -> opaque(X).
1268
 
 
1269
 
opaque_3(X) -> opaque(X).
1270
 
 
1271
 
 
1272
 
change_target_addr_config(suite) -> [];
1273
 
change_target_addr_config(Config) when list(Config) ->
1274
 
    p("Testing changing target address config..."),
1275
 
    ?LOG("change_target_addr_config -> entry",[]),
1276
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1277
 
 
1278
 
    put(sname,snmp_suite),
1279
 
    put(verbosity,trace),
1280
 
 
1281
 
    MA = whereis(snmp_master_agent),
1282
 
 
1283
 
    ?LOG("change_target_addr_config -> load TestTrap",[]),
1284
 
    ?line load_master("TestTrap"),
1285
 
 
1286
 
    ?LOG("change_target_addr_config -> set trace verbosity for local_db",[]),
1287
 
    ?line snmp:verbosity(snmp_local_db,trace),
1288
 
 
1289
 
    %% First send some traps that will arive att the original manager
1290
 
    ?LOG("change_target_addr_config -> send trap",[]),
1291
 
    try_test(ma_trap1, [MA]),
1292
 
 
1293
 
    ?LOG("change_target_addr_config -> set silence verbosity for local_db",[]),
1294
 
    ?line snmp:verbosity(snmp_local_db,silence),
1295
 
 
1296
 
    %% Start new dummy listener
1297
 
    ?LOG("change_target_addr_config -> start dummy manager",[]),
1298
 
    ?line {ok,Pid,NewPort} = dummy_manager_start(MA),
1299
 
    
1300
 
    %% Reconfigure
1301
 
    ?LOG("change_target_addr_config -> reconfigure",[]),
1302
 
    AgentDir = ?config(agent_dir, Config),
1303
 
    ?line rewrite_target_addr_conf(AgentDir, NewPort),
1304
 
    ?line snmp_target_mib:reconfigure(AgentDir),
1305
 
 
1306
 
    %% Send the trap again
1307
 
    ?LOG("change_target_addr_config -> send trap again",[]),
1308
 
    catch dummy_manager_send_trap2(Pid),
1309
 
 
1310
 
    ?LOG("change_target_addr_config -> await trap ack",[]),
1311
 
    catch dummy_manager_await_trap2_ack(),
1312
 
 
1313
 
    ?LOG("change_target_addr_config -> stop dummy manager",[]),
1314
 
    ?line ok = dummy_manager_stop(Pid),
1315
 
 
1316
 
    ?LOG("change_target_addr_config -> reset target address config",[]),
1317
 
    ?line reset_target_addr_conf(AgentDir),
1318
 
 
1319
 
    ?LOG("change_target_addr_config -> unload TestTrap",[]),
1320
 
    ?line unload_master("TestTrap").
1321
 
 
1322
 
 
1323
 
dummy_manager_start(MA) ->
1324
 
    ?DBG("dummy_manager_start -> entry",[]),
1325
 
    Pid = spawn(get(mgr_node), ?MODULE,dummy_manager_init,[self(),MA]),
1326
 
    ?DBG("dummy_manager_start -> Pid: ~p",[Pid]),
1327
 
    await_dummy_manager_started(Pid).
1328
 
 
1329
 
await_dummy_manager_started(Pid) ->
1330
 
    receive
1331
 
        {dummy_manager_started,Pid,Port} ->
1332
 
            ?DBG("dummy_manager_start -> acknowledge received with"
1333
 
                "~n   Port: ~p",[Port]),
1334
 
            {ok,Pid,Port};
1335
 
        {'EXIT', Pid, Reason} ->
1336
 
            {error, Pid, Reason};
1337
 
        O ->
1338
 
            ?LOG("dummy_manager_start -> received unknown message:"
1339
 
                 "~n   ~p",[O]),
1340
 
            await_dummy_manager_started(Pid)
1341
 
    end.
1342
 
 
1343
 
dummy_manager_stop(Pid) ->
1344
 
    ?DBG("dummy_manager_stop -> entry with Pid: ~p",[Pid]),
1345
 
    Pid ! stop,
1346
 
    receive
1347
 
        {dummy_manager_stopping, Pid} -> 
1348
 
            ?DBG("dummy_manager_stop -> acknowledge received",[]),
1349
 
            ok
1350
 
    after 10000 ->
1351
 
            ?ERR("dummy_manager_stop -> timeout",[]),
1352
 
            timeout
1353
 
    end.
1354
 
 
1355
 
dummy_manager_send_trap2(Pid) ->
1356
 
    ?DBG("dummy_manager_send_trap2 -> entry",[]),
1357
 
    Pid ! {send_trap,testTrap2}.
1358
 
 
1359
 
dummy_manager_await_trap2_ack() ->
1360
 
    ?DBG("dummy_manager_await_trap2 -> entry",[]),
1361
 
    receive
1362
 
        {received_trap,Trap} ->
1363
 
            ?LOG("dummy_manager_await_trap2 -> received trap: ~p",[Trap]),
1364
 
            %% Note: 
1365
 
            %% Without this sleep the v2_inform_i testcase failes! There
1366
 
            %% is no relation between these two test cases as far as I
1367
 
            %% able to figure out...
1368
 
            sleep(60000),
1369
 
            ok;
1370
 
        O ->
1371
 
            ?ERR("dummy_manager_await_trap2 -> unexpected message: ~p",[O]),
1372
 
            ok
1373
 
    after 10000 ->
1374
 
            ?ERR("dummy_manager_await_trap2 -> timeout",[]),
1375
 
            timeout
1376
 
    end.
1377
 
 
1378
 
dummy_manager_init(Parent,MA) ->
1379
 
    ?DBG("dummy_manager_init -> entry with"
1380
 
           "~n   Parent: ~p"
1381
 
           "~n   MA:     ~p",[Parent,MA]),
1382
 
    {ok,S} = gen_udp:open(0,[{recbuf,65535}]),
1383
 
    ?DBG("dummy_manager_init -> S: ~p",[S]),
1384
 
    {ok,Port} = inet:port(S),
1385
 
    ?DBG("dummy_manager_init -> Port: ~p",[Port]),
1386
 
    Parent ! {dummy_manager_started,self(),Port},
1387
 
    dummy_manager_loop(Parent,S,MA).
1388
 
 
1389
 
dummy_manager_loop(P,S,MA) ->
1390
 
    ?LOG("dummy_manager_loop -> ready for receive",[]),
1391
 
    receive
1392
 
        {send_trap,Trap} ->
1393
 
            ?LOG("dummy_manager_loop -> received trap send request"
1394
 
                 "~n   Trap: ~p",[Trap]),
1395
 
            snmp:send_trap(MA, Trap, "standard trap"),
1396
 
            dummy_manager_loop(P,S,MA);
1397
 
        {udp, UdpId, Ip, UdpPort, Bytes} ->
1398
 
            ?LOG("dummy_manager_loop -> received upd message"
1399
 
                 "~n   from: ~p:~p"
1400
 
                 "~n   size: ~p",
1401
 
                 [Ip, UdpPort, dummy_manager_message_sz(Bytes)]),
1402
 
            R = dummy_manager_handle_message(Bytes),
1403
 
            ?DBG("dummy_manager_loop -> R: ~p",[R]),
1404
 
            P ! R,
1405
 
            dummy_manager_loop(P,S,MA);
1406
 
        stop ->
1407
 
            ?DBG("dummy_manager_loop -> received stop request",[]),
1408
 
            P ! {dummy_manager_stopping, self()},
1409
 
            gen_udp:close(S),
1410
 
            exit(normal);
1411
 
        O ->
1412
 
            ?LOG("dummy_manager_loop -> received unknown message:"
1413
 
                 "~n   ~p",[O]),
1414
 
            dummy_manager_loop(P,S,MA)
1415
 
    end.
1416
 
 
1417
 
dummy_manager_message_sz(B) when binary(B) ->
1418
 
    size(B);
1419
 
dummy_manager_message_sz(L) when list(L) ->
1420
 
    length(L);
1421
 
dummy_manager_message_sz(_) ->
1422
 
    undefined.
1423
 
 
1424
 
dummy_manager_handle_message(Bytes) ->
1425
 
    case (catch snmp_pdus:dec_message(Bytes)) of
1426
 
        {'EXIT',Reason} ->
1427
 
            ?ERR("dummy_manager_handle_message -> "
1428
 
                   "failed decoding message only:~n   ~p",[Reason]),
1429
 
            {error,Reason};
1430
 
        M ->
1431
 
            ?DBG("dummy_manager_handle_message -> decoded message:"
1432
 
                   "~n   ~p",[M]),
1433
 
            {received_trap,M}
1434
 
    end.
1435
 
 
1436
 
 
1437
 
api(suite) -> [];
1438
 
api(Config) when list(Config) ->
1439
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1440
 
 
1441
 
    ?line load_master("OLD-SNMPEA-MIB"),
1442
 
    ?line init_old(),
1443
 
    try_test(api_test, [node()]),
1444
 
    ?line unload_master("OLD-SNMPEA-MIB").
1445
 
 
1446
 
api_2(X) -> api(X).
1447
 
 
1448
 
api_3(X) -> api(X).
1449
 
 
1450
 
 
1451
 
subagent(suite) -> [];
1452
 
subagent(Config) when list(Config) ->
1453
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1454
 
 
1455
 
    ?line {ok, SA} = start_subagent(SaNode, ?klas1, "Klas1"),
1456
 
    try_test(load_test_sa),
1457
 
    
1458
 
    p("Testing unregister subagent..."),
1459
 
    MA = whereis(snmp_master_agent),
1460
 
    rpc:call(SaNode, snmp, unregister_subagent, [MA, SA]),
1461
 
    try_test(unreg_test),
1462
 
 
1463
 
    p("Loading previous subagent mib in master and testing..."),
1464
 
    ?line ok = snmp:load_mibs(MA, [MibDir ++ "Klas1"]),
1465
 
    try_test(load_test),
1466
 
 
1467
 
    p("Unloading previous subagent mib in master and testing..."),
1468
 
    ?line ok = snmp:unload_mibs(MA, [MibDir ++ "Klas1"]),
1469
 
    try_test(unreg_test),
1470
 
    p("Testing register subagent..."),
1471
 
    rpc:call(SaNode, snmp, register_subagent,
1472
 
             [MA, ?klas1, SA]),
1473
 
    try_test(load_test_sa),
1474
 
 
1475
 
    ?line stop_subagent(SA),
1476
 
    try_test(unreg_test).
1477
 
    
1478
 
subagent_2(X) -> subagent(X).
1479
 
 
1480
 
subagent_3(X) -> subagent(X).
1481
 
 
1482
 
 
1483
 
mnesia(suite) -> [];
1484
 
mnesia(Config) when list(Config) ->
1485
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1486
 
 
1487
 
    p("Starting subagent with mnesia impl..."),
1488
 
    {ok, SA} = start_subagent(SaNode, ?klas2, "Klas2"),
1489
 
    ?line load_master("OLD-SNMPEA-MIB"),
1490
 
    ?line init_old(),
1491
 
 
1492
 
    try_test(big_test_2),
1493
 
 
1494
 
    p("Testing unregister subagent..."),
1495
 
    MA = whereis(snmp_master_agent),
1496
 
    rpc:call(SaNode, snmp, unregister_subagent, [MA, SA]),
1497
 
    try_test(unreg_test),
1498
 
    ?line unload_master("OLD-SNMPEA-MIB"),
1499
 
    ?line stop_subagent(SA).
1500
 
 
1501
 
mnesia_2(X) -> mnesia(X).
1502
 
 
1503
 
mnesia_3(X) -> mnesia(X).
1504
 
 
1505
 
 
1506
 
multiple_reqs(suite) ->
1507
 
    {req, [], {conf, init_mul, mul_cases(), finish_mul}}.
1508
 
 
1509
 
mul_cases() ->
1510
 
    [mul_get, mul_get_err, mul_next, mul_next_err, mul_set_err].
1511
 
    
1512
 
multiple_reqs_2(suite) ->
1513
 
    {req, [], {conf, init_mul, mul_cases_2(), finish_mul}}.
1514
 
 
1515
 
multiple_reqs_3(X) -> 
1516
 
    {req, [], {conf, init_mul, mul_cases_3(), finish_mul}}.
1517
 
 
1518
 
 
1519
 
mul_cases_2() ->
1520
 
    [mul_get_2, mul_get_err_2, mul_next_2, mul_next_err_2, mul_set_err_2].
1521
 
    
1522
 
 
1523
 
mul_cases_3() ->
1524
 
    [mul_get_3, mul_get_err_3, mul_next_3, mul_next_err_3, mul_set_err_3].
1525
 
    
1526
 
 
1527
 
init_mul(Config) when list(Config) ->
1528
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1529
 
 
1530
 
    ?line {ok, SA} = start_subagent(SaNode, ?klas1, "Klas1"),
1531
 
    ?line load_master("OLD-SNMPEA-MIB"),
1532
 
    ?line init_old(),
1533
 
    [{mul_sub, SA} | Config].
1534
 
 
1535
 
finish_mul(Config) when list(Config) ->
1536
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1537
 
    
1538
 
    SA = ?config(mul_sub, Config),
1539
 
    
1540
 
    ?line unload_master("OLD-SNMPEA-MIB"),
1541
 
    ?line stop_subagent(SA),
1542
 
    lists:keydelete(mul_sub, 1, Config).
1543
 
    
1544
 
mul_get(suite) -> [];
1545
 
mul_get(Config) when list(Config) ->
1546
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1547
 
    
1548
 
    p("Testing multiple get..."),
1549
 
    try_test(do_mul_get).
1550
 
 
1551
 
mul_get_2(X) -> mul_get(X).
1552
 
 
1553
 
mul_get_3(X) -> mul_get(X).
1554
 
 
1555
 
             
1556
 
mul_get_err(suite) -> [];
1557
 
mul_get_err(Config) when list(Config) ->
1558
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1559
 
    
1560
 
    p("Testing multiple get with error..."),
1561
 
    try_test(do_mul_get_err).
1562
 
 
1563
 
mul_get_err_2(X) -> mul_get_err(X).
1564
 
 
1565
 
mul_get_err_3(X) -> mul_get_err(X).
1566
 
 
1567
 
             
1568
 
mul_next(suite) -> [];
1569
 
mul_next(Config) when list(Config) ->
1570
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1571
 
    
1572
 
    p("Testing multiple next..."),
1573
 
    try_test(do_mul_next).
1574
 
 
1575
 
mul_next_2(X) -> mul_next(X).
1576
 
 
1577
 
mul_next_3(X) -> mul_next(X).
1578
 
 
1579
 
             
1580
 
mul_next_err(suite) -> [];
1581
 
mul_next_err(Config) when list(Config) ->
1582
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1583
 
    
1584
 
    p("Testing multiple next..."),
1585
 
    try_test(do_mul_next_err).
1586
 
 
1587
 
mul_next_err_2(X) -> mul_next_err(X).
1588
 
 
1589
 
mul_next_err_3(X) -> mul_next_err(X).
1590
 
 
1591
 
             
1592
 
mul_set(suite) -> [];
1593
 
mul_set(Config) when list(Config) ->
1594
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1595
 
    
1596
 
    p("Testing multiple set..."),
1597
 
    try_test(do_mul_set).
1598
 
 
1599
 
mul_set_2(X) -> mul_set(X).
1600
 
 
1601
 
mul_set_3(X) -> mul_set(X).
1602
 
 
1603
 
             
1604
 
mul_set_err(suite) -> [];
1605
 
mul_set_err(Config) when list(Config) ->
1606
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1607
 
    
1608
 
    p("Testing multiple set with error..."),
1609
 
    try_test(do_mul_set_err).
1610
 
 
1611
 
mul_set_err_2(X) -> mul_set_err(X).
1612
 
 
1613
 
mul_set_err_3(X) -> mul_set_err(X).
1614
 
 
1615
 
 
1616
 
sa_register(suite) -> [];
1617
 
sa_register(Config) when list(Config) ->
1618
 
    ?DBG("sa_register -> entry", []),
1619
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1620
 
 
1621
 
    ?DBG("sa_register -> start subagent", []),
1622
 
    ?line {ok, SA} = start_subagent(SaNode, ?klas1, "Klas1"),
1623
 
 
1624
 
    ?DBG("sa_register -> unregister subagent", []),
1625
 
    p("Testing unregister subagent (2)..."),
1626
 
    MA = whereis(snmp_master_agent),
1627
 
    rpc:call(SaNode, snmp, unregister_subagent, [MA, ?klas1]),
1628
 
    try_test(unreg_test),
1629
 
 
1630
 
    p("Loading SA-MIB..."),
1631
 
    ?DBG("sa_register -> unload mibs", []),
1632
 
    snmp:unload_mibs(SA, [MibDir ++ "Klas1"]),
1633
 
    ?DBG("sa_register -> unload mibs", []),
1634
 
    snmp:load_mibs(SA, [MibDir ++ "SA-MIB"]),
1635
 
    ?DBG("sa_register -> register subagent", []),
1636
 
    rpc:call(SaNode, snmp, register_subagent, [MA,?sa,SA]),
1637
 
    try_test(sa_mib),
1638
 
 
1639
 
    ?DBG("sa_register -> stop subagent", []),
1640
 
    ?line stop_subagent(SA).
1641
 
    
1642
 
sa_register_2(X) -> sa_register(X).
1643
 
 
1644
 
sa_register_3(X) -> sa_register(X).
1645
 
 
1646
 
 
1647
 
v1_trap(suite) -> [];
1648
 
v1_trap(Config) when list(Config) ->
1649
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1650
 
 
1651
 
    ?line {ok, SA} = start_subagent(SaNode, ?sa, "SA-MIB"),
1652
 
 
1653
 
    p("Testing trap sending from master agent..."),
1654
 
    MA = whereis(snmp_master_agent),
1655
 
 
1656
 
    ?line load_master("TestTrap"),
1657
 
    ?line load_master("TestTrapv2"),
1658
 
 
1659
 
    try_test(ma_trap1, [MA]),
1660
 
    try_test(ma_trap2, [MA]),
1661
 
    try_test(ma_v2_2_v1_trap, [MA]),
1662
 
    try_test(ma_v2_2_v1_trap2, [MA]),
1663
 
 
1664
 
    p("Testing trap sending from subagent..."),
1665
 
    try_test(sa_trap1, [SA]),
1666
 
    try_test(sa_trap2, [SA]),
1667
 
    try_test(sa_trap3, [SA]),
1668
 
    
1669
 
    ?line unload_master("TestTrap"),
1670
 
    ?line unload_master("TestTrapv2"),
1671
 
 
1672
 
    ?line stop_subagent(SA).
1673
 
 
1674
 
v2_trap(suite) -> [];
1675
 
v2_trap(Config) when list(Config) ->
1676
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1677
 
 
1678
 
    ?line {ok, SA} = start_subagent(SaNode, ?sa, "SA-MIB"),
1679
 
 
1680
 
    p("Testing trap sending from master agent..."),
1681
 
    MA = whereis(snmp_master_agent),
1682
 
 
1683
 
    ?line load_master("TestTrap"),
1684
 
    ?line load_master("TestTrapv2"),
1685
 
 
1686
 
    
1687
 
    try_test(ma_v2_trap1, [MA]),
1688
 
    try_test(ma_v2_trap2, [MA]),
1689
 
    try_test(ma_v1_2_v2_trap, [MA]),
1690
 
    try_test(ma_v1_2_v2_trap2, [MA]),
1691
 
 
1692
 
    try_test(sa_mib),
1693
 
    p("Testing trap sending from subagent..."),
1694
 
    try_test(sa_v1_2_v2_trap1, [SA]),
1695
 
    try_test(sa_v1_2_v2_trap2, [SA]),
1696
 
    try_test(sa_v1_2_v2_trap3, [SA]),
1697
 
    
1698
 
    ?line unload_master("TestTrap"),
1699
 
    ?line unload_master("TestTrapv2"),
1700
 
 
1701
 
    ?line stop_subagent(SA).
1702
 
 
1703
 
v3_trap(X) ->
1704
 
    v2_trap(X).
1705
 
 
1706
 
v2_inform(suite) ->
1707
 
    {req, [], {conf, init_v2_inform, [v2_inform_i], finish_v2_inform}}.
1708
 
 
1709
 
v3_inform(X) ->
1710
 
    %% v2_inform(X).
1711
 
    {req, [], {conf, init_v3_inform, [v3_inform_i], finish_v3_inform}}. 
1712
 
 
1713
 
init_v2_inform(Config) when list(Config) ->
1714
 
    Dir = ?config(agent_dir, Config),
1715
 
%    snmp_internal_mib:configure(Dir),
1716
 
    Config.
1717
 
 
1718
 
init_v3_inform(X) ->
1719
 
    init_v2_inform(X).
1720
 
 
1721
 
finish_v2_inform(Config) when list(Config) ->
1722
 
    Dir = ?config(agent_dir, Config),
1723
 
%   snmp_internal_mib:configure(Dir),
1724
 
    Config.
1725
 
 
1726
 
finish_v3_inform(X) ->
1727
 
    finish_v2_inform(X).
1728
 
 
1729
 
 
1730
 
 
1731
 
v2_inform_i(suite) -> [];
1732
 
v2_inform_i(Config) when list(Config) ->
1733
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1734
 
 
1735
 
    p("Testing inform sending from master agent...  NOTE! This test\ntakes a "
1736
 
      "few minutes (5) to complete."),
1737
 
    MA = whereis(snmp_master_agent),
1738
 
 
1739
 
    ?line load_master("TestTrap"),
1740
 
    ?line load_master("TestTrapv2"),
1741
 
 
1742
 
    try_test(ma_v2_inform1, [MA]),
1743
 
 
1744
 
    ?line unload_master("TestTrap"),
1745
 
    ?line unload_master("TestTrapv2").
1746
 
 
1747
 
v3_inform_i(X) -> v2_inform_i(X).
1748
 
 
1749
 
 
1750
 
sa_error(suite) -> [];
1751
 
sa_error(Config) when list(Config) ->
1752
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1753
 
 
1754
 
    ?line load_master("OLD-SNMPEA-MIB"),
1755
 
    ?line init_old(),
1756
 
    ?line {ok, SA} = start_subagent(SaNode, ?sa, "SA-MIB"),
1757
 
 
1758
 
    p("Testing sa bad value (is_set_ok)..."),
1759
 
    try_test(sa_errs_bad_value),
1760
 
 
1761
 
    p("Testing sa gen err (set)..."),
1762
 
    try_test(sa_errs_gen_err),
1763
 
 
1764
 
    p("Testing too big..."),
1765
 
    try_test(sa_too_big),
1766
 
 
1767
 
    ?line unload_master("OLD-SNMPEA-MIB"),
1768
 
    stop_subagent(SA).
1769
 
 
1770
 
sa_error_2(X) -> sa_error(X).
1771
 
 
1772
 
sa_error_3(X) -> sa_error(X).
1773
 
 
1774
 
 
1775
 
next_across_sa(suite) -> [];
1776
 
next_across_sa(Config) when list(Config) ->
1777
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1778
 
    MA = whereis(snmp_master_agent),
1779
 
 
1780
 
    ?line {ok, SA} = start_subagent(SaNode, ?sa, "SA-MIB"),
1781
 
 
1782
 
    p("Loading another subagent mib..."),
1783
 
    ?line ok = snmp:load_mibs(SA, [MibDir ++ "Klas1"]),
1784
 
 
1785
 
    rpc:call(SaNode, snmp, register_subagent, [MA, ?klas1, SA]),
1786
 
    try_test(load_test_sa),
1787
 
    
1788
 
    p("Testing next across subagent (endOfMibView from SA)..."),
1789
 
    try_test(next_across_sa),
1790
 
 
1791
 
    p("Unloading mib"),
1792
 
    snmp:unload_mibs(SA, [MibDir ++ "Klas1"]),
1793
 
    rpc:call(SaNode, snmp, unregister_subagent, [MA, ?klas1]),
1794
 
    try_test(unreg_test),
1795
 
 
1796
 
    p("Starting another subagent"),
1797
 
    ?line {ok, SA2} = start_subagent(SaNode, ?klas1, "Klas1"),
1798
 
    p("Testing next across subagent (wrong prefix from SA)..."),
1799
 
    try_test(next_across_sa),
1800
 
    
1801
 
    stop_subagent(SA),
1802
 
    stop_subagent(SA2).
1803
 
 
1804
 
next_across_sa_2(X) -> next_across_sa(X).
1805
 
 
1806
 
next_across_sa_3(X) -> next_across_sa(X).
1807
 
 
1808
 
 
1809
 
undo(suite) -> [];
1810
 
undo(Config) when list(Config) ->
1811
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1812
 
    MA = whereis(snmp_master_agent),
1813
 
 
1814
 
    ?line {ok, SA} = start_subagent(SaNode, ?sa, "SA-MIB"),
1815
 
 
1816
 
    p("Testing undo phase at master agent..."),
1817
 
    ?line ok = snmp:load_mibs(MA, [MibDir ++ "Klas3"]),
1818
 
    ?line ok = snmp:load_mibs(MA, [MibDir ++ "Klas4"]),
1819
 
    try_test(undo_test),
1820
 
    try_test(api_test2),
1821
 
    ?line ok = snmp:unload_mibs(MA, [MibDir ++ "Klas3"]),
1822
 
 
1823
 
    p("Testing bad return values from instrum. funcs..."),
1824
 
    try_test(bad_return),
1825
 
 
1826
 
    ?line ok = snmp:unload_mibs(MA, [MibDir ++ "Klas4"]),
1827
 
 
1828
 
    p("Testing undo phase at subagent..."),
1829
 
    ?line ok = snmp:load_mibs(SA, [MibDir ++ "Klas3"]),
1830
 
    ?line ok = snmp:load_mibs(SA, [MibDir ++ "Klas4"]),
1831
 
    ?line ok = snmp:register_subagent(MA, ?klas3, SA),
1832
 
    ?line ok = snmp:register_subagent(MA, ?klas4, SA),
1833
 
    try_test(undo_test),
1834
 
    try_test(api_test3),
1835
 
 
1836
 
    p("Testing undo phase across master/subagents..."),
1837
 
    try_test(undo_test),
1838
 
    try_test(api_test3),
1839
 
    stop_subagent(SA).
1840
 
 
1841
 
undo_2(X) -> undo(X).
1842
 
 
1843
 
undo_3(X) -> undo(X).
1844
 
 
1845
 
%% Req. Test2
1846
 
v1_processing(suite) -> [];
1847
 
v1_processing(Config) when list(Config) ->
1848
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1849
 
 
1850
 
    ?line load_master("Test2"),
1851
 
    try_test(v1_proc),
1852
 
    ?line unload_master("Test2").
1853
 
 
1854
 
%% Req. Test2
1855
 
v2_processing(suite) -> [];
1856
 
v2_processing(Config) when list(Config) ->
1857
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1858
 
 
1859
 
    ?line load_master("Test2"),
1860
 
    try_test(v2_proc),
1861
 
    ?line unload_master("Test2").
1862
 
 
1863
 
%% Req. Test2
1864
 
v3_processing(suite) -> [];
1865
 
v3_processing(Config) when list(Config) ->
1866
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1867
 
 
1868
 
    ?line load_master("Test2"),
1869
 
    try_test(v2_proc), % same as v2!
1870
 
    ?line unload_master("Test2").
1871
 
 
1872
 
 
1873
 
%% We'll try get/set/trap and inform for all the auth & priv protocols.
1874
 
%% For informs, the mgr is auth-engine. The agent has to sync.  This is
1875
 
%% accomplished by the first inform sent.  That one will generate a
1876
 
%% report, which makes it in sync.  The notification-generating
1877
 
%% application times out, and send again.  This time it'll work.
1878
 
v3_security(suite) -> [v3_crypto_basic, v3_md5_auth, v3_sha_auth, v3_des_priv].
1879
 
 
1880
 
v3_crypto_basic(suite) -> [];
1881
 
v3_crypto_basic(Config) ->
1882
 
    EID = [0,0,0,0,0,0,0,0,0,0,0,2],
1883
 
    %% From rfc2274 appendix A.3.1
1884
 
    ?line KMd5_1 = snmp:passwd2localized_key(md5, "maplesyrup", EID),
1885
 
    ?line [16#52,16#6f,16#5e,16#ed,16#9f,16#cc,16#e2,16#6f,
1886
 
           16#89,16#64,16#c2,16#93,16#07,16#87,16#d8,16#2b] =
1887
 
        KMd5_1,
1888
 
    %% From rfc2274 appendix A.3.2
1889
 
    ?line KSHA_1 = snmp:passwd2localized_key(sha, "maplesyrup", EID),
1890
 
    ?line [16#66,16#95,16#fe,16#bc,16#92,16#88,16#e3,16#62,16#82,16#23,
1891
 
           16#5f,16#c7,16#15,16#1f,16#12,16#84,16#97,16#b3,16#8f,16#3f] = 
1892
 
        KSHA_1,
1893
 
    %% From rfc2274, appendix A.5.1
1894
 
    ?line KMd5_2 = snmp:passwd2localized_key(md5, "newsyrup", EID),
1895
 
    ?line [16#00,16#00,16#00,16#00,16#00,16#00,16#00,16#00,
1896
 
           16#00,16#00,16#00,16#00,16#00,16#00,16#00,16#00,
1897
 
           16#88,16#05,16#61,16#51,16#41,16#67,16#6c,16#c9,
1898
 
           16#19,16#61,16#74,16#e7,16#42,16#a3,16#25,16#51] =
1899
 
        snmp_user_based_sm_mib:mk_key_change(md5, KMd5_1, KMd5_2, 16,
1900
 
                                             [0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0]),
1901
 
    %% From rfc2274, appendix A.5.2
1902
 
    ?line KSHA_2 = snmp:passwd2localized_key(sha, "newsyrup", EID),
1903
 
    ?line [16#00,16#00,16#00,16#00,16#00,16#00,16#00,16#00,
1904
 
           16#00,16#00,16#00,16#00,16#00,16#00,16#00,16#00,
1905
 
           16#00,16#00,16#00,16#00,16#9c,16#10,16#17,16#f4,
1906
 
           16#fd,16#48,16#3d,16#2d,16#e8,16#d5,16#fa,16#db,
1907
 
           16#f8,16#43,16#92,16#cb,16#06,16#45,16#70,16#51] =
1908
 
        snmp_user_based_sm_mib:mk_key_change(sha, KSHA_1, KSHA_2, 20,
1909
 
                             [0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0]),
1910
 
    KSHA_1t = lists:sublist(KSHA_1, 16),
1911
 
    KSHA_2t = lists:sublist(KSHA_2, 16),
1912
 
    ?line [16#00,16#00,16#00,16#00,16#00,16#00,16#00,16#00,
1913
 
           16#00,16#00,16#00,16#00,16#00,16#00,16#00,16#00,
1914
 
           16#7e,16#f8,16#d8,16#a4,16#c9,16#cd,16#b2,16#6b,
1915
 
           16#47,16#59,16#1c,16#d8,16#52,16#ff,16#88,16#b5] =
1916
 
        snmp_user_based_sm_mib:mk_key_change(sha, KSHA_1t, KSHA_2t, 16,
1917
 
                                             [0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0]),
1918
 
 
1919
 
    %% Try with correct random
1920
 
    ?line Kc1 = snmp_user_based_sm_mib:mk_key_change(md5, KMd5_1, KMd5_2),
1921
 
    ?line KMd5_2 = snmp_user_based_sm_mib:extract_new_key(md5, KMd5_1, Kc1),
1922
 
    ?line Kc2 = snmp_user_based_sm_mib:mk_key_change(sha, KSHA_1, KSHA_2),
1923
 
    ?line KSHA_2 = snmp_user_based_sm_mib:extract_new_key(sha, KSHA_1, Kc2),
1924
 
    ok.
1925
 
    
1926
 
 
1927
 
 
1928
 
v3_md5_auth(suite) -> [];
1929
 
v3_md5_auth(Config) when list(Config) ->
1930
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1931
 
    p("Testing MD5 authentication...takes a few seconds..."),
1932
 
    
1933
 
    AgentDir = ?config(agent_dir, Config),
1934
 
    ?line rewrite_target_params_conf(AgentDir, "authMD5", authNoPriv),
1935
 
    ?line snmp_target_mib:reconfigure(AgentDir),
1936
 
 
1937
 
    MA = whereis(snmp_master_agent),
1938
 
 
1939
 
    ?line load_master("Test2"),
1940
 
    ?line load_master("TestTrap"),
1941
 
    ?line load_master("TestTrapv2"),
1942
 
 
1943
 
    try_test(v3_sync, [[{v2_proc, []},
1944
 
                   {ma_v2_trap1, [MA]},
1945
 
                   {v3_inform_sync, [MA]}]],
1946
 
        [{sec_level, authNoPriv}, {user, "authMD5"}]),
1947
 
 
1948
 
    ?line unload_master("TestTrapv2"),
1949
 
    ?line unload_master("TestTrap"),
1950
 
    ?line unload_master("Test2"),
1951
 
    ?line reset_target_params_conf(AgentDir).
1952
 
 
1953
 
v3_sha_auth(suite) -> [];
1954
 
v3_sha_auth(Config) when list(Config) ->
1955
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1956
 
    p("Testing SHA authentication...takes a few seconds..."),
1957
 
 
1958
 
    AgentDir = ?config(agent_dir, Config),
1959
 
    ?line rewrite_target_params_conf(AgentDir, "authSHA", authNoPriv),
1960
 
    ?line snmp_target_mib:reconfigure(AgentDir),
1961
 
 
1962
 
    MA = whereis(snmp_master_agent),
1963
 
 
1964
 
    ?line load_master("Test2"),
1965
 
    ?line load_master("TestTrap"),
1966
 
    ?line load_master("TestTrapv2"),
1967
 
 
1968
 
    try_test(v3_sync, [[{v2_proc, []},
1969
 
                   {ma_v2_trap1, [MA]},
1970
 
                   {v3_inform_sync, [MA]}]],
1971
 
        [{sec_level, authNoPriv}, {user, "authSHA"}]),
1972
 
 
1973
 
    ?line unload_master("TestTrapv2"),
1974
 
    ?line unload_master("TestTrap"),
1975
 
    ?line unload_master("Test2"),
1976
 
    ?line reset_target_params_conf(AgentDir).
1977
 
 
1978
 
v3_des_priv(suite) -> [];
1979
 
v3_des_priv(Config) when list(Config) ->
1980
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
1981
 
    p("Testing DES encryption...takes a few seconds..."),
1982
 
 
1983
 
    AgentDir = ?config(agent_dir, Config),
1984
 
    ?line rewrite_target_params_conf(AgentDir, "privDES", authPriv),
1985
 
    ?line snmp_target_mib:reconfigure(AgentDir),
1986
 
 
1987
 
    MA = whereis(snmp_master_agent),
1988
 
 
1989
 
    ?line load_master("Test2"),
1990
 
    ?line load_master("TestTrap"),
1991
 
    ?line load_master("TestTrapv2"),
1992
 
 
1993
 
    try_test(v3_sync, [[{v2_proc, []},
1994
 
                   {ma_v2_trap1, [MA]},
1995
 
                   {v3_inform_sync, [MA]}]],
1996
 
        [{sec_level, authPriv}, {user, "privDES"}]),
1997
 
 
1998
 
    ?line unload_master("TestTrapv2"),
1999
 
    ?line unload_master("TestTrap"),
2000
 
    ?line unload_master("Test2"),
2001
 
    ?line reset_target_params_conf(AgentDir).
2002
 
 
2003
 
-define(usmStatsNotInTimeWindows_instance, [1,3,6,1,6,3,15,1,1,2,0]).
2004
 
 
2005
 
%% Make sure mgr is in sync with agent
2006
 
v3_sync(Funcs) ->
2007
 
    ?DBG("v3_sync -> entry with Funcs: ~p",[Funcs]),
2008
 
    g([[sysDescr, 0]]),
2009
 
    expect(432, report, [{?usmStatsNotInTimeWindows_instance, any}]),
2010
 
    g([[sysDescr, 0]]),
2011
 
    expect(433, [{[sysDescr,0], any}]),
2012
 
    lists:foreach(fun({Func, Args}) -> apply(?MODULE, Func, Args) end, Funcs).
2013
 
 
2014
 
v3_inform_sync(MA) ->
2015
 
    ?DBG("v3_sync -> entry with MA: ~p => Send notification",[MA]),
2016
 
    ?line snmp:send_notification(MA, testTrapv22, no_receiver,
2017
 
                                 "standard inform", []),
2018
 
    %% Make sure agent is in sync with mgr...
2019
 
    ?DBG("v3_sync -> wait some time: ",[]),
2020
 
    sleep(20000), % more than 1500*10 in target_addr.conf
2021
 
    ?DBG("v3_sync -> await response",[]),
2022
 
    ?line expect(1, {inform, true},
2023
 
                 [{[sysUpTime, 0], any},
2024
 
                  {[snmpTrapOID, 0], ?system ++ [0,1]}]).
2025
 
 
2026
 
 
2027
 
v2_caps(suite) -> [];
2028
 
v2_caps(Config) when list(Config) ->
2029
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
2030
 
 
2031
 
    try_test(v2_caps_i, [node()]).
2032
 
 
2033
 
v2_caps_3(X) -> v2_caps(X).
2034
 
 
2035
 
 
2036
 
v2_caps_i(Node) ->
2037
 
    ?line Idx = rpc:call(Node, snmp, add_agent_caps, [[1,2,3,4,5], "test cap"]),
2038
 
    g([[sysORID, Idx], [sysORDescr, Idx]]),
2039
 
    ?line expect(1, [{[sysORID, Idx], [1,2,3,4,5]},
2040
 
                     {[sysORDescr, Idx], "test cap"}]),
2041
 
    ?line rpc:call(Node, snmp, del_agent_caps, [Idx]),
2042
 
    g([[sysORID, Idx]]),
2043
 
    ?line expect(2, [{[sysORID, Idx], noSuchInstance}]).
2044
 
    
2045
 
 
2046
 
%% Req. Test2
2047
 
v1_proc() ->
2048
 
    %% According to RFC1157.
2049
 
    %% Template: <Section>:<list no>
2050
 
    v1_get_p(),
2051
 
    v1_get_next_p(),
2052
 
    v1_set_p().
2053
 
    
2054
 
    
2055
 
v1_get_p() ->
2056
 
    %% 4.1.2:1
2057
 
    g([[test2]]),
2058
 
    ?line expect(10, noSuchName, 1, [{[test2], 'NULL'}]),
2059
 
    g([[tDescr]]),
2060
 
    ?line expect(11, noSuchName, 1, [{[tDescr], 'NULL'}]),
2061
 
    g([[tDescr2,0]]),
2062
 
    ?line expect(12, noSuchName, 1, [{[tDescr2,0], 'NULL'}]),
2063
 
    g([[tDescr3,0]]),
2064
 
    ?line expect(131, noSuchName, 1, [{[tDescr3,0], 'NULL'}]),
2065
 
    g([[tDescr4,0]]),
2066
 
    ?line expect(132, noSuchName, 1, [{[tDescr4,0], 'NULL'}]),
2067
 
    g([[sysDescr, 0], [tDescr,0]]), % Outside mibview
2068
 
    ?line expect(14, noSuchName, 2, [{[sysDescr, 0], 'NULL'},
2069
 
                                     {[tDescr,0], 'NULL'}]),
2070
 
    g([[sysDescr,3]]),
2071
 
    ?line expect(15, noSuchName, 1, [{[sysDescr, 3], 'NULL'}]),
2072
 
    
2073
 
    %% 4.1.2:2
2074
 
    g([[tTable]]),
2075
 
    ?line expect(20, noSuchName, 1, [{[tTable], 'NULL'}]),
2076
 
    g([[tEntry]]),
2077
 
    ?line expect(21, noSuchName, 1, [{[tEntry], 'NULL'}]),
2078
 
    
2079
 
    %% 4.1.2:3
2080
 
    g([[tTooBig, 0]]),
2081
 
    ?line expect(30, tooBig, 0, [{[tTooBig, 0], 'NULL'}]),
2082
 
 
2083
 
    %% 4.1.2:4
2084
 
    g([[tGenErr1, 0]]),
2085
 
    ?line expect(40, genErr, 1, [{[tGenErr1, 0], 'NULL'}]),
2086
 
    g([[tGenErr2, 0]]),
2087
 
    ?line expect(41, genErr, 1, [{[tGenErr2, 0], 'NULL'}]),
2088
 
    g([[sysDescr, 0], [tGenErr3, 0]]),
2089
 
    ?line expect(42, genErr, 2, [{[sysDescr, 0], 'NULL'},
2090
 
                                 {[tGenErr3, 0], 'NULL'}]).
2091
 
    
2092
 
    
2093
 
v1_get_next_p() ->
2094
 
    %% 4.1.3:1
2095
 
    gn([[1,3,7,1]]),
2096
 
    ?line expect(10, noSuchName, 1, [{[1,3,7,1], 'NULL'}]),
2097
 
    gn([[tDescr2]]),
2098
 
    ?line expect(11, tooBig, 0, any),
2099
 
    
2100
 
    %% 4.1.3:2
2101
 
    gn([[tTooBig]]),
2102
 
    io:format("We currently don't handle tooBig correct!!!\n"),
2103
 
%    ?line expect(20, tooBig, 0, [{[tTooBig], 'NULL'}]),
2104
 
    ?line expect(20, tooBig, 0, any),
2105
 
 
2106
 
    %% 4.1.3:3
2107
 
    gn([[tGenErr1]]),
2108
 
%    ?line expect(40, genErr, 1, [{[tGenErr1], 'NULL'}]),
2109
 
    ?line expect(40, genErr, 1, any),
2110
 
    gn([[tGenErr2]]),
2111
 
%    ?line expect(41, genErr, 1, [{[tGenErr2], 'NULL'}]),
2112
 
    ?line expect(41, genErr, 1, any),
2113
 
    gn([[sysDescr], [tGenErr3]]),
2114
 
%    ?line expect(42, genErr, 2, [{[sysDescr], 'NULL'},
2115
 
%                                {[tGenErr3], 'NULL'}]).
2116
 
    ?line expect(42, genErr, 2, any).
2117
 
    
2118
 
v1_set_p() ->
2119
 
    %% 4.1.5:1
2120
 
    s([{[1,3,7,0], i, 4}]),
2121
 
    ?line expect(10, noSuchName, 1, [{[1,3,7,0], 4}]),
2122
 
    s([{[tDescr,0], s, "outside mibview"}]),
2123
 
    ?line expect(11, noSuchName, 1, [{[tDescr,0], "outside mibview"}]),
2124
 
    s([{[tDescr3,0], s, "read-only"}]),
2125
 
    ?line expect(12, noSuchName, 1, [{[tDescr3,0], "read-only"}]),
2126
 
    s([{[tDescr3], s, "noSuchObject"}]),
2127
 
    ?line expect(13, noSuchName, 1, [{[tDescr3], "noSuchObject"}]),
2128
 
    s([{[tDescr3,1], s, "noSuchInstance"}]),
2129
 
    ?line expect(14, noSuchName, 1, [{[tDescr3,1], "noSuchInstance"}]),
2130
 
    s([{[tDescr2,0], s, "inconsistentName"}]),
2131
 
    ?line expect(15, noSuchName, 1, [{[tDescr2,0], "inconsistentName"}]),
2132
 
 
2133
 
    %% 4.1.5:2
2134
 
    s([{[tDescr2, 0], i, 4}]),
2135
 
    ?line expect(20, badValue, 1, [{[tDescr2, 0], 4}]),
2136
 
    s([{[tDescr2, 0], s, "badValue"}]),
2137
 
    ?line expect(21, badValue, 1, [{[tDescr2, 0], "badValue"}]),
2138
 
    
2139
 
    %% 4.1.5:3
2140
 
    %% The standard is quite incorrect here.  The resp pdu was too big.  In
2141
 
    %% the resp pdu, we have the original vbs.  In the tooBig pdu we still
2142
 
    %% have to original vbs => the tooBig pdu is too big as well!!!  It
2143
 
    %% may not get it to the manager, unless the agent uses 'NULL' instead
2144
 
    %% of the std-like original value.
2145
 
    s([{[tTooBig, 0], s, ?tooBigStr}]),
2146
 
    %% according to std:
2147
 
%    ?line expect(30, tooBig, 0, [{[tTooBig, 0], ?tooBigStr}]),
2148
 
    ?line expect(30, tooBig, 0, [{[tTooBig, 0], 'NULL'}]),
2149
 
    
2150
 
    %% 4.1.5:4
2151
 
    s([{[tDescr2, 0], s, "is_set_ok_fail"}]),
2152
 
    ?line expect(40, genErr, 1, [{[tDescr2, 0], "is_set_ok_fail"}]),
2153
 
    s([{[tDescr2, 0], s, "commit_fail"}]),
2154
 
    ?line expect(41, genErr, 1, [{[tDescr2, 0], "commit_fail"}]).
2155
 
    
2156
 
%% Req. Test2
2157
 
v2_proc() ->
2158
 
    %% According to RFC1905.
2159
 
    %% Template: <Section>:<list no>
2160
 
    ?DBG("v2_proc -> entry",[]),
2161
 
    v2_get_p(),
2162
 
    v2_get_next_p(),
2163
 
    v2_get_bulk_p(),
2164
 
    v2_set_p().
2165
 
 
2166
 
v2_get_p() ->
2167
 
    %% 4.2.1:2
2168
 
    ?DBG("v2_get_p -> entry",[]),
2169
 
    g([[test2]]),
2170
 
    ?line expect(10, [{[test2], noSuchObject}]),
2171
 
    g([[tDescr]]),
2172
 
    ?line expect(11, [{[tDescr], noSuchObject}]),
2173
 
    g([[tDescr4,0]]),
2174
 
    ?line expect(12, [{[tDescr4,0], noSuchObject}]),
2175
 
    g([[sysDescr, 0], [tDescr,0]]), % Outside mibview
2176
 
    ?line expect(13, [{[sysDescr,0], "Erlang SNMP agent"},
2177
 
                      {[tDescr,0], noSuchObject}]),
2178
 
    g([[tTable]]),
2179
 
    ?line expect(14, [{[tTable], noSuchObject}]),
2180
 
    g([[tEntry]]),
2181
 
    ?line expect(15, [{[tEntry], noSuchObject}]),
2182
 
    
2183
 
    %% 4.2.1:3
2184
 
    g([[tDescr2,0]]), %% instrum ret noSuchName!!!
2185
 
    ?line expect(20, [{[tDescr2,0], noSuchInstance}]), 
2186
 
    g([[tDescr3,0]]),
2187
 
    ?line expect(21, [{[tDescr3,0], noSuchInstance}]),
2188
 
    g([[sysDescr,3]]),
2189
 
    ?line expect(22, [{[sysDescr, 3], noSuchInstance}]),
2190
 
    g([[tIndex,1]]),
2191
 
    ?line expect(23, [{[tIndex, 1], noSuchInstance}]),
2192
 
 
2193
 
    %% 4.2.1 - any other error: genErr
2194
 
    g([[tGenErr1, 0]]),
2195
 
    ?line expect(30, genErr, 1, [{[tGenErr1, 0], 'NULL'}]),
2196
 
    g([[tGenErr2, 0]]),
2197
 
    ?line expect(31, genErr, 1, [{[tGenErr2, 0], 'NULL'}]),
2198
 
    g([[sysDescr, 0], [tGenErr3, 0]]),
2199
 
    ?line expect(32, genErr, 2, [{[sysDescr, 0], 'NULL'},
2200
 
                                 {[tGenErr3, 0], 'NULL'}]),
2201
 
    
2202
 
    %% 4.2.1 - tooBig
2203
 
    g([[tTooBig, 0]]),
2204
 
    ?line expect(40, tooBig, 0, []).
2205
 
 
2206
 
    
2207
 
v2_get_next_p() ->
2208
 
    %% 4.2.2:2
2209
 
    ?DBG("v2_get_next_p -> entry",[]),
2210
 
    gn([[1,3,7,1]]),
2211
 
    ?line expect(10, [{[1,3,7,1], endOfMibView}]),
2212
 
    gn([[sysDescr], [1,3,7,1]]),
2213
 
    ?line expect(11, [{[sysDescr, 0], "Erlang SNMP agent"},
2214
 
                      {[1,3,7,1], endOfMibView}]),
2215
 
    gn([[tCnt2, 1]]),
2216
 
    ?line expect(12, [{[tCnt2,2], 100}]),
2217
 
    gn([[tCnt2, 2]]),
2218
 
    ?line expect(12, [{[tCnt2,2], endOfMibView}]),
2219
 
    
2220
 
    %% 4.2.2 - any other error: genErr
2221
 
    gn([[tGenErr1]]),
2222
 
    ?line expect(20, genErr, 1, [{[tGenErr1], 'NULL'}]),
2223
 
    gn([[tGenErr2]]),
2224
 
    ?line expect(21, genErr, 1, [{[tGenErr2], 'NULL'}]),
2225
 
    gn([[sysDescr], [tGenErr3]]),
2226
 
    ?line expect(22, genErr, 2, [{[sysDescr], 'NULL'},
2227
 
                                 {[tGenErr3], 'NULL'}]),
2228
 
    
2229
 
    %% 4.2.2 - tooBig
2230
 
    gn([[tTooBig]]),
2231
 
    ?line expect(20, tooBig, 0, []).
2232
 
 
2233
 
v2_get_bulk_p() ->
2234
 
    %% 4.2.3
2235
 
    ?DBG("v2_get_bulk_p -> entry",[]),
2236
 
    gb(1, 1, []),
2237
 
    ?line expect(10, []),
2238
 
    gb(-1, 1, []),
2239
 
    ?line expect(11, []),
2240
 
    gb(-1, -1, []),
2241
 
    ?line expect(12, []),
2242
 
    gb(-1, -1, []),
2243
 
    ?line expect(13, []),
2244
 
    gb(2, 0, [[sysDescr], [1,3,7,1]]),
2245
 
    ?line expect(14, [{[sysDescr, 0], "Erlang SNMP agent"},
2246
 
                      {[1,3,7,1], endOfMibView}]),
2247
 
    gb(1, 2, [[sysDescr], [1,3,7,1]]),
2248
 
    ?line expect(15, [{[sysDescr, 0], "Erlang SNMP agent"},
2249
 
                      {[1,3,7,1], endOfMibView}]),
2250
 
    gb(0, 2, [[sysDescr], [1,3,7,1]]),
2251
 
    ?line expect(16, [{[sysDescr, 0], "Erlang SNMP agent"},
2252
 
                      {[1,3,7,1], endOfMibView},
2253
 
                      {[sysObjectID, 0], [1,2,3]},
2254
 
                      {[1,3,7,1], endOfMibView}]),
2255
 
    
2256
 
    gb(2, 2, [[sysDescr], [1,3,7,1], [sysDescr], [1,3,7,1]]),
2257
 
    ?line expect(17, [{[sysDescr, 0], "Erlang SNMP agent"},
2258
 
                      {[1,3,7,1], endOfMibView},
2259
 
                      {[sysDescr, 0], "Erlang SNMP agent"},                   
2260
 
                      {[1,3,7,1], endOfMibView},
2261
 
                      {[sysObjectID, 0], [1,2,3]},
2262
 
                      {[1,3,7,1], endOfMibView}]),
2263
 
    
2264
 
    gb(1, 2, [[sysDescr], [sysDescr], [tTooBig]]),
2265
 
    ?line expect(18, [{[sysDescr, 0], "Erlang SNMP agent"},
2266
 
                      {[sysDescr, 0], "Erlang SNMP agent"}]),
2267
 
    
2268
 
    gb(1,12, [[tDescr2], [sysDescr]]), % next one after tDescr2 is tTooBig.
2269
 
    ?line expect(19, []),
2270
 
    
2271
 
    gb(2,2, [[sysDescr], [sysObjectID], [tGenErr1], [sysDescr]]),
2272
 
    ?line expect(20, genErr, 3, [{[sysDescr], 'NULL'},
2273
 
                                 {[sysObjectID], 'NULL'},
2274
 
                                 {[tGenErr1], 'NULL'},
2275
 
                                 {[sysDescr], 'NULL'}]),
2276
 
    gb(0, 2, [[tCnt2, 1]]),
2277
 
    ?line expect(21, [{[tCnt2,2], 100},
2278
 
                      {[tCnt2,2], endOfMibView}]).
2279
 
    
2280
 
    
2281
 
v2_set_p() ->
2282
 
    %% 4.2.5:1
2283
 
    ?DBG("v2_set_p -> entry",[]),
2284
 
    s([{[1,3,7,0], i, 4}]),
2285
 
    ?line expect(10, noAccess, 1, [{[1,3,7,0], 4}]),
2286
 
    s([{[tDescr,0], s, "outside mibview"}]),
2287
 
    ?line expect(11, noAccess, 1, [{[tDescr,0], "outside mibview"}]),
2288
 
    
2289
 
    %% 4.2.5:2
2290
 
    s([{[1,3,6,1,0], s, "noSuchObject"}]),
2291
 
    ?line expect(20, notWritable, 1, [{[1,3,6,1,0], "noSuchObject"}]),
2292
 
    
2293
 
    %% 4.2.5:3
2294
 
    s([{[tDescr2, 0], i, 4}]),
2295
 
    ?line expect(30, wrongType, 1, [{[tDescr2, 0], 4}]),
2296
 
    s([{[tDescr2, 0], s, "badValue"}]),
2297
 
    ?line expect(31, badValue, 1, [{[tDescr2, 0], "badValue"}]),
2298
 
 
2299
 
    %% 4.2.5:4
2300
 
    s([{[tStr, 0], s, ""}]),
2301
 
    ?line expect(40, wrongLength, 1, [{[tStr, 0], ""}]),
2302
 
    s([{[tStr, 0], s, "12345"}]),
2303
 
    ?line expect(40, wrongLength, 1, [{[tStr, 0], "12345"}]),
2304
 
    
2305
 
    %% 4.2.5:5 - N/A
2306
 
 
2307
 
    %% 4.2.5:6
2308
 
    s([{[tInt1, 0], i, 0}]),
2309
 
    ?line expect(60, wrongValue, 1, [{[tInt1, 0], 0}]),
2310
 
    s([{[tInt1, 0], i, 5}]),
2311
 
    ?line expect(61, wrongValue, 1, [{[tInt1, 0], 5}]),
2312
 
    s([{[tInt2, 0], i, 0}]),
2313
 
    ?line expect(62, wrongValue, 1, [{[tInt2, 0], 0}]),
2314
 
    s([{[tInt2, 0], i, 5}]),
2315
 
    ?line expect(63, wrongValue, 1, [{[tInt2, 0], 5}]),
2316
 
    s([{[tInt3, 0], i, 5}]),
2317
 
    ?line expect(64, wrongValue, 1, [{[tInt3, 0], 5}]),
2318
 
    
2319
 
    %% 4.2.5:7
2320
 
    s([{[tDescrX, 1, 1], s, "noCreation"}]),
2321
 
    ?line expect(70, noCreation, 1, [{[tDescrX, 1, 1], "noCreation"}]),
2322
 
 
2323
 
    %% 4.2.5:8
2324
 
    s([{[tDescrX, 1, 2], s, "inconsistentName"}]),
2325
 
    ?line expect(80, inconsistentName, 1,
2326
 
                 [{[tDescrX, 1, 2], "inconsistentName"}]),
2327
 
    
2328
 
    %% 4.2.5:9
2329
 
    s([{[tCnt, 1, 2], i, 5}]),
2330
 
    ?line expect(90, notWritable, 1, [{[tCnt, 1, 2], 5}]),
2331
 
    s([{[tDescr3,0], s, "read-only"}]),
2332
 
    ?line expect(90, notWritable, 1, [{[tDescr3,0], "read-only"}]),
2333
 
 
2334
 
    %% 4.2.5:10
2335
 
    s([{[tDescr2,0], s, "inconsistentValue"}]),
2336
 
    ?line expect(100, inconsistentValue, 1,
2337
 
                 [{[tDescr2,0], "inconsistentValue"}]),
2338
 
    
2339
 
    %% 4.2.5:11
2340
 
    s([{[tDescr2,0], s, "resourceUnavailable"}]),
2341
 
    ?line expect(110, resourceUnavailable, 1,
2342
 
                 [{[tDescr2,0],"resourceUnavailable"}]),
2343
 
    
2344
 
    %% 4.2.5:12
2345
 
    s([{[tDescr2, 0], s, "is_set_ok_fail"}]),
2346
 
    ?line expect(120, genErr, 1, [{[tDescr2, 0], "is_set_ok_fail"}]).
2347
 
    
2348
 
    %% commitFailed and undoFailed is tested by the 'undo' case.
2349
 
    
2350
 
 
2351
 
%% Req. OLD-SNMPEA-MIB
2352
 
table_test() ->
2353
 
    io:format("Testing simple get, next and set on communityTable...~n"),
2354
 
%% {[147,214,36,45], "public", 2, readWrite}.
2355
 
%% {[147,214,36,45], "standard trap", 2, read}.
2356
 
    Key1c3 = [intCommunityViewIndex,get(mip),is("public")],
2357
 
    Key2c3 = [intCommunityViewIndex,get(mip),is("standard trap")],
2358
 
    Key1c4 = [intCommunityAccess,get(mip),is("public")],
2359
 
    EndKey = [intCommunityEntry,[9],get(mip),is("public")],
2360
 
    gn([[intCommunityEntry]]),
2361
 
    ?line expect(7, [{Key1c3, 2}]),
2362
 
    gn([[intCommunityTable]]),
2363
 
    ?line expect(71, [{Key1c3, 2}]),
2364
 
    gn([[community]]),
2365
 
    ?line expect(72, [{Key1c3, 2}]),
2366
 
    gn([[otpSnmpeaMIB]]),
2367
 
    ?line expect(73, [{Key1c3, 2}]),
2368
 
    gn([[ericsson]]),
2369
 
    ?line expect(74, [{Key1c3, 2}]),
2370
 
    gn([Key1c3]),
2371
 
    ?line expect(8, [{Key2c3, 2}]),
2372
 
    gn([Key2c3]),
2373
 
    ?line expect(9, [{Key1c4, 2}]),
2374
 
    gn([EndKey]),
2375
 
    AgentIp = [intAgentIpAddress,0],
2376
 
    ?line expect(10, [{[intAgentIpAddress,0], any}]),
2377
 
    g([Key1c3]),
2378
 
    ?line expect(11, [{Key1c3, 2}]),
2379
 
    g([EndKey]),
2380
 
    ?line ?v1_2(expect(12, noSuchName, 1, any),
2381
 
                expect(12, [{EndKey, noSuchObject}])),
2382
 
 
2383
 
    io:format("Testing row creation/deletion on communityTable...~n"),
2384
 
    NewKeyc3 = [intCommunityViewIndex,get(mip),is("test")],
2385
 
    NewKeyc4 = [intCommunityAccess,get(mip),is("test")],
2386
 
    NewKeyc5 = [intCommunityStatus,get(mip),is("test")],
2387
 
    s([{NewKeyc5, ?createAndGo}]),
2388
 
    ?line expect(14, ?v1_2(badValue, inconsistentValue), 1,any),
2389
 
    s([{NewKeyc5, ?createAndGo}, {NewKeyc3, 2}, {NewKeyc4, 2}]),
2390
 
    ?line expect(15, [{NewKeyc5, ?createAndGo},{NewKeyc3, 2}, {NewKeyc4, 2}]),
2391
 
    g([NewKeyc4]),
2392
 
    ?line expect(16, [{NewKeyc4, 2}]),
2393
 
    s([{NewKeyc5, ?destroy}]),
2394
 
    ?line expect(17, [{NewKeyc5, ?destroy}]),
2395
 
    s([{NewKeyc4, 2}]),
2396
 
    ?line expect(18, ?v1_2(noSuchName, inconsistentName), 1,[{NewKeyc4, 2}]),
2397
 
    s([{NewKeyc5, ?createAndWait}]),
2398
 
    ?line expect(19, [{NewKeyc5, ?createAndWait}]),
2399
 
    g([NewKeyc5]),
2400
 
    ?line expect(20, [{NewKeyc5, ?notReady}]),
2401
 
    s([{NewKeyc4, 2}]),
2402
 
    ?line expect(21, [{NewKeyc4, 2}]),
2403
 
    g([NewKeyc5]),
2404
 
    ?line expect(22, [{NewKeyc5, ?notReady}]),
2405
 
    s([{NewKeyc3, 2}]),
2406
 
    ?line expect(23, [{NewKeyc3, 2}]),
2407
 
    g([NewKeyc5]),
2408
 
    ?line expect(24, [{NewKeyc5, ?notInService}]),
2409
 
    s([{NewKeyc5, ?active}]),
2410
 
    ?line expect(25, [{NewKeyc5, ?active}]),
2411
 
    s([{NewKeyc5, ?destroy}]),
2412
 
    ?line expect(26, [{NewKeyc5, ?destroy}]),
2413
 
    s([{NewKeyc3, 3}]),
2414
 
    ?line expect(27, ?v1_2(noSuchName, inconsistentName), 1,[{NewKeyc3, 3}]),
2415
 
    otp_1128().
2416
 
 
2417
 
%% Req. system group
2418
 
simple_standard_test() ->
2419
 
    ?DBG("simple_standard_test -> gn 1,1", []),
2420
 
    gn([[1,1]]),
2421
 
    ?line expect(1, [{[sysDescr,0], "Erlang SNMP agent"}]),
2422
 
 
2423
 
    ?DBG("simple_standard_test -> gn 1,3", []),
2424
 
    gn([[1,3]]),
2425
 
    ?line expect(11, [{[sysDescr,0], "Erlang SNMP agent"}]),
2426
 
 
2427
 
    ?DBG("simple_standard_test -> gn 1,3,6", []),
2428
 
    gn([[1,3,6]]),
2429
 
    ?line expect(12, [{[sysDescr,0], "Erlang SNMP agent"}]),
2430
 
 
2431
 
    ?DBG("simple_standard_test -> gn 1,3,6,1", []),
2432
 
    gn([[1,3,6,1]]),
2433
 
    ?line expect(13, [{[sysDescr,0], "Erlang SNMP agent"}]),
2434
 
 
2435
 
    ?DBG("simple_standard_test -> gn 1,3,6,1,2", []),
2436
 
    gn([[1,3,6,1,2]]),
2437
 
    ?line expect(14, [{[sysDescr,0], "Erlang SNMP agent"}]),
2438
 
 
2439
 
    ?DBG("simple_standard_test -> gn 1,3,6,1,2,1", []),
2440
 
    gn([[1,3,6,1,2,1]]),
2441
 
    ?line expect(15, [{[sysDescr,0], "Erlang SNMP agent"}]),
2442
 
 
2443
 
    ?DBG("simple_standard_test -> gn 1,3,6,1,2,1,1", []),
2444
 
    gn([[1,3,6,1,2,1,1]]),
2445
 
    ?line expect(16, [{[sysDescr,0], "Erlang SNMP agent"}]),
2446
 
 
2447
 
    ?DBG("simple_standard_test -> gn sysDescr", []),
2448
 
    gn([[sysDescr]]),
2449
 
    ?line expect(17, [{[sysDescr,0], "Erlang SNMP agent"}]),
2450
 
 
2451
 
    ?DBG("simple_standard_test -> g sysDescr,0", []),
2452
 
    g([[sysDescr,0]]),
2453
 
    ?line expect(2, [{[sysDescr,0], "Erlang SNMP agent"}]),
2454
 
 
2455
 
    ?DBG("simple_standard_test -> g sysDescr", []),
2456
 
    g([[sysDescr]]),
2457
 
    ?line ?v1_2(expect(3, noSuchName, 1, any),
2458
 
                expect(3, [{[sysDescr], noSuchObject}])),
2459
 
 
2460
 
    ?DBG("simple_standard_test -> g 1,6,7,0", []),
2461
 
    g([[1,6,7,0]]),
2462
 
    ?line ?v1_2(expect(41, noSuchName, 1, any),
2463
 
                expect(3, [{[1,6,7,0], noSuchObject}])),
2464
 
 
2465
 
    ?DBG("simple_standard_test -> gn 1,13", []),
2466
 
    gn([[1,13]]),
2467
 
    ?line ?v1_2(expect(4, noSuchName,1, any),
2468
 
                expect(4, [{[1,13], endOfMibView}])),
2469
 
 
2470
 
    ?DBG("simple_standard_test -> s sysLocation,0", []),
2471
 
    s([{[sysLocation, 0], "new_value"}]),
2472
 
    ?line expect(5, [{[sysLocation, 0], "new_value"}]),
2473
 
 
2474
 
    ?DBG("simple_standard_test -> g sysLocation,0", []),
2475
 
    g([[sysLocation, 0]]),
2476
 
    ?line expect(6, [{[sysLocation, 0], "new_value"}]),
2477
 
    io:format("Testing noSuchName and badValue...~n"),
2478
 
 
2479
 
    ?DBG("simple_standard_test -> s sysServices,0 3", []),
2480
 
    s([{[sysServices,0], 3}]),
2481
 
    ?line expect(61, ?v1_2(noSuchName, notWritable), 1, any),
2482
 
 
2483
 
    ?DBG("simple_standard_test -> s sysServices,0 i 3", []),
2484
 
    s([{[sysLocation, 0], i, 3}]),
2485
 
    ?line expect(62, ?v1_2(badValue, wrongType), 1, any),
2486
 
 
2487
 
    ?DBG("simple_standard_test -> done", []),
2488
 
    ok.
2489
 
 
2490
 
%% This is run in the agent node
2491
 
db_notify_client(suite) -> [];
2492
 
db_notify_client(Config) when list(Config) ->
2493
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
2494
 
    ?DBG("~n\tSaNode: ~p~n\tMgrNode: ~p~n\tMibDir: ~p",
2495
 
           [SaNode,MgrNode,MibDir]),
2496
 
    snmp_local_db:register_notify_client(self(),?MODULE),
2497
 
 
2498
 
    %% This call (the manager) will issue to set operations, so
2499
 
    %% we expect to receive to notify(insert) calls.
2500
 
    try_test(db_notify_client_test),
2501
 
 
2502
 
    ?DBG("await first notify",[]),
2503
 
    receive 
2504
 
        {db_notify_test_reply,insert} -> ?DBG("first notify received",[]),ok
2505
 
    end,
2506
 
    
2507
 
    ?DBG("await second notify",[]),
2508
 
    receive 
2509
 
        {db_notify_test_reply,insert} -> ?DBG("second notify received",[]),ok
2510
 
    end,
2511
 
 
2512
 
    snmp_local_db:unregister_notify_client(self()).
2513
 
 
2514
 
 
2515
 
%% This is run in the manager node
2516
 
db_notify_client_test() ->
2517
 
    ?DBG("set first new sysLocation",[]),
2518
 
    s([{[sysLocation, 0], "new_value"}]),
2519
 
    ?line expect(5, [{[sysLocation, 0], "new_value"}]),
2520
 
 
2521
 
    ?DBG("set second new sysLocation",[]),
2522
 
    s([{[sysLocation, 0], "new_value"}]),
2523
 
    ?line expect(5, [{[sysLocation, 0], "new_value"}]).
2524
 
 
2525
 
notify(Pid,What) -> 
2526
 
    ?DBG("notify(~p,~p) -> called",[Pid,What]),
2527
 
    Pid ! {db_notify_test_reply,What}.
2528
 
 
2529
 
 
2530
 
%% Req: system group, OLD-SNMPEA-MIB, Klas1
2531
 
big_test() ->
2532
 
    p("Testing simple next/get/set @ master agent..."),
2533
 
    simple_standard_test(),
2534
 
    
2535
 
    p("Testing simple next/get/set @ subagent..."),
2536
 
    gn([[klas1]]),
2537
 
    ?line expect(1, [{[fname,0], ""}]),
2538
 
    g([[fname,0]]),
2539
 
    ?line expect(2, [{[fname,0], ""}]),
2540
 
    s([{[fname,0], s, "test set"}]),
2541
 
    ?line expect(3, [{[fname,0], "test set"}]),
2542
 
    g([[fname,0]]),
2543
 
    ?line expect(4, [{[fname,0], "test set"}]),
2544
 
    
2545
 
    p("Testing next from last instance in master to subagent..."),
2546
 
    gn([[?v1_2(sysServices, sysORLastChange),0]]),
2547
 
    ?line expect(5, [{[fname,0], "test set"}]),
2548
 
    gn([[1,1],
2549
 
        [?v1_2(sysServices, sysORLastChange),0]]),
2550
 
    ?line expect(51, [{[sysDescr,0], "Erlang SNMP agent"},
2551
 
                {[fname,0], "test set"}]),
2552
 
    s([{[fname,0], s, ""}]),
2553
 
    ?line expect(52, [{[fname,0], ""}]),
2554
 
    
2555
 
    table_test(),
2556
 
 
2557
 
    p("Adding one row in subagent table"),
2558
 
    FTab = [friendsEntry],
2559
 
    s([{[friendsEntry, [2, 3]], s, "kompis3"},
2560
 
       {[friendsEntry, [3, 3]], i, ?createAndGo}]),
2561
 
    ?line expect(6, [{[friendsEntry, [2, 3]], "kompis3"},
2562
 
               {[friendsEntry, [3, 3]], ?createAndGo}]),
2563
 
    g([[friendsEntry, [2, 3]],
2564
 
       [friendsEntry, [3, 3]]]),
2565
 
    ?line expect(7, [{[friendsEntry, [2, 3]], "kompis3"},
2566
 
               {[friendsEntry, [3, 3]], ?active}]),
2567
 
    s([{[friendsEntry, [3, 3]], i, ?destroy}]),
2568
 
    ?line expect(8, [{[friendsEntry, [3, 3]], ?destroy}]),
2569
 
    
2570
 
    otp_1131(),
2571
 
 
2572
 
    p("Adding two rows in subagent table with special INDEX"),
2573
 
    s([{[kompissEntry, [1, 3]], s, "kompis3"},
2574
 
       {[kompissEntry, [2, 3]], i, ?createAndGo}]),
2575
 
    ?line expect(9, [{[kompissEntry, [1, 3]], "kompis3"},
2576
 
               {[kompissEntry, [2, 3]], ?createAndGo}]),
2577
 
    g([[kompissEntry, [1, 3]],
2578
 
       [kompissEntry, [2, 3]]]),
2579
 
    ?line expect(10, [{[kompissEntry, [1, 3]], "kompis3"},
2580
 
                {[kompissEntry, [2, 3]], ?active}]),
2581
 
    gn([[kompissEntry, [1]],
2582
 
        [kompissEntry, [2]]]),
2583
 
    ?line expect(11, [{[kompissEntry, [1, 3]], "kompis3"},
2584
 
                {[kompissEntry, [2, 3]], ?active}]),
2585
 
    s([{[kompissEntry, [1, 2]], s, "kompis3"},
2586
 
       {[kompissEntry, [2, 2]], i, ?createAndGo}]),
2587
 
    ?line expect(12, [{[kompissEntry, [1, 2]], "kompis3"},
2588
 
                {[kompissEntry, [2, 2]], ?createAndGo}]),
2589
 
    gn([[kompissEntry, [1, 1]],
2590
 
        [kompissEntry, [2, 1]]]),
2591
 
    ?line expect(13, [{[kompissEntry, [1, 2]], "kompis3"},
2592
 
                {[kompissEntry, [2, 2]], ?active}]),
2593
 
    s([{[kompissEntry, [2, 3]], i, ?destroy}]),
2594
 
    ?line expect(14, [{[kompissEntry, [2, 3]], ?destroy}]),
2595
 
    s([{[kompissEntry, [2, 2]], i, ?destroy}]),
2596
 
    ?line expect(15, [{[kompissEntry, [2, 2]], ?destroy}]),
2597
 
    ok.
2598
 
 
2599
 
%% Req. system group, Klas2, OLD-SNMPEA-MIB
2600
 
big_test_2() ->
2601
 
    p("Testing simple next/get/set @ master agent (2)..."),
2602
 
    simple_standard_test(),
2603
 
    
2604
 
    p("Testing simple next/get/set @ subagent (2)..."),
2605
 
    gn([[klas2]]),
2606
 
    ?line expect(1, [{[fname2,0], ""}]),
2607
 
    g([[fname2,0]]),
2608
 
    ?line expect(2, [{[fname2,0], ""}]),
2609
 
    s([{[fname2,0], s, "test set"}]),
2610
 
    ?line expect(3, [{[fname2,0], "test set"}]),
2611
 
    g([[fname2,0]]),
2612
 
    ?line expect(4, [{[fname2,0], "test set"}]),
2613
 
 
2614
 
    otp_1298(),
2615
 
 
2616
 
    p("Testing next from last object in master to subagent (2)..."),
2617
 
    gn([[?v1_2(sysServices, sysORLastChange),0]]),
2618
 
    ?line expect(5, [{[fname2,0], "test set"}]),
2619
 
    gn([[1,1],
2620
 
        [?v1_2(sysServices, sysORLastChange),0]]),
2621
 
    ?line expect(51, [{[sysDescr,0], "Erlang SNMP agent"},
2622
 
                {[fname2,0], "test set"}]),
2623
 
    
2624
 
    table_test(),
2625
 
    
2626
 
    p("Adding one row in subagent table (2)"),
2627
 
    FTab = [friendsEntry2],
2628
 
    s([{[friendsEntry2, [2, 3]], s, "kompis3"},
2629
 
       {[friendsEntry2, [3, 3]], i, ?createAndGo}]),
2630
 
    ?line expect(6, [{[friendsEntry2, [2, 3]], "kompis3"},
2631
 
               {[friendsEntry2, [3, 3]], ?createAndGo}]),
2632
 
    g([[friendsEntry2, [2, 3]],
2633
 
       [friendsEntry2, [3, 3]]]),
2634
 
    ?line expect(7, [{[friendsEntry2, [2, 3]], "kompis3"},
2635
 
               {[friendsEntry2, [3, 3]], ?active}]),
2636
 
    s([{[friendsEntry2, [3, 3]], i, ?destroy}]),
2637
 
    ?line expect(8, [{[friendsEntry2, [3, 3]], ?destroy}]),
2638
 
    
2639
 
    p("Adding two rows in subagent table with special INDEX (2)"),
2640
 
    s([{[kompissEntry2, [1, 3]], s, "kompis3"},
2641
 
       {[kompissEntry2, [2, 3]], i, ?createAndGo}]),
2642
 
    ?line expect(9, [{[kompissEntry2, [1, 3]], "kompis3"},
2643
 
               {[kompissEntry2, [2, 3]], ?createAndGo}]),
2644
 
    g([[kompissEntry2, [1, 3]],
2645
 
       [kompissEntry2, [2, 3]]]),
2646
 
    ?line expect(10, [{[kompissEntry2, [1, 3]], "kompis3"},
2647
 
                {[kompissEntry2, [2, 3]], ?active}]),
2648
 
    gn([[kompissEntry2, [1]],
2649
 
        [kompissEntry2, [2]]]),
2650
 
    ?line expect(11, [{[kompissEntry2, [1, 3]], "kompis3"},
2651
 
                {[kompissEntry2, [2, 3]], ?active}]),
2652
 
    s([{[kompissEntry2, [1, 2]], s, "kompis3"},
2653
 
       {[kompissEntry2, [2, 2]], i, ?createAndGo}]),
2654
 
    ?line expect(12, [{[kompissEntry2, [1, 2]], "kompis3"},
2655
 
                {[kompissEntry2, [2, 2]], ?createAndGo}]),
2656
 
    gn([[kompissEntry2, [1, 1]],
2657
 
        [kompissEntry2, [2, 1]]]),
2658
 
    ?line expect(13, [{[kompissEntry2, [1, 2]], "kompis3"},
2659
 
                {[kompissEntry2, [2, 2]], ?active}]),
2660
 
    s([{[kompissEntry2, [2, 3]], i, ?destroy}]),
2661
 
    ?line expect(14, [{[kompissEntry2, [2, 3]], ?destroy}]),
2662
 
    s([{[kompissEntry2, [2, 2]], i, ?destroy}]),
2663
 
    ?line expect(15, [{[kompissEntry2, [2, 2]], ?destroy}]),
2664
 
    ok.
2665
 
 
2666
 
%% Req. Test1
2667
 
multi_threaded_test() ->
2668
 
    p("Testing multi threaded agent..."),
2669
 
    g([[multiStr,0]]),
2670
 
    Pid = get_multi_pid(),
2671
 
    g([[sysUpTime,0]]),
2672
 
    ?line expect(1, [{[sysUpTime,0], any}]),
2673
 
    s([{[sysLocation, 0], s, "pelle"}]),
2674
 
    ?line expect(2, [{[sysLocation, 0], "pelle"}]),
2675
 
    Pid ! continue,
2676
 
    ?line expect(3, [{[multiStr,0], "ok"}]),
2677
 
    
2678
 
    s([{[multiStr, 0], s, "block"}]),
2679
 
    Pid2 = get_multi_pid(),    
2680
 
    g([[sysUpTime,0]]),
2681
 
    ?line expect(4, [{[sysUpTime,0], any}]),
2682
 
    g([[multiStr,0]]),
2683
 
    Pid3 = get_multi_pid(),
2684
 
    g([[sysUpTime,0]]),
2685
 
    ?line expect(5, [{[sysUpTime,0], any}]),
2686
 
    s([{[sysLocation, 0], s, "kalle"}]),
2687
 
    Pid3 ! continue,
2688
 
    ?line expect(6, [{[multiStr,0], "ok"}]),
2689
 
    Pid2 ! continue,
2690
 
    ?line expect(7, [{[multiStr,0], "block"}]),
2691
 
    ?line expect(8, [{[sysLocation,0], "kalle"}]).
2692
 
 
2693
 
%% Req. Test1, TestTrapv2
2694
 
mt_trap_test(MA) ->
2695
 
    snmp:send_trap(MA, testTrapv22, "standard trap"),
2696
 
    ?line expect(1, v2trap, [{[sysUpTime, 0], any},
2697
 
                             {[snmpTrapOID, 0], ?system ++ [0,1]}]),
2698
 
 
2699
 
    snmp:send_trap(MA, mtTrap, "standard trap"),
2700
 
    Pid = get_multi_pid(),
2701
 
    g([[sysUpTime,0]]),
2702
 
    ?line expect(2, [{[sysUpTime,0], any}]),
2703
 
    snmp:send_trap(MA, testTrapv22, "standard trap"),
2704
 
    ?line expect(3, v2trap, [{[sysUpTime, 0], any},
2705
 
                             {[snmpTrapOID, 0], ?system ++ [0,1]}]),
2706
 
    Pid ! continue,
2707
 
    ?line expect(4, v2trap, [{[sysUpTime, 0], any},
2708
 
                             {[snmpTrapOID, 0], ?testTrap ++ [2]},
2709
 
                             {[multiStr,0], "ok"}]).
2710
 
 
2711
 
    
2712
 
get_multi_pid() ->
2713
 
    get_multi_pid(10).
2714
 
get_multi_pid(0) ->
2715
 
    ?line ?FAIL(no_global_name);
2716
 
get_multi_pid(N) ->
2717
 
    sleep(1000),
2718
 
    case global:whereis_name(snmp_multi_tester) of
2719
 
        Pid when pid(Pid) -> Pid;
2720
 
        _ -> get_multi_pid(N-1)
2721
 
    end.
2722
 
 
2723
 
%% Req. Test1
2724
 
types_v2_test() ->
2725
 
    p("Testing v2 types..."),
2726
 
 
2727
 
    s([{[bits1,0], 2#10}]),
2728
 
    ?line expect(1, [{[bits1,0], ?str(2#10)}]),
2729
 
    g([[bits1,0]]),
2730
 
    ?line expect(2, [{[bits1,0], ?str(2#101)}]),
2731
 
    
2732
 
    s([{[bits2,0], 2#11000000110}]),
2733
 
    ?line expect(3, [{[bits2,0], ?str(2#11000000110)}]),
2734
 
    g([[bits2,0]]),
2735
 
    ?line expect(4, [{[bits2,0], ?str(2#11000000110)}]),
2736
 
    
2737
 
    g([[bits3,0]]),
2738
 
    ?line expect(50, genErr, 1, any),
2739
 
    
2740
 
    g([[bits4,0]]),
2741
 
    ?line expect(51, genErr, 1, any),
2742
 
    
2743
 
    s([{[bits1,0], s, [2#10]}]),
2744
 
    ?line expect(6, ?v1_2(badValue, wrongValue), 1, any),
2745
 
 
2746
 
    s([{[bits2,0], 2#11001001101010011}]),
2747
 
    ?line expect(7, ?v1_2(badValue, wrongValue), 1, any).
2748
 
    
2749
 
 
2750
 
%% Req. Test1
2751
 
implied_test(MA) ->
2752
 
    ?LOG("implied_test -> start",[]),
2753
 
    p("Testing IMPLIED..."),
2754
 
 
2755
 
    snmp:verbosity(MA,trace),
2756
 
    snmp:verbosity(MA,trace),
2757
 
 
2758
 
    %% Create two rows, check that they are get-nexted in correct order.
2759
 
    Idx1 = "apa",
2760
 
    Idx2 = "qq",
2761
 
    ?DBG("implied_test -> (send) create row 1 '~s' in table 1",[Idx1]),
2762
 
    s([{[testStatus, Idx1], i, ?createAndGo}, {[testDescr, Idx1],s,"row 1"}]),
2763
 
    ?line expect(1, [{[testStatus, Idx1], ?createAndGo},
2764
 
                     {[testDescr, Idx1], "row 1"}]),
2765
 
    ?DBG("implied_test -> (send) create row 2 '~s' in table 1",[Idx2]),
2766
 
    s([{[testStatus, Idx2], i, ?createAndGo}, {[testDescr, Idx2],s,"row 2"}]),
2767
 
    ?line expect(2, [{[testStatus, Idx2], ?createAndGo},
2768
 
                     {[testDescr, Idx2], "row 2"}]),
2769
 
    ?DBG("implied_test -> get-next(testDescr)",[]),
2770
 
    gn([[testDescr]]),
2771
 
    ?line expect(3, [{[testDescr,Idx1], "row 1"}]),
2772
 
    ?DBG("implied_test -> get-next(testDescr) of row 1",[]),
2773
 
    gn([[testDescr,Idx1]]),
2774
 
    ?line expect(4, [{[testDescr,Idx2], "row 2"}]),
2775
 
 
2776
 
    % Delete the rows
2777
 
    ?DBG("implied_test -> (send) delete row 1 '~s' from table 1",[Idx1]),
2778
 
    s([{[testStatus, Idx1], i, ?destroy}]),
2779
 
    ?line expect(5, [{[testStatus, Idx1], ?destroy}]),
2780
 
    ?DBG("implied_test -> (send) delete row 2 '~s' from table 1",[Idx2]),
2781
 
    s([{[testStatus, Idx2], i, ?destroy}]),
2782
 
    ?line expect(6, [{[testStatus, Idx2], ?destroy}]),
2783
 
 
2784
 
    %% Try the same in other table
2785
 
    Idx3 = [1, "apa"],
2786
 
    Idx4 = [1, "qq"],
2787
 
    ?DBG("implied_test -> (send) create row 1 '~s' in table 2",[Idx3]),
2788
 
    s([{[testStatus2, Idx3], i, ?createAndGo}, {[testDescr2,Idx3],s,"row 1"}]),
2789
 
    ?line expect(1, [{[testStatus2, Idx3], ?createAndGo},
2790
 
                     {[testDescr2, Idx3], "row 1"}]),
2791
 
    ?DBG("implied_test -> (send) create row 2 '~s' in table 2",[Idx4]),
2792
 
    s([{[testStatus2, Idx4], i, ?createAndGo}, {[testDescr2,Idx4],s,"row 2"}]),
2793
 
    ?line expect(2, [{[testStatus2, Idx4], ?createAndGo},
2794
 
                     {[testDescr2, Idx4], "row 2"}]),
2795
 
    ?DBG("implied_test -> get-next(testDescr2)",[]),
2796
 
    gn([[testDescr2]]),
2797
 
    ?line expect(3, [{[testDescr2,Idx3], "row 1"}]),
2798
 
    ?DBG("implied_test -> get-next(testDescr2) of row 1",[]),
2799
 
    gn([[testDescr2,Idx3]]),
2800
 
    ?line expect(4, [{[testDescr2,Idx4], "row 2"}]),
2801
 
 
2802
 
    % Delete the rows
2803
 
    ?DBG("implied_test -> (send) delete row 1 '~s' from table 2",[Idx3]),
2804
 
    s([{[testStatus2, Idx3], i, ?destroy}]),
2805
 
    ?line expect(5, [{[testStatus2, Idx3], ?destroy}]),
2806
 
    ?DBG("implied_test -> (send) delete row 2 '~s' from table 2",[Idx4]),
2807
 
    s([{[testStatus2, Idx4], i, ?destroy}]),
2808
 
    ?line expect(6, [{[testStatus2, Idx4], ?destroy}]),
2809
 
 
2810
 
    snmp:debug(MA,true),
2811
 
 
2812
 
    ?LOG("implied_test -> done",[]).
2813
 
    
2814
 
    
2815
 
 
2816
 
%% Req. Test1
2817
 
sparse_table_test() ->
2818
 
    p("Testing sparse table..."),
2819
 
 
2820
 
    %% Create two rows, check that they are get-nexted in correct order.
2821
 
    Idx1 = 1,
2822
 
    Idx2 = 2,
2823
 
    s([{[sparseStatus, Idx1], i, ?createAndGo},
2824
 
       {[sparseDescr, Idx1], s, "row 1"}]),
2825
 
    ?line expect(1, [{[sparseStatus, Idx1], ?createAndGo},
2826
 
                     {[sparseDescr, Idx1], "row 1"}]),
2827
 
    s([{[sparseStatus, Idx2], i, ?createAndGo},
2828
 
       {[sparseDescr, Idx2], s, "row 2"}]),
2829
 
    ?line expect(2, [{[sparseStatus, Idx2], ?createAndGo},
2830
 
                     {[sparseDescr, Idx2], "row 2"}]),
2831
 
    ?v1_2(gn([[sparseIndex], [sparseDescr,Idx1], [sparseDescr,Idx2],
2832
 
              [sparseStatus,Idx1], [sparseStatus,Idx2]]),
2833
 
          gb(0,5,[[sparseIndex]])),
2834
 
    ?line expect(3, [{[sparseDescr,Idx1], "row 1"},
2835
 
                     {[sparseDescr,Idx2], "row 2"},
2836
 
                     {[sparseStatus,Idx1], ?active},
2837
 
                     {[sparseStatus,Idx2], ?active},
2838
 
                     {[sparseStr,0], "slut"}]),
2839
 
    % Delete the rows
2840
 
    s([{[sparseStatus, Idx1], i, ?destroy}]),
2841
 
    ?line expect(4, [{[sparseStatus, Idx1], ?destroy}]),
2842
 
    s([{[sparseStatus, Idx2], i, ?destroy}]),
2843
 
    ?line expect(5, [{[sparseStatus, Idx2], ?destroy}]).
2844
 
 
2845
 
 
2846
 
%% Req. Test1
2847
 
cnt_64_test(MA) ->
2848
 
    ?LOG("start cnt64 test (~p)",[MA]),
2849
 
    snmp:verbosity(MA,trace),
2850
 
    ?LOG("start cnt64 test",[]),
2851
 
    p("Testing Counter64, and at the same time, RowStatus is not last column"),
2852
 
    
2853
 
    ?DBG("get cnt64",[]),
2854
 
    g([[cnt64,0]]),
2855
 
    ?DBG("await response",[]),
2856
 
    ?line ?v1_2(expect(1, noSuchName, 1, any),
2857
 
                expect(1, [{[cnt64,0],18446744073709551615}])),
2858
 
    ?DBG("get-next cnt64",[]),
2859
 
    gn([[cnt64]]),
2860
 
    ?DBG("await response",[]),
2861
 
    ?line ?v1_2(expect(2, [{[cnt64Str,0], "after cnt64"}]),
2862
 
                expect(2, [{[cnt64,0],18446744073709551615}])),
2863
 
    ?DBG("send cntTrap",[]),
2864
 
    snmp:send_trap(MA,cntTrap,"standard trap",[{sysContact,"pelle"},
2865
 
                                               {cnt64, 10},
2866
 
                                               {sysLocation, "here"}]),
2867
 
    ?DBG("await response",[]),
2868
 
    ?line ?v1_2(expect(3, trap, [test], 6, 1, [{[sysContact,0], "pelle"},
2869
 
                                               {[sysLocation,0], "here"}]),
2870
 
                expect(3, v2trap, [{[sysUpTime, 0], any},
2871
 
                                   {[snmpTrapOID, 0], ?testTrap ++ [1]},
2872
 
                                   {[sysContact,0], "pelle"},
2873
 
                                   {[cnt64,0], 10},
2874
 
                                   {[sysLocation,0], "here"}])),
2875
 
    
2876
 
    %% Create two rows, check that they are get-nexted in correct order.
2877
 
    Idx1 = 1,
2878
 
    Idx2 = 2,
2879
 
    ?DBG("create row (cntStatus): ~p",[Idx1]),
2880
 
    s([{[cntStatus, Idx1], i, ?createAndGo}]),
2881
 
    ?DBG("await response",[]),
2882
 
    ?line expect(1, [{[cntStatus, Idx1], ?createAndGo}]),
2883
 
    ?DBG("create row (cntStatus): ~p",[Idx2]),
2884
 
    s([{[cntStatus, Idx2], i, ?createAndGo}]),
2885
 
    ?DBG("await response",[]),
2886
 
    ?line expect(2, [{[cntStatus, Idx2], ?createAndGo}]),
2887
 
 
2888
 
    ?DBG("get-next (cntIndex)",[]),
2889
 
    gn([[cntIndex]]),
2890
 
    ?DBG("await response",[]),
2891
 
    ?line ?v1_2(expect(3, [{[cntStatus,Idx1], ?active}]),
2892
 
                expect(3, [{[cntCnt,Idx1], 0}])),
2893
 
    % Delete the rows
2894
 
    ?DBG("delete row (cntStatus): ~p",[Idx1]),
2895
 
    s([{[cntStatus, Idx1], i, ?destroy}]),
2896
 
    ?DBG("await response",[]),
2897
 
    ?line expect(4, [{[cntStatus, Idx1], ?destroy}]),
2898
 
    ?DBG("delete row (cntStatus): ~p",[Idx2]),
2899
 
    s([{[cntStatus, Idx2], i, ?destroy}]),
2900
 
    ?DBG("await response",[]),
2901
 
    ?line expect(5, [{[cntStatus, Idx2], ?destroy}]),
2902
 
    catch snmp:debug(MA,true),
2903
 
    ?DBG("done",[]),
2904
 
    ok.
2905
 
 
2906
 
%% Req. Test1
2907
 
opaque_test() ->
2908
 
    p("Testing Opaque datatype..."),
2909
 
    g([[opaqueObj,0]]),
2910
 
    ?line expect(1, [{[opaqueObj,0], "opaque-data"}]).
2911
 
    
2912
 
%% Req. OLD-SNMPEA-MIB
2913
 
api_test(MaNode) ->
2914
 
    ?line {value, OID} = rpc:call(MaNode, snmp, name_to_oid,
2915
 
                                  [intAgentIpAddress]),
2916
 
    ?line {value, intAgentIpAddress} = rpc:call(MaNode, snmp,
2917
 
                                                oid_to_name, [OID]),
2918
 
    ?line false = rpc:call(MaNode, snmp, name_to_oid, [intAgentIpAddres]),
2919
 
    ?line false = rpc:call(MaNode, snmp, oid_to_name,
2920
 
                           [[1,5,32,3,54,3,3,34,4]]),
2921
 
    ?line {value, 2} = rpc:call(MaNode, snmp, enum_to_int,
2922
 
                                [intViewType, excluded]),
2923
 
    ?line {value, excluded} = rpc:call(MaNode, snmp, int_to_enum,
2924
 
                                       [intViewType, 2]),
2925
 
    ?line false = rpc:call(MaNode, snmp, enum_to_int, [intViewType, exclude]),
2926
 
    ?line false = rpc:call(MaNode, snmp, enum_to_int,
2927
 
                           [intAgentIpAddress, exclude]),
2928
 
    ?line false = rpc:call(MaNode, snmp, enum_to_int,
2929
 
                           [intAgentIpAddre, exclude]),
2930
 
    ?line false = rpc:call(MaNode, snmp, int_to_enum, [intViewType, 3]),
2931
 
    ?line false = rpc:call(MaNode, snmp, int_to_enum, [intAgentIpAddress, 2]),
2932
 
    ?line false = rpc:call(MaNode, snmp, int_to_enum, [intAgentIpAddre, 2]),
2933
 
    ?line {value, active} = rpc:call(MaNode, snmp,
2934
 
                                     int_to_enum, ['RowStatus', ?active]),
2935
 
    ?line {value, ?destroy} = rpc:call(MaNode, snmp,
2936
 
                                       enum_to_int, ['RowStatus', destroy]),
2937
 
    ?line false = rpc:call(MaNode, snmp,
2938
 
                           enum_to_int, ['RowStatus', xxxdestroy]),
2939
 
    ?line false = rpc:call(MaNode, snmp,
2940
 
                           enum_to_int, ['xxRowStatus', destroy]),
2941
 
    ?line false = rpc:call(MaNode, snmp, int_to_enum, ['RowStatus', 25]),
2942
 
    ?line false = rpc:call(MaNode, snmp, int_to_enum, ['xxRowStatus', 1]),
2943
 
    ?line case snmp:date_and_time() of
2944
 
              List when list(List), length(List) == 8 -> ok;
2945
 
              List when list(List), length(List) == 11 -> ok
2946
 
    end.
2947
 
 
2948
 
%% Req. Klas3
2949
 
api_test2() ->
2950
 
    g([[fname3,0]]),
2951
 
    ?line expect(1, [{[fname3,0], "ok"}]),
2952
 
    g([[fname4,0]]),
2953
 
    ?line expect(2, [{[fname4,0], 1}]).
2954
 
 
2955
 
api_test3() ->
2956
 
    g([[fname3,0]]),
2957
 
    ?line expect(1, [{[fname3,0], "ok"}]).
2958
 
    
2959
 
    
2960
 
unreg_test() ->
2961
 
    gn([[?v1_2(sysServices, sysORLastChange),0]]),
2962
 
    ?line expect(1, [{[snmpInPkts, 0], any}]).
2963
 
 
2964
 
load_test() ->
2965
 
    gn([[?v1_2(sysServices, sysORLastChange),0]]),
2966
 
    ?line expect(1, [{[fname,0], ""}]).
2967
 
 
2968
 
%% Req. Klas1
2969
 
load_test_sa() ->
2970
 
    gn([[?v1_2(sysServices,sysORLastChange), 0]]),
2971
 
    ?line expect(1, [{[fname,0], any}]).
2972
 
    
2973
 
%% Req. system group, Klas1, OLD-SNMPEA-MIB
2974
 
do_mul_get() ->
2975
 
    Key1c3 = [intCommunityEntry,[3],get(mip),is("public")],
2976
 
    Key1c4 = [intCommunityEntry,[4],get(mip),is("public")],
2977
 
    s([{[fname,0], s, "test set"}]),
2978
 
    ?line expect(3, [{[fname,0], "test set"}]),
2979
 
    g([[sysDescr,0], Key1c4, [fname,0],Key1c3,
2980
 
               [sysName,0]]),
2981
 
    ?line expect(1, [{[sysDescr,0], "Erlang SNMP agent"},
2982
 
                     {Key1c4, 2},
2983
 
                     {[fname,0], "test set"},
2984
 
                     {Key1c3, 2},
2985
 
                     {[sysName,0], "test"}]),
2986
 
    g([[1,3,7,1], Key1c4, [sysDescr,0], [1,3,7,2], Key1c3, [sysDescr,0]]),
2987
 
    ?line ?v1_2(expect(2, noSuchName, [1,4], any),
2988
 
                expect(2, [{[1,3,7,1], noSuchObject},
2989
 
                           {Key1c4, 2},
2990
 
                           {[sysDescr,0], "Erlang SNMP agent"},
2991
 
                           {[1,3,7,2], noSuchObject},
2992
 
                           {Key1c3, 2},
2993
 
                           {[sysDescr,0], "Erlang SNMP agent"}])).
2994
 
 
2995
 
%% Req. v1, system group, Klas1, OLD-SNMPEA-MIB, *ej* Klas3.
2996
 
do_mul_get_err() ->
2997
 
    Key1c3 = [intCommunityEntry,[3],get(mip),is("public")],
2998
 
    Key1c4 = [intCommunityEntry,[4],get(mip),is("public")],
2999
 
    s([{[fname,0], s, "test set"}]),
3000
 
    ?line expect(3, [{[fname,0], "test set"}]),
3001
 
    g([[sysDescr,0],Key1c4,[fname,0], Key1c3, [sysName,2]]),
3002
 
    ?line ?v1_2(expect(1, noSuchName, 5, any),
3003
 
                expect(1, [{[sysDescr,0], "Erlang SNMP agent"},
3004
 
                           {Key1c4, 2},
3005
 
                           {[fname,0], "test set"},
3006
 
                           {Key1c3, 2},
3007
 
                           {[sysName,2], noSuchInstance}])),
3008
 
    g([[sysDescr,0],Key1c4,[fname3,0], Key1c3, [sysName,1]]),
3009
 
    ?line ?v1_2(expect(1, noSuchName, [3,5], any),
3010
 
                expect(1, [{[sysDescr,0], "Erlang SNMP agent"},
3011
 
                           {Key1c4, 2},
3012
 
                           {[fname3,0], noSuchObject},
3013
 
                           {Key1c3, 2},
3014
 
                           {[sysName,1], noSuchInstance}])).
3015
 
 
3016
 
 
3017
 
%% Req. system group, Klas1, OLD-SNMPEA-MIB
3018
 
do_mul_next() ->
3019
 
    Key1c3s = [intCommunityEntry,[3],get(mip),is("publi")],
3020
 
    Key1c4s = [intCommunityEntry,[4],get(mip),is("publi")],
3021
 
    Key1c3 = [intCommunityEntry,[3],get(mip),is("public")],
3022
 
    Key1c4 = [intCommunityEntry,[4],get(mip),is("public")],
3023
 
    s([{[fname,0], s, "test set"}]),
3024
 
    ?line expect(3, [{[fname,0], "test set"}]),
3025
 
    gn([[sysDescr], Key1c4s, [fname],Key1c3s,[sysName]]),
3026
 
    ?line expect(1, [{[sysDescr,0], "Erlang SNMP agent"},
3027
 
               {Key1c4, 2}, {[fname,0], "test set"},
3028
 
               {Key1c3, 2}, {[sysName,0], "test"}]).
3029
 
 
3030
 
%% Req. system group, Klas1, OLD-SNMPEA-MIB
3031
 
do_mul_next_err() ->
3032
 
    Key1c3s = [intCommunityEntry,[3],get(mip),is("publi")],
3033
 
    Key1c4s = [intCommunityEntry,[4],get(mip),is("publi")],
3034
 
    Key1c3 = [intCommunityEntry,[3],get(mip),is("public")],
3035
 
    Key1c4 = [intCommunityEntry,[4],get(mip),is("public")],
3036
 
    s([{[fname,0], s, "test set"}]),
3037
 
    ?line expect(3, [{[fname,0], "test set"}]),
3038
 
    gn([[sysDescr], Key1c4s, [1,3,6,999], [fname],[1,3,90], Key1c3s,[sysName]]),
3039
 
    ?line ?v1_2(expect(1, noSuchName, [3,5], any),
3040
 
                expect(1, [{[sysDescr,0], "Erlang SNMP agent"},
3041
 
                           {Key1c4, 2},
3042
 
                           {[1,3,6,999], endOfMibView},
3043
 
                           {[fname,0], "test set"},
3044
 
                           {[1,3,90], endOfMibView},
3045
 
                           {Key1c3, 2},
3046
 
                           {[sysName,0], "test"}])).
3047
 
                
3048
 
 
3049
 
%% Req. system group, Klas1, OLD-SNMPEA-MIB
3050
 
do_mul_set() ->
3051
 
    p("Adding one row in subagent table, and one in master table"),
3052
 
    NewKeyc3 = [intCommunityEntry,[3],get(mip),is("test")],
3053
 
    NewKeyc4 = [intCommunityEntry,[4],get(mip),is("test")],
3054
 
    NewKeyc5 = [intCommunityEntry,[5],get(mip),is("test")],
3055
 
    s([{[friendsEntry, [2, 3]], "kompis3"},
3056
 
       {NewKeyc3, 2},
3057
 
       {[sysLocation,0], "new_value"},
3058
 
       {NewKeyc5, ?createAndGo},
3059
 
       {NewKeyc4, 2},
3060
 
       {[friendsEntry, [3, 3]], ?createAndGo}]),
3061
 
    ?line expect(1, [{[friendsEntry, [2, 3]], "kompis3"},
3062
 
               {NewKeyc3, 2},
3063
 
               {[sysLocation,0], "new_value"},
3064
 
               {NewKeyc5, ?createAndGo},
3065
 
               {NewKeyc4, 2},
3066
 
               {[friendsEntry, [3, 3]], ?createAndGo}]),
3067
 
    g([[friendsEntry, [2, 3]],
3068
 
               [sysLocation,0],
3069
 
               [friendsEntry, [3, 3]]]),
3070
 
    ?line expect(2, [{[friendsEntry, [2, 3]], "kompis3"},
3071
 
               {[sysLocation,0], "new_value"},
3072
 
               {[friendsEntry, [3, 3]], ?active}]),
3073
 
    g([NewKeyc4]),
3074
 
    ?line expect(3, [{NewKeyc4, 2}]),
3075
 
    s([{[friendsEntry, [3, 3]], ?destroy},
3076
 
       {NewKeyc5, ?destroy}]),
3077
 
    ?line expect(4, [{[friendsEntry, [3, 3]], ?destroy},
3078
 
               {NewKeyc5, ?destroy}]).
3079
 
 
3080
 
%% Req. system group, Klas1, OLD-SNMPEA-MIB
3081
 
do_mul_set_err() ->
3082
 
    NewKeyc3 = [intCommunityEntry,[3],get(mip),is("test")],
3083
 
    NewKeyc4 = [intCommunityEntry,[4],get(mip),is("test")],
3084
 
    NewKeyc5 = [intCommunityEntry,[5],get(mip),is("test")],
3085
 
    p("Adding one row in subagent table, and one in master table"),
3086
 
    s([{[friendsEntry, [2, 3]], s, "kompis3"},
3087
 
       {NewKeyc3, 2},
3088
 
       {[sysUpTime,0], 45},   % sysUpTime (readOnly)
3089
 
       {NewKeyc5, ?createAndGo},
3090
 
       {NewKeyc4, 2},
3091
 
       {[friendsEntry, [3, 3]], ?createAndGo}]),
3092
 
    ?line expect(1, ?v1_2(noSuchName, notWritable), 3, any),
3093
 
    g([[friendsEntry, [2, 3]]]),
3094
 
    ?line ?v1_2(expect(2, noSuchName, 1, any),
3095
 
                expect(2, [{[friendsEntry, [2,3]], noSuchInstance}])),
3096
 
    g([NewKeyc4]),
3097
 
    ?line ?v1_2(expect(3, noSuchName, 1, any),
3098
 
                expect(3, [{NewKeyc4, noSuchInstance}])).
3099
 
 
3100
 
%% Req. SA-MIB
3101
 
sa_mib() ->
3102
 
    g([[sa, [2,0]]]),
3103
 
    ?line expect(1, [{[sa, [2,0]], 3}]),
3104
 
    s([{[sa, [1,0]], s, "sa_test"}]),
3105
 
    ?line expect(2, [{[sa, [1,0]], "sa_test"}]).
3106
 
 
3107
 
ma_trap1(MA) ->
3108
 
    snmp:send_trap(MA, testTrap2, "standard trap"),
3109
 
    ?line expect(1, trap, [system], 6, 1, [{[system, [4,0]],
3110
 
                                    "{mbj,eklas}@erlang.ericsson.se"}]),
3111
 
    snmp:send_trap(MA, testTrap1, "standard trap"),
3112
 
    ?line expect(2, trap, [1,2,3] , 1, 0, [{[system, [4,0]],
3113
 
                                      "{mbj,eklas}@erlang.ericsson.se"}]).
3114
 
 
3115
 
ma_trap2(MA) ->
3116
 
    snmp:send_trap(MA,testTrap2,"standard trap",[{sysContact,"pelle"}]),
3117
 
    ?line expect(3, trap, [system], 6, 1, [{[system, [4,0]], "pelle"}]).
3118
 
 
3119
 
ma_v2_2_v1_trap(MA) ->
3120
 
    snmp:send_trap(MA,testTrapv22,"standard trap",[{sysContact,"pelle"}]),
3121
 
    ?line expect(3, trap, [system], 6, 1, [{[system, [4,0]], "pelle"}]).    
3122
 
 
3123
 
ma_v2_2_v1_trap2(MA) ->
3124
 
    snmp:send_trap(MA,linkUp,"standard trap",[{ifIndex, [1], 1},
3125
 
                                              {ifAdminStatus, [1], 1},
3126
 
                                              {ifOperStatus, [1], 2}]),
3127
 
    ?line expect(3, trap, [1,2,3], 3, 0, [{[ifIndex, 1], 1},
3128
 
                                         {[ifAdminStatus, 1], 1},
3129
 
                                         {[ifOperStatus, 1], 2}]).    
3130
 
 
3131
 
sa_trap1(SA) ->
3132
 
    snmp:send_trap(SA, saTrap, "standard trap"),
3133
 
    ?line expect(4, trap, [ericsson], 6, 1, [{[system, [4,0]],
3134
 
                                      "{mbj,eklas}@erlang.ericsson.se"},
3135
 
                                     {[sa, [1,0]], "sa_test"}]).
3136
 
 
3137
 
sa_trap2(SA) ->
3138
 
    snmp:send_trap(SA, saTrap, "standard trap",[{sysContact,"pelle"}]),
3139
 
    ?line expect(5, trap, [ericsson], 6, 1, [{[system, [4,0]],
3140
 
                                      "pelle"},
3141
 
                                     {[sa, [1,0]], "sa_test"}]).
3142
 
 
3143
 
sa_trap3(SA) ->
3144
 
    snmp:send_trap(SA, saTrap2, "standard trap",
3145
 
                         [{intViewSubtree, [4], [1,2,3,4]}]),
3146
 
    ?line expect(6, trap, [ericsson], 6, 2, [{[system, [4,0]],
3147
 
                                      "{mbj,eklas}@erlang.ericsson.se"},
3148
 
                                     {[sa, [1,0]], "sa_test"},
3149
 
                                     {[intViewSubtree,4],[1,2,3,4]}]).
3150
 
 
3151
 
ma_v2_trap1(MA) ->
3152
 
    ?DBG("ma_v2_traps -> entry with MA = ~p => "
3153
 
           "send standard trap: testTrapv22",[MA]),
3154
 
    snmp:send_trap(MA, testTrapv22, "standard trap"),
3155
 
    ?line expect(1, v2trap, [{[sysUpTime, 0], any},
3156
 
                             {[snmpTrapOID, 0], ?system ++ [0,1]}]),
3157
 
    ?DBG("ma_v2_traps -> send standard trap: testTrapv21",[]),
3158
 
    snmp:send_trap(MA, testTrapv21, "standard trap"),
3159
 
    ?line expect(2, v2trap, [{[sysUpTime, 0], any},
3160
 
                             {[snmpTrapOID, 0], ?snmp ++ [1]}]).
3161
 
 
3162
 
ma_v2_trap2(MA) ->
3163
 
    snmp:send_trap(MA,testTrapv22,"standard trap",[{sysContact,"pelle"}]),
3164
 
    ?line expect(3, v2trap, [{[sysUpTime, 0], any},
3165
 
                             {[snmpTrapOID, 0], ?system ++ [0,1]},
3166
 
                             {[system, [4,0]], "pelle"}]).
3167
 
 
3168
 
%% Note:  This test case takes a while... actually a couple of minutes.
3169
 
ma_v2_inform1(MA) ->
3170
 
    ?DBG("ma_v2_inform -> entry with MA = ~p => "
3171
 
           "send notification: testTrapv22",[MA]),
3172
 
    ?line snmp:send_notification(MA, testTrapv22, no_receiver, "standard inform", []),
3173
 
    ?line expect(1, {inform, true},
3174
 
                 [{[sysUpTime, 0], any},
3175
 
                  {[snmpTrapOID, 0], ?system ++ [0,1]}]),
3176
 
 
3177
 
    ?DBG("ma_v2_inform -> send notification: testTrapv22",[]),
3178
 
    snmp:send_notification(MA, testTrapv22, {tag1, self()},
3179
 
                           "standard inform", []),
3180
 
    ?line expect(1, {inform, true},
3181
 
                 [{[sysUpTime, 0], any},
3182
 
                  {[snmpTrapOID, 0], ?system ++ [0,1]}]),
3183
 
    ?DBG("ma_v2_inform -> await targets",[]),
3184
 
    receive
3185
 
        {snmp_targets, tag1, [_]} ->
3186
 
            ok;
3187
 
        {snmp_targets, tag1, Addrs1} ->
3188
 
            ?line ?FAIL({bad_addrs, Addrs1})
3189
 
    after
3190
 
        5000 ->
3191
 
            ?ERR("ma_v2_inform1 -> awaiting snmp_targets(tag1) timeout",[]),
3192
 
            ?line ?FAIL(nothing_at_all)
3193
 
    end,
3194
 
    ?DBG("ma_v2_inform -> await notification",[]),
3195
 
    receive
3196
 
        {snmp_notification, tag1, {got_response, _}} ->
3197
 
            ok;
3198
 
        {snmp_notification, tag1, {no_response, _}} ->
3199
 
            ?line ?FAIL(no_response)
3200
 
    after
3201
 
        20000 ->
3202
 
            ?ERR("ma_v2_inform1 -> "
3203
 
                   "awaiting snmp_notification(tag1) timeout",[]),
3204
 
            ?line ?FAIL(nothing_at_all)
3205
 
    end,
3206
 
    
3207
 
    %%
3208
 
    %% -- The rest is possibly erroneous...
3209
 
    %% 
3210
 
 
3211
 
    ?DBG("ma_v2_inform -> send notification: testTrapv22",[]),
3212
 
    snmp:send_notification(MA, testTrapv22, {tag2, self()},
3213
 
                           "standard inform", []),
3214
 
    ?line expect(2, {inform, false},
3215
 
                 [{[sysUpTime, 0], any},
3216
 
                  {[snmpTrapOID, 0], ?system ++ [0,1]}]),
3217
 
    ?DBG("ma_v2_inform -> await targets",[]),
3218
 
    receive
3219
 
        {snmp_targets, tag2, [_]} ->
3220
 
            ok;
3221
 
        {snmp_targets, tag2, Addrs2} ->
3222
 
            ?ERR("ma_v2_inform1 -> awaiting snmp_targets(tag2) timeout",[]),
3223
 
            ?line ?FAIL({bad_addrs, Addrs2})
3224
 
    after
3225
 
        5000 ->
3226
 
            ?line ?FAIL(nothing_at_all)
3227
 
    end,
3228
 
    ?DBG("ma_v2_inform -> await notification",[]),
3229
 
    receive
3230
 
        {snmp_notification, tag2, {got_response, _}} ->
3231
 
            ?line ?FAIL(got_response);
3232
 
        {snmp_notification, tag2, {no_response, _}} ->
3233
 
            ok
3234
 
    after
3235
 
        240000 ->
3236
 
            ?ERR("ma_v2_inform1 -> "
3237
 
                   "awaiting snmp_notification(tag2) timeout",[]),
3238
 
            ?line ?FAIL(nothing_at_all)
3239
 
    end.
3240
 
    
3241
 
 
3242
 
ma_v1_2_v2_trap(MA) ->
3243
 
    snmp:send_trap(MA,linkDown,"standard trap",[{ifIndex, [1], 1}]),
3244
 
    ?line expect(2, v2trap, [{[sysUpTime, 0], any},
3245
 
                             {[snmpTrapOID, 0], ?snmpTraps ++ [3]},
3246
 
                             {[ifIndex, 1], 1},
3247
 
                             {[snmpTrapEnterprise, 0], [1,2,3]}]).
3248
 
 
3249
 
    
3250
 
ma_v1_2_v2_trap2(MA) ->
3251
 
    snmp:send_trap(MA,testTrap2,"standard trap",[{sysContact,"pelle"}]),
3252
 
    ?line expect(3, v2trap, [{[sysUpTime, 0], any},
3253
 
                             {[snmpTrapOID, 0], ?system ++ [0,1]},
3254
 
                             {[system, [4,0]], "pelle"},
3255
 
                             {[snmpTrapEnterprise, 0], ?system}]).
3256
 
    
3257
 
 
3258
 
sa_v1_2_v2_trap1(SA) ->
3259
 
    snmp:send_trap(SA, saTrap, "standard trap"),
3260
 
    ?line expect(4, v2trap, [{[sysUpTime, 0], any},
3261
 
                             {[snmpTrapOID, 0], ?ericsson ++ [0, 1]},
3262
 
                             {[system, [4,0]],
3263
 
                              "{mbj,eklas}@erlang.ericsson.se"},
3264
 
                             {[sa, [1,0]], "sa_test"},
3265
 
                             {[snmpTrapEnterprise, 0], ?ericsson}]).
3266
 
 
3267
 
sa_v1_2_v2_trap2(SA) ->
3268
 
    snmp:send_trap(SA, saTrap, "standard trap",[{sysContact,"pelle"}]),
3269
 
    ?line expect(4, v2trap, [{[sysUpTime, 0], any},
3270
 
                             {[snmpTrapOID, 0], ?ericsson ++ [0, 1]},
3271
 
                             {[system, [4,0]], "pelle"},
3272
 
                             {[sa, [1,0]], "sa_test"},
3273
 
                             {[snmpTrapEnterprise, 0], ?ericsson}]).
3274
 
                             
3275
 
 
3276
 
sa_v1_2_v2_trap3(SA) ->
3277
 
    snmp:send_trap(SA, saTrap2, "standard trap",
3278
 
                         [{intViewSubtree, [4], [1,2,3,4]}]),
3279
 
    ?line expect(4, v2trap, [{[sysUpTime, 0], any},
3280
 
                             {[snmpTrapOID, 0], ?ericsson ++ [0, 2]},
3281
 
                             {[system, [4,0]],
3282
 
                              "{mbj,eklas}@erlang.ericsson.se"},
3283
 
                             {[sa, [1,0]], "sa_test"},
3284
 
                             {[intViewSubtree,4],[1,2,3,4]},
3285
 
                             {[snmpTrapEnterprise, 0], ?ericsson}]).
3286
 
                             
3287
 
 
3288
 
%% Req. SA-MIB, OLD-SNMPEA-MIB
3289
 
sa_errs_bad_value() ->
3290
 
    NewKeyc3 = [intCommunityEntry,[3],get(mip),is("test")],
3291
 
    NewKeyc4 = [intCommunityEntry,[4],get(mip),is("test")],
3292
 
    NewKeyc5 = [intCommunityEntry,[5],get(mip),is("test")],
3293
 
    s([{NewKeyc3, 2},
3294
 
       {[sa, [2,0]], 5}, % badValue (i is_set_ok)
3295
 
       {NewKeyc5, ?createAndGo},
3296
 
       {NewKeyc4, 2}]),
3297
 
    ?line expect(1, badValue, 2, any),   
3298
 
    s([{NewKeyc3, 2},
3299
 
       {[sa, [2,0]], 6}, % wrongValue (i is_set_ok)
3300
 
       {NewKeyc5, ?createAndGo},
3301
 
       {NewKeyc4, 2}]),
3302
 
    ?line expect(1, ?v1_2(badValue, wrongValue), 2, any),   
3303
 
    g([NewKeyc4]),
3304
 
    ?line ?v1_2(expect(2, noSuchName, 1, any),
3305
 
                expect(2, [{NewKeyc4, noSuchInstance}])).
3306
 
 
3307
 
%% Req. SA-MIB, OLD-SNMPEA-MIB
3308
 
sa_errs_gen_err() ->
3309
 
    NewKeyc3 = [intCommunityEntry,[3],get(mip),is("test")],
3310
 
    NewKeyc4 = [intCommunityEntry,[4],get(mip),is("test")],
3311
 
    NewKeyc5 = [intCommunityEntry,[5],get(mip),is("test")],
3312
 
    s([{NewKeyc3, 2},{NewKeyc4, 2},
3313
 
       {NewKeyc5, ?createAndGo}, {[sa, [3,0]], 5}]),
3314
 
    ?line expect(1, genErr, 4, any),
3315
 
% The row might have been added; we don't know.
3316
 
% (as a matter of fact we do - it is added, because the agent
3317
 
% first sets its own vars, and then th SAs. Lets destroy it.
3318
 
    s([{NewKeyc5, ?destroy}]),
3319
 
    ?line expect(2, [{NewKeyc5, ?destroy}]).
3320
 
 
3321
 
%% Req. SA-MIB, OLD-SNMPEA-MIB
3322
 
sa_too_big() ->
3323
 
    g([[sa, [4,0]]]),
3324
 
    ?line expect(1, tooBig).
3325
 
 
3326
 
%% Req. Klas1, system group, snmp group (v1/v2)
3327
 
next_across_sa() ->
3328
 
    gn([[sysDescr],[klas1,5]]),
3329
 
    ?line expect(1, [{[sysDescr,0], "Erlang SNMP agent"},
3330
 
               {[snmpInPkts, 0], any}]).
3331
 
 
3332
 
%% snmp_mgr:s([{[fStatus3, 1], 4}, {[fname3,0], "ok"}]). -> noError
3333
 
%% snmp_mgr:s([{[fStatus3, 1], 4}, {[fname3,0], "hoj"}]). -> {badValue, 2}
3334
 
%% snmp_mgr:s([{[fStatus3, 3], 4}, {[fname3,0], "hoj"}]). -> {genErr, 1}
3335
 
%% snmp_mgr:s([{[fStatus3, 4], 4}, {[fname3,0], "ok"}]). -> {genErr, 1}
3336
 
%% snmp_mgr:s([{[fStatus3, 4], 4}, {[fname3,0], "ufail"}]). -> {genErr, 1}
3337
 
%% snmp_mgr:s([{[fStatus3, 1], 4}, {[fname3,0], "xfail"}]). -> {genErr, 2}
3338
 
%% Req. Klas3, Klas4
3339
 
undo_test() ->
3340
 
    s([{[fStatus3, 1], 4}, {[fname3,0], "ok"}]),
3341
 
    ?line expect(1, [{[fStatus3, 1], 4}, {[fname3,0], "ok"}]),
3342
 
    s([{[fStatus3, 1], 4}, {[fname3,0], "hoj"}]),
3343
 
    ?line expect(2, ?v1_2(badValue, inconsistentValue), 2, any), 
3344
 
    s([{[fStatus3, 3], 4}, {[fname3,0], "hoj"}]),
3345
 
    ?line expect(3, ?v1_2(genErr, undoFailed), 1, any), 
3346
 
    s([{[fStatus3, 4], 4}, {[fname3,0], "ok"}]),
3347
 
    ?line expect(4, ?v1_2(genErr, commitFailed), 1, any), 
3348
 
% unfortunatly we don't know if we'll get undoFailed or commitFailed.
3349
 
% it depends on which order the agent traverses the varbind list.
3350
 
%    s([{[fStatus3, 4], 4}, {[fname3,0], "ufail"}]),
3351
 
%    ?line expect(5, ?v1_2(genErr, undoFailed), 1, any),
3352
 
    s([{[fStatus3, 1], 4}, {[fname3,0], "xfail"}]),
3353
 
    ?line expect(6, genErr, 2, any).
3354
 
    
3355
 
%% Req. Klas3, Klas4
3356
 
bad_return() ->
3357
 
    g([[fStatus4,4],
3358
 
       [fName4,4]]),
3359
 
    ?line expect(4, genErr, 2, any),
3360
 
    g([[fStatus4,5],
3361
 
       [fName4,5]]),
3362
 
    ?line expect(5, genErr, 1, any),
3363
 
    g([[fStatus4,6],
3364
 
       [fName4,6]]),
3365
 
    ?line expect(6, genErr, 2, any),
3366
 
    gn([[fStatus4,7],
3367
 
       [fName4,7]]),
3368
 
    ?line expect(7, genErr, 2, any),
3369
 
    gn([[fStatus4,8],
3370
 
       [fName4,8]]),
3371
 
    ?line expect(8, genErr, 1, any),
3372
 
    gn([[fStatus4,9],
3373
 
       [fName4,9]]),
3374
 
    ?line expect(9, genErr, 2, any).
3375
 
 
3376
 
 
3377
 
%%%-----------------------------------------------------------------
3378
 
%%% Test the implementation of standard mibs.
3379
 
%%% We should *at least* try to GET all variables, just to make
3380
 
%%% sure the instrumentation functions work.
3381
 
%%% Note that many of the functions in the standard mib is
3382
 
%%% already tested by the normal tests.
3383
 
%%%-----------------------------------------------------------------
3384
 
standard_mibs(suite) ->
3385
 
    [snmp_standard_mib, snmp_community_mib,
3386
 
     snmp_framework_mib,
3387
 
     snmp_target_mib, snmp_notification_mib,
3388
 
     snmp_view_based_acm_mib].
3389
 
 
3390
 
standard_mibs_2(suite) ->
3391
 
    [snmpv2_mib_2, snmp_community_mib_2,
3392
 
     snmp_framework_mib_2,
3393
 
     snmp_target_mib_2, snmp_notification_mib_2,
3394
 
     snmp_view_based_acm_mib_2].
3395
 
 
3396
 
standard_mibs_3(suite) ->
3397
 
    [snmpv2_mib_3,snmp_framework_mib_3, snmp_mpd_mib_3,
3398
 
     snmp_target_mib_3, snmp_notification_mib_3,
3399
 
     snmp_view_based_acm_mib_3, snmp_user_based_sm_mib_3].
3400
 
 
3401
 
%%-----------------------------------------------------------------
3402
 
%% For this test, the agent is configured for v1.
3403
 
%% o  Test the counters and control objects in SNMP-STANDARD-MIB
3404
 
%%-----------------------------------------------------------------
3405
 
snmp_standard_mib(suite) -> [];
3406
 
snmp_standard_mib(Config) when list(Config) ->
3407
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
3408
 
    try_test(std_mib_init),
3409
 
 
3410
 
    InBadVsns = try_test(std_mib_a),
3411
 
    put(vsn, v2),
3412
 
    try_test(std_mib_read),
3413
 
    put(vsn, v1),
3414
 
    Bad = try_test(std_mib_b, [InBadVsns]),
3415
 
    try_test(std_mib_read, [], [{community, "bad community"}]),
3416
 
    try_test(std_mib_write, [], [{community, "public"}]),
3417
 
    try_test(std_mib_asn_err),
3418
 
    try_test(std_mib_c, [Bad]),
3419
 
    try_test(standard_mib_a),
3420
 
    
3421
 
    try_test(std_mib_finish),
3422
 
    try_test(standard_mib_test_finish, [], [{community, "bad community"}]).
3423
 
 
3424
 
%% Req. SNMP-STANDARD-MIB
3425
 
standard_mib_a() ->
3426
 
    ?line [OutPkts] = get_req(2, [[snmpOutPkts,0]]),
3427
 
    ?line [OutPkts2] = get_req(3, [[snmpOutPkts,0]]),
3428
 
    ?line OutPkts2 = OutPkts + 1,
3429
 
    %% There are some more counters we could test here, but it's not that
3430
 
    %% important, since they are removed from SNMPv2-MIB.
3431
 
    ok.
3432
 
 
3433
 
%% Req. SNMP-STANDARD-MIB | SNMPv2-MIB
3434
 
std_mib_init() ->
3435
 
    %% disable authentication failure traps.  (otherwise w'd get many of
3436
 
    %% them - this is also a test to see that it works).
3437
 
    s([{[snmpEnableAuthenTraps,0], 2}]),
3438
 
    ?line expect(1, [{[snmpEnableAuthenTraps, 0], 2}]).
3439
 
 
3440
 
%% Req. SNMP-STANDARD-MIB | SNMPv2-MIB
3441
 
std_mib_finish() ->
3442
 
    %% enable again
3443
 
    s([{[snmpEnableAuthenTraps,0], 1}]),
3444
 
    ?line expect(1, [{[snmpEnableAuthenTraps, 0], 1}]).
3445
 
 
3446
 
%% Req. SNMP-STANDARD-MIB
3447
 
standard_mib_test_finish() ->
3448
 
    %% force a authenticationFailure
3449
 
    std_mib_write(),
3450
 
    %% check that we got a trap
3451
 
    ?line expect(2, trap, [1,2,3], 4, 0, []).
3452
 
 
3453
 
%% Req. SNMP-STANDARD-MIB | SNMPv2-MIB
3454
 
std_mib_read() ->
3455
 
    g([[sysUpTime,0]]), % try a bad <something>; msg dropped, no reply
3456
 
    ?line expect(1, timeout). % make sure we don't get a trap!
3457
 
 
3458
 
 
3459
 
%% Req. SNMP-STANDARD-MIB | SNMPv2-MIB
3460
 
std_mib_write() ->
3461
 
    s([{[sysLocation, 0], "new_value"}]).
3462
 
 
3463
 
%% Req. SNMP-STANDARD-MIB | SNMPv2-MIB
3464
 
std_mib_asn_err() ->
3465
 
    snmp_mgr:send_bytes([48,99,67,12,0,0,0,0,0,0,5]).
3466
 
 
3467
 
%%-----------------------------------------------------------------
3468
 
%% For this test, the agent is configured for v2 and v3.
3469
 
%% o  Test the counters and control objects in SNMPv2-MIB
3470
 
%%-----------------------------------------------------------------
3471
 
snmpv2_mib_2(suite) -> [];
3472
 
snmpv2_mib_2(Config) when list(Config) ->
3473
 
    ?LOG("snmpv2_mib_2 -> start",[]),
3474
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
3475
 
 
3476
 
    ?DBG("snmpv2_mib_2 -> standard mib init",[]),
3477
 
    try_test(std_mib_init),
3478
 
 
3479
 
    ?DBG("snmpv2_mib_2 -> get number of (so far) bad versions",[]),
3480
 
    InBadVsns = try_test(std_mib_a),
3481
 
 
3482
 
    ?DBG("snmpv2_mib_2 -> make a bad version read",[]),
3483
 
    put(vsn, v1),
3484
 
    try_test(std_mib_read),
3485
 
 
3486
 
    ?DBG("snmpv2_mib_2 -> bad version read",[]),
3487
 
    put(vsn, v2),
3488
 
    Bad = try_test(std_mib_b, [InBadVsns]),
3489
 
 
3490
 
    ?DBG("snmpv2_mib_2 -> read with bad community",[]),
3491
 
    try_test(std_mib_read, [], [{community, "bad community"}]),
3492
 
 
3493
 
    ?DBG("snmpv2_mib_2 -> write with public community",[]),
3494
 
    try_test(std_mib_write, [], [{community, "public"}]),
3495
 
 
3496
 
    ?DBG("snmpv2_mib_2 -> asn err",[]),
3497
 
    try_test(std_mib_asn_err),
3498
 
 
3499
 
    ?DBG("snmpv2_mib_2 -> check counters",[]),
3500
 
    try_test(std_mib_c, [Bad]),
3501
 
 
3502
 
    ?DBG("snmpv2_mib_2 -> get som counters",[]),
3503
 
    try_test(snmpv2_mib_a),
3504
 
    
3505
 
    ?DBG("snmpv2_mib_2 -> enable auth traps, and await some",[]),
3506
 
    try_test(std_mib_finish),
3507
 
 
3508
 
    ?DBG("snmpv2_mib_2 -> force auth failure, and await trap, "
3509
 
          "then disable auth traps",[]),
3510
 
    try_test(snmpv2_mib_test_finish, [], [{community, "bad community"}]),
3511
 
    
3512
 
    ?LOG("snmpv2_mib_2 -> done",[]).
3513
 
    
3514
 
%% Req. SNMPv2-MIB
3515
 
snmpv2_mib_3(suite) -> [];
3516
 
snmpv2_mib_3(Config) when list(Config) ->
3517
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
3518
 
 
3519
 
    InBadVsns = try_test(std_mib_a),
3520
 
    put(vsn, v1),
3521
 
    try_test(std_mib_read),
3522
 
    put(vsn, v3),
3523
 
    Bad = try_test(std_mib_b, [InBadVsns]),
3524
 
    try_test(snmpv2_mib_a),
3525
 
 
3526
 
    try_test(std_mib_finish).
3527
 
    
3528
 
-define(authenticationFailure, [1,3,6,1,6,3,1,1,5,5]).
3529
 
 
3530
 
%% Req. SNMPv2-MIB
3531
 
snmpv2_mib_test_finish() ->
3532
 
    %% force a authenticationFailure
3533
 
    ?DBG("ma_v2_inform -> write to std mib",[]),
3534
 
    std_mib_write(),
3535
 
 
3536
 
    %% check that we got a trap
3537
 
    ?DBG("ma_v2_inform -> await trap",[]),
3538
 
    ?line expect(2, v2trap, [{[sysUpTime,0], any},
3539
 
                             {[snmpTrapOID,0], ?authenticationFailure}]),
3540
 
 
3541
 
    %% and the the inform
3542
 
    ?DBG("ma_v2_inform -> await inform",[]),
3543
 
    ?line expect(2, {inform,true}, [{[sysUpTime,0], any},
3544
 
                                    {[snmpTrapOID,0],?authenticationFailure}]).
3545
 
 
3546
 
%% Req. SNMP-STANDARD-MIB | SNMPv2-MIB
3547
 
std_mib_a() ->
3548
 
    ?line [InPkts] = get_req(2, [[snmpInPkts,0]]),
3549
 
    ?line [InPkts2] = get_req(3, [[snmpInPkts,0]]),
3550
 
    ?line InPkts2 = InPkts + 1,
3551
 
 
3552
 
    ?line [InBadVsns] = get_req(4, [[snmpInBadVersions,0]]),
3553
 
    InBadVsns.
3554
 
 
3555
 
%% Req. SNMP-STANDARD-MIB | SNMPv2-MIB
3556
 
std_mib_b(InBadVsns) ->
3557
 
    ?line [InBadVsns2] = get_req(1, [[snmpInBadVersions,0]]),
3558
 
    ?line InBadVsns2 = InBadVsns + 1,
3559
 
    ?line [InPkts] = get_req(2, [[snmpInPkts,0]]),
3560
 
    ?line [InPkts2] = get_req(3, [[snmpInPkts,0]]),
3561
 
    ?line InPkts2 = InPkts + 1,
3562
 
    ?line [InBadCommunityNames, InBadCommunityUses, InASNErrs] =
3563
 
        get_req(4, [[snmpInBadCommunityNames,0],
3564
 
                    [snmpInBadCommunityUses,0],
3565
 
                    [snmpInASNParseErrs, 0]]),
3566
 
    {InBadCommunityNames, InBadCommunityUses, InASNErrs}.
3567
 
    
3568
 
%% Req. SNMP-STANDARD-MIB | SNMPv2-MIB
3569
 
std_mib_c({InBadCommunityNames, InBadCommunityUses, InASNErrs}) ->
3570
 
    ?line [InBadCommunityNames2, InBadCommunityUses2, InASNErrs2] =
3571
 
        get_req(1, [[snmpInBadCommunityNames,0],
3572
 
                    [snmpInBadCommunityUses,0],
3573
 
                    [snmpInASNParseErrs, 0]]),
3574
 
    ?line InBadCommunityNames2 = InBadCommunityNames + 1,
3575
 
    ?line InBadCommunityUses2 = InBadCommunityUses + 1,
3576
 
    ?line InASNErrs2 = InASNErrs + 1.
3577
 
 
3578
 
%% Req. SNMPv2-MIB
3579
 
snmpv2_mib_a() ->
3580
 
    ?line [SetSerial] = get_req(2, [[snmpSetSerialNo,0]]),
3581
 
    s([{[snmpSetSerialNo,0], SetSerial}, {[sysLocation, 0], "val2"}]),
3582
 
    ?line expect(3, [{[snmpSetSerialNo,0], SetSerial},
3583
 
                     {[sysLocation, 0], "val2"}]),
3584
 
    s([{[sysLocation, 0], "val3"}, {[snmpSetSerialNo,0], SetSerial}]),
3585
 
    ?line expect(4, inconsistentValue, 2,
3586
 
                 [{[sysLocation, 0], "val3"},
3587
 
                  {[snmpSetSerialNo,0], SetSerial}]),
3588
 
    ?line ["val2"] = get_req(5, [[sysLocation,0]]).
3589
 
    
3590
 
    
3591
 
%%-----------------------------------------------------------------
3592
 
%% o  Bad community uses/name is tested already
3593
 
%%    in SNMPv2-MIB and STANDARD-MIB.
3594
 
%% o  Test add/deletion of rows.
3595
 
%%-----------------------------------------------------------------
3596
 
snmp_community_mib(suite) -> [];
3597
 
snmp_community_mib(Config) when list(Config) ->
3598
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
3599
 
    ?line load_master_std("SNMP-COMMUNITY-MIB"),
3600
 
    try_test(snmp_community_mib),
3601
 
    ?line unload_master("SNMP-COMMUNITY-MIB").
3602
 
 
3603
 
snmp_community_mib_2(X) -> snmp_community_mib(X).
3604
 
 
3605
 
%% Req. SNMP-COMMUNITY-MIB
3606
 
snmp_community_mib() ->
3607
 
    ?INF("NOT YET IMPLEMENTED", []),
3608
 
    nyi.
3609
 
 
3610
 
%%-----------------------------------------------------------------
3611
 
%% o  Test engine boots / time
3612
 
%%-----------------------------------------------------------------
3613
 
snmp_framework_mib(suite) -> [];
3614
 
snmp_framework_mib(Config) when list(Config) ->
3615
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
3616
 
    ?line load_master_std("SNMP-FRAMEWORK-MIB"),
3617
 
    try_test(snmp_framework_mib),
3618
 
    ?line unload_master("SNMP-FRAMEWORK-MIB").
3619
 
 
3620
 
snmp_framework_mib_2(X) -> snmp_framework_mib(X).
3621
 
 
3622
 
snmp_framework_mib_3(suite) -> [];
3623
 
snmp_framework_mib_3(Config) when list(Config) ->
3624
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
3625
 
    try_test(snmp_framework_mib).
3626
 
 
3627
 
 
3628
 
%% Req. SNMP-FRAMEWORK-MIB
3629
 
snmp_framework_mib() ->
3630
 
    ?line ["agentEngine"] = get_req(1, [[snmpEngineID,0]]),
3631
 
    ?line [EngineTime] = get_req(2, [[snmpEngineTime,0]]),
3632
 
    sleep(5000),
3633
 
    ?line [EngineTime2] = get_req(3, [[snmpEngineTime,0]]),
3634
 
    if 
3635
 
        EngineTime+7 < EngineTime2 ->
3636
 
            ?line ?FAIL({too_large_diff, EngineTime, EngineTime2});
3637
 
        EngineTime+4 > EngineTime2 ->
3638
 
            ?line ?FAIL({too_large_diff, EngineTime, EngineTime2});
3639
 
        true -> ok
3640
 
    end,
3641
 
    ?line case get_req(4, [[snmpEngineBoots,0]]) of
3642
 
              [Boots] when integer(Boots) -> ok;
3643
 
              Else -> ?FAIL(Else)
3644
 
          end,
3645
 
    ok.
3646
 
 
3647
 
%%-----------------------------------------------------------------
3648
 
%% o  Test the counters
3649
 
%%-----------------------------------------------------------------
3650
 
snmp_mpd_mib_3(suite) -> [];
3651
 
snmp_mpd_mib_3(Config) when list(Config) ->
3652
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
3653
 
    UnknownPDUHs = try_test(snmp_mpd_mib_a),
3654
 
    try_test(snmp_mpd_mib_b, [], [{context_engine_id, "bad engine"}]),
3655
 
    try_test(snmp_mpd_mib_c, [UnknownPDUHs]).
3656
 
    
3657
 
 
3658
 
%% Req. SNMP-MPD-MIB
3659
 
snmp_mpd_mib_a() ->
3660
 
    ?line [UnknownSecs, InvalidMsgs] =
3661
 
        get_req(1, [[snmpUnknownSecurityModels,0],
3662
 
                    [snmpInvalidMsgs,0]]),
3663
 
    Pdu = #pdu{type = 'get-request',
3664
 
               request_id = 23,
3665
 
               error_status = noError,
3666
 
               error_index = 0,
3667
 
               varbinds = []},
3668
 
    SPdu = #scopedPdu{contextEngineID = "agentEngine",
3669
 
                      contextName = "",
3670
 
                      data = Pdu},
3671
 
    ?line SPDUBytes = snmp_pdus:enc_scoped_pdu(SPdu),
3672
 
    V3Hdr1 = #v3_hdr{msgID = 21,
3673
 
                     msgMaxSize = 484,
3674
 
                     msgFlags = [7],
3675
 
                     msgSecurityModel = 23,  % bad sec model
3676
 
                     msgSecurityParameters = []},
3677
 
    V3Hdr2 = #v3_hdr{msgID = 21,
3678
 
                     msgMaxSize = 484,
3679
 
                     msgFlags = [6], % bad flag combination
3680
 
                     msgSecurityModel = 3,
3681
 
                     msgSecurityParameters = []},
3682
 
    Message1 = #message{version = 'version-3', vsn_hdr = V3Hdr1,
3683
 
                        data = SPDUBytes},
3684
 
    Message2 = #message{version = 'version-3', vsn_hdr = V3Hdr2,
3685
 
                        data = SPDUBytes},
3686
 
    ?line MsgBytes1 = snmp_pdus:enc_message_only(Message1),
3687
 
    ?line MsgBytes2 = snmp_pdus:enc_message_only(Message2),
3688
 
    snmp_mgr:send_bytes(MsgBytes1),
3689
 
    snmp_mgr:send_bytes(MsgBytes2),
3690
 
 
3691
 
    ?line [UnknownSecs2, InvalidMsgs2, UnknownPDUHs] =
3692
 
        get_req(1, [[snmpUnknownSecurityModels,0],
3693
 
                    [snmpInvalidMsgs,0],
3694
 
                    [snmpUnknownPDUHandlers, 0]]),
3695
 
    ?line UnknownSecs2 = UnknownSecs + 1,
3696
 
    ?line InvalidMsgs2 = InvalidMsgs + 1,
3697
 
    UnknownPDUHs.
3698
 
 
3699
 
-define(snmpUnknownPDUHandlers_instance, [1,3,6,1,6,3,11,2,1,3,0]).
3700
 
snmp_mpd_mib_b() ->
3701
 
    g([[sysUpTime,0]]),
3702
 
    ?line expect(1, report, [{?snmpUnknownPDUHandlers_instance, any}]).
3703
 
    
3704
 
 
3705
 
snmp_mpd_mib_c(UnknownPDUHs) ->
3706
 
    ?line [UnknownPDUHs2] = get_req(1, [[snmpUnknownPDUHandlers, 0]]),
3707
 
    ?line UnknownPDUHs2 = UnknownPDUHs + 1.
3708
 
 
3709
 
 
3710
 
snmp_target_mib(suite) -> [];
3711
 
snmp_target_mib(Config) when list(Config) ->
3712
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
3713
 
    ?line load_master_std("SNMP-TARGET-MIB"),
3714
 
    try_test(snmp_target_mib),
3715
 
    ?line unload_master("SNMP-TARGET-MIB").
3716
 
 
3717
 
snmp_target_mib_2(X) -> snmp_target_mib(X).
3718
 
 
3719
 
snmp_target_mib_3(X) -> snmp_target_mib(X).
3720
 
 
3721
 
snmp_target_mib() ->
3722
 
    ?INF("NOT YET IMPLEMENTED", []),
3723
 
    nyi.
3724
 
 
3725
 
snmp_notification_mib(suite) -> [];
3726
 
snmp_notification_mib(Config) when list(Config) ->
3727
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
3728
 
    ?line load_master_std("SNMP-NOTIFICATION-MIB"),
3729
 
    try_test(snmp_notification_mib),
3730
 
    ?line unload_master("SNMP-NOTIFICATION-MIB").
3731
 
 
3732
 
snmp_notification_mib_2(X) -> snmp_notification_mib(X).
3733
 
 
3734
 
snmp_notification_mib_3(X) -> snmp_notification_mib(X).
3735
 
 
3736
 
snmp_notification_mib() ->
3737
 
    ?INF("NOT YET IMPLEMENTED", []),
3738
 
    nyi.
3739
 
 
3740
 
%%-----------------------------------------------------------------
3741
 
%% o  add/delete views and try them
3742
 
%% o  try boundaries
3743
 
%%-----------------------------------------------------------------
3744
 
snmp_view_based_acm_mib(suite) -> [];
3745
 
snmp_view_based_acm_mib(Config) when list(Config) ->
3746
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
3747
 
    ?line load_master_std("SNMP-VIEW-BASED-ACM-MIB"),
3748
 
    ?line load_master("Test2"),
3749
 
    snmp_view_based_acm_mib(),
3750
 
    ?line unload_master("Test2"),
3751
 
    ?line unload_master("SNMP-VIEW-BASED-ACM-MIB").
3752
 
 
3753
 
snmp_view_based_acm_mib_2(X) -> snmp_view_based_acm_mib(X).
3754
 
 
3755
 
snmp_view_based_acm_mib_3(X) -> snmp_view_based_acm_mib(X).
3756
 
 
3757
 
snmp_view_based_acm_mib() ->
3758
 
    snmp:verbosity(snmp_net_if,trace),
3759
 
    snmp:verbosity(snmp_master_agent,trace),
3760
 
    ?LOG("start snmp_view_based_acm_mib test",[]),
3761
 
    %% The user "no-rights" is present in USM, and is mapped to security
3762
 
    %% name 'no-rights", which is not present in VACM.
3763
 
    %% So, we'll add rights for it, try them and delete them.
3764
 
    %% We'll give "no-rights" write access to tDescr.0 and read access
3765
 
    %% to tDescr2.0
3766
 
    %% These are the options we'll use to the mgr
3767
 
    Opts = [{user, "no-rights"}, {community, "no-rights"}],
3768
 
    %% Find the valid secmodel, and one invalid secmodel.
3769
 
    {SecMod, InvSecMod} = 
3770
 
        case get(vsn) of
3771
 
            v1 -> {?SEC_V1, ?SEC_V2C};
3772
 
            v2 -> {?SEC_V2C, ?SEC_USM};
3773
 
            v3 -> {?SEC_USM, ?SEC_V1}
3774
 
        end,
3775
 
    ?DBG("assign rights for 'no-rights'",[]),
3776
 
    ?line try_test(use_no_rights, [], Opts),
3777
 
 
3778
 
    %% Now, add a mapping from "no-rights" -> "no-rights-group"
3779
 
    GRow1Status = [vacmSecurityToGroupStatus,[SecMod, 9,"no-rights"]],
3780
 
    GRow1 = 
3781
 
        [{[vacmGroupName, [SecMod, 9,"no-rights"]], "no-rights-group"},
3782
 
         {GRow1Status, ?createAndGo}],
3783
 
    ?DBG("set '~p'",[GRow1]),
3784
 
    ?line try_test(do_set, [GRow1]),
3785
 
 
3786
 
    ?DBG("assign rights for 'no-rights'",[]),
3787
 
    ?line try_test(use_no_rights, [], Opts),
3788
 
 
3789
 
    %% Create a mapping for another sec model, and make sure it dosn't
3790
 
    %% give us access
3791
 
    GRow2Status = [vacmSecurityToGroupStatus,[InvSecMod, 9,"no-rights"]],
3792
 
    GRow2 = [{[vacmGroupName, [InvSecMod, 9, "no-rights"]], "initial"},
3793
 
             {GRow2Status, ?createAndGo}],
3794
 
 
3795
 
    ?DBG("set '~p'",[GRow2]),
3796
 
    ?line try_test(do_set, [GRow2]),
3797
 
 
3798
 
    ?DBG("assign rights for 'no-rights'",[]),
3799
 
    ?line try_test(use_no_rights, [], Opts),
3800
 
 
3801
 
    %% Delete that row
3802
 
    ?line try_test(del_row, [GRow2Status]),
3803
 
    
3804
 
    RVName = "rv_name",
3805
 
    WVName = "wv_name",
3806
 
 
3807
 
    %% Access row
3808
 
    ARow1Idx = [15 | "no-rights-group"] ++ [0, ?SEC_ANY, 1],
3809
 
    ARow1Status = [vacmAccessStatus, ARow1Idx],
3810
 
    ARow1 = [{[vacmAccessContextMatch, ARow1Idx], 1},
3811
 
             {[vacmAccessReadViewName, ARow1Idx], RVName},
3812
 
             {[vacmAccessWriteViewName, ARow1Idx], WVName},
3813
 
             {ARow1Status, ?createAndGo}],
3814
 
    
3815
 
    %% This access row would give acces, if InvSecMod was valid.
3816
 
    ARow2Idx = [15 | "no-rights-group"] ++ [0, InvSecMod, 1],
3817
 
    ARow2Status = [vacmAccessStatus, ARow2Idx],
3818
 
    ARow2 = [{[vacmAccessContextMatch, ARow2Idx], 1},
3819
 
             {[vacmAccessReadViewName, ARow2Idx], "internet"},
3820
 
             {[vacmAccessWriteViewName, ARow2Idx], "internet"},
3821
 
             {ARow2Status, ?createAndGo}],
3822
 
    
3823
 
    ?line try_test(do_set, [ARow2]),
3824
 
 
3825
 
    ?line try_test(use_no_rights, [], Opts),
3826
 
 
3827
 
    %% Delete that row
3828
 
    ?line try_test(del_row, [ARow2Status]),
3829
 
    
3830
 
 
3831
 
    %% Add valid row
3832
 
    ?line try_test(do_set, [ARow1]),
3833
 
 
3834
 
    ?line try_test(use_no_rights, [], Opts),
3835
 
 
3836
 
    %% Create the view family
3837
 
    VRow1Idx = mk_ln(RVName) ++ mk_ln(?xDescr),         % object access
3838
 
    VRow2Idx = mk_ln(RVName) ++ mk_ln(?xDescr2 ++ [0]), % instance access
3839
 
    VRow3Idx = mk_ln(WVName) ++ mk_ln(?xDescr),         % object access
3840
 
    VRow4Idx = mk_ln(WVName) ++ mk_ln(?xDescr ++ [0]),  % instance access
3841
 
    VRow1Status = [vacmViewTreeFamilyStatus, VRow1Idx],
3842
 
    VRow2Status = [vacmViewTreeFamilyStatus, VRow2Idx],
3843
 
    VRow3Status = [vacmViewTreeFamilyStatus, VRow3Idx],
3844
 
    VRow4Status = [vacmViewTreeFamilyStatus, VRow4Idx],
3845
 
    
3846
 
    ?line try_test(add_row, [VRow1Status]),
3847
 
    ?line try_test(add_row, [VRow2Status]),
3848
 
    ?line try_test(add_row, [VRow3Status]),
3849
 
 
3850
 
    %% We're supposed to have access now...
3851
 
    ?line try_test(use_rights, [], Opts),
3852
 
 
3853
 
    %% Change Row3 to Row4
3854
 
    ?line try_test(del_row, [VRow3Status]),
3855
 
    ?line try_test(add_row, [VRow4Status]),
3856
 
 
3857
 
    %% We should still have access...
3858
 
    ?line try_test(use_rights, [], Opts),
3859
 
 
3860
 
    %% Delete rows
3861
 
    ?line try_test(del_row, [GRow1Status]),
3862
 
    
3863
 
    ?line try_test(use_no_rights, [], Opts),
3864
 
 
3865
 
    %% Delete rest of rows
3866
 
    ?line try_test(del_row, [ARow1Status]),
3867
 
    ?line try_test(del_row, [VRow1Status]),
3868
 
    ?line try_test(del_row, [VRow2Status]),
3869
 
    ?line try_test(del_row, [VRow4Status]),
3870
 
 
3871
 
    ?line try_test(use_no_rights, [], Opts),
3872
 
    snmp:debug(snmp_master_agent,true).
3873
 
 
3874
 
do_set(Row) ->
3875
 
    s(Row),
3876
 
    expect(1, Row).
3877
 
    
3878
 
add_row(RowStatus) ->
3879
 
    s([{RowStatus, ?createAndGo}]),
3880
 
    expect(1, [{RowStatus, ?createAndGo}]).
3881
 
 
3882
 
del_row(RowStatus) ->
3883
 
    s([{RowStatus, ?destroy}]),
3884
 
    expect(1, [{RowStatus, ?destroy}]).
3885
 
    
3886
 
    
3887
 
 
3888
 
use_no_rights() ->
3889
 
    g([[xDescr,0]]),
3890
 
    ?v1_2_3(expect(11, noSuchName, 1, any),
3891
 
            expect(12, [{[xDescr,0], noSuchObject}]),
3892
 
            expect(13, authorizationError, 1, any)),
3893
 
    g([[xDescr2,0]]),
3894
 
    ?v1_2_3(expect(21, noSuchName, 1, any),
3895
 
            expect(22, [{[xDescr2,0], noSuchObject}]),
3896
 
            expect(23, authorizationError, 1, any)),
3897
 
    gn([[xDescr]]),
3898
 
    ?v1_2_3(expect(31, noSuchName, 1, any),
3899
 
            expect(32, [{[xDescr], endOfMibView}]),
3900
 
            expect(33, authorizationError, 1, any)),
3901
 
    s([{[xDescr,0], "tryit"}]),
3902
 
    ?v1_2_3(expect(41, noSuchName, 1, any),
3903
 
            expect(42, noAccess, 1, any),
3904
 
            expect(43, authorizationError, 1, any)).
3905
 
 
3906
 
 
3907
 
use_rights() ->
3908
 
    g([[xDescr,0]]),
3909
 
    expect(1, [{[xDescr,0], any}]),
3910
 
    g([[xDescr2,0]]),
3911
 
    expect(2, [{[xDescr2,0], any}]),
3912
 
    s([{[xDescr,0], "tryit"}]),
3913
 
    expect(3, noError, 0, any),
3914
 
    g([[xDescr,0]]),
3915
 
    expect(4, [{[xDescr,0], "tryit"}]).
3916
 
 
3917
 
mk_ln(X) ->
3918
 
    [length(X) | X].
3919
 
 
3920
 
%%-----------------------------------------------------------------
3921
 
%% o  add/delete users and try them
3922
 
%% o  test all secLevels
3923
 
%% o  test all combinations of protocols
3924
 
%% o  try bad ops; check counters
3925
 
%%-----------------------------------------------------------------
3926
 
snmp_user_based_sm_mib_3(suite) -> [];
3927
 
snmp_user_based_sm_mib_3(Config) when list(Config) ->
3928
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
3929
 
    AgentDir = ?config(agent_dir, Config),
3930
 
    ?line load_master_std("SNMP-USER-BASED-SM-MIB"),
3931
 
 
3932
 
    %% The newUser used here already has VACM access.
3933
 
    
3934
 
    %% Add a new user in the simplest way; just createAndGo
3935
 
    try_test(v3_sync, [[{usm_add_user1, []}]],
3936
 
        [{sec_level, authPriv}, {user, "privDES"}]),
3937
 
 
3938
 
    %% Try to use the new user
3939
 
    ?line load_master("Test2"),
3940
 
    try_test(v3_sync, [[{usm_use_user, []}]],
3941
 
        [{sec_level, authPriv}, {user, "newUser"}]),
3942
 
    ?line unload_master("Test2"),
3943
 
 
3944
 
    ShaKey1 = snmp:passwd2localized_key(sha, "new sha password", "agentEngine"),
3945
 
    DesKey1 = lists:sublist(ShaKey1, 16),
3946
 
 
3947
 
    %% Change the new user's keys - 1
3948
 
    try_test(v3_sync, [[{usm_key_change1, [ShaKey1, DesKey1]}]],
3949
 
        [{sec_level, authPriv}, {user, "newUser"}]),
3950
 
 
3951
 
    %% Try to use the new keys
3952
 
    MgrDir = ?config(mgr_dir, Config),
3953
 
    ?line rewrite_usm_mgr(MgrDir, ShaKey1, DesKey1),
3954
 
    ?line load_master("Test2"),
3955
 
    try_test(v3_sync, [[{usm_use_user, []}]],
3956
 
        [{sec_level, authPriv}, {user, "newUser"}]),
3957
 
    ?line unload_master("Test2"),
3958
 
 
3959
 
    ShaKey2 = snmp:passwd2localized_key(sha, "newer password", "agentEngine"),
3960
 
    DesKey2 = lists:sublist(ShaKey2, 16),
3961
 
 
3962
 
    %% Change the new user's keys - 2
3963
 
    ?line try_test(v3_sync, 
3964
 
              [[{usm_key_change2, [ShaKey1, DesKey1, ShaKey2, DesKey2]}]],
3965
 
              [{sec_level, authPriv}, {user, "newUser"}]),
3966
 
 
3967
 
    %% Try to use the new keys
3968
 
    reset_usm_mgr(MgrDir),
3969
 
    ?line rewrite_usm_mgr(MgrDir, ShaKey2, DesKey2),
3970
 
    ?line load_master("Test2"),
3971
 
    ?line try_test(v3_sync, [[{usm_use_user, []}]],
3972
 
              [{sec_level, authPriv}, {user, "newUser"}]),
3973
 
    ?line unload_master("Test2"),
3974
 
    reset_usm_mgr(MgrDir),
3975
 
 
3976
 
    %% Change the new user's keys - 3
3977
 
    ?line try_test(v3_sync,
3978
 
              [[{usm_key_change3, [ShaKey2, DesKey2, ShaKey1, DesKey1]}]],
3979
 
              [{sec_level, authPriv}, {user, "privDES"}]),
3980
 
 
3981
 
    %% Try to use the new keys
3982
 
    ?line rewrite_usm_mgr(MgrDir, ShaKey1, DesKey1),
3983
 
    ?line load_master("Test2"),
3984
 
    try_test(v3_sync, [[{usm_use_user, []}]],
3985
 
        [{sec_level, authPriv}, {user, "newUser"}]),
3986
 
    ?line unload_master("Test2"),
3987
 
    reset_usm_mgr(MgrDir),
3988
 
 
3989
 
    %% Try some read requests
3990
 
    ?line try_test(v3_sync, [[{usm_read, []}]],
3991
 
              [{sec_level, authPriv}, {user, "privDES"}]),
3992
 
 
3993
 
    %% Delete the new user
3994
 
    ?line try_test(v3_sync, [[{usm_del_user, []}]],
3995
 
              [{sec_level, authPriv}, {user, "privDES"}]),
3996
 
 
3997
 
    %% Try some bad requests
3998
 
    ?line try_test(v3_sync, [[{usm_bad, []}]],
3999
 
              [{sec_level, authPriv}, {user, "privDES"}]),
4000
 
 
4001
 
    ?line unload_master("SNMP-USER-BASED-SM-MIB").
4002
 
 
4003
 
-define(usmUserSecurityName, [1,3,6,1,6,3,15,1,2,2,1,3]).
4004
 
 
4005
 
usm_add_user1() ->
4006
 
    NewRowIndex = [11,"agentEngine", 7, "newUser"],
4007
 
    RowPointer = ?usmUserSecurityName ++ [11|"agentEngine"] ++ [7|"privDES"],
4008
 
    Vbs1  = [{[usmUserCloneFrom, NewRowIndex], RowPointer},
4009
 
             {[usmUserStatus, NewRowIndex], ?createAndGo}],
4010
 
    ?line s(Vbs1),
4011
 
    ?line expect(1, Vbs1),
4012
 
    ok.
4013
 
    
4014
 
usm_use_user() ->
4015
 
    v2_proc().
4016
 
 
4017
 
 
4018
 
%% Change own public keys
4019
 
usm_key_change1(ShaKey, DesKey) ->
4020
 
    NewRowIndex = [11,"agentEngine", 7, "newUser"],
4021
 
    ShaKeyChange = snmp_user_based_sm_mib:mk_key_change(sha,
4022
 
                                                        "passwd_shaxxxxxxxxxx",
4023
 
                                                        ShaKey),
4024
 
    DesKeyChange = snmp_user_based_sm_mib:mk_key_change(sha,
4025
 
                                                        "passwd_desxxxxxx",
4026
 
                                                        DesKey),
4027
 
    Vbs1 = [{[usmUserAuthKeyChange, NewRowIndex], ShaKeyChange},
4028
 
            {[usmUserPrivKeyChange, NewRowIndex], DesKeyChange}],
4029
 
    s(Vbs1),
4030
 
    ?line expect(1, Vbs1).
4031
 
    
4032
 
%% Change own private keys
4033
 
usm_key_change2(OldShaKey, OldDesKey, ShaKey, DesKey) ->
4034
 
    NewRowIndex = [11,"agentEngine", 7, "newUser"],
4035
 
    ShaKeyChange = snmp_user_based_sm_mib:mk_key_change(sha,
4036
 
                                                        OldShaKey,
4037
 
                                                        ShaKey),
4038
 
    DesKeyChange = snmp_user_based_sm_mib:mk_key_change(sha,
4039
 
                                                        OldDesKey,
4040
 
                                                        DesKey),
4041
 
    Vbs1 = [{[usmUserOwnAuthKeyChange, NewRowIndex], ShaKeyChange},
4042
 
            {[usmUserOwnPrivKeyChange, NewRowIndex], DesKeyChange}],
4043
 
    s(Vbs1),
4044
 
    ?line expect(1, Vbs1).
4045
 
    
4046
 
%% Change other's public keys
4047
 
usm_key_change3(OldShaKey, OldDesKey, ShaKey, DesKey) ->
4048
 
    NewRowIndex = [11,"agentEngine", 7, "newUser"],
4049
 
    ShaKeyChange = snmp_user_based_sm_mib:mk_key_change(sha,
4050
 
                                                        OldShaKey,
4051
 
                                                        ShaKey),
4052
 
    DesKeyChange = snmp_user_based_sm_mib:mk_key_change(sha,
4053
 
                                                        OldDesKey,
4054
 
                                                        DesKey),
4055
 
    Vbs1 = [{[usmUserOwnAuthKeyChange, NewRowIndex], ShaKeyChange}],
4056
 
    s(Vbs1),
4057
 
    ?line expect(1, noAccess, 1, any),
4058
 
    Vbs2 = [{[usmUserOwnPrivKeyChange, NewRowIndex], DesKeyChange}],
4059
 
    s(Vbs2),
4060
 
    ?line expect(2, noAccess, 1, any),
4061
 
    
4062
 
    
4063
 
    Vbs3 = [{[usmUserAuthKeyChange, NewRowIndex], ShaKeyChange},
4064
 
            {[usmUserPrivKeyChange, NewRowIndex], DesKeyChange}],
4065
 
    s(Vbs3),
4066
 
    ?line expect(1, Vbs3).
4067
 
 
4068
 
usm_read() ->
4069
 
    NewRowIndex = [11,"agentEngine", 7, "newUser"],
4070
 
    ?line g([[usmUserSecurityName, NewRowIndex],
4071
 
             [usmUserCloneFrom, NewRowIndex],
4072
 
             [usmUserAuthKeyChange, NewRowIndex],
4073
 
             [usmUserOwnAuthKeyChange, NewRowIndex],
4074
 
             [usmUserPrivKeyChange, NewRowIndex],
4075
 
             [usmUserOwnPrivKeyChange, NewRowIndex]]),
4076
 
    ?line expect(1, 
4077
 
                 [{[usmUserSecurityName, NewRowIndex], "newUser"},
4078
 
                  {[usmUserCloneFrom, NewRowIndex], [0,0]},
4079
 
                  {[usmUserAuthKeyChange, NewRowIndex], ""},
4080
 
                  {[usmUserOwnAuthKeyChange, NewRowIndex], ""},
4081
 
                  {[usmUserPrivKeyChange, NewRowIndex], ""},
4082
 
                  {[usmUserOwnPrivKeyChange, NewRowIndex], ""}]),
4083
 
    ok.
4084
 
    
4085
 
    
4086
 
 
4087
 
usm_del_user() ->
4088
 
    NewRowIndex = [11,"agentEngine", 7, "newUser"],
4089
 
    Vbs1  = [{[usmUserStatus, NewRowIndex], ?destroy}],
4090
 
    ?line s(Vbs1),
4091
 
    ?line expect(1, Vbs1),
4092
 
    ok.
4093
 
 
4094
 
-define(usmUserCloneFrom, [1,3,6,1,6,3,15,1,2,2,1,4]).
4095
 
 
4096
 
-define(usmNoAuthProtocol, [1,3,6,1,6,3,10,1,1,1]).
4097
 
 
4098
 
-define(usmHMACMD5AuthProtocol, [1,3,6,1,6,3,10,1,1,2]).
4099
 
 
4100
 
-define(usmHMACSHAAuthProtocol, [1,3,6,1,6,3,10,1,1,3]).
4101
 
 
4102
 
-define(usmNoPrivProtocol, [1,3,6,1,6,3,10,1,2,1]).
4103
 
 
4104
 
-define(usmDESPrivProtocol, [1,3,6,1,6,3,10,1,2,2]).
4105
 
 
4106
 
usm_bad() ->
4107
 
    NewRowIndex = [11,"agentEngine", 7, "newUser"],
4108
 
    RowPointer1 = ?usmUserSecurityName ++ [11|"agentEngine"] ++ [7|"privDOS"],
4109
 
    Vbs1  = [{[usmUserCloneFrom, NewRowIndex], RowPointer1},
4110
 
             {[usmUserStatus, NewRowIndex], ?createAndGo}],
4111
 
    ?line s(Vbs1),
4112
 
    ?line expect(1, inconsistentName, 1, any),
4113
 
 
4114
 
    RowPointer2 = ?usmUserCloneFrom ++ [11|"agentEngine"] ++ [7|"privDES"],
4115
 
    Vbs2  = [{[usmUserCloneFrom, NewRowIndex], RowPointer2},
4116
 
             {[usmUserStatus, NewRowIndex], ?createAndGo}],
4117
 
    ?line s(Vbs2),
4118
 
    ?line expect(2, wrongValue, 1, any),
4119
 
 
4120
 
    RowPointer3 = ?usmUserSecurityName ++ [11|"agentEngine"] ++ [7|"privDES"],
4121
 
    Vbs3  = [{[usmUserCloneFrom, NewRowIndex], RowPointer3},
4122
 
             {[usmUserStatus, NewRowIndex], ?createAndGo}],
4123
 
    ?line s(Vbs3),
4124
 
    ?line expect(3, Vbs3),
4125
 
    ?line s([{[usmUserAuthProtocol, NewRowIndex], ?usmNoAuthProtocol}]),
4126
 
    ?line expect(4, inconsistentValue, 1, any),
4127
 
    ?line s([{[usmUserAuthProtocol, NewRowIndex], ?usmHMACMD5AuthProtocol}]),
4128
 
    ?line expect(5, inconsistentValue, 1, any),
4129
 
    ?line s([{[usmUserAuthProtocol, NewRowIndex], ?usmDESPrivProtocol}]),
4130
 
    ?line expect(6, wrongValue, 1, any),
4131
 
    ?line s([{[usmUserPrivProtocol, NewRowIndex], ?usmHMACSHAAuthProtocol}]),
4132
 
    ?line expect(7, wrongValue, 1, any),
4133
 
 
4134
 
    Vbs4  = [{[usmUserStatus, NewRowIndex], ?destroy}],
4135
 
    ?line s(Vbs4),
4136
 
    ?line expect(1, Vbs4),
4137
 
 
4138
 
    ok.
4139
 
    
4140
 
 
4141
 
%%-----------------------------------------------------------------
4142
 
%% Loop through entire MIB, to make sure that all instrum. funcs
4143
 
%% works.
4144
 
%% Load all std mibs that are not loaded by default.
4145
 
%%-----------------------------------------------------------------
4146
 
loop_mib(suite) -> [];
4147
 
loop_mib(Config) when list(Config) ->
4148
 
    ?LOG("loop_mib -> initiate case",[]),
4149
 
    %% snmp:verbosity(snmp_master_agent,debug),
4150
 
    %% snmp:verbosity(snmp_mib,info),
4151
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
4152
 
    ?DBG("loop_mib -> ~n"
4153
 
           "\tSaNode:  ~p~n"
4154
 
           "\tMgrNode: ~p~n"
4155
 
           "\tMibDir:  ~p",[SaNode, MgrNode, MibDir]),
4156
 
    ?DBG("loop_mib -> load mib SNMP-COMMUNITY-MIB",[]),
4157
 
    ?line load_master_std("SNMP-COMMUNITY-MIB"),
4158
 
    ?DBG("loop_mib -> load mib SNMP-MPD-MIB",[]),
4159
 
    ?line load_master_std("SNMP-MPD-MIB"),
4160
 
    ?DBG("loop_mib -> load mib SNMP-TARGET-MIB",[]),
4161
 
    ?line load_master_std("SNMP-TARGET-MIB"),
4162
 
    ?DBG("loop_mib -> load mib SNMP-NOTIFICATION-MIB",[]),
4163
 
    ?line load_master_std("SNMP-NOTIFICATION-MIB"),
4164
 
    ?DBG("loop_mib -> load mib SNMP-FRAMEWORK-MIB",[]),
4165
 
    ?line load_master_std("SNMP-FRAMEWORK-MIB"),
4166
 
    ?DBG("loop_mib -> load mib SNMP-VIEW-BASED-ACM-MIB",[]),
4167
 
    ?line load_master_std("SNMP-VIEW-BASED-ACM-MIB"),
4168
 
    ?DBG("loop_mib -> try",[]),
4169
 
    try_test(loop_mib_1),
4170
 
    ?DBG("loop_mib -> unload mib SNMP-COMMUNITY-MIB",[]),
4171
 
    ?line unload_master("SNMP-COMMUNITY-MIB"),
4172
 
    ?DBG("loop_mib -> unload mib SNMP-MPD-MIB",[]),
4173
 
    ?line unload_master("SNMP-MPD-MIB"),
4174
 
    ?DBG("loop_mib -> unload mib SNMP-TARGET-MIB",[]),
4175
 
    ?line unload_master("SNMP-TARGET-MIB"),
4176
 
    ?DBG("loop_mib -> unload mib SNMP-NOTIFICATION-MIB",[]),
4177
 
    ?line unload_master("SNMP-NOTIFICATION-MIB"),
4178
 
    ?DBG("loop_mib -> unload mib SNMP-FRAMEWORK-MIB",[]),
4179
 
    ?line unload_master("SNMP-FRAMEWORK-MIB"),
4180
 
    ?DBG("loop_mib -> unload mib SNMP-VIEW-BASED-ACM-MIB",[]),
4181
 
    ?line unload_master("SNMP-VIEW-BASED-ACM-MIB"),
4182
 
    %% snmp:verbosity(snmp_master_agent,log),
4183
 
    %% snmp:verbosity(snmp_mib,silence),
4184
 
    ?LOG("loop_mib -> done",[]).
4185
 
    
4186
 
 
4187
 
loop_mib_2(suite) -> [];
4188
 
loop_mib_2(Config) when list(Config) ->
4189
 
    ?LOG("loop_mib_2 -> initiate case",[]),
4190
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
4191
 
    ?DBG("loop_mib_2 -> ~n"
4192
 
           "\tSaNode:  ~p~n"
4193
 
           "\tMgrNode: ~p~n"
4194
 
           "\tMibDir:  ~p",[SaNode, MgrNode, MibDir]),
4195
 
    ?DBG("loop_mib_2 -> load mibs",[]),
4196
 
    ?line load_master_std("SNMP-COMMUNITY-MIB"),
4197
 
    ?line load_master_std("SNMP-MPD-MIB"),
4198
 
    ?line load_master_std("SNMP-TARGET-MIB"),
4199
 
    ?line load_master_std("SNMP-NOTIFICATION-MIB"),
4200
 
    ?line load_master_std("SNMP-FRAMEWORK-MIB"),
4201
 
    ?line load_master_std("SNMP-VIEW-BASED-ACM-MIB"),
4202
 
    try_test(loop_mib_2),
4203
 
    ?DBG("loop_mib_2 -> unload mibs",[]),
4204
 
    ?line unload_master("SNMP-COMMUNITY-MIB"),
4205
 
    ?line unload_master("SNMP-MPD-MIB"),
4206
 
    ?line unload_master("SNMP-TARGET-MIB"),
4207
 
    ?line unload_master("SNMP-NOTIFICATION-MIB"),
4208
 
    ?line unload_master("SNMP-FRAMEWORK-MIB"),
4209
 
    ?line unload_master("SNMP-VIEW-BASED-ACM-MIB"),
4210
 
    ?LOG("loop_mib_2 -> done",[]).
4211
 
 
4212
 
 
4213
 
loop_mib_3(suite) -> [];
4214
 
loop_mib_3(Config) when list(Config) ->
4215
 
    ?LOG("loop_mib_3 -> initiate case",[]),
4216
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
4217
 
    ?DBG("loop_mib_3 -> ~n"
4218
 
           "\tSaNode:  ~p~n"
4219
 
           "\tMgrNode: ~p~n"
4220
 
           "\tMibDir:  ~p",[SaNode, MgrNode, MibDir]),
4221
 
    ?DBG("loop_mib_3 -> load mibs",[]),
4222
 
    ?line load_master_std("SNMP-TARGET-MIB"),
4223
 
    ?line load_master_std("SNMP-NOTIFICATION-MIB"),
4224
 
    ?line load_master_std("SNMP-VIEW-BASED-ACM-MIB"),
4225
 
    ?line load_master_std("SNMP-USER-BASED-SM-MIB"),
4226
 
    try_test(loop_mib_2),
4227
 
    ?DBG("loop_mib_3 -> unload mibs",[]),
4228
 
    ?line unload_master("SNMP-TARGET-MIB"),
4229
 
    ?line unload_master("SNMP-NOTIFICATION-MIB"),
4230
 
    ?line unload_master("SNMP-VIEW-BASED-ACM-MIB"),
4231
 
    ?line unload_master("SNMP-USER-BASED-SM-MIB"),
4232
 
    ?LOG("loop_mib_3 -> done",[]).
4233
 
 
4234
 
 
4235
 
%% Req. As many mibs all possible
4236
 
loop_mib_1() ->
4237
 
    ?DBG("loop_mib_1 -> entry",[]),
4238
 
    N = loop_it_1([1,1], 0),
4239
 
    io:format(user, "found ~w varibles\n", [N]),
4240
 
    ?line N = if N < 100 -> 100;
4241
 
                 true -> N
4242
 
              end.
4243
 
            
4244
 
 
4245
 
loop_it_1(Oid, N) ->
4246
 
    ?DBG("loop_it_1 -> entry with"
4247
 
           "~n   Oid: ~p"
4248
 
           "~n   N:   ~p",[Oid,N]),
4249
 
    case get_next_req([Oid]) of
4250
 
        #pdu{type='get-response', error_status=noError, error_index=0,
4251
 
             varbinds=[#varbind{oid = NOid,value = Value}]} when NOid > Oid ->
4252
 
            ?DBG("loop_it_1 -> "
4253
 
                   "~n   NOid:  ~p"
4254
 
                   "~n   Value: ~p",[NOid,Value]),
4255
 
            ?line [Value2] = get_req(1, [NOid]), % must not be same
4256
 
            ?DBG("loop_it_1 -> Value2: ~p",[Value2]),
4257
 
            loop_it_1(NOid, N+1);
4258
 
        #pdu{type='get-response', error_status=noSuchName, error_index=1,
4259
 
             varbinds=[_]} ->
4260
 
            ?DBG("loop_it_1 -> done",[]),
4261
 
            N;
4262
 
        #pdu{type = Type, 
4263
 
             error_status = EStatus, 
4264
 
             error_index = EIdx, 
4265
 
             varbinds = Varbinds} ->
4266
 
            exit({unexpected_pdu, {Oid, N}, {Type, EStatus, EIdx, Varbinds}}) 
4267
 
    end.
4268
 
            
4269
 
%% Req. As many mibs all possible
4270
 
loop_mib_2() ->
4271
 
    ?DBG("loop_mib_1 -> entry",[]),
4272
 
    N = loop_it_2([1,1], 0),
4273
 
    io:format(user, "found ~w varibles\n", [N]),
4274
 
    ?line N = if N < 100 -> 100;
4275
 
                 true -> N
4276
 
              end.
4277
 
    
4278
 
 
4279
 
loop_it_2(Oid, N) ->
4280
 
    ?DBG("loop_it_2 -> entry with"
4281
 
           "~n   Oid: ~p"
4282
 
           "~n   N:   ~p",[Oid,N]),
4283
 
    case get_next_req([Oid]) of
4284
 
        #pdu{type='get-response', error_status=noError, error_index=0,
4285
 
             varbinds=[#varbind{oid = NOid, value = endOfMibView}]} ->
4286
 
            ?DBG("loop_it_2 -> NOid: ~p",[NOid]),
4287
 
            N;
4288
 
        #pdu{type='get-response', error_status=noError, error_index=0,
4289
 
             varbinds=[#varbind{oid = NOid,value = Value}]} when NOid > Oid ->
4290
 
            ?DBG("loop_it_2 -> "
4291
 
                   "~n   NOid:  ~p"
4292
 
                   "~n   Value: ~p",[NOid,Value]),
4293
 
            ?line [Value2] = get_req(1, [NOid]), % must not be same
4294
 
            ?DBG("loop_it_2 -> Value2: ~p",[Value2]),
4295
 
            loop_it_2(NOid, N+1);
4296
 
        #pdu{type = Type, 
4297
 
             error_status = EStatus, 
4298
 
             error_index = EIdx, 
4299
 
             varbinds = Varbinds} ->
4300
 
            exit({unexpected_pdu, {Oid, N}, {Type, EStatus, EIdx, Varbinds}}) 
4301
 
    end.
4302
 
            
4303
 
 
4304
 
%%%-----------------------------------------------------------------
4305
 
%%% Testing of reported bugs and other tickets.
4306
 
%%%-----------------------------------------------------------------
4307
 
 
4308
 
reported_bugs(suite) ->
4309
 
    [otp_1128, otp_1129, otp_1131, otp_1162,
4310
 
     otp_1222, otp_1298, otp_1331, otp_1338,
4311
 
     otp_1342, otp_2776, otp_2979, otp_3187, otp_3725].
4312
 
 
4313
 
reported_bugs_2(suite) ->
4314
 
    [otp_1128_2, otp_1129_2, otp_1131_2, otp_1162_2,
4315
 
     otp_1222_2, otp_1298_2, otp_1331_2, otp_1338_2,
4316
 
     otp_1342_2, otp_2776_2, otp_2979_2, otp_3187_2].
4317
 
 
4318
 
reported_bugs_3(suite) ->
4319
 
    [otp_1128_3, otp_1129_3, otp_1131_3, otp_1162_3,
4320
 
     otp_1222_3, otp_1298_3, otp_1331_3, otp_1338_3,
4321
 
     otp_1342_3, otp_2776_3, otp_2979_3, otp_3187_3,
4322
 
     otp_3542].
4323
 
 
4324
 
 
4325
 
%% These are (ticket) test cases where the initiation has to be done
4326
 
%% individually.
4327
 
tickets(suite) ->
4328
 
    [otp_4394].
4329
 
 
4330
 
%%-----------------------------------------------------------------
4331
 
%% Ticket: OTP-1128
4332
 
%% Slogan: Bug in handling of createAndWait set-requests.
4333
 
%%-----------------------------------------------------------------
4334
 
otp_1128(suite) -> [];
4335
 
otp_1128(Config) when list(Config) ->
4336
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
4337
 
    ?line load_master("OLD-SNMPEA-MIB"),
4338
 
    ?line init_old(),
4339
 
    try_test(otp_1128),
4340
 
    ?line unload_master("OLD-SNMPEA-MIB").
4341
 
 
4342
 
otp_1128_2(X) -> otp_1128(X).
4343
 
 
4344
 
otp_1128_3(X) -> otp_1128(X).
4345
 
 
4346
 
otp_1128() ->
4347
 
    io:format("Testing bug reported in ticket OTP-1128...~n"),
4348
 
 
4349
 
    NewKeyc3 = [intCommunityViewIndex,get(mip),is("test")],
4350
 
    NewKeyc4 = [intCommunityAccess,get(mip),is("test")],
4351
 
    NewKeyc5 = [intCommunityStatus,get(mip),is("test")],
4352
 
 
4353
 
    s([{NewKeyc5, ?createAndWait}, {NewKeyc4, 2}]),
4354
 
    ?line expect(28, [{NewKeyc5, ?createAndWait}, {NewKeyc4, 2}]),
4355
 
    g([NewKeyc5]),
4356
 
    ?line expect(29, [{NewKeyc5, ?notReady}]),
4357
 
    s([{NewKeyc5, ?active}, {NewKeyc3, 2}]),
4358
 
    ?line expect(30, [{NewKeyc5, ?active}, {NewKeyc3, 2}]),
4359
 
    g([NewKeyc5]),
4360
 
    ?line expect(31, [{NewKeyc5, ?active}]),
4361
 
    s([{NewKeyc5, ?destroy}]),
4362
 
    ?line expect(32, [{NewKeyc5, ?destroy}]).
4363
 
 
4364
 
%%-----------------------------------------------------------------
4365
 
%% Ticket: OTP-1129, OTP-1169
4366
 
%% Slogan: snmp:int_to_enum crashes on bad oids
4367
 
%%-----------------------------------------------------------------
4368
 
otp_1129(suite) -> [];
4369
 
otp_1129(Config) when list(Config) ->
4370
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
4371
 
    ?line load_master("Klas3"),
4372
 
    try_test(otp_1129_i, [node()]),
4373
 
    ?line unload_master("Klas3").
4374
 
 
4375
 
otp_1129_2(X) -> otp_1129(X).
4376
 
 
4377
 
otp_1129_3(X) -> otp_1129(X).
4378
 
 
4379
 
otp_1129_i(MaNode) ->
4380
 
    io:format("Testing bug reported in ticket OTP-1129...~n"),
4381
 
    false = rpc:call(MaNode, snmp, int_to_enum, [iso, 1]),
4382
 
    false = rpc:call(MaNode, snmp, int_to_enum, [isox, 1]).
4383
 
 
4384
 
%%-----------------------------------------------------------------
4385
 
%% Ticket: OTP-1131
4386
 
%% Slogan: Agent crashes / erlang node halts if RowIndex in a
4387
 
%%         setrequest is of bad type, e.g. an INDEX {INTEGER},
4388
 
%%         and RowIdenx [3,2].
4389
 
%%-----------------------------------------------------------------
4390
 
otp_1131(suite) -> [];
4391
 
otp_1131(Config) when list(Config) ->
4392
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
4393
 
    ?line load_master("Klas1"),
4394
 
    try_test(otp_1131),
4395
 
    ?line unload_master("Klas1").
4396
 
 
4397
 
otp_1131_2(X) -> otp_1131(X).
4398
 
 
4399
 
otp_1131_3(X) -> otp_1131(X).
4400
 
 
4401
 
otp_1131() ->
4402
 
    io:format("Testing bug reported in ticket OTP-1131...~n"),
4403
 
    s([{[friendsEntry, [2, 3, 1]], s, "kompis3"},
4404
 
       {[friendsEntry, [3, 3, 1]], i, ?createAndGo}]),
4405
 
    ?line expect(1, ?v1_2(noSuchName, noCreation), 2, any).
4406
 
 
4407
 
 
4408
 
%%-----------------------------------------------------------------
4409
 
%% Ticket: OTP-1162
4410
 
%% Slogan: snmp_agent can't handle wrongValue from instrum.func
4411
 
%%-----------------------------------------------------------------
4412
 
otp_1162(suite) -> [];
4413
 
otp_1162(Config) when list(Config) ->
4414
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
4415
 
    ?line {ok, SA} = start_subagent(SaNode, ?sa, "SA-MIB"),
4416
 
    try_test(otp_1162),
4417
 
    stop_subagent(SA).
4418
 
 
4419
 
otp_1162_2(X) -> otp_1162(X).
4420
 
 
4421
 
otp_1162_3(X) -> otp_1162(X).
4422
 
 
4423
 
otp_1162() ->
4424
 
    s([{[sa, [2,0]], 6}]), % wrongValue (i is_set_ok)
4425
 
    ?line expect(1, ?v1_2(badValue, wrongValue), 1, any).
4426
 
 
4427
 
 
4428
 
%%-----------------------------------------------------------------
4429
 
%% Ticket: OTP-1222
4430
 
%% Slogan: snmp agent crash if faulty index is returned from instrum
4431
 
%%-----------------------------------------------------------------
4432
 
otp_1222(suite) -> [];
4433
 
otp_1222(Config) when list(Config) ->
4434
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
4435
 
    ?line load_master("Klas3"),
4436
 
    ?line load_master("Klas4"),
4437
 
    try_test(otp_1222),
4438
 
    ?line unload_master("Klas3"),
4439
 
    ?line unload_master("Klas4").
4440
 
 
4441
 
otp_1222_2(X) -> otp_1222(X).
4442
 
 
4443
 
otp_1222_3(X) -> otp_1222(X).
4444
 
 
4445
 
otp_1222() ->
4446
 
    io:format("Testing bug reported in ticket OTP-1222...~n"),
4447
 
    s([{[fStatus4,1], 4}, {[fName4,1], 1}]),
4448
 
    ?line expect(1, genErr, 0, any),
4449
 
    s([{[fStatus4,2], 4}, {[fName4,2], 1}]),
4450
 
    ?line expect(2, genErr, 0, any).
4451
 
 
4452
 
%%-----------------------------------------------------------------
4453
 
%% Ticket: OTP-1298
4454
 
%% Slogan: Negative INTEGER values are treated as positive.
4455
 
%%-----------------------------------------------------------------
4456
 
otp_1298(suite) -> [];
4457
 
otp_1298(Config) when list(Config) ->
4458
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
4459
 
    ?line load_master("Klas2"),
4460
 
    try_test(otp_1298),
4461
 
    ?line unload_master("Klas2").
4462
 
 
4463
 
otp_1298_2(X) -> otp_1298(X).
4464
 
 
4465
 
otp_1298_3(X) -> otp_1298(X).
4466
 
 
4467
 
otp_1298() ->
4468
 
    io:format("Testing bug reported in ticket OTP-1298...~n"),
4469
 
    s([{[fint,0], -1}]),
4470
 
    ?line expect(1298, [{[fint,0], -1}]).
4471
 
    
4472
 
 
4473
 
%%-----------------------------------------------------------------
4474
 
%% Ticket: OTP-1331
4475
 
%% Slogan: snmp_generic should return noError when deleting non-ex row
4476
 
%%-----------------------------------------------------------------
4477
 
otp_1331(suite) -> [];
4478
 
otp_1331(Config) when list(Config) ->
4479
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
4480
 
    ?line load_master("OLD-SNMPEA-MIB"),
4481
 
    ?line init_old(),
4482
 
    try_test(otp_1331),
4483
 
    ?line unload_master("OLD-SNMPEA-MIB").
4484
 
 
4485
 
otp_1331_2(X) -> otp_1331(X).
4486
 
 
4487
 
otp_1331_3(X) -> otp_1331(X).
4488
 
 
4489
 
otp_1331() ->
4490
 
    NewKeyc5 = [intCommunityStatus,[127,32,0,0],is("test")],
4491
 
    s([{NewKeyc5, ?destroy}]),
4492
 
    ?line expect(1, [{NewKeyc5, ?destroy}]).
4493
 
 
4494
 
 
4495
 
%%-----------------------------------------------------------------
4496
 
%% Ticket: OTP-1338
4497
 
%% Slogan: snmp bug in initialisation of default values for mnesia tabs
4498
 
%%-----------------------------------------------------------------
4499
 
otp_1338(suite) -> [];
4500
 
otp_1338(Config) when list(Config) ->
4501
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
4502
 
    ?line load_master("Klas2"),
4503
 
    try_test(otp_1338),
4504
 
    ?line unload_master("Klas2").
4505
 
 
4506
 
otp_1338_2(X) -> otp_1338(X).
4507
 
 
4508
 
otp_1338_3(X) -> otp_1338(X).
4509
 
 
4510
 
otp_1338() ->
4511
 
    s([{[kStatus2, 7], i, ?createAndGo}]),
4512
 
    ?line expect(1, [{[kStatus2, 7], ?createAndGo}]),
4513
 
    g([[kName2, 7]]),
4514
 
    ?line expect(2, [{[kName2, 7], "JJJ"}]).
4515
 
 
4516
 
%%-----------------------------------------------------------------
4517
 
%% Ticket: OTP-1342
4518
 
%% Slogan: default impl of snmp table can't handle bad index access,
4519
 
%%         Set when INDEX is read-write gets into an infinite loop!
4520
 
%%-----------------------------------------------------------------
4521
 
otp_1342(suite) -> [];
4522
 
otp_1342(Config) when list(Config) ->
4523
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
4524
 
    ?line load_master("Klas4"),
4525
 
    try_test(otp_1342),
4526
 
    ?line unload_master("Klas4").
4527
 
 
4528
 
otp_1342_2(X) -> otp_1342(X).
4529
 
 
4530
 
otp_1342_3(X) -> otp_1342(X).
4531
 
 
4532
 
otp_1342() ->
4533
 
    s([{[fIndex5, 1], i, 1},
4534
 
       {[fName5, 1], i, 3},
4535
 
       {[fStatus5, 1], i, ?createAndGo}]),
4536
 
    ?line expect(1, ?v1_2(noSuchName, noCreation), 3, any).
4537
 
 
4538
 
 
4539
 
%%-----------------------------------------------------------------
4540
 
%% Ticket: OTP-1366
4541
 
%% Slogan: snmp traps not sent to all managers
4542
 
%% Note: NYI! We need a way to tell the test server that we need
4543
 
%%       mgrs on two different machines.
4544
 
%%-----------------------------------------------------------------
4545
 
otp_1366(suite) -> [];
4546
 
otp_1366(Config) when list(Config) ->
4547
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
4548
 
    ?line load_master("OLD-SNMPEA-MIB"),
4549
 
    ?line init_old(),
4550
 
    try_test(otp_1366),
4551
 
    ?line unload_master("OLD-SNMPEA-MIB").
4552
 
 
4553
 
otp_1366_2(X) -> otp_1366(X).
4554
 
 
4555
 
otp_1366_3(X) -> otp_1366(X).
4556
 
 
4557
 
otp_1366() ->
4558
 
    ?INF("NOT YET IMPLEMENTED", []),
4559
 
    'NYI'.
4560
 
 
4561
 
%%-----------------------------------------------------------------
4562
 
%% Ticket: OTP-2776
4563
 
%% Slogan: snmp:validate_date_and_time() fails when time is 00:00
4564
 
%%-----------------------------------------------------------------
4565
 
otp_2776(suite) -> [];
4566
 
otp_2776(Config) when list(Config) ->
4567
 
  {SaNode, MgrNode, MibDir} = init_case(Config),
4568
 
  try_test(otp_2776).
4569
 
 
4570
 
otp_2776_2(X) -> otp_2776(X).
4571
 
 
4572
 
otp_2776_3(X) -> otp_2776(X).
4573
 
 
4574
 
otp_2776() ->
4575
 
  io:format("Testing bug reported in ticket OTP-2776...~n"),
4576
 
 
4577
 
  Dt01_valid   = [19,98,9,1,1,0,23,0,43,0,0],
4578
 
  Dt02_valid   = [19,98,9,1,0,0,0,0,43,0,0],  % This is what is fixed: 00:00
4579
 
  Dt03_valid   = [19,98,2,28,1,0,23,0,43,0,0],
4580
 
  Dt04_invalid = [19,98,2,29,1,0,23,0,43,0,0],
4581
 
  Dt05_valid   = [19,96,2,29,1,0,23,0,43,0,0],
4582
 
  Dt06_valid   = [20,0,2,29,1,0,23,0,43,0,0],
4583
 
  Dt07_invalid = [19,96,2,30,1,0,23,0,43,0,0], % This is also fixed: 30/2
4584
 
  Dt08_valid   = [19,98,4,30,1,0,23,0,43,0,0],
4585
 
  Dt09_invalid = [19,98,4,31,1,0,23,0,43,0,0], % This is also fixed: 31/4
4586
 
  Dt10_invalid = [], 
4587
 
  Dt11_invalid = [kalle,hobbe], 
4588
 
  L = [{ 1, true,  Dt01_valid},
4589
 
       { 2, true,  Dt02_valid},
4590
 
       { 3, true,  Dt03_valid},
4591
 
       { 4, false, Dt04_invalid},
4592
 
       { 5, true,  Dt05_valid},
4593
 
       { 6, true,  Dt06_valid},
4594
 
       { 7, false, Dt07_invalid},
4595
 
       { 8, true,  Dt08_valid},
4596
 
       { 9, false, Dt09_invalid},
4597
 
       {10, false, Dt10_invalid},
4598
 
       {11, false, Dt11_invalid}],
4599
 
  
4600
 
  ?line ok = validate_dat(L).
4601
 
 
4602
 
 
4603
 
validate_dat(L) -> validate_dat(L,[]).
4604
 
 
4605
 
validate_dat([],V) -> 
4606
 
  Fun = fun({_,X}) -> case X of
4607
 
                        ok -> false;
4608
 
                        _  -> true
4609
 
                      end
4610
 
        end,
4611
 
  validate_dat1( lists:reverse( lists:filter(Fun,V) ) );
4612
 
validate_dat([{Id,E,Dat}|T],V) ->
4613
 
  validate_dat(T,[validate_dat2(Id,E,Dat) | V]).
4614
 
 
4615
 
validate_dat1([]) -> ok;
4616
 
validate_dat1(L)  -> {error,L}.
4617
 
 
4618
 
validate_dat2(Id, E, Dat) ->
4619
 
  Res = case {E,snmp:validate_date_and_time(Dat)} of
4620
 
          {E,E} -> ok;
4621
 
          {E,A} -> {E,A}
4622
 
        end,
4623
 
  {Id, Res}.
4624
 
 
4625
 
 
4626
 
%%-----------------------------------------------------------------
4627
 
%% Ticket: OTP-2979
4628
 
%% Slogan: get-next on more than 1 column in an empty table
4629
 
%%         returns bad response.
4630
 
%%-----------------------------------------------------------------
4631
 
otp_2979(suite) -> [];
4632
 
otp_2979(Config) when list(Config) ->
4633
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
4634
 
    ?line load_master("Test1"),
4635
 
    ?line init_old(),
4636
 
    try_test(otp_2979),
4637
 
    ?line unload_master("Test1").
4638
 
 
4639
 
otp_2979_2(X) -> otp_2979(X).
4640
 
 
4641
 
otp_2979_3(X) -> otp_2979(X).
4642
 
 
4643
 
otp_2979() ->
4644
 
    gn([[sparseDescr], [sparseStatus]]),
4645
 
    ?line expect(1, [{[sparseStr,0], "slut"},
4646
 
                     {[sparseStr,0], "slut"}]).
4647
 
 
4648
 
%%-----------------------------------------------------------------
4649
 
%% Ticket: OTP-3187
4650
 
%% Slogan: get-next on vacmAccessTable for colums > 5 returns
4651
 
%%         endOfTable - should return value.
4652
 
%%-----------------------------------------------------------------
4653
 
otp_3187(suite) -> [];
4654
 
otp_3187(Config) when list(Config) ->
4655
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
4656
 
    ?line load_master_std("SNMP-VIEW-BASED-ACM-MIB"),
4657
 
    otp_3187(),
4658
 
    ?line unload_master("SNMP-VIEW-BASED-ACM-MIB").
4659
 
 
4660
 
otp_3187_2(X) -> otp_3187(X).
4661
 
 
4662
 
otp_3187_3(X) -> otp_3187(X).
4663
 
 
4664
 
otp_3187() ->
4665
 
    ?line Elements =
4666
 
       snmp_view_based_acm_mib:vacmAccessTable(get_next,[],[4,5,6]),
4667
 
    lists:foreach(fun(E) ->
4668
 
                           ?line if E == endOfTable ->
4669
 
                                        ?FAIL(endOfTable);
4670
 
                                       true -> ok
4671
 
                                end
4672
 
                   end, Elements).
4673
 
 
4674
 
%%-----------------------------------------------------------------
4675
 
%% Ticket: OTP-3542
4676
 
%% Slogan: 
4677
 
%%-----------------------------------------------------------------
4678
 
otp_3542(suite) -> [];
4679
 
otp_3542(Config) when list(Config) ->
4680
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
4681
 
    try_test(otp_3542).
4682
 
 
4683
 
otp_3542() ->
4684
 
    io:format("SNMP v3 discovery...~n"),
4685
 
    ?line Res = snmp_mgr:d(),
4686
 
    io:format("SNMP v3 discovery result: ~p~n",[Res]).
4687
 
 
4688
 
 
4689
 
%%-----------------------------------------------------------------
4690
 
%% Ticket: OTP-3725
4691
 
%% Slogan: Slow response time on snmp:int_to_enum
4692
 
%%-----------------------------------------------------------------
4693
 
otp_3725(suite) -> [];
4694
 
otp_3725(Config) when list(Config) ->
4695
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
4696
 
 
4697
 
    ?line load_master("OLD-SNMPEA-MIB"),
4698
 
    ?line init_old(),
4699
 
    try_test(otp_3725_test, [node()]),
4700
 
    ?line unload_master("OLD-SNMPEA-MIB").
4701
 
 
4702
 
%% Req. OLD-SNMPEA-MIB
4703
 
otp_3725_test(MaNode) ->
4704
 
    io:format("Testing feature requested in ticket OTP-3725...~n"),
4705
 
    ?line rpc:call(MaNode,snmp,verbosity,[snmp_symbolic_store,trace]),
4706
 
    ?line Db = rpc:call(MaNode,snmp,get_symbolic_store_db,[]),
4707
 
    ?DBG("otp_3725_test -> Db = ~p",[Db]),
4708
 
 
4709
 
    ?line {value, OID} = rpc:call(MaNode, snmp, name_to_oid,
4710
 
                                  [Db, intAgentIpAddress]),
4711
 
    ?DBG("otp_3725_test -> name_to_oid for ~p: ~p",[intAgentIpAddress,OID]),
4712
 
    ?line {value, intAgentIpAddress} = rpc:call(MaNode, snmp, oid_to_name, 
4713
 
                                                [Db,OID]),
4714
 
    ?DBG("otp_3725_test -> oid_to_name for ~p: ~p",[OID,intAgentIpAddress]),
4715
 
    ?line false = rpc:call(MaNode, snmp, name_to_oid, [Db, intAgentIpAddres]),
4716
 
    ?line false = rpc:call(MaNode, snmp, oid_to_name,
4717
 
                           [Db, [1,5,32,3,54,3,3,34,4]]),
4718
 
    ?line {value, 2} = rpc:call(MaNode, snmp, enum_to_int,
4719
 
                                [Db, intViewType, excluded]),
4720
 
    ?line {value, excluded} = rpc:call(MaNode, snmp, int_to_enum,
4721
 
                                       [Db, intViewType, 2]),
4722
 
    ?line false = rpc:call(MaNode, snmp, enum_to_int, 
4723
 
                           [Db, intViewType, exclude]),
4724
 
    ?line false = rpc:call(MaNode, snmp, enum_to_int,
4725
 
                           [Db, intAgentIpAddress, exclude]),
4726
 
    ?line false = rpc:call(MaNode, snmp, enum_to_int,
4727
 
                           [Db, intAgentIpAddre, exclude]),
4728
 
    ?line false = rpc:call(MaNode, snmp, int_to_enum, [Db, intViewType, 3]),
4729
 
    ?line false = rpc:call(MaNode, snmp, int_to_enum, 
4730
 
                           [Db, intAgentIpAddress, 2]),
4731
 
    ?line false = rpc:call(MaNode, snmp, int_to_enum, 
4732
 
                           [Db, intAgentIpAddre, 2]),
4733
 
    ?line {value, active} = rpc:call(MaNode, snmp, int_to_enum, 
4734
 
                                     [Db, 'RowStatus', ?active]),
4735
 
    ?line {value, ?destroy} = rpc:call(MaNode, snmp, enum_to_int, 
4736
 
                                       [Db, 'RowStatus', destroy]),
4737
 
    ?line false = rpc:call(MaNode, snmp, enum_to_int, 
4738
 
                           [Db, 'RowStatus', xxxdestroy]),
4739
 
    ?line false = rpc:call(MaNode, snmp, enum_to_int, 
4740
 
                           [Db, 'xxRowStatus', destroy]),
4741
 
    ?line false = rpc:call(MaNode, snmp, int_to_enum, [Db, 'RowStatus', 25]),
4742
 
    ?line false = rpc:call(MaNode, snmp, int_to_enum, [Db, 'xxRowStatus', 1]),
4743
 
    ok.
4744
 
 
4745
 
 
4746
 
%%-----------------------------------------------------------------
4747
 
%% Ticket: OTP-4394
4748
 
%% Slogan: Target mib tag list check invalid
4749
 
%%-----------------------------------------------------------------
4750
 
 
4751
 
 
4752
 
otp_4394(suite) -> {req, [], {conf, 
4753
 
                              init_otp_4394, 
4754
 
                              [otp_4394_test], 
4755
 
                              finish_otp_4394}}.
4756
 
 
4757
 
init_otp_4394(Config) when list(Config) ->
4758
 
    ?DBG("init_otp_4394 -> entry with"
4759
 
           "~n   Config: ~p", [Config]),
4760
 
    ?line AgentDir = ?config(agent_dir, Config),
4761
 
    ?line MgrDir   = ?config(mgr_dir, Config),
4762
 
    ?line Ip       = ?config(ip, Config),
4763
 
    ?line otp_4394_config(AgentDir, MgrDir, Ip),
4764
 
    MasterAgentVerbosity = {master_agent_verbosity, trace},
4765
 
    NetIfVerbosity       = {net_if_verbosity,       trace},
4766
 
    Opts = [MasterAgentVerbosity,NetIfVerbosity],
4767
 
    [{vsn, v1} | start_v1_agent(Config,Opts)].
4768
 
 
4769
 
otp_4394_config(AgentDir, MgrDir, Ip0) ->
4770
 
    ?DBG("otp_4394_config -> entry with"
4771
 
           "~n   AgentDir: ~p"
4772
 
           "~n   MgrDir:   ~p"
4773
 
           "~n   Ip0:      ~p", [AgentDir, MgrDir, Ip0]),
4774
 
    Ver = [1],
4775
 
    Ip = tuple_to_list(Ip0), 
4776
 
    ?line snmp_config:write_files(AgentDir, Ver, Ip, 
4777
 
                                  ?TRAP_UDP, Ip, "4000", "OTP-4394 test"),
4778
 
    ?line case update_usm(Ver, AgentDir) of
4779
 
        true ->
4780
 
            ?line copy_file(filename:join(AgentDir, "usm.conf"),
4781
 
                            filename:join(MgrDir, "usm.conf")),
4782
 
            ?line update_usm_mgr(Ver, MgrDir);
4783
 
        false ->
4784
 
            ?line ok
4785
 
    end,
4786
 
    C1 = {"a", "all-rights", "initial", "", "pc"},
4787
 
    C2 = {"c", "secret", "secret_name", "", "secret_tag"},
4788
 
    ?line write_community_conf(AgentDir, [C1, C2]),
4789
 
    ?line update_vacm(Ver, AgentDir),
4790
 
    Ta1 = {"shelob v1", 
4791
 
           [134,138,177,177], 5000, 1500, 3, %% Anv�nd Ip och modda
4792
 
           "pc1", 
4793
 
           "target_v1", "", 
4794
 
           %% [255,255,255,255,0,0], 
4795
 
           [],
4796
 
           2048},
4797
 
    Ta2 = {"bifur v1", 
4798
 
           [134,138,177,75], 5000, 1500, 3, %% Anv�nd Ip
4799
 
           "pc2", 
4800
 
           "target_v1", "", 
4801
 
           %% [255,255,255,255,0,0],
4802
 
           [], 2048},
4803
 
    ?line write_target_addr_conf(AgentDir, [Ta1, Ta2]),
4804
 
    ?line write_target_params_conf(AgentDir, Ver),
4805
 
    ?line write_notify_conf(AgentDir),
4806
 
    ok.
4807
 
    
4808
 
 
4809
 
 
4810
 
finish_otp_4394(Config) when list(Config) ->
4811
 
    ?DBG("finish_otp_4394 -> entry", []),
4812
 
    C1 = stop_agent(Config),
4813
 
    delete_files(C1),
4814
 
    erase(mgr_node),
4815
 
    C2 = lists:keydelete(vsn, 1, C1).
4816
 
 
4817
 
otp_4394_test(suite) -> [];
4818
 
otp_4394_test(Config) ->
4819
 
    ?DBG("otp_4394_test -> entry", []),
4820
 
    {SaNode, MgrNode, MibDir} = init_case(Config),
4821
 
    try_test(otp_4394_test1),
4822
 
    ?DBG("otp_4394_test -> done", []),
4823
 
    ok.
4824
 
 
4825
 
otp_4394_test1() ->
4826
 
    ?DBG("otp_4394_test1 -> entry", []),
4827
 
    gn([[1,1]]),
4828
 
    Res = 
4829
 
        case snmp_mgr:expect(1, [{[sysDescr,0],  "Erlang SNMP agent"}]) of
4830
 
            %% {error, 1, {"?",[]}, {"~w",[timeout]}}
4831
 
            {error, 1, _, {_, [timeout]}} ->
4832
 
                ?DBG("otp_4394_test1 -> expected result: timeout", []),
4833
 
                ok;
4834
 
            Else ->
4835
 
                Else
4836
 
        end,
4837
 
    ?DBG("otp_4394_test1 -> done with: ~p", [Res]),
4838
 
    Res.
4839
 
 
4840
 
 
4841
 
%%%--------------------------------------------------
4842
 
%%% Used to test the standard mib with our
4843
 
%%% configuration.
4844
 
%%%--------------------------------------------------
4845
 
run(F, A, Opts) ->
4846
 
    M = get(mib_dir),
4847
 
    Dir = get(mgr_dir),
4848
 
    User = snmp_misc:get_option(user, Opts, "all-rights"),
4849
 
    SecLevel = snmp_misc:get_option(sec_level, Opts, noAuthNoPriv),
4850
 
    EngineID = snmp_misc:get_option(engine_id, Opts, "agentEngine"),
4851
 
    CtxEngineID = snmp_misc:get_option(context_engine_id, Opts, EngineID),
4852
 
    Community = snmp_misc:get_option(community, Opts, "all-rights"),
4853
 
    ?DBG("run -> start crypto app",[]),
4854
 
    Crypto = case os:type() of
4855
 
                 vxworks ->
4856
 
                     no_crypto;
4857
 
                 _ ->
4858
 
                     crypto:start()
4859
 
             end,
4860
 
    ?DBG("run -> Crypto: ~p",[Crypto]),
4861
 
    catch snmp_mgr:stop(), % If we had a running mgr from a failed case
4862
 
    StdM = filename:join(code:priv_dir(snmp), "mibs") ++ "/",
4863
 
    ?DBG("run -> config:~n"
4864
 
           "\tM:           ~p~n"
4865
 
           "\tDir:         ~p~n"
4866
 
           "\tUser:        ~p~n"
4867
 
           "\tSecLevel:    ~p~n"
4868
 
           "\tEngineID:    ~p~n"
4869
 
           "\tCtxEngineID: ~p~n"
4870
 
           "\tCommunity:   ~p~n"
4871
 
           "\tStdM:        ~p",
4872
 
           [M,Dir,User,SecLevel,EngineID,CtxEngineID,Community,StdM]),
4873
 
    case snmp_mgr:start([%% {agent, machine()},
4874
 
                         {packet_server_debug,true},
4875
 
                         {debug,true},
4876
 
                         {agent, get(master_host)}, 
4877
 
                         {agent_udp, 4000},
4878
 
                         {trap_udp, 5000},
4879
 
                         {recbuf,65535},
4880
 
                         quiet,
4881
 
                         get(vsn),
4882
 
                         {community, Community},
4883
 
                         {user, User},
4884
 
                         {sec_level, SecLevel},
4885
 
                         {engine_id, EngineID},
4886
 
                         {context_engine_id, CtxEngineID},
4887
 
                         {dir, Dir},
4888
 
                         {mibs, mibs(StdM, M)}]) of
4889
 
        {ok, Pid} ->
4890
 
            Res = apply(?MODULE, F, A),
4891
 
            catch snmp_mgr:stop(),
4892
 
            Res;
4893
 
        Err ->
4894
 
            io:format("Error starting manager: ~p\n", [Err]),
4895
 
            catch snmp_mgr:stop(),
4896
 
            ?line exit({mgr_start, Err})
4897
 
    end.
4898
 
            
4899
 
 
4900
 
mibs(StdMibDir,MibDir) ->
4901
 
    [join(StdMibDir, ?v1_2("STANDARD-MIB.bin", "SNMPv2-MIB.bin")),
4902
 
     join(MibDir, "OLD-SNMPEA-MIB.bin"),
4903
 
     join(StdMibDir, "SNMP-FRAMEWORK-MIB"),
4904
 
     join(StdMibDir, "SNMP-MPD-MIB"),
4905
 
     join(StdMibDir, "SNMP-VIEW-BASED-ACM-MIB"),
4906
 
     join(StdMibDir, "SNMP-USER-BASED-SM-MIB"),
4907
 
     join(StdMibDir, "SNMP-TARGET-MIB"),
4908
 
     join(StdMibDir, "SNMP-NOTIFICATION-MIB"),
4909
 
     join(MibDir, "Klas1.bin"),
4910
 
     join(MibDir, "Klas2.bin"), 
4911
 
     join(MibDir, "Klas3.bin"),
4912
 
     join(MibDir, "Klas4.bin"),
4913
 
     join(MibDir, "SA-MIB.bin"),
4914
 
     join(MibDir, "TestTrap.bin"),
4915
 
     join(MibDir, "Test1.bin"),
4916
 
     join(MibDir, "Test2.bin"),
4917
 
     join(MibDir, "TestTrapv2.bin")].
4918
 
 
4919
 
join(D,F) ->
4920
 
    filename:join(D,F).
4921
 
 
4922
 
%% string used in index
4923
 
is(S) -> [length(S) | S].
4924
 
 
4925
 
try_test(Func) ->
4926
 
    call(get(mgr_node), ?MODULE, run, [Func, [], []]).
4927
 
 
4928
 
try_test(Func, A) ->
4929
 
    call(get(mgr_node), ?MODULE, run, [Func, A, []]).
4930
 
 
4931
 
try_test(Func, A, Opts) ->
4932
 
    call(get(mgr_node), ?MODULE, run, [Func, A, Opts]).
4933
 
 
4934
 
call(N,M,F,A) ->
4935
 
    ?DBG("call -> entry with~n"
4936
 
           "    N:     ~p~n"
4937
 
           "    M:     ~p~n"
4938
 
           "    F:     ~p~n"
4939
 
           "    A:     ~p~n"
4940
 
           "  when~n"
4941
 
           "    get(): ~p",
4942
 
           [N,M,F,A,get()]),
4943
 
    spawn(N, ?MODULE, wait, [self(),get(),M,F,A]),
4944
 
    receive
4945
 
        {done, {'EXIT', Rn}, Loc} ->
4946
 
            ?DBG("call -> returned ~p",[{done, {'EXIT', Rn}, Loc}]),
4947
 
            put(test_server_loc, Loc),
4948
 
            exit(Rn);
4949
 
        {done, Ret, Zed} -> 
4950
 
            ?DBG("call -> returned ~p~n",[{done, Ret, Zed}]),
4951
 
            Ret
4952
 
    end.
4953
 
 
4954
 
wait(From, Env, M, F, A) ->
4955
 
    ?DBG("wait -> entry with ~n"
4956
 
           "\tFrom: ~p~n"
4957
 
           "\tEnv:  ~p",[From,Env]),
4958
 
    lists:foreach(fun({K,V}) -> put(K,V) end, Env),
4959
 
    Rn = (catch apply(M, F, A)),
4960
 
    ?DBG("wait -> Rn = ~p", [Rn]),
4961
 
    From ! {done, Rn, get(test_server_loc)},
4962
 
    exit(Rn).
4963
 
 
4964
 
expect(A,B) -> ok = snmp_mgr:expect(A,B).
4965
 
expect(A,B,C) -> ok = snmp_mgr:expect(A,B,C).
4966
 
expect(A,B,C,D) -> ok = snmp_mgr:expect(A,B,C,D).
4967
 
expect(A,B,C,D,E,F) -> ok = snmp_mgr:expect(A,B,C,D,E,F).
4968
 
 
4969
 
get_req(Id, Vars) ->
4970
 
    ?DBG("get_req -> entry with~n"
4971
 
           "\tId:   ~p~n"
4972
 
           "\tVars: ~p",[Id,Vars]),
4973
 
    g(Vars),
4974
 
    ?DBG("get_req -> await response",[]),
4975
 
    {ok, Val} = snmp_mgr:get_response(Id, Vars), 
4976
 
    ?DBG("get_req -> response: ~p",[Val]),
4977
 
    Val.
4978
 
 
4979
 
get_next_req(Vars) ->
4980
 
    ?DBG("get_next_req -> entry with Vars '~p', send request",[Vars]),
4981
 
    gn(Vars),
4982
 
    ?DBG("get_next_req -> await response",[]),
4983
 
    Response = snmp_mgr:receive_response(),
4984
 
    ?DBG("get_next_req -> response: ~p",[Response]),
4985
 
    Response.
4986
 
 
4987
 
 
4988
 
 
4989
 
from(H, [H | T]) -> T;
4990
 
from(H, [_ | T]) -> from(H, T);
4991
 
from(H, []) -> [].
4992
 
 
4993
 
start_node(Name) ->
4994
 
    ?LOG("start_node -> entry with Name: ~p",[Name]),
4995
 
    M = list_to_atom(from($@, atom_to_list(node()))),
4996
 
    ?DBG("start_node -> M: ~p",[M]),
4997
 
    Pa = filename:dirname(code:which(?MODULE)),
4998
 
    ?DBG("start_node -> Pa: ~p",[Pa]),
4999
 
 
5000
 
    Args = case init:get_argument('CC_TEST') of
5001
 
               {ok, [[]]} ->
5002
 
                   " -pa /clearcase/otp/libraries/snmp/ebin ";
5003
 
               {ok, [[Path]]} ->
5004
 
                   " -pa " ++ Path;
5005
 
               error ->
5006
 
                      ""
5007
 
              end,
5008
 
    %% Do not use start_link!!! (the proc that calls this one is tmp)
5009
 
    ?DBG("start_node -> Args: ~p~n",[Args]),
5010
 
    A = Args ++ " -pa " ++ Pa,
5011
 
    case (catch ?START_NODE(Name, A)) of
5012
 
        {ok, Node} ->
5013
 
            %% Tell the test_server to not clean up things it never started.
5014
 
            ?DBG("start_node -> Node: ~p",[Node]),
5015
 
            {ok, Node};
5016
 
        Else  -> 
5017
 
            ?ERR("start_node -> failed with(other): Else: ~p",[Else]),
5018
 
            ?line ?FAIL(Else)
5019
 
    end.
5020
 
 
5021
 
 
5022
 
stop_node(Node) ->
5023
 
    ?LOG("stop_node -> Node: ~p",[Node]),
5024
 
    rpc:cast(Node, erlang, halt, []).
5025
 
 
5026
 
p(X) ->
5027
 
    io:format(user, X++"\n", []).
5028
 
 
5029
 
sleep(X) ->
5030
 
    receive
5031
 
        after
5032
 
            X -> ok
5033
 
        end.
5034
 
 
5035
 
%%%-----------------------------------------------------------------
5036
 
%%% Configuration
5037
 
%%%-----------------------------------------------------------------
5038
 
config(Ver, MgrDir, AgentDir, MIp, AIp) ->
5039
 
    ?line snmp_config:write_files(AgentDir, Ver,MIp, 
5040
 
                                  ?TRAP_UDP, AIp, "4000", "test"),
5041
 
    ?line case update_usm(Ver, AgentDir) of
5042
 
        true ->
5043
 
            ?line copy_file(filename:join(AgentDir, "usm.conf"),
5044
 
                            filename:join(MgrDir, "usm.conf")),
5045
 
            ?line update_usm_mgr(Ver, MgrDir);
5046
 
        false ->
5047
 
            ?line ok
5048
 
    end,
5049
 
    ?line update_community(Ver, AgentDir),
5050
 
    ?line update_vacm(Ver, AgentDir),
5051
 
    ?line write_target_addr_conf(AgentDir, MIp, ?TRAP_UDP, Ver),
5052
 
    ?line write_target_params_conf(AgentDir, Ver),
5053
 
    ?line write_notify_conf(AgentDir),
5054
 
    ok.
5055
 
 
5056
 
delete_files(Config) ->
5057
 
    Dir = ?config(agent_dir, Config),
5058
 
    {ok, List} = file:list_dir(Dir),
5059
 
    lists:foreach(fun(FName) -> file:delete(filename:join(Dir, FName)) end,
5060
 
                  List).
5061
 
 
5062
 
update_usm(Ver, Dir) ->
5063
 
    case lists:member(3, Ver) of
5064
 
        true ->
5065
 
            {ok, Fid} = file:open(filename:join(Dir,"usm.conf"),[read,write]),
5066
 
            file:position(Fid, eof),
5067
 
            ok = io:format(Fid, "{\"agentEngine\", \"all-rights\", "
5068
 
                           "\"all-rights\", zeroDotZero, "
5069
 
                           "usmNoAuthProtocol, \"\", \"\", "
5070
 
                           "usmNoPrivProtocol, \"\", \"\", \"\", "
5071
 
                           "\"\", \"\"}.\n", []),
5072
 
            ok = io:format(Fid, "{\"agentEngine\", \"no-rights\", "
5073
 
                           "\"no-rights\", zeroDotZero, "
5074
 
                           "usmNoAuthProtocol, \"\", \"\", "
5075
 
                           "usmNoPrivProtocol, \"\", \"\", \"\", "
5076
 
                           "\"\", \"\"}.\n", []),
5077
 
            ok = io:format(Fid, "{\"agentEngine\", \"authMD5\", "
5078
 
                           "\"authMD5\", zeroDotZero, "
5079
 
                           "usmHMACMD5AuthProtocol, \"\", \"\", "
5080
 
                           "usmNoPrivProtocol, \"\", \"\", \"\", "
5081
 
                           "\"passwd_md5xxxxxx\", \"\"}.\n", []),
5082
 
            ok = io:format(Fid, "{\"agentEngine\", \"authSHA\", "
5083
 
                           "\"authSHA\", zeroDotZero, "
5084
 
                           "usmHMACSHAAuthProtocol, \"\", \"\", "
5085
 
                           "usmNoPrivProtocol, \"\", \"\", \"\", "
5086
 
                           "\"passwd_shaxxxxxxxxxx\", \"\"}.\n", []),
5087
 
            ok = io:format(Fid, "{\"agentEngine\", \"privDES\", "
5088
 
                           "\"privDES\", zeroDotZero, "
5089
 
                           "usmHMACSHAAuthProtocol, \"\", \"\", "
5090
 
                           "usmDESPrivProtocol, \"\", \"\", \"\", "
5091
 
                           "\"passwd_shaxxxxxxxxxx\", \"passwd_desxxxxxx\"}.\n",
5092
 
                           []),
5093
 
            ok = io:format(Fid, "{\"mgrEngine\", \"all-rights\", "
5094
 
                           "\"all-rights\", zeroDotZero, "
5095
 
                           "usmNoAuthProtocol, \"\", \"\", "
5096
 
                           "usmNoPrivProtocol, \"\", \"\", \"\", "
5097
 
                           "\"\", \"\"}.\n", []),
5098
 
            ok = io:format(Fid, "{\"mgrEngine\", \"no-rights\", "
5099
 
                           "\"no-rights\", zeroDotZero, "
5100
 
                           "usmNoAuthProtocol, \"\", \"\", "
5101
 
                           "usmNoPrivProtocol, \"\", \"\", \"\", "
5102
 
                           "\"\", \"\"}.\n", []),
5103
 
            ok = io:format(Fid, "{\"mgrEngine\", \"authMD5\", "
5104
 
                           "\"authMD5\", zeroDotZero, "
5105
 
                           "usmHMACMD5AuthProtocol, \"\", \"\", "
5106
 
                           "usmNoPrivProtocol, \"\", \"\", \"\", "
5107
 
                           "\"passwd_md5xxxxxx\", \"\"}.\n", []),
5108
 
            ok = io:format(Fid, "{\"mgrEngine\", \"authSHA\", "
5109
 
                           "\"authSHA\", zeroDotZero, "
5110
 
                           "usmHMACSHAAuthProtocol, \"\", \"\", "
5111
 
                           "usmNoPrivProtocol, \"\", \"\", \"\", "
5112
 
                           "\"passwd_shaxxxxxxxxxx\", \"\"}.\n", []),
5113
 
            ok = io:format(Fid, "{\"mgrEngine\", \"privDES\", "
5114
 
                           "\"privDES\", zeroDotZero, "
5115
 
                           "usmHMACSHAAuthProtocol, \"\", \"\", "
5116
 
                           "usmDESPrivProtocol, \"\", \"\", \"\", "
5117
 
                           "\"passwd_shaxxxxxxxxxx\", \"passwd_desxxxxxx\"}.\n",
5118
 
                           []),
5119
 
            file:close(Fid),
5120
 
            true;
5121
 
        false ->
5122
 
            false
5123
 
    end.
5124
 
    
5125
 
update_usm_mgr(Ver, Dir) ->
5126
 
    case lists:member(3, Ver) of
5127
 
        true ->
5128
 
            {ok, Fid} = file:open(filename:join(Dir,"usm.conf"),[read,write]),
5129
 
            file:position(Fid, eof),
5130
 
            ok = io:format(Fid, "{\"agentEngine\", \"newUser\", "
5131
 
                           "\"newUser\", zeroDotZero, "
5132
 
                           "usmHMACSHAAuthProtocol, \"\", \"\", "
5133
 
                           "usmDESPrivProtocol, \"\", \"\", \"\", "
5134
 
                           "\"passwd_shaxxxxxxxxxx\", \"passwd_desxxxxxx\"}.\n",
5135
 
                           []),
5136
 
            ok = io:format(Fid, "{\"mgrEngine\", \"newUser\", "
5137
 
                           "\"newUser\", zeroDotZero, "
5138
 
                           "usmHMACSHAAuthProtocol, \"\", \"\", "
5139
 
                           "usmDESPrivProtocol, \"\", \"\", \"\", "
5140
 
                           "\"passwd_shaxxxxxxxxxx\", \"passwd_desxxxxxx\"}.\n",
5141
 
                           []),
5142
 
            file:close(Fid),
5143
 
            true;
5144
 
        false ->
5145
 
            false
5146
 
    end.
5147
 
 
5148
 
rewrite_usm_mgr(Dir, ShaKey, DesKey) -> 
5149
 
    ?line ok = file:rename(filename:join(Dir,"usm.conf"),
5150
 
                           filename:join(Dir,"usm.old")),
5151
 
    ?line {ok, Fid} = file:open(filename:join(Dir,"usm.conf"),write),
5152
 
    ok = io:format(Fid, "{\"agentEngine\", \"newUser\", "
5153
 
                   "\"newUser\", zeroDotZero, "
5154
 
                   "usmHMACSHAAuthProtocol, \"\", \"\", "
5155
 
                   "usmDESPrivProtocol, \"\", \"\", \"\", "
5156
 
                   "\"~s\", \"~s\"}.\n",
5157
 
                   [ShaKey, DesKey]),
5158
 
    ok = io:format(Fid, "{\"mgrEngine\", \"newUser\", "
5159
 
                   "\"newUser\", zeroDotZero, "
5160
 
                   "usmHMACSHAAuthProtocol, \"\", \"\", "
5161
 
                   "usmDESPrivProtocol, \"\", \"\", \"\", "
5162
 
                   "\"~s\", \"~s\"}.\n",
5163
 
                   [ShaKey, DesKey]),
5164
 
    file:close(Fid).
5165
 
 
5166
 
reset_usm_mgr(Dir) ->
5167
 
    ?line ok = file:rename(filename:join(Dir,"usm.old"),
5168
 
                           filename:join(Dir,"usm.conf")).
5169
 
 
5170
 
 
5171
 
update_community([v3], Dir) -> ok;
5172
 
update_community(_, Dir) ->
5173
 
    {ok, Fid} = file:open(filename:join(Dir,"community.conf"),[read,write]),
5174
 
    file:position(Fid, eof),
5175
 
    ok=io:format(Fid,"{\"no-rights\",\"no-rights\",\"no-rights\",\"\",\"\"}.\n",
5176
 
                 []),
5177
 
    file:close(Fid).
5178
 
    
5179
 
    
5180
 
-define(tDescr_instance, [1,3,6,1,2,1,16,1,0]).
5181
 
update_vacm(Ver, Dir) ->
5182
 
    {ok, Fid} = file:open(filename:join(Dir,"vacm.conf"),[read,write]),
5183
 
    file:position(Fid, eof),
5184
 
    ok=io:format(Fid,"{vacmSecurityToGroup,usm,\"authMD5\",\"initial\"}.\n",[]),
5185
 
    ok=io:format(Fid,"{vacmSecurityToGroup,usm,\"authSHA\",\"initial\"}.\n",[]),
5186
 
    ok=io:format(Fid,"{vacmSecurityToGroup,usm,\"privDES\",\"initial\"}.\n",[]),
5187
 
    ok=io:format(Fid,"{vacmSecurityToGroup,usm,\"newUser\",\"initial\"}.\n",[]),
5188
 
    ok = io:format(Fid, "{vacmViewTreeFamily, \"internet\", "
5189
 
                   "~w, excluded, null}.\n", [?tDescr_instance]),
5190
 
    file:close(Fid).
5191
 
    
5192
 
    
5193
 
vacm_ver(1) -> v1;
5194
 
vacm_ver(2) -> v2c;
5195
 
vacm_ver(3) -> usm.
5196
 
     
5197
 
 
5198
 
write_community_conf(Dir, Confs) ->
5199
 
    {ok, Fid} = file:open(filename:join(Dir,"community.conf"),write),
5200
 
    ok = write_community_conf1(Fid, Confs),
5201
 
    file:close(Fid).
5202
 
 
5203
 
write_community_conf1(_, []) ->
5204
 
    ok;
5205
 
write_community_conf1(Fid, [{ComIdx, ComName, SecName, CtxName, TransTag}|Confs]) ->
5206
 
    ok = io:format(Fid, "{\"~s\", \"~s\", \"~s\", \"~s\", \"~s\"}.~n",
5207
 
                   [ComIdx, ComName, SecName, CtxName, TransTag]),
5208
 
    write_community_conf1(Fid, Confs).
5209
 
    
5210
 
 
5211
 
write_target_addr_conf(Dir, Confs) ->
5212
 
    {ok, Fid} = file:open(filename:join(Dir,"target_addr.conf"),write),
5213
 
    ok = write_target_addr_conf1(Fid, Confs),
5214
 
    file:close(Fid).
5215
 
 
5216
 
 
5217
 
write_target_addr_conf1(_, []) ->
5218
 
    ok;
5219
 
write_target_addr_conf1(Fid, 
5220
 
                       [{Name, Ip, Port, Timeout, Retry, TagList, ParamName, 
5221
 
                         EngineId, TMask, MaxMsgSz}|Confs]) ->
5222
 
    ok = io:format(Fid, "{\"~s\", ~w, ~w, ~w, ~w, \"~s\", \"~s\", \"~s\", ~w, ~w}.~n",
5223
 
                   [Name, Ip, Port, Timeout, Retry, TagList, ParamName, 
5224
 
                    EngineId, TMask, MaxMsgSz]),
5225
 
    write_target_addr_conf1(Fid, Confs).
5226
 
    
5227
 
write_target_addr_conf(Dir, ManagerIp, UDP, Vers) -> 
5228
 
    {ok, Fid} = file:open(filename:join(Dir,"target_addr.conf"),write),
5229
 
    lists:foreach(fun(Ver) ->
5230
 
                          ok = io:format(Fid, "{\"~s\", ~w, ~s, 1500, 3, "
5231
 
                                         "\"std_trap\", \"~s\"}.~n",
5232
 
                                         [mk_ip(ManagerIp, Ver),
5233
 
                                          ManagerIp, UDP, mk_param(Ver)]),
5234
 
                          case Ver of
5235
 
                              1 -> ok;
5236
 
                              2 ->
5237
 
                                  ok = io:format(Fid, "{\"~s.2\",~w,~s,1500,3, "
5238
 
                                                 "\"std_inform\", \"~s\"}.~n",
5239
 
                                                 [mk_ip(ManagerIp, Ver),
5240
 
                                                  ManagerIp, UDP,
5241
 
                                                  mk_param(Ver)]);
5242
 
                              3 ->
5243
 
                                  ok = io:format(Fid, "{\"~s.3\",~w,~s,1500,3, "
5244
 
                                                 "\"std_inform\", \"~s\", "
5245
 
                                                 "\"mgrEngine\", [], 1024}.~n",
5246
 
                                                 [mk_ip(ManagerIp, Ver),
5247
 
                                                  ManagerIp, UDP,
5248
 
                                                  mk_param(Ver)])
5249
 
                          end
5250
 
                  end,
5251
 
                  Vers),
5252
 
    file:close(Fid).
5253
 
 
5254
 
mk_param(1) -> "target_v1";
5255
 
mk_param(2) -> "target_v2";
5256
 
mk_param(3) -> "target_v3".
5257
 
     
5258
 
mk_ip([A,B,C,D], Ver) ->
5259
 
    io_lib:format("~w.~w.~w.~w v~w", [A,B,C,D,Ver]).
5260
 
 
5261
 
 
5262
 
rewrite_target_addr_conf(Dir,NewPort) -> 
5263
 
    TAFile = filename:join(Dir, "target_addr.conf"),
5264
 
    ?DBG("rewrite_target_addr_conf -> read target file info of address config file",[]),
5265
 
    case file:read_file_info(TAFile) of
5266
 
        {ok, _} -> ok;
5267
 
        {error, R} -> ?ERR("failure reading file info of "
5268
 
                          "target address config file: ~p",[R]),
5269
 
                      ok  
5270
 
    end,
5271
 
 
5272
 
    ?line [TrapAddr|Addrs] = 
5273
 
        snmp_misc:read(TAFile,{?MODULE, rewrite_target_addr_conf1}),
5274
 
 
5275
 
    ?DBG("rewrite_target_addr_conf -> TrapAddr: ~p",[TrapAddr]),
5276
 
 
5277
 
    NewAddrs = [rewrite_target_addr_conf2(NewPort,TrapAddr)|Addrs],
5278
 
    
5279
 
    ?DBG("rewrite_target_addr_conf -> NewAddrs: ~p",[NewAddrs]),
5280
 
 
5281
 
    ?line ok = file:rename(filename:join(Dir,"target_addr.conf"),
5282
 
                           filename:join(Dir,"target_addr.old")),
5283
 
    ?line {ok, Fid} = file:open(filename:join(Dir,"target_addr.conf"),write),
5284
 
    
5285
 
    ?line ok = rewrite_target_addr_conf3(Fid,NewAddrs),
5286
 
 
5287
 
    file:close(Fid).
5288
 
 
5289
 
rewrite_target_addr_conf1(O) -> 
5290
 
    {ok,O}.
5291
 
 
5292
 
rewrite_target_addr_conf2(NewPort,{Name,Ip,Port,Timeout,Retry,
5293
 
                                   "std_trap",EngineId}) -> 
5294
 
    ?LOG("rewrite_target_addr_conf2 -> entry with std_trap",[]),
5295
 
    {Name,Ip,NewPort,Timeout,Retry,"std_trap",EngineId};
5296
 
rewrite_target_addr_conf2(_NewPort,O) -> 
5297
 
    ?LOG("rewrite_target_addr_conf2 -> entry with "
5298
 
         "~n   O: ~p",[O]),
5299
 
    O.
5300
 
 
5301
 
 
5302
 
rewrite_target_addr_conf3(_,[]) -> ok;
5303
 
rewrite_target_addr_conf3(Fid,[{Name,Ip,Port,Timeout,Retry,
5304
 
                                ParamName,EngineId}|T]) -> 
5305
 
    ?LOG("rewrite_target_addr_conf3 -> write(1) ~s",[ParamName]),
5306
 
    io:format(Fid, 
5307
 
              "{\"~s\", " % Name
5308
 
              "~p, "      % Ip
5309
 
              "~p, "      % Port
5310
 
              "~p, "      % Timeout
5311
 
              "~p, "      % Retry
5312
 
              "\"~s\", "  % ParamsName
5313
 
              "\"~s\"}.", % EngineId
5314
 
              [Name,Ip,Port,Timeout,Retry,ParamName,EngineId]),
5315
 
    rewrite_target_addr_conf3(Fid,T);
5316
 
rewrite_target_addr_conf3(Fid,[{Name,Ip,Port,Timeout,Retry,TagList,
5317
 
                                ParamName,EngineId,TMask,MMS}|T]) ->
5318
 
    ?LOG("rewrite_target_addr_conf3 -> write(2) ~s",[ParamName]),
5319
 
    io:format(Fid, 
5320
 
              "{\"~s\", " % Name
5321
 
              "~p, "      % Ip
5322
 
              "~p, "      % Port
5323
 
              "~p, "      % Timeout
5324
 
              "~p, "      % Retry
5325
 
              "\"~s\", "  % TagList
5326
 
              "\"~s\", "  % ParamsName
5327
 
              "\"~s\","   % EngineId
5328
 
              "~p, "      % TMask
5329
 
              "~p}.",     % MMS
5330
 
              [Name,Ip,Port,Timeout,Retry,TagList,ParamName,
5331
 
               EngineId,TMask,MMS]),
5332
 
    rewrite_target_addr_conf3(Fid,T).
5333
 
    
5334
 
reset_target_addr_conf(Dir) ->
5335
 
    ?line ok = file:rename(filename:join(Dir,"target_addr.old"),
5336
 
                           filename:join(Dir,"target_addr.conf")).
5337
 
 
5338
 
write_target_params_conf(Dir, Vers) -> 
5339
 
    {ok, Fid} = file:open(filename:join(Dir,"target_params.conf"),write),
5340
 
    lists:foreach(fun(Ver) ->
5341
 
                          MP = if Ver == 1 -> v1;
5342
 
                                  Ver == 2 -> v2c;
5343
 
                                  Ver == 3 -> v3
5344
 
                               end,
5345
 
                          SM = if Ver == 1 -> v1;
5346
 
                                  Ver == 2 -> v2c;
5347
 
                                  Ver == 3 -> usm
5348
 
                               end,
5349
 
                          ok = io:format(Fid, "{\"target_v~w\", ~w, ~w, "
5350
 
                                         "\"all-rights\", noAuthNoPriv}.~n",
5351
 
                                         [Ver, MP, SM])
5352
 
                  end,
5353
 
                  Vers),
5354
 
    file:close(Fid).
5355
 
 
5356
 
rewrite_target_params_conf(Dir, SecName, SecLevel) -> 
5357
 
    ?line ok = file:rename(filename:join(Dir,"target_params.conf"),
5358
 
                           filename:join(Dir,"target_params.old")),
5359
 
    ?line {ok, Fid} = file:open(filename:join(Dir,"target_params.conf"),write),
5360
 
    ?line ok = io:format(Fid, "{\"target_v3\", v3, usm, \"~s\", ~w}.~n",
5361
 
                         [SecName, SecLevel]),
5362
 
    file:close(Fid).
5363
 
 
5364
 
reset_target_params_conf(Dir) ->
5365
 
    ?line ok = file:rename(filename:join(Dir,"target_params.old"),
5366
 
                           filename:join(Dir,"target_params.conf")).
5367
 
 
5368
 
write_notify_conf(Dir) -> 
5369
 
    {ok, Fid} = file:open(filename:join(Dir,"notify.conf"),write),
5370
 
    ok = io:format(Fid, "{\"standard trap\", \"std_trap\", trap}.~n", []),
5371
 
    ok = io:format(Fid, "{\"standard inform\", \"std_inform\",inform}.~n", []),
5372
 
    file:close(Fid).
5373
 
 
5374
 
ver_to_trap_str([1]) -> "v1";
5375
 
ver_to_trap_str([2]) -> "v2";
5376
 
% default is to use the latest snmp version
5377
 
ver_to_trap_str([1,2]) -> "v2".
5378
 
 
5379
 
 
5380
 
 
5381
 
write_view_conf(Dir) -> 
5382
 
    {ok, Fid} = file:open(a(Dir,"view.conf"),write),
5383
 
    ok = io:format(Fid, "{2, [1,3,6], included, null}.~n", []),
5384
 
    ok = io:format(Fid, "{2, ~w, excluded, null}.~n", [?tDescr_instance]),
5385
 
    file:close(Fid).
5386
 
 
5387
 
a(A,B) -> lists:append(A,B).
5388
 
 
5389
 
 
5390
 
%
5391
 
% SNMP compiler tests
5392
 
%
5393
 
 
5394
 
write_mib(Filename,Desc) ->
5395
 
    Binary = "Test DEFINITIONS ::= BEGIN
5396
 
 
5397
 
IMPORTS
5398
 
    MODULE-IDENTITY, OBJECT-TYPE, 
5399
 
    snmpModules, mib-2
5400
 
        FROM SNMPv2-SMI ;
5401
 
 
5402
 
snmpMIB MODULE-IDENTITY
5403
 
    LAST-UPDATED \"9511090000Z\"
5404
 
    ORGANIZATION \"\" 
5405
 
    CONTACT-INFO \"\"
5406
 
    DESCRIPTION
5407
 
    ::= { snmpModules 1 }
5408
 
 
5409
 
 
5410
 
test   OBJECT IDENTIFIER ::= { mib-2 15 }
5411
 
 
5412
 
bits1 OBJECT-TYPE
5413
 
    SYNTAX      BITS { b0(0), b1(1), b2(2) }
5414
 
    MAX-ACCESS  read-write
5415
 
    STATUS      current
5416
 
    DESCRIPTION \"" ++ Desc ++ "\"
5417
 
    ::= { test 1 }
5418
 
 
5419
 
END",
5420
 
    Message = file:write_file(Filename ,Binary),
5421
 
    case Message of
5422
 
        ok -> ok;
5423
 
        {error, Reason} ->
5424
 
           exit({failed_writing_mib,Reason})
5425
 
    end.
5426
 
 
5427
 
read_mib(Filename) ->
5428
 
    case file:read_file(Filename) of
5429
 
        {ok,Bin} -> 
5430
 
            binary_to_term(Bin);     
5431
 
        {error,Reason} ->
5432
 
            exit({failed_reading_mib,Filename,Reason})
5433
 
    end.
5434
 
 
5435
 
check_mib([],_,_) ->
5436
 
    not_found;
5437
 
check_mib([#me{oid = Oid, description = Description}| T], Oid, Testdata ) ->
5438
 
    check_desc(Description, Testdata);
5439
 
check_mib([H|T], Oid, Testdata ) ->
5440
 
    check_mib(T, Oid, Testdata ).
5441
 
    
5442
 
check_desc(Desc, Desc) ->
5443
 
    ok;
5444
 
check_desc(Desc1, Desc2) ->
5445
 
    exit({'description not equal', Desc1, Desc2}).
5446
 
 
5447
 
comp_description(suite) -> [];
5448
 
comp_description(Config) when list(Config) ->
5449
 
    Dir = ?config(agent_dir, Config),
5450
 
    Filename = Dir ++ "/test",
5451
 
    Desctext = "This is a test description",
5452
 
    Oid = [1,3,6,1,2,1,15,1],
5453
 
    write_mib(Filename ++".mib",Desctext),
5454
 
    ?line {ok,_} = snmp:c(Filename ++ ".mib", [{outdir,      Dir},
5455
 
                                               {group_check, false},
5456
 
                                               {warnings,    false},
5457
 
                                               {description, false}]),
5458
 
    Term = read_mib(Filename ++ ".bin"),
5459
 
    check_mib(Term#mib.mes, Oid,  undefined),
5460
 
    ?line {ok,_} = snmp:c(Filename ++ ".mib", [{outdir,      Dir},
5461
 
                                               {group_check, false},
5462
 
                                               {warnings,    false},
5463
 
                                               {description, true}]),
5464
 
    Term2 = read_mib(Filename ++ ".bin"),
5465
 
    check_mib(Term2#mib.mes, Oid, Desctext),
5466
 
    
5467
 
    %% Cleanup
5468
 
    file:delete(Filename ++ ".mib"),
5469
 
    file:delete(Filename ++ ".bin"),
5470
 
    ok.
5471
 
 
5472
 
write_oid_conflict_mib(Filename) ->
5473
 
    MibText = "TESTv2 DEFINITIONS ::= BEGIN
5474
 
 
5475
 
IMPORTS
5476
 
    MODULE-IDENTITY, OBJECT-TYPE, NOTIFICATION-TYPE,
5477
 
    Integer32, snmpModules ,experimental
5478
 
        FROM SNMPv2-SMI
5479
 
    MODULE-COMPLIANCE, OBJECT-GROUP, NOTIFICATION-GROUP
5480
 
        FROM SNMPv2-CONF
5481
 
    DisplayString 
5482
 
        FROM SNMPv2-TC
5483
 
    RowStatus
5484
 
        FROM STANDARD-MIB;
5485
 
 
5486
 
 
5487
 
exampleModule MODULE-IDENTITY
5488
 
        LAST-UPDATED \"0005290000Z\"
5489
 
        ORGANIZATION \"Erlang\"
5490
 
        CONTACT-INFO \" test mib
5491
 
                        Ericsson Utvecklings AB
5492
 
                        Open System
5493
 
                        Box 1505
5494
 
                        SE-125 25 �LVSJ�\"
5495
 
 
5496
 
        DESCRIPTION 
5497
 
                \" Objects for management \"
5498
 
        REVISION   \"0005290000Z\"
5499
 
        DESCRIPTION 
5500
 
                \"The initial version\"
5501
 
        ::= { snmpModules 1 }
5502
 
 
5503
 
example1 OBJECT IDENTIFIER ::= { experimental 7}
5504
 
 
5505
 
 
5506
 
         myName OBJECT-TYPE
5507
 
              SYNTAX      DisplayString
5508
 
              MAX-ACCESS  read-write
5509
 
              STATUS  current
5510
 
              DESCRIPTION
5511
 
                      \"My own name\"
5512
 
              ::= { example1 1 }
5513
 
 
5514
 
         myNotification NOTIFICATION-TYPE
5515
 
              STATUS      current 
5516
 
              DESCRIPTION 
5517
 
                \"test trap.\" 
5518
 
              ::= { example1 1 }
5519
 
 
5520
 
          friendsTable OBJECT-TYPE
5521
 
              SYNTAX  SEQUENCE OF FriendsEntry
5522
 
              MAX-ACCESS  not-accessible
5523
 
              STATUS   current
5524
 
              DESCRIPTION
5525
 
                      \"A list of friends.\"
5526
 
              ::= { example1 4 }
5527
 
 
5528
 
          friendsEntry OBJECT-TYPE
5529
 
              SYNTAX  FriendsEntry
5530
 
              MAX-ACCESS  not-accessible
5531
 
              STATUS  current
5532
 
              DESCRIPTION
5533
 
                      \"\"
5534
 
              INDEX   { fIndex }
5535
 
              ::= { friendsTable 1 }
5536
 
 
5537
 
          FriendsEntry ::= SEQUENCE {
5538
 
                fIndex   INTEGER,
5539
 
                fName    DisplayString,
5540
 
                fAddress DisplayString,
5541
 
                fStatus  RowStatus
5542
 
                }
5543
 
 
5544
 
          fIndex OBJECT-TYPE
5545
 
              SYNTAX      INTEGER
5546
 
              MAX-ACCESS  read-only
5547
 
              STATUS      current
5548
 
               DESCRIPTION
5549
 
                      \"number of friend\"
5550
 
              ::= { friendsEntry 1 }
5551
 
 
5552
 
          fName OBJECT-TYPE
5553
 
              SYNTAX      DisplayString (SIZE (0..255))
5554
 
              MAX-ACCESS  read-write
5555
 
              STATUS      current
5556
 
              DESCRIPTION
5557
 
                      \"Name of  a friend\"
5558
 
              ::= { friendsEntry 2 }
5559
 
 
5560
 
          fAddress OBJECT-TYPE
5561
 
              SYNTAX      DisplayString (SIZE (0..255))
5562
 
              MAX-ACCESS  read-write
5563
 
              STATUS      current
5564
 
              DESCRIPTION
5565
 
                      \"Address of a friend\"
5566
 
              ::= { friendsEntry 3 }
5567
 
 
5568
 
           fStatus OBJECT-TYPE
5569
 
              SYNTAX      RowStatus
5570
 
              MAX-ACCESS  read-write
5571
 
              STATUS      current
5572
 
              DESCRIPTION
5573
 
                      \"The status of this conceptual row.\"
5574
 
              ::= { friendsEntry 4 }
5575
 
 
5576
 
 
5577
 
friendGroup OBJECT-GROUP
5578
 
        OBJECTS { myName, fIndex, fName,fAddress, fStatus } 
5579
 
        STATUS current
5580
 
        DESCRIPTION \" A object group\"
5581
 
        ::= { example1 2 }
5582
 
 
5583
 
myNotificationGroup NOTIFICATION-GROUP 
5584
 
      NOTIFICATIONS { myNotification } 
5585
 
      STATUS     current 
5586
 
      DESCRIPTION 
5587
 
        \"Test notification group\" 
5588
 
      ::= { example1 3 }
5589
 
END",
5590
 
 
5591
 
    file:write_file(Filename, MibText).
5592
 
 
5593
 
oid_conflicts(suite) -> [];
5594
 
oid_conflicts(Config) when list(Config) ->
5595
 
    Dir = ?config(agent_dir, Config),
5596
 
    ?DBG("oid_conflicts -> Dir: ~p",[Dir]),
5597
 
    Mib = Dir ++ "TESTv2.mib",
5598
 
    ?DBG("oid_conflicts -> write test mib",[]),
5599
 
    ?line ok = write_oid_conflict_mib(Mib),
5600
 
    ?DBG("oid_conflicts -> compile test mib",[]),
5601
 
    ?line {error,compilation_failed} = 
5602
 
        snmp:c(Mib,[{outdir, Dir},{verbosity,trace}]),
5603
 
    ok.
5604
 
 
5605
 
 
5606
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
5607
 
 
5608
 
copy_file(From, To) ->
5609
 
    {ok, Bin} = file:read_file(From),
5610
 
    ok = file:write_file(To, Bin).
5611
 
 
5612
 
 
5613
 
 
5614
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
5615
 
 
5616
 
display_memory_usage() ->
5617
 
    Info       = snmp:info(snmp_master_agent),
5618
 
    TreeSize   = lists_key1search(tree_size_bytes,  Info),
5619
 
    ProcMem    = lists_key1search(process_memory,   Info),
5620
 
    MibDbSize  = lists_key1search([db_memory,mib],  Info),
5621
 
    NodeDbSize = lists_key1search([db_memory,node], Info),
5622
 
    TreeDbSize = lists_key1search([db_memory,tree], Info),
5623
 
    ?INF("Memory usage: "
5624
 
        "~n   Tree size:           ~p"
5625
 
        "~n   Process memory size: ~p"
5626
 
        "~n   Mib db size:         ~p"
5627
 
        "~n   Node db size:        ~p"
5628
 
        "~n   Tree db size:        ~p", 
5629
 
    [TreeSize, ProcMem, MibDbSize, NodeDbSize, TreeDbSize]).
5630
 
    
5631
 
lists_key1search([], Res) ->
5632
 
    Res;
5633
 
lists_key1search([Key|Keys], List) when atom(Key), list(List) ->
5634
 
    case lists:keysearch(Key, 1, List) of
5635
 
        {value, {Key, Val}} ->
5636
 
            lists_key1search(Keys, Val);
5637
 
        false ->
5638
 
            undefined
5639
 
    end;
5640
 
lists_key1search(Key, List) when atom(Key) ->
5641
 
    case lists:keysearch(Key, 1, List) of
5642
 
        {value, {Key, Val}} ->
5643
 
            Val;
5644
 
        false ->
5645
 
            undefined
5646
 
    end.