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

« back to all changes in this revision

Viewing changes to lib/snmp/test/snmp_compiler_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: Test the snmp mib compiler
 
20
%% 
 
21
%% Run test: ts:run(snmp, snmp_compiler_test, [batch]).
 
22
%% 
 
23
%%----------------------------------------------------------------------
 
24
-module(snmp_compiler_test).
 
25
 
 
26
%%----------------------------------------------------------------------
 
27
%% Include files
 
28
%%----------------------------------------------------------------------
 
29
-include("test_server.hrl").
 
30
-include("snmp_test_lib.hrl").
 
31
-include_lib("snmp/include/snmp_types.hrl").
 
32
 
 
33
 
 
34
%%----------------------------------------------------------------------
 
35
%% External exports
 
36
%%----------------------------------------------------------------------
 
37
-export([
 
38
         all/1, 
 
39
         init_per_testcase/2, fin_per_testcase/2,
 
40
 
 
41
         description/1,
 
42
         oid_conflicts/1,
 
43
         imports/1,
 
44
         module_identity/1,
 
45
 
 
46
         tickets/1,
 
47
         otp_6150/1
 
48
 
 
49
        ]).
 
50
 
 
51
%%----------------------------------------------------------------------
 
52
%% Internal exports
 
53
%%----------------------------------------------------------------------
 
54
-export([
 
55
        ]).
 
56
 
 
57
%%----------------------------------------------------------------------
 
58
%% Macros
 
59
%%----------------------------------------------------------------------
 
60
 
 
61
%%----------------------------------------------------------------------
 
62
%% Records
 
63
%%----------------------------------------------------------------------
 
64
 
 
65
%%======================================================================
 
66
%% External functions
 
67
%%======================================================================
 
68
 
 
69
init_per_testcase(_Case, Config) when list(Config) ->
 
70
    Dir = ?config(priv_dir, Config),
 
71
    DataDir = ?config(data_dir, Config),
 
72
    [_|RL] = lists:reverse(filename:split(DataDir)),
 
73
    MibDir = join(lists:reverse(["snmp_test_data"|RL])),
 
74
    CompDir = join(Dir, "comp_dir/"),
 
75
    ?line ok = file:make_dir(CompDir),
 
76
    [{comp_dir, CompDir},{mib_dir, MibDir}|Config].
 
77
 
 
78
fin_per_testcase(_Case, Config) when list(Config) ->
 
79
    CompDir = ?config(comp_dir, Config),
 
80
    ?line ok = ?DEL_DIR(CompDir),
 
81
    lists:keydelete(comp_dir, 1, Config).
 
82
 
 
83
 
 
84
%%======================================================================
 
85
%% Test case definitions
 
86
%%======================================================================
 
87
 
 
88
all(suite) ->
 
89
    [
 
90
     description,
 
91
     oid_conflicts,
 
92
     imports,
 
93
     module_identity,
 
94
     tickets
 
95
    ].
 
96
 
 
97
tickets(suite) ->
 
98
    [
 
99
     otp_6150
 
100
    ].
 
101
 
 
102
 
 
103
%%======================================================================
 
104
%% Test functions
 
105
%%======================================================================
 
106
 
 
107
description(suite) -> [];
 
108
description(Config) when list(Config) ->
 
109
    put(tname,desc),
 
110
    p("starting with Config: ~p~n", [Config]),
 
111
 
 
112
    Dir = ?config(comp_dir, Config),
 
113
    Filename   = join(Dir,"test"),
 
114
    MibSrcName = Filename ++ ".mib",
 
115
    MibBinName = Filename ++ ".bin",
 
116
    Desctext   = "This is a test description",
 
117
    Oid = [1,3,6,1,2,1,15,1],
 
118
    write_mib(MibSrcName,Desctext),
 
119
    ?line {ok,_} = snmpc:compile(MibSrcName, [{outdir,      Dir},
 
120
                                              {group_check, false},
 
121
                                              {warnings,    false},
 
122
                                              {description, false}]),
 
123
    MIB1 = read_mib(MibBinName),
 
124
    %% io:format("description -> MIB1: ~n~p~n", [MIB1]),
 
125
    check_mib(MIB1#mib.mes, Oid,  undefined),
 
126
    ?line {ok,_} = snmpc:compile(MibSrcName, [{outdir,      Dir},
 
127
                                              {group_check, false},
 
128
                                              {warnings,    false},
 
129
                                              {description, true}]),
 
130
    MIB2 = read_mib(MibBinName),
 
131
    %% io:format("description -> MIB2: ~n~p~n", [MIB2]),
 
132
    check_mib(MIB2#mib.mes, Oid, Desctext),
 
133
 
 
134
    %% Cleanup
 
135
    file:delete(MibSrcName),
 
136
    file:delete(MibBinName),
 
137
    ok.
 
138
 
 
139
 
 
140
oid_conflicts(suite) -> [];
 
141
oid_conflicts(Config) when list(Config) ->
 
142
    put(tname,oid_conflicts),
 
143
    p("starting with Config: ~p~n", [Config]),
 
144
 
 
145
    Dir = ?config(comp_dir, Config),
 
146
    Mib = join(Dir,"TESTv2.mib"),
 
147
    ?line ok = write_oid_conflict_mib(Mib),
 
148
    ?line {error,compilation_failed} = 
 
149
        snmpc:compile(Mib,[{outdir, Dir},{verbosity,trace}]),
 
150
    ok.
 
151
 
 
152
 
 
153
imports(suite) ->
 
154
    [];
 
155
imports(Config) when list(Config) ->
 
156
    ?SKIP(not_yet_implemented).
 
157
 
 
158
 
 
159
module_identity(suite) ->
 
160
    [];
 
161
module_identity(Config) when list(Config) ->
 
162
    ?SKIP(not_yet_implemented).
 
163
 
 
164
 
 
165
otp_6150(suite) ->
 
166
    [];
 
167
otp_6150(Config) when is_list(Config) ->
 
168
    put(tname,otp_6150),
 
169
    p("starting with Config: ~p~n", [Config]),
 
170
 
 
171
    Dir     = ?config(comp_dir, Config),
 
172
    MibDir  = ?config(mib_dir,  Config),
 
173
    MibFile = join(MibDir, "ERICSSON-TOP-MIB.mib"),
 
174
    ?line {ok, Mib} = snmpc:compile(MibFile, [{outdir, Dir}, {verbosity, trace}]),
 
175
    io:format("otp_6150 -> Mib: ~n~p~n", [Mib]),
 
176
    ok.
 
177
 
 
178
 
 
179
%%======================================================================
 
180
%% Internal functions
 
181
%%======================================================================
 
182
 
 
183
write_oid_conflict_mib(Filename) ->
 
184
    MibText = "TESTv2 DEFINITIONS ::= BEGIN
 
185
 
 
186
IMPORTS
 
187
        MODULE-IDENTITY, OBJECT-TYPE, NOTIFICATION-TYPE,
 
188
    Integer32, snmpModules ,experimental
 
189
        FROM SNMPv2-SMI
 
190
        MODULE-COMPLIANCE, OBJECT-GROUP, NOTIFICATION-GROUP
 
191
        FROM SNMPv2-CONF
 
192
        DisplayString 
 
193
        FROM SNMPv2-TC
 
194
        RowStatus
 
195
        FROM STANDARD-MIB;
 
196
 
 
197
 
 
198
exampleModule MODULE-IDENTITY
 
199
LAST-UPDATED \"0005290000Z\"
 
200
        ORGANIZATION \"Erlang\"
 
201
        CONTACT-INFO \" test mib
 
202
                        Ericsson Utvecklings AB
 
203
Open System
 
204
Box 1505
 
205
SE-125 25 �LVSJ�\"
 
206
 
 
207
DESCRIPTION 
 
208
\" Objects for management \"
 
209
        REVISION   \"0005290000Z\"
 
210
        DESCRIPTION 
 
211
\"The initial version\"
 
212
        ::= { snmpModules 1 }
 
213
 
 
214
example1 OBJECT IDENTIFIER ::= { experimental 7}
 
215
-- example2 OBJECT IDENTIFIER ::= { experimental 7}
 
216
 
 
217
 
 
218
myName OBJECT-TYPE
 
219
SYNTAX      DisplayString
 
220
MAX-ACCESS  read-write
 
221
STATUS  current
 
222
DESCRIPTION
 
223
\"My own name\"
 
224
              ::= { example1 1 }
 
225
 
 
226
myNotification NOTIFICATION-TYPE
 
227
STATUS      current 
 
228
DESCRIPTION 
 
229
\"test trap.\" 
 
230
              ::= { example1 1 }
 
231
 
 
232
friendsTable OBJECT-TYPE
 
233
SYNTAX  SEQUENCE OF FriendsEntry
 
234
MAX-ACCESS  not-accessible
 
235
STATUS   current
 
236
DESCRIPTION
 
237
\"A list of friends.\"
 
238
              ::= { example1 4 }
 
239
 
 
240
friendsEntry OBJECT-TYPE
 
241
SYNTAX  FriendsEntry
 
242
MAX-ACCESS  not-accessible
 
243
STATUS  current
 
244
DESCRIPTION
 
245
\"\"
 
246
              INDEX   { fIndex }
 
247
::= { friendsTable 1 }
 
248
 
 
249
FriendsEntry ::= SEQUENCE {
 
250
                   fIndex   INTEGER,
 
251
                   fName    DisplayString,
 
252
                   fAddress DisplayString,
 
253
                   fStatus  RowStatus
 
254
                  }
 
255
 
 
256
fIndex OBJECT-TYPE
 
257
SYNTAX      INTEGER
 
258
MAX-ACCESS  read-only
 
259
STATUS      current
 
260
DESCRIPTION
 
261
\"number of friend\"
 
262
              ::= { friendsEntry 1 }
 
263
 
 
264
fName OBJECT-TYPE
 
265
SYNTAX      DisplayString (SIZE (0..255))
 
266
MAX-ACCESS  read-write
 
267
STATUS      current
 
268
DESCRIPTION
 
269
\"Name of  a friend\"
 
270
              ::= { friendsEntry 2 }
 
271
 
 
272
fAddress OBJECT-TYPE
 
273
SYNTAX      DisplayString (SIZE (0..255))
 
274
MAX-ACCESS  read-write
 
275
STATUS      current
 
276
DESCRIPTION
 
277
\"Address of a friend\"
 
278
              ::= { friendsEntry 3 }
 
279
 
 
280
fStatus OBJECT-TYPE
 
281
SYNTAX      RowStatus
 
282
MAX-ACCESS  read-write
 
283
STATUS      current
 
284
DESCRIPTION
 
285
\"The status of this conceptual row.\"
 
286
              ::= { friendsEntry 4 }
 
287
 
 
288
-- myName2 OBJECT IDENTIFIER ::= { example1 1 }
 
289
 
 
290
friendGroup OBJECT-GROUP
 
291
OBJECTS { myName, fIndex, fName,fAddress, fStatus } 
 
292
STATUS current
 
293
DESCRIPTION \" A object group\"
 
294
        ::= { example1 2 }
 
295
 
 
296
myNotificationGroup NOTIFICATION-GROUP 
 
297
NOTIFICATIONS { myNotification } 
 
298
STATUS     current 
 
299
DESCRIPTION 
 
300
\"Test notification group\" 
 
301
      ::= { example1 3 }
 
302
END",
 
303
 
 
304
    file:write_file(Filename, MibText).
 
305
 
 
306
 
 
307
write_mib(Filename,Desc) ->
 
308
    Binary = "Test DEFINITIONS ::= BEGIN
 
309
 
 
310
IMPORTS
 
311
        MODULE-IDENTITY, OBJECT-TYPE, 
 
312
    snmpModules, mib-2
 
313
        FROM SNMPv2-SMI ;
 
314
 
 
315
snmpMIB MODULE-IDENTITY
 
316
LAST-UPDATED \"9511090000Z\"
 
317
    ORGANIZATION \"\" 
 
318
    CONTACT-INFO \"\"
 
319
    DESCRIPTION
 
320
::= { snmpModules 1 }
 
321
 
 
322
 
 
323
test   OBJECT IDENTIFIER ::= { mib-2 15 }
 
324
 
 
325
bits1 OBJECT-TYPE
 
326
SYNTAX      BITS { b0(0), b1(1), b2(2) }
 
327
MAX-ACCESS  read-write
 
328
STATUS      current
 
329
DESCRIPTION     \"" ++ Desc ++ "\"
 
330
    ::= { test 1 }
 
331
 
 
332
END",
 
333
    Message = file:write_file(Filename ,Binary),
 
334
case Message of
 
335
    ok -> ok;
 
336
    {error, Reason} ->
 
337
        exit({failed_writing_mib,Reason})
 
338
end.
 
339
 
 
340
 
 
341
read_mib(Filename) ->
 
342
    case file:read_file(Filename) of
 
343
        {ok,Bin} -> 
 
344
            binary_to_term(Bin);     
 
345
        {error,Reason} ->
 
346
            exit({failed_reading_mib,Filename,Reason})
 
347
    end.
 
348
 
 
349
check_mib([],_,_) ->
 
350
    not_found;
 
351
check_mib([#me{oid = Oid, description = Description}| _T], Oid, Testdata) ->
 
352
    check_desc(Description, Testdata);
 
353
check_mib([_H|T], Oid, Testdata ) ->
 
354
    check_mib(T, Oid, Testdata ).
 
355
 
 
356
check_desc(Desc, Desc) ->
 
357
    ok;
 
358
check_desc(Desc1, Desc2) ->
 
359
    exit({'description not equal', Desc1, Desc2}).
 
360
 
 
361
 
 
362
join(Comp) ->
 
363
    filename:join(Comp).
 
364
 
 
365
join(A,B) ->
 
366
    filename:join(A,B).
 
367
 
 
368
 
 
369
%% ------
 
370
 
 
371
%% p(F) ->
 
372
%%     p(F, []).
 
373
 
 
374
p(F, A) ->
 
375
    p(get(tname), F, A).
 
376
 
 
377
p(TName, F, A) ->
 
378
    io:format("*** [~w][~s] ***"
 
379
              "~n" ++ F ++ "~n", [TName,format_timestamp(now())|A]).
 
380
 
 
381
format_timestamp({_N1, _N2, N3}   = Now) ->
 
382
    {Date, Time}   = calendar:now_to_datetime(Now),
 
383
    {YYYY,MM,DD}   = Date,
 
384
    {Hour,Min,Sec} = Time,
 
385
    FormatDate =
 
386
        io_lib:format("~.4w:~.2.0w:~.2.0w ~.2.0w:~.2.0w:~.2.0w 4~w",
 
387
                      [YYYY,MM,DD,Hour,Min,Sec,round(N3/1000)]),
 
388
    lists:flatten(FormatDate).
 
389