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

« back to all changes in this revision

Viewing changes to lib/snmp/src/snmp_mib_to_hrl.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_mib_to_hrl).
19
 
 
20
 
-include("snmp_types.hrl").
21
 
-include("snmp_generic.hrl").
22
 
-include_lib("stdlib/include/erl_compile.hrl").
23
 
 
24
 
%% External exports
25
 
-export([convert/1, compile/3]).
26
 
 
27
 
%%-----------------------------------------------------------------
28
 
%% Func: convert/1
29
 
%% Args: MibName = string() without extension.
30
 
%% Purpose: Produce a .hrl file with oid for tables and variables,
31
 
%%          column numbers for columns and values for enums.
32
 
%%          Writes only the first occurence of a name.  Prints a
33
 
%%          warning if a duplicate name is found.
34
 
%% Returns: ok | {error, Reason}
35
 
%% Note: The Mib must be compiled.
36
 
%%-----------------------------------------------------------------
37
 
convert(MibName) ->
38
 
    MibFile = MibName ++ ".bin",
39
 
    HrlFile = MibName ++ ".hrl",
40
 
    convert(MibFile, HrlFile, MibName, true).
41
 
 
42
 
convert(MibFile, HrlFile, MibName, Verbose) ->
43
 
    case snmp_misc:read_mib(MibFile) of
44
 
        {ok, #mib{asn1_types = Types, mes = MEs, traps = Traps}} ->
45
 
            resolve(Types, MEs, Traps, HrlFile, 
46
 
                    filename:basename(MibName), Verbose),
47
 
            ok;
48
 
        {error, Reason} ->
49
 
            {error, Reason}
50
 
    end.
51
 
 
52
 
resolve(Types, MEs, Traps, HrlFile, MibName, Verbose) ->
53
 
    case file:open(HrlFile, write) of
54
 
        {ok, Fd} ->
55
 
            insert_header(Fd),
56
 
            insert_begin(Fd, MibName),
57
 
            insert_notifs(Traps, Fd),
58
 
            insert_oids(MEs, Fd),
59
 
            insert_range(MEs, Fd),
60
 
            insert_enums(Types, MEs, Fd),
61
 
            insert_defvals(MEs, Fd),
62
 
            insert_end(Fd),
63
 
            file:close(Fd),
64
 
            case Verbose of
65
 
                true ->
66
 
                    io:format("~p written.~n", [HrlFile]);
67
 
                false ->
68
 
                    ok
69
 
            end;
70
 
        {error, Reason} ->
71
 
            {error, Reason}
72
 
    end.
73
 
 
74
 
insert_header(Fd) ->
75
 
    io:format(Fd, "%%% This file was automatically generated by "
76
 
              "snmp_mib_to_hrl v~s~n", [?version]),
77
 
    {Y,Mo,D} = date(),
78
 
    {H,Mi,S} = time(),
79
 
    io:format(Fd, "%%% Date: ~2.2.0w-~s-~w::~2.2.0w:~2.2.0w:~2.2.0w~n",
80
 
              [D,month(Mo),Y,H,Mi,S]).
81
 
 
82
 
insert_begin(Fd, MibName) ->
83
 
    io:format(Fd, 
84
 
              "-ifndef('~s').~n"
85
 
              "-define('~s', true).~n", [MibName, MibName]).
86
 
 
87
 
insert_end(Fd) ->
88
 
    io:format(Fd, "-endif.~n", []).
89
 
 
90
 
insert_oids([#me{imported = true} | T], Fd) ->
91
 
    insert_oids(T, Fd);
92
 
insert_oids([#me{entrytype = table_column, oid = Oid, aliasname = Name} | T],
93
 
            Fd) ->
94
 
    io:format(Fd, "-define(~w, ~w).~n", [Name, lists:last(Oid)]),
95
 
    insert_oids(T, Fd);
96
 
insert_oids([#me{entrytype = variable, oid = Oid, aliasname = Name} | T],
97
 
            Fd) ->
98
 
    io:format(Fd, "-define(~w, ~w).~n", [Name, Oid]),
99
 
    io:format(Fd, "-define(~w, ~w).~n", [merge_atoms(Name, instance),
100
 
                                         Oid ++ [0]]),
101
 
    insert_oids(T, Fd);
102
 
insert_oids([#me{oid = Oid, aliasname = Name} | T], Fd) ->
103
 
    io:format(Fd, "~n-define(~w, ~w).~n", [Name, Oid]),
104
 
    insert_oids(T, Fd);
105
 
insert_oids([], _Fd) -> ok.
106
 
 
107
 
 
108
 
insert_notifs(Traps, Fd) ->
109
 
    Notifs = [Notif || #notification{} = Notif <- Traps],
110
 
    case Notifs of
111
 
        [] ->
112
 
            ok;
113
 
        _ -> 
114
 
            io:format(Fd, "~n%% Notifications~n", []),
115
 
            insert_notifs2(Notifs, Fd)
116
 
    end.
117
 
    
118
 
insert_notifs2([], _Fd) ->
119
 
    ok;
120
 
insert_notifs2([#notification{trapname = Name, oid = Oid}|T], Fd) ->
121
 
    io:format(Fd, "-define(~w, ~w).~n", [Name, Oid]),
122
 
    insert_notifs2(T, Fd);
123
 
insert_notifs2([_|T], Fd) -> % Crap
124
 
    insert_notifs2(T, Fd).
125
 
 
126
 
%%-----------------------------------------------------------------
127
 
%% There's nothing strange with this function!  Enums can be
128
 
%% defined in types and in mibentries; therefore, we first call
129
 
%% ins_types and then ins_mes to insert enums from different places.
130
 
%%-----------------------------------------------------------------
131
 
insert_enums(Types, MEs, Fd) ->
132
 
    T = ins_types(Types, Fd, []),
133
 
    ins_mes(MEs, T, Fd).
134
 
 
135
 
%% Insert all types, but not the imported.  Ret the names of inserted
136
 
%% types.
137
 
ins_types([#asn1_type{aliasname = Name, 
138
 
                      assocList = Alist, 
139
 
                      imported  = false} | T],
140
 
          Fd, Res) 
141
 
  when list(Alist) ->
142
 
    case lists:keysearch(enums, 1, Alist) of
143
 
        {value, {enums, Enums}} when Enums /= [] ->
144
 
            case Enums of
145
 
                [] -> ins_types(T, Fd, Res);
146
 
                NewEnums ->
147
 
                    io:format(Fd, "~n%% Definitions from ~w~n", [Name]),
148
 
                    ins_enums(NewEnums, Name, Fd),
149
 
                    ins_types(T, Fd, [Name | Res])
150
 
            end;
151
 
        _ -> ins_types(T, Fd, Res)
152
 
    end;
153
 
ins_types([_ | T], Fd, Res)  ->
154
 
    ins_types(T, Fd, Res);
155
 
ins_types([], _Fd, Res) -> Res.
156
 
 
157
 
ins_mes([#me{entrytype = internal} | T], Types, Fd) ->
158
 
    ins_mes(T, Types, Fd);
159
 
ins_mes([#me{entrytype = table} | T], Types, Fd) ->
160
 
    ins_mes(T, Types, Fd);
161
 
ins_mes([#me{aliasname = Name, 
162
 
             asn1_type = #asn1_type{assocList = Alist,
163
 
                                    aliasname = Aname},
164
 
             imported  = false} | T],
165
 
        Types, Fd)
166
 
  when list(Alist) ->
167
 
    case lists:keysearch(enums, 1, Alist) of
168
 
        {value, {enums, Enums}} when Enums /= [] ->
169
 
            case Enums of
170
 
                [] -> ins_mes(T, Types, Fd);
171
 
                NewEnums ->
172
 
                    %% Now, check if the type is already inserted
173
 
                    %% (by ins_types).
174
 
                    case lists:member(Aname, Types) of
175
 
                        false ->
176
 
                            io:format(Fd, "~n%% Enum definitions from ~w~n",
177
 
                                      [Name]),
178
 
                            ins_enums(NewEnums, Name, Fd),
179
 
                            ins_mes(T, Types, Fd);
180
 
                        _ -> ins_mes(T, Types, Fd)
181
 
                    end
182
 
            end;
183
 
        _ -> ins_mes(T, Types, Fd)
184
 
    end;
185
 
ins_mes([_ | T], Types, Fd) ->
186
 
    ins_mes(T, Types, Fd);
187
 
ins_mes([], _Types, _Fd) -> ok.
188
 
 
189
 
ins_enums([{Name, Val} | T], Origin, Fd) ->
190
 
    EnumName = merge_atoms(Origin, Name),
191
 
    io:format(Fd, "-define(~w, ~w).~n", [EnumName, Val]),
192
 
    ins_enums(T, Origin, Fd);
193
 
ins_enums([], _Origin,  _Fd) ->
194
 
    ok.
195
 
 
196
 
%%----------------------------------------------------------------------
197
 
%% Solves the problem with placing '' around some atoms.
198
 
%% You can't write two atoms using ~w_~w.
199
 
%%----------------------------------------------------------------------
200
 
merge_atoms(TypeOrigin, Name) ->
201
 
    list_to_atom(lists:append([atom_to_list(TypeOrigin), "_",
202
 
                               atom_to_list(Name)])).
203
 
 
204
 
insert_defvals(Mes, Fd) ->
205
 
    io:format(Fd, "~n%% Default values~n", []),
206
 
    insert_defvals2(Mes, Fd),
207
 
    io:format(Fd, "~n", []).
208
 
 
209
 
insert_defvals2([#me{imported = true} | T], Fd) ->
210
 
    insert_defvals2(T, Fd);
211
 
insert_defvals2([#me{entrytype = table_column, assocList = Alist, 
212
 
                    aliasname = Name} | T],
213
 
            Fd) ->
214
 
    case snmp_misc:assq(defval, Alist) of
215
 
        {value, Val} ->
216
 
            Atom = merge_atoms('default', Name),
217
 
            io:format(Fd, "-define(~w, ~w).~n", [Atom, Val]);
218
 
        _ -> ok
219
 
    end,
220
 
    insert_defvals2(T, Fd);
221
 
insert_defvals2([#me{entrytype = variable, assocList = Alist, aliasname = Name}
222
 
                | T],
223
 
            Fd) ->
224
 
    case snmp_misc:assq(variable_info, Alist) of
225
 
        {value, VarInfo} ->
226
 
            case VarInfo#variable_info.defval of
227
 
                undefined -> ok;
228
 
                Val ->
229
 
                    Atom = merge_atoms('default', Name),
230
 
                    io:format(Fd, "-define(~w, ~w).~n", [Atom, Val])
231
 
            end;
232
 
        _ -> ok
233
 
    end,
234
 
    insert_defvals2(T, Fd);
235
 
insert_defvals2([_ | T], Fd) ->
236
 
    insert_defvals2(T, Fd);
237
 
insert_defvals2([], _Fd) -> ok.
238
 
 
239
 
insert_range(Mes, Fd) ->
240
 
    io:format(Fd, "~n%% Range values~n", []),
241
 
    insert_range2(Mes, Fd),
242
 
    io:format(Fd, "~n", []).
243
 
 
244
 
insert_range2([#me{imported = true} | T], Fd)->
245
 
    insert_range2(T,Fd);
246
 
insert_range2([#me{asn1_type=#asn1_type{bertype='OCTET STRING',lo=Low,hi=High},aliasname=Name}|T],Fd)->
247
 
    case Low==undefined of
248
 
        true->
249
 
            insert_range2(T,Fd);
250
 
        false->
251
 
            AtomLow = merge_atoms('low', Name),
252
 
            AtomHigh = merge_atoms('high', Name),
253
 
            io:format(Fd,"-define(~w, ~w).~n",[AtomLow,Low]),
254
 
            io:format(Fd,"-define(~w, ~w).~n",[AtomHigh,High]),
255
 
            insert_range2(T,Fd)
256
 
    end;
257
 
insert_range2([#me{asn1_type=#asn1_type{bertype='Unsigned32',lo=Low,hi=High},aliasname=Name}|T],Fd)->
258
 
            AtomLow = merge_atoms('low', Name),
259
 
            AtomHigh = merge_atoms('high', Name),
260
 
            io:format(Fd,"-define(~w, ~w).~n",[AtomLow,Low]),
261
 
            io:format(Fd,"-define(~w, ~w).~n",[AtomHigh,High]),
262
 
            insert_range2(T,Fd);
263
 
insert_range2([#me{asn1_type=#asn1_type{bertype='Counter32',lo=Low,hi=High},aliasname=Name}|T],Fd)->
264
 
            AtomLow = merge_atoms('low', Name),
265
 
            AtomHigh = merge_atoms('high', Name),
266
 
            io:format(Fd,"-define(~w, ~w).~n",[AtomLow,Low]),
267
 
            io:format(Fd,"-define(~w, ~w).~n",[AtomHigh,High]),
268
 
            insert_range2(T,Fd);
269
 
insert_range2([#me{asn1_type=#asn1_type{bertype='INTEGER',lo=Low,hi=High},aliasname=Name}|T],Fd)->
270
 
    case Low==undefined of
271
 
        true->
272
 
            insert_range2(T,Fd);
273
 
        false->
274
 
            AtomLow = merge_atoms('low', Name),
275
 
            AtomHigh = merge_atoms('high', Name),
276
 
            io:format(Fd,"-define(~w, ~w).~n",[AtomLow,Low]),
277
 
            io:format(Fd,"-define(~w, ~w).~n",[AtomHigh,High]),
278
 
            insert_range2(T,Fd)
279
 
    end; 
280
 
insert_range2([_|T],Fd) ->
281
 
    insert_range2(T,Fd);
282
 
insert_range2([],Fd) ->
283
 
    ok.
284
 
 
285
 
month(1) -> "Jan";
286
 
month(2) -> "Feb";
287
 
month(3) -> "Mar";
288
 
month(4) -> "Apr";
289
 
month(5) -> "May";
290
 
month(6) -> "Jun";
291
 
month(7) -> "Jul";
292
 
month(8) -> "Aug";
293
 
month(9) -> "Sep";
294
 
month(10) -> "Oct";
295
 
month(11) -> "Nov";
296
 
month(12) -> "Dec".
297
 
 
298
 
%%%-----------------------------------------------------------------
299
 
%%% Interface for erl_compile.
300
 
%%%-----------------------------------------------------------------
301
 
 
302
 
compile(Input, Output, Opts) ->
303
 
    Verbose = Opts#options.verbose,
304
 
    case convert(Input++".bin", Output++".hrl", Input, Verbose) of
305
 
        ok ->
306
 
            ok;
307
 
        {error, Reason} ->
308
 
            io:format("~p", [Reason]),
309
 
            error
310
 
    end.
311