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

« back to all changes in this revision

Viewing changes to lib/snmp/test/snmp_conf_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
%%----------------------------------------------------------------------
 
19
%% Purpose:
 
20
%%----------------------------------------------------------------------
 
21
-module(snmp_conf_test).
 
22
 
 
23
%%----------------------------------------------------------------------
 
24
%% Include files
 
25
%%----------------------------------------------------------------------
 
26
-include("test_server.hrl").
 
27
-include("snmp_test_lib.hrl").
 
28
 
 
29
-include_lib("snmp/include/STANDARD-MIB.hrl").
 
30
-include_lib("snmp/include/OTP-SNMPEA-MIB.hrl").
 
31
 
 
32
 
 
33
%%----------------------------------------------------------------------
 
34
%% External exports
 
35
%%----------------------------------------------------------------------
 
36
-export([
 
37
         all/1, 
 
38
         init_per_testcase/2, fin_per_testcase/2,
 
39
 
 
40
         check_mandatory/1,
 
41
         check_integer1/1,
 
42
         check_integer2/1,
 
43
         check_string1/1,
 
44
         check_string2/1,
 
45
         check_atom/1,
 
46
         check_ip/1,
 
47
         check_taddress/1,
 
48
         check_packet_size/1,
 
49
         check_oid/1,
 
50
         check_sec_model1/1,
 
51
         check_sec_model2/1,
 
52
         check_sec_level/1,
 
53
         check_timer/1,
 
54
 
 
55
         read/1,
 
56
         read_files/1
 
57
        ]).
 
58
 
 
59
%%----------------------------------------------------------------------
 
60
%% Internal exports
 
61
%%----------------------------------------------------------------------
 
62
-export([
 
63
        ]).
 
64
 
 
65
%%----------------------------------------------------------------------
 
66
%% Macros
 
67
%%----------------------------------------------------------------------
 
68
 
 
69
%%----------------------------------------------------------------------
 
70
%% Records
 
71
%%----------------------------------------------------------------------
 
72
 
 
73
%%======================================================================
 
74
%% External functions
 
75
%%======================================================================
 
76
 
 
77
init_per_testcase(_Case, Config) when list(Config) ->
 
78
    Config.
 
79
 
 
80
fin_per_testcase(_Case, Config) when list(Config) ->
 
81
    Config.
 
82
 
 
83
%%======================================================================
 
84
%% Test case definitions
 
85
%%======================================================================
 
86
all(suite) ->
 
87
    [
 
88
     check_mandatory,
 
89
     check_integer1,
 
90
     check_integer2,
 
91
     check_string1,
 
92
     check_string2,
 
93
     check_atom,
 
94
     check_ip,
 
95
     check_taddress,
 
96
     check_packet_size,
 
97
     check_oid,
 
98
     check_sec_model1,
 
99
     check_sec_model2,
 
100
     check_sec_level,
 
101
     check_timer,
 
102
 
 
103
     read,
 
104
     read_files
 
105
    ].
 
106
 
 
107
 
 
108
%%======================================================================
 
109
%% Test functions
 
110
%%======================================================================
 
111
 
 
112
check_mandatory(suite) -> [];
 
113
check_mandatory(Config) when list(Config) ->
 
114
    ?P(check_mandatory),
 
115
    %% d("check_mandatory -> entry"),
 
116
    A1 = [{a, hej}, {b, hopp}, {c, 10}, {d, 10101}, {f, 10.88}],
 
117
    B1 = [{a, {value, hejsan}}, 
 
118
          {b, mandatory}, 
 
119
          {d, {value, 20202}}, 
 
120
          {e, {value, "kalle"}}],
 
121
    ?line {ok, L1} = verify_mandatory(A1, B1),
 
122
    ?DBG("check_mandatory -> L1: ~p", [L1]),
 
123
    A2 = [{a, hej}, {c, 10}, {d, 10101}, {f, 10.88}],
 
124
    B2 = [{a, {value, hejsan}}, 
 
125
          {b, mandatory}, 
 
126
          {d, {value, 20202}}, 
 
127
          {e, {value, "kalle"}}],
 
128
    ?line ok = verify_not_mandatory(A2, B2),
 
129
    ok.
 
130
 
 
131
verify_mandatory(A, B) ->
 
132
    case (catch snmp_conf:check_mandatory(A, B)) of
 
133
        {'EXIT', Reason} ->
 
134
            ?FAIL({mandatory_fail, A, B, Reason});
 
135
        {ok, A} ->
 
136
            ?FAIL({mandatory_not_updated, A, B});
 
137
        {ok, L} when A /= L ->
 
138
            verify_mandatory2(B, L)
 
139
    end.
 
140
 
 
141
verify_mandatory2([], L) ->
 
142
    {ok, L};
 
143
verify_mandatory2([{Key, _}|T], L) ->
 
144
    case lists:keysearch(Key, 1, L) of
 
145
        false ->
 
146
            ?FAIL({missing_key, Key, L});
 
147
        {value, _} ->
 
148
            verify_mandatory2(T, L)
 
149
    end.
 
150
 
 
151
verify_not_mandatory(A, B) ->
 
152
    case (catch snmp_conf:check_mandatory(A, B)) of
 
153
        {error, _Reason} ->
 
154
            ok;
 
155
        Else ->
 
156
            ?FAIL({mandatory_not_fail, Else})
 
157
    end.
 
158
 
 
159
 
 
160
%%======================================================================
 
161
 
 
162
check_integer1(suite) -> [];
 
163
check_integer1(Config) when list(Config) ->
 
164
    ?P(check_integer1),
 
165
    ?line ok = verify_int(0),
 
166
    ?line ok = verify_int(16#FF),
 
167
    ?line ok = verify_int(16#FFFF),
 
168
    ?line ok = verify_int(16#FFFFFFFF),
 
169
    ?line ok = verify_int(-1),
 
170
    ?line ok = verify_int(-333),
 
171
 
 
172
    ?line ok = verify_not_int("kalle & hobbe"),
 
173
    ?line ok = verify_not_int(kalle_och_hobbe),
 
174
    ?line ok = verify_not_int(1.5),
 
175
 
 
176
    ok.
 
177
 
 
178
verify_int(Val) ->
 
179
    case (catch snmp_conf:check_integer(Val)) of
 
180
        {error, Reason} ->
 
181
            ?FAIL({verify_int, Val, Reason});
 
182
        ok ->
 
183
            ok
 
184
    end.
 
185
 
 
186
verify_not_int(Val) ->
 
187
    case (catch snmp_conf:check_integer(Val)) of
 
188
        ok ->
 
189
            ?FAIL({verify_int, Val});
 
190
        {error, _Reason} ->
 
191
            ok
 
192
    end.
 
193
 
 
194
%%======================================================================
 
195
 
 
196
check_integer2(suite) -> [];
 
197
check_integer2(Config) when list(Config) ->
 
198
    ?P(check_integer2),
 
199
 
 
200
    ?line ok = verify_int(0,      any),
 
201
    ?line ok = verify_int(-22222, any),
 
202
    ?line ok = verify_int(33333,  any),
 
203
    ?line ok = verify_int(1,      pos),
 
204
    ?line ok = verify_int(9999,   pos),
 
205
    ?line ok = verify_int(-1,     neg),
 
206
    ?line ok = verify_int(-9999,  neg),
 
207
    ?line ok = verify_int(1,      {gt, 0}),
 
208
    ?line ok = verify_int(88888,  {gt, -255}),
 
209
    ?line ok = verify_int(88888,  {gte, -255}),
 
210
    ?line ok = verify_int(88888,  {gte, 88888}),
 
211
    ?line ok = verify_int(88888,  {lt,  88889}),
 
212
    ?line ok = verify_int(88888,  {lte, 88888}),
 
213
    ?line ok = verify_int(88888,  {eq,  88888}),
 
214
    ?line ok = verify_int(88888,  {range, 88887,88889}),
 
215
 
 
216
    ?line ok = verify_not_int("kalle & hobbe", any),
 
217
    ?line ok = verify_not_int(kalle_och_hobbe, any),
 
218
    ?line ok = verify_not_int(1.5,             any),
 
219
 
 
220
    ?line ok = verify_not_int(0,      pos),
 
221
    ?line ok = verify_not_int(-22222, pos),
 
222
    ?line ok = verify_not_int(33333,  neg),
 
223
    ?line ok = verify_not_int(0,      {gt,  0}),
 
224
    ?line ok = verify_not_int(33333,  {gt,  99999}),
 
225
    ?line ok = verify_not_int(33333,  {gt,  33333}),
 
226
    ?line ok = verify_not_int(33333,  {gte, 33334}),
 
227
    ?line ok = verify_not_int(33333,  {lt,  33333}),
 
228
    ?line ok = verify_not_int(33333,  {lte, 33332}),
 
229
    ?line ok = verify_not_int(33333,  {eq,  33332}),
 
230
    ?line ok = verify_not_int(33333,  {eq,  -33333}),
 
231
    ?line ok = verify_not_int(33333,  {range, 33334, 33338}),
 
232
    ?line ok = verify_not_int(33339,  {range, 33334, 33338}),
 
233
    ?line ok = verify_not_int(33333,  {gt,  kalle}),
 
234
    ?line ok = verify_not_int(33333,  {gt,  1.55}),
 
235
    ?line ok = verify_not_int(33333,  {gte, "hejsan"}),
 
236
    ?line ok = verify_not_int(33333,  {lt,  hobbe}),
 
237
    ?line ok = verify_not_int(33333,  {lte, 1.7666}),
 
238
    ?line ok = verify_not_int(33333,  {eq,  33333.0}),
 
239
    ?line ok = verify_not_int(33333,  {eq,  -33333.0}),
 
240
    ?line ok = verify_not_int(33333,  {range, kalle, 33338}),
 
241
    ?line ok = verify_not_int(33339,  {range, 33334, kalle}),
 
242
    ?line ok = verify_not_int(33339,  {kalle, 33334, kalle}),
 
243
 
 
244
    ok.
 
245
 
 
246
verify_int(Val, Cond) ->
 
247
    case (catch snmp_conf:check_integer(Val, Cond)) of
 
248
        {error, Reason} ->
 
249
            ?FAIL({verify_int, Val, Cond, Reason});
 
250
        ok ->
 
251
            ok
 
252
    end.
 
253
 
 
254
verify_not_int(Val, Cond) ->
 
255
    case (catch snmp_conf:check_integer(Val, Cond)) of
 
256
        ok ->
 
257
            ?FAIL({verify_int, Val, Cond});
 
258
        {error, _Reason} ->
 
259
            ok
 
260
    end.
 
261
 
 
262
%%======================================================================
 
263
 
 
264
check_string1(suite) -> [];
 
265
check_string1(Config) when list(Config) ->
 
266
    ?P(check_string1),
 
267
    ?line ok = verify_string("kalle & hobbe"),
 
268
    ?line ok = verify_not_string(kalle_hobbe),
 
269
    ?line ok = verify_not_string(1000),
 
270
    ?line ok = verify_not_string(1.0),
 
271
    ok.
 
272
 
 
273
verify_string(Val) ->
 
274
    case (catch snmp_conf:check_string(Val)) of
 
275
        {error, Reason} ->
 
276
            ?FAIL({verify_string, Val, Reason});
 
277
        ok ->
 
278
            ok
 
279
    end.
 
280
 
 
281
verify_not_string(Val) ->
 
282
    case (catch snmp_conf:check_string(Val)) of
 
283
        ok ->
 
284
            ?FAIL({verify_string, Val});
 
285
        {error, _Reason} ->
 
286
            ok
 
287
    end.
 
288
 
 
289
 
 
290
%%======================================================================
 
291
 
 
292
check_string2(suite) -> [];
 
293
check_string2(Config) when list(Config) ->
 
294
    ?P(check_string2),
 
295
    Str = "kalle & hobbe",
 
296
    ?line ok = verify_string(Str, any),
 
297
    ?line ok = verify_string(Str, {gt,  length(Str) - 1}),
 
298
    ?line ok = verify_string(Str, {gte, length(Str)}),
 
299
    ?line ok = verify_string(Str, {lt,  length(Str) + 1}),
 
300
    ?line ok = verify_string(Str, {lte, length(Str)}),
 
301
    ?line ok = verify_string(Str, length(Str)),
 
302
 
 
303
    ?line ok = verify_not_string(kalle_hobbe, any),
 
304
    ?line ok = verify_not_string(1000, any),
 
305
    ?line ok = verify_not_string(1.0, any),
 
306
    ?line ok = verify_not_string(Str, {gt,  length(Str)}),
 
307
    ?line ok = verify_not_string(Str, {gte, length(Str) + 1}),
 
308
    ?line ok = verify_not_string(Str, {lt,  length(Str)}),
 
309
    ?line ok = verify_not_string(Str, {lte, length(Str) - 1}),
 
310
    ?line ok = verify_not_string(Str, length(Str) + 1),
 
311
    ok.
 
312
 
 
313
verify_string(Val, Limit) ->
 
314
    case (catch snmp_conf:check_string(Val, Limit)) of
 
315
        {error, Reason} ->
 
316
            ?FAIL({verify_string, Val, Limit, Reason});
 
317
        ok ->
 
318
            ok
 
319
    end.
 
320
    
 
321
verify_not_string(Val, Limit) ->
 
322
    case (catch snmp_conf:check_string(Val, Limit)) of
 
323
        ok ->
 
324
            ?FAIL({verify_string, Val, Limit});
 
325
        {error, _Reason} ->
 
326
            ok
 
327
    end.
 
328
 
 
329
 
 
330
%%======================================================================
 
331
 
 
332
check_atom(suite) -> [];
 
333
check_atom(Config) when list(Config) ->
 
334
    ?P(check_atom),
 
335
    Atoms = [{kalle, "kalle"}, {hobbe, "hobbe"}, {dummy, "dummy"}],
 
336
    ?line ok = verify_atom(kalle, Atoms),
 
337
    ?line ok = verify_not_atom(anka, Atoms),
 
338
    ?line ok = verify_not_atom("kalle", Atoms),
 
339
    ?line ok = verify_not_atom(1000, Atoms),
 
340
    ok.
 
341
 
 
342
verify_atom(Val, Atoms) ->
 
343
    case (catch snmp_conf:check_atom(Val, Atoms)) of
 
344
        {error, Reason} ->
 
345
            ?FAIL({verify_atom, Val, Atoms, Reason});
 
346
        {ok, _} ->
 
347
            ok
 
348
    end.
 
349
 
 
350
verify_not_atom(Val, Atoms) ->
 
351
    case (catch snmp_conf:check_atom(Val, Atoms)) of
 
352
        ok ->
 
353
            ?FAIL({verify_atom, Val, Atoms});
 
354
        {error, _Reason} ->
 
355
            ok
 
356
    end.
 
357
 
 
358
 
 
359
%%======================================================================
 
360
 
 
361
check_ip(suite) -> [];
 
362
check_ip(Config) when list(Config) ->
 
363
    ?P(check_ip),
 
364
    ?line ok = verify_ip([1,2,3,4]),
 
365
    ?line ok = verify_not_ip([1,2,3]),
 
366
    ?line ok = verify_not_ip([1,2,3,4,5]),
 
367
    ?line ok = verify_not_ip(kalle),
 
368
    ?line ok = verify_not_ip(1000),
 
369
    ?line ok = verify_not_ip([1,2,3.0,4]),
 
370
    ?line ok = verify_not_ip([1,two,3,4]),
 
371
    ok.
 
372
 
 
373
verify_ip(Val) ->
 
374
    case (catch snmp_conf:check_ip(Val)) of
 
375
        {error, Reason} ->
 
376
            ?FAIL({verify_ip, Val, Reason});
 
377
        ok ->
 
378
            ok
 
379
    end.
 
380
 
 
381
verify_not_ip(Val) ->
 
382
    case (catch snmp_conf:check_ip(Val)) of
 
383
        ok ->
 
384
            ?FAIL({verify_ip, Val});
 
385
        {error, _Reason} ->
 
386
            ok
 
387
    end.
 
388
 
 
389
 
 
390
%%======================================================================
 
391
 
 
392
check_taddress(suite) -> [];
 
393
check_taddress(Config) when list(Config) ->
 
394
    ?P(check_taddress),
 
395
    ?line ok = verify_taddress([1,2,3,4,5,6]),
 
396
    ?line ok = verify_not_taddress([1,2,3,4,5]),
 
397
    ?line ok = verify_not_taddress([1,2,3,4,5,6,7]),
 
398
    ?line ok = verify_not_taddress(kalle),
 
399
    ?line ok = verify_not_taddress(1000),
 
400
    ?line ok = verify_not_taddress([1,2,3.0,4,5,6]),
 
401
    ?line ok = verify_not_taddress([1,two,3,4,5,6]),
 
402
    ok.
 
403
 
 
404
verify_taddress(Val) ->
 
405
    case (catch snmp_conf:check_taddress(Val)) of
 
406
        {error, Reason} ->
 
407
            ?FAIL({verify_taddress, Val, Reason});
 
408
        ok ->
 
409
            ok
 
410
    end.
 
411
 
 
412
verify_not_taddress(Val) ->
 
413
    case (catch snmp_conf:check_taddress(Val)) of
 
414
        ok ->
 
415
            ?FAIL({verify_taddress, Val});
 
416
        {error, _Reason} ->
 
417
            ok
 
418
    end.
 
419
 
 
420
 
 
421
%%======================================================================
 
422
 
 
423
check_packet_size(suite) -> [];
 
424
check_packet_size(Config) when list(Config) ->
 
425
    ?P(check_packet_size),
 
426
    Min = 484,
 
427
    Max = 2147483647,
 
428
    ?line ok = verify_packet_size(Min),
 
429
    ?line ok = verify_packet_size(2*Min),
 
430
    ?line ok = verify_packet_size(Max),
 
431
    ?line ok = verify_not_packet_size(Min-1),
 
432
    ?line ok = verify_not_packet_size(Max+1),
 
433
    ?line ok = verify_not_packet_size(kalle),
 
434
    ?line ok = verify_not_packet_size("kalle"),
 
435
    ?line ok = verify_not_packet_size(1.0),
 
436
    ?line ok = verify_not_packet_size(1.0*Max),
 
437
    ok.
 
438
 
 
439
verify_packet_size(Val) ->
 
440
    case (catch snmp_conf:check_packet_size(Val)) of
 
441
        {error, Reason} ->
 
442
            ?FAIL({verify_packet_size, Val, Reason});
 
443
        ok ->
 
444
            ok
 
445
    end.
 
446
 
 
447
verify_not_packet_size(Val) ->
 
448
    case (catch snmp_conf:check_packet_size(Val)) of
 
449
        ok ->
 
450
            ?FAIL({verify_packet_size, Val});
 
451
        {error, _Reason} ->
 
452
            ok
 
453
    end.
 
454
 
 
455
 
 
456
%%======================================================================
 
457
 
 
458
check_oid(suite) -> [];
 
459
check_oid(Config) when list(Config) ->
 
460
    ?P(check_oid),
 
461
    [_,_|Rest] = ?otpSnmpeaModule,
 
462
    ErrOid = [6,16|Rest],
 
463
    ?line ok = verify_oid(?system),
 
464
    ?line ok = verify_oid(?sysDescr_instance),
 
465
    ?line ok = verify_oid(?otpSnmpeaModule),
 
466
    ?line ok = verify_not_oid(kalle),
 
467
    ?line ok = verify_not_oid("kalle"),
 
468
    ?line ok = verify_not_oid(1000),
 
469
    ?line ok = verify_not_oid(1.0),
 
470
    ?line ok = verify_not_oid(ErrOid),
 
471
    ok.
 
472
 
 
473
verify_oid(Val) ->
 
474
    case (catch snmp_conf:check_oid(Val)) of
 
475
        {error, Reason} ->
 
476
            ?FAIL({verify_oid, Val, Reason});
 
477
        ok ->
 
478
            ok
 
479
    end.
 
480
 
 
481
verify_not_oid(Val) ->
 
482
    case (catch snmp_conf:check_oid(Val)) of
 
483
        ok ->
 
484
            ?FAIL({verify_oid, Val});
 
485
        {error, _Reason} ->
 
486
            ok
 
487
    end.
 
488
 
 
489
 
 
490
%%======================================================================
 
491
 
 
492
check_sec_model1(suite) -> [];
 
493
check_sec_model1(Config) when list(Config) ->
 
494
    ?P(check_sec_model1),
 
495
    Exclude1 = [],
 
496
    Exclude2 = [v1],
 
497
    Exclude3 = [v1,usm],
 
498
    ?line ok = verify_sec_model(any, Exclude1),
 
499
    ?line ok = verify_sec_model(v1,  Exclude1),
 
500
    ?line ok = verify_sec_model(v2c, Exclude1),
 
501
    ?line ok = verify_sec_model(usm, Exclude1),
 
502
    ?line ok = verify_sec_model(any, Exclude2),
 
503
    ?line ok = verify_sec_model(v2c, Exclude2),
 
504
    ?line ok = verify_not_sec_model(v1, Exclude2),
 
505
    ?line ok = verify_not_sec_model(v1, Exclude3),
 
506
    ?line ok = verify_not_sec_model(usm, Exclude3),
 
507
    ok.
 
508
 
 
509
verify_sec_model(Val, Exclude) ->
 
510
    case (catch snmp_conf:check_sec_model(Val, Exclude)) of
 
511
        {error, Reason} ->
 
512
            ?FAIL({verify_sec_model, Val, Reason});
 
513
        {ok, _} ->
 
514
            ok
 
515
    end.
 
516
 
 
517
verify_not_sec_model(Val, Exclude) ->
 
518
    case (catch snmp_conf:check_sec_model(Val, Exclude)) of
 
519
        {ok, Res} ->
 
520
            ?FAIL({verify_sec_model, Val, Res});
 
521
        {error, _Reason} ->
 
522
            ok
 
523
    end.
 
524
 
 
525
 
 
526
%%======================================================================
 
527
 
 
528
check_sec_model2(suite) -> [];
 
529
check_sec_model2(Config) when list(Config) ->
 
530
    ?P(check_sec_model2),
 
531
    ?line ok = verify_sec_model(v1,  v1,  []),
 
532
    ?line ok = verify_sec_model(v1,  v1,  [v2c]),
 
533
    ?line ok = verify_sec_model(v2c, v2c, []),
 
534
    ?line ok = verify_sec_model(v2c, v2c, [v1]),
 
535
    ?line ok = verify_sec_model(v3,  usm, []),
 
536
    ?line ok = verify_sec_model(v3,  usm, [v2c]),
 
537
    ?line ok = verify_not_sec_model(v1,    v2c, []),
 
538
    ?line ok = verify_not_sec_model(v1,    v3,  [v2c]),
 
539
    ?line ok = verify_not_sec_model(v1,    v1,  [v1]),
 
540
    ?line ok = verify_not_sec_model(v2c,   v1,  []),
 
541
    ?line ok = verify_not_sec_model(v2c,   v3,  [v3]),
 
542
    ?line ok = verify_not_sec_model(v2c,   v2c, [v2c]),
 
543
    ?line ok = verify_not_sec_model(v3,    v1,  []),
 
544
    ?line ok = verify_not_sec_model(v3,    v2c, [v1]),
 
545
    ?line ok = verify_not_sec_model(v3,    v3,  [v2c]),
 
546
    ?line ok = verify_not_sec_model(kalle, v3,  []),
 
547
    ?line ok = verify_not_sec_model(1000,  v3,  []),
 
548
    ?line ok = verify_not_sec_model(1.0,   v3,  []),
 
549
    ok.
 
550
 
 
551
 
 
552
verify_sec_model(M1, M2, Exclude) ->
 
553
    case (catch snmp_conf:check_sec_model(M1, M2, Exclude)) of
 
554
        {error, Reason} ->
 
555
            ?FAIL({verify_sec_model, M1, M2, Reason});
 
556
        {ok, _} ->
 
557
            ok
 
558
    end.
 
559
 
 
560
verify_not_sec_model(M1, M2, Exclude) ->
 
561
    case (catch snmp_conf:check_sec_model(M1, M2, Exclude)) of
 
562
        {ok, Res} ->
 
563
            ?FAIL({verify_sec_model, M1, M2, Res});
 
564
        {error, _Reason} ->
 
565
            ok
 
566
    end.
 
567
 
 
568
 
 
569
%%======================================================================
 
570
 
 
571
check_sec_level(suite) -> [];
 
572
check_sec_level(Config) when list(Config) ->
 
573
    ?P(check_sec_level),
 
574
    ?line ok = verify_sec_level(noAuthNoPriv),
 
575
    ?line ok = verify_sec_level(authNoPriv),
 
576
    ?line ok = verify_sec_level(authPriv),
 
577
    ?line ok = verify_not_sec_level(kalle),
 
578
    ?line ok = verify_not_sec_level("noAuthNoPriv"),
 
579
    ?line ok = verify_not_sec_level(1000),
 
580
    ?line ok = verify_not_sec_level(1.0),
 
581
    ok.
 
582
 
 
583
 
 
584
verify_sec_level(Val) ->
 
585
    case (catch snmp_conf:check_sec_level(Val)) of
 
586
        {error, Reason} ->
 
587
            ?FAIL({verify_sec_level, Val, Reason});
 
588
        {ok, _} ->
 
589
            ok;
 
590
        Error ->
 
591
            ?FAIL({verify_sec_level, Val, Error})
 
592
    end.
 
593
 
 
594
verify_not_sec_level(Val) ->
 
595
    case (catch snmp_conf:check_sec_level(Val)) of
 
596
        {ok, Res} ->
 
597
            ?FAIL({verify_sec_level, Val, Res});
 
598
        {error, _Reason} ->
 
599
            ok;
 
600
        {'EXIT', _Reason} ->
 
601
            ok
 
602
    end.
 
603
 
 
604
 
 
605
%%======================================================================
 
606
 
 
607
check_timer(suite) -> [];
 
608
check_timer(Config) when list(Config) ->
 
609
    ?P(check_timer),
 
610
    ?line ok = verify_timer(infinity),
 
611
    ?line ok = verify_timer(1),
 
612
    ?line ok = verify_timer(10),
 
613
    ?line ok = verify_timer(2147483647),
 
614
    ?line ok = verify_timer(2*2147483647),
 
615
    ?line ok = verify_timer({1,1,0,0}),
 
616
    ?line ok = verify_timer({10,10,10,10}),
 
617
    ?line ok = verify_timer({2147483647,2147483647,2147483647,2147483647}),
 
618
    ?line ok = verify_not_timer(ytinifni),
 
619
    ?line ok = verify_not_timer("ytinifni"),
 
620
    ?line ok = verify_not_timer(0),
 
621
    ?line ok = verify_not_timer(-10),
 
622
    ?line ok = verify_not_timer({0,1,0,0}),
 
623
    ?line ok = verify_not_timer({1,0,0,0}),
 
624
    ?line ok = verify_not_timer({1,1,-1,0}),
 
625
    ?line ok = verify_not_timer({1,1,0,-1}),
 
626
    ?line ok = verify_not_timer({1.0,1,0,0}),
 
627
    ?line ok = verify_not_timer({1,1.0,0,0}),
 
628
    ?line ok = verify_not_timer({1,1,1.0,0}),
 
629
    ?line ok = verify_not_timer({1,1,0,1.0}),
 
630
    ?line ok = verify_not_timer({"1",1,0,0}),
 
631
    ?line ok = verify_not_timer({1,"1",0,0}),
 
632
    ?line ok = verify_not_timer({1,1,"0",0}),
 
633
    ?line ok = verify_not_timer({1,1,0,"0"}),
 
634
    ok.
 
635
 
 
636
verify_timer(Val) ->
 
637
    case (catch snmp_conf:check_timer(Val)) of
 
638
        {error, Reason} ->
 
639
            ?FAIL({verify_timer, Val, Reason});
 
640
        {ok, _} ->
 
641
            ok
 
642
    end.
 
643
 
 
644
verify_not_timer(Val) ->
 
645
    case (catch snmp_conf:check_timer(Val)) of
 
646
        {ok, Res} ->
 
647
            ?FAIL({verify_timer, Val, Res});
 
648
        {error, _Reason} ->
 
649
            ok
 
650
    end.
 
651
 
 
652
 
 
653
%%======================================================================
 
654
 
 
655
read(suite) -> [];
 
656
read(Config) when list(Config) ->
 
657
    ?P(read),
 
658
    ?SKIP(not_implemented_yet).
 
659
 
 
660
 
 
661
%%======================================================================
 
662
 
 
663
read_files(suite) -> [];
 
664
read_files(Config) when list(Config) ->
 
665
    ?P(read_files),
 
666
    ?SKIP(not_implemented_yet).
 
667
 
 
668
 
 
669
%%======================================================================
 
670
%% Internal functions
 
671
%%======================================================================
 
672
 
 
673
% d(F) ->
 
674
%     d(F, []).
 
675
 
 
676
% d(F, A) ->
 
677
%     io:format("~w:" ++ F ++ "~n", [?MODULE|A]).