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

« back to all changes in this revision

Viewing changes to lib/snmp/src/compile/snmpc.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(snmpc).
 
19
 
 
20
%% API
 
21
-export([compile/1, compile/2, compile/3,
 
22
         mib_to_hrl/1, mib_to_hrl/3, 
 
23
         is_consistent/1]).
 
24
 
 
25
%% Debug
 
26
-export([look_at/1]).
 
27
 
 
28
%% Internal Exports
 
29
-export([init/3]).
 
30
 
 
31
-include_lib("stdlib/include/erl_compile.hrl").
 
32
-include("snmp_types.hrl").
 
33
-include("snmpc.hrl").
 
34
 
 
35
 
 
36
look_at(Mib) ->
 
37
    io:format("~p ~n", [snmpc_lib:look_at(Mib)]).
 
38
 
 
39
 
 
40
%%-----------------------------------------------------------------
 
41
%% Misc compiler stuff
 
42
%%-----------------------------------------------------------------
 
43
 
 
44
is_consistent(Filenames) ->
 
45
    snmpc_lib:is_consistent(Filenames).
 
46
 
 
47
mib_to_hrl(MibName) ->
 
48
    snmpc_mib_to_hrl:convert(MibName).
 
49
 
 
50
mib_to_hrl(MibName, HrlFile, Opts) ->
 
51
    snmpc_mib_to_hrl:compile(MibName, HrlFile, Opts).
 
52
 
 
53
 
 
54
%%%-----------------------------------------------------------------
 
55
%%% Interface for erl_compile.
 
56
%%%-----------------------------------------------------------------
 
57
 
 
58
compile(Input, _Output, Options) ->
 
59
    case compile(Input, make_options(Options)) of
 
60
        {ok, _} ->
 
61
            ok;
 
62
        {error, Reason} ->
 
63
            io:format("~p", [Reason]),
 
64
            error
 
65
    end.
 
66
 
 
67
%% Converts generic options to format expected by compile/2
 
68
 
 
69
make_options(#options{includes = Incs,
 
70
                      outdir   = Outdir,
 
71
                      warning  = Warning,
 
72
                      specific = Spec}) ->
 
73
 
 
74
    OutdirOpt = {outdir, Outdir},
 
75
 
 
76
    WarningOpt = 
 
77
        case Warning of
 
78
            0 -> {warnings, false};
 
79
            _ -> {warnings, true}
 
80
        end,
 
81
 
 
82
    IncludeOpt =
 
83
        {i, case Incs of
 
84
                [] ->
 
85
                    [""];
 
86
                _ ->
 
87
                    lists:map(fun(Dir) -> Dir++"/" end, Incs)
 
88
            end},
 
89
 
 
90
    [WarningOpt, OutdirOpt, IncludeOpt | Spec].
 
91
 
 
92
%% Returns: {ok, File}|{error, Reason}
 
93
compile([AtomFilename]) when atom(AtomFilename) ->
 
94
    compile(atom_to_list(AtomFilename), []), % from cmd line
 
95
    halt();
 
96
compile(FileName) -> 
 
97
    compile(FileName, []).
 
98
 
 
99
 
 
100
%%----------------------------------------------------------------------
 
101
%% Options:
 
102
%%          {deprecated,  bool()}                         true
 
103
%%          {group_check, bool()}                         true
 
104
%%          {db,          volatile|persistent|mnesia}     volatile
 
105
%%          {i,           [import_dir_string()]}          ["./"]
 
106
%%          {il,          [import_lib_dir_string()]}      []
 
107
%%          {warnings,    bool()}                         true
 
108
%%          {outdir,      string()}                       "./"
 
109
%%          description
 
110
%%          imports
 
111
%%          module_identity
 
112
%%          {module, string()}
 
113
%%          no_defs
 
114
%% (hidden) {verbosity,   trace|debug|log|info|silence}   silence
 
115
%% (hidden) version 
 
116
%% (hidden) options 
 
117
%%----------------------------------------------------------------------
 
118
 
 
119
compile(FileName, Options) when list(FileName) ->
 
120
    true = snmpc_misc:is_string(FileName),
 
121
    DefOpts = [{deprecated,  true},
 
122
               {group_check, true},
 
123
               {i,           ["./"]},
 
124
               {db,          volatile},
 
125
               {warnings,    true},
 
126
               {outdir,      "./"},
 
127
               {il,          []}],
 
128
    Opts = update_options(DefOpts, Options),
 
129
    case check_options(Opts) of
 
130
        ok ->
 
131
            maybe_display_version(Opts),
 
132
            maybe_display_options(Opts),
 
133
            Pid = spawn_link(?MODULE,init,[self(),FileName,Opts]),
 
134
            receive
 
135
                {compile_result,R} -> R;
 
136
                {'EXIT',Pid, Reason} when Reason =/= normal ->
 
137
                    exit(Reason)
 
138
            end;
 
139
        {error, Reason} -> 
 
140
            {error, Reason}
 
141
    end.
 
142
 
 
143
maybe_display_version(Opts) ->
 
144
    case lists:member(version, Opts) of
 
145
        true ->
 
146
            Vsn = (catch get_version()),
 
147
            io:format("version: ~s~n", [Vsn]);
 
148
        false ->
 
149
            ok
 
150
    end.
 
151
 
 
152
get_version() ->
 
153
    MI   = ?MODULE:module_info(),
 
154
    Attr = get_info(attributes, MI),
 
155
    Vsn  = get_info(app_vsn, Attr),
 
156
    Comp = get_info(compile, MI),
 
157
    Time = get_info(time, Comp),
 
158
    {Year, Month, Day, Hour, Min, Sec} = Time,
 
159
    io_lib:format("~s [~.4w-~.2.0w-~.2.0w ~.2.0w:~.2.0w:~.2.0w]", 
 
160
                  [Vsn, Year, Month, Day, Hour, Min, Sec]).
 
161
 
 
162
maybe_display_options(Opts) ->
 
163
    case lists:member(options, Opts) of
 
164
        true ->
 
165
            {F, A} = get_options(Opts, [], []),
 
166
            io:format("options: " ++ F ++ "~n", A);
 
167
        false ->
 
168
            ok
 
169
    end.
 
170
 
 
171
get_options([], Formats, Args) ->
 
172
    {lists:concat(lists:reverse(Formats)), lists:reverse(Args)};
 
173
get_options([{deprecated, Val}|Opts], Formats, Args) ->
 
174
    get_options(Opts, ["~n   deprecated:  ~w"|Formats], [Val|Args]);
 
175
get_options([{group_check, Val}|Opts], Formats, Args) ->
 
176
    get_options(Opts, ["~n   group_check: ~w"|Formats], [Val|Args]);
 
177
get_options([{db, Val}|Opts], Formats, Args) ->
 
178
    get_options(Opts, ["~n   db:          ~w"|Formats], [Val|Args]);
 
179
get_options([{i, Val}|Opts], Formats, Args) ->
 
180
    get_options(Opts, ["~n   i:           ~p"|Formats], [Val|Args]);
 
181
get_options([{il, Val}|Opts], Formats, Args) ->
 
182
    get_options(Opts, ["~n   il:          ~p"|Formats], [Val|Args]);
 
183
get_options([{outdir, Val}|Opts], Formats, Args) ->
 
184
    get_options(Opts, ["~n   outdir:      ~s"|Formats], [Val|Args]);
 
185
get_options([{description, Val}|Opts], Formats, Args) ->
 
186
    get_options(Opts, ["~n   description: ~w"|Formats], [Val|Args]);
 
187
get_options([description|Opts], Formats, Args) ->
 
188
    get_options(Opts, ["~n   description"|Formats], Args);
 
189
get_options([{warnings, Val}|Opts], Formats, Args) ->
 
190
    get_options(Opts, ["~n   warnings:    ~w"|Formats], [Val|Args]);
 
191
get_options([{verbosity, Val}|Opts], Formats, Args) ->
 
192
    get_options(Opts, ["~n   verbosity:   ~w"|Formats], [Val|Args]);
 
193
get_options([imports|Opts], Formats, Args) ->
 
194
    get_options(Opts, ["~n   imports"|Formats], Args);
 
195
get_options([module_identity|Opts], Formats, Args) ->
 
196
    get_options(Opts, ["~n   module_identity"|Formats], Args);
 
197
get_options([_|Opts], Formats, Args) ->
 
198
    get_options(Opts, Formats, Args).
 
199
    
 
200
 
 
201
get_info(Key, Info) ->
 
202
    case lists:keysearch(Key, 1, Info) of
 
203
        {value, {Key, Val}} ->
 
204
            Val;
 
205
        false ->
 
206
            throw("undefined")
 
207
    end.
 
208
 
 
209
% p(F, A) ->
 
210
%     io:format("DBG: " ++ F ++ "~n", A).
 
211
 
 
212
update_options([], Options) -> 
 
213
    Options;
 
214
update_options([{Key,DefVal}|DefOpts], Options) ->
 
215
    case snmpc_misc:assq(Key, Options) of
 
216
        false ->
 
217
            update_options(DefOpts, [{Key,DefVal}|Options]);
 
218
        {value, Val} when Key == i ->
 
219
            Options1 = 
 
220
                lists:keyreplace(Key, 1, Options, {Key, Val++DefVal}),
 
221
            update_options(DefOpts, Options1);
 
222
        {value, Val} when Key == il ->
 
223
            Options1 = 
 
224
                lists:keyreplace(Key, 1, Options, {Key, Val++DefVal}),
 
225
            update_options(DefOpts, Options1);
 
226
        {value, DefVal} -> %% Same value, no need to update
 
227
            update_options(DefOpts, Options);
 
228
        {value, Val} ->    %% New value, so update
 
229
            Options1 = 
 
230
                lists:keyreplace(Key, 1, Options, {Key, Val}),
 
231
            update_options(DefOpts, Options1)
 
232
    end;
 
233
update_options([Opt|DefOpts], Options) ->
 
234
    case lists:member(Opt, Options) of
 
235
        true ->
 
236
            update_options(DefOpts, Options);
 
237
        false ->
 
238
            update_options(DefOpts, [Opt|Options])
 
239
    end.
 
240
 
 
241
check_options([]) -> ok;
 
242
check_options([no_symbolic_info|T]) -> check_options(T);
 
243
check_options([{outdir, Str} | T]) when list(Str) ->
 
244
    check_options(T);
 
245
check_options([{debug, Atom} | T]) when atom(Atom) ->
 
246
    check_options(T);
 
247
check_options([{deprecated, Atom} | T]) when atom(Atom) ->
 
248
    check_options(T);                
 
249
check_options([{group_check, Atom} | T]) when atom(Atom) ->
 
250
    check_options(T);
 
251
check_options([{warnings, Bool} | T]) ->
 
252
    check_bool(warnings, Bool),
 
253
    check_options(T);
 
254
check_options([{db, volatile} | T]) ->
 
255
    check_options(T);
 
256
check_options([{db, persistent} | T]) ->
 
257
    check_options(T);
 
258
check_options([{db, mnesia} | T]) ->
 
259
    check_options(T);
 
260
check_options([{i, [Str|_]} | T]) when list(Str) ->
 
261
    check_options(T);
 
262
check_options([{il, []} | T]) ->
 
263
    check_options(T);
 
264
check_options([{il, [Str|_]} | T]) when list(Str) ->
 
265
    check_options(T);
 
266
check_options([{description, Bool}| T]) ->
 
267
    check_bool(description, Bool),
 
268
    check_options(T);
 
269
check_options([description| T]) -> %% same as {description, true}
 
270
    check_options(T);
 
271
check_options([{verbosity, V} | T]) when atom(V) ->
 
272
    snmpc_lib:vvalidate(V),
 
273
    check_options(T);
 
274
check_options([version| T]) ->
 
275
    check_options(T);
 
276
check_options([options| T]) ->
 
277
    check_options(T);
 
278
check_options([imports| T]) ->
 
279
    check_options(T);
 
280
check_options([module_identity| T]) ->
 
281
    check_options(T);
 
282
check_options([{module, M} | T]) when atom(M) ->
 
283
    check_options(T);
 
284
check_options([no_defs| T]) ->
 
285
    check_options(T);
 
286
check_options([Opt|_]) ->
 
287
    {error, {invalid_option, Opt}}.
 
288
 
 
289
 
 
290
check_bool(_Key, Bool) when Bool == true; Bool == false ->
 
291
    ok;
 
292
check_bool(Key, Val) ->
 
293
    {error, {invalid_option, {Key, Val}}}.
 
294
    
 
295
get_group_check(Options) ->
 
296
    snmpc_lib:key1search(group_check, Options, true).
 
297
 
 
298
get_deprecated(Options) ->
 
299
    snmpc_lib:key1search(deprecated, Options, true).
 
300
 
 
301
get_description(Options) ->
 
302
    case lists:member(description,Options) of
 
303
        false ->
 
304
            snmpc_lib:key1search(description,Options,false);
 
305
        true ->
 
306
            true
 
307
    end.
 
308
 
 
309
make_description(Message) ->
 
310
    case get(description) of
 
311
        true ->
 
312
            Message;
 
313
        _ -> 
 
314
            undefined
 
315
    end.
 
316
 
 
317
    
 
318
                
 
319
%%----------------------------------------------------------------------
 
320
%% verbosity stuff
 
321
%%----------------------------------------------------------------------
 
322
 
 
323
t(F,A)   -> snmpc_lib:t(F,A).
 
324
%% d(F,A)   -> snmpc_lib:d(F,A).
 
325
l(F,A)   -> snmpc_lib:l(F,A).
 
326
i(F,A)   -> snmpc_lib:i(F,A).
 
327
i(F,A,L) -> snmpc_lib:i(F,A,L).
 
328
%% w(F,A)   -> snmpc_lib:w(F,A).
 
329
w(F,A,L) -> snmpc_lib:w(F,A,L).
 
330
 
 
331
%% Verbosity level is selected from three (historical reasons)
 
332
%% options: warnings, debug and verbosity
 
333
%% - If warnings is true, then verbosity is _atleast_ warning
 
334
%%   (even if the verbosity flag is set to silence)
 
335
%% - If debug is true, the verbosity is _atleast_ log
 
336
%% - Otherwise, verbosity is used as is.
 
337
get_verbosity(Options) ->
 
338
    WarningsSeverity = 
 
339
        case snmpc_lib:key1search(warnings, Options) of
 
340
            true ->
 
341
                warning;
 
342
            _ ->
 
343
                silence
 
344
        end,
 
345
    case snmpc_lib:key1search(verbosity, Options) of
 
346
        undefined ->
 
347
            %% Backward compatible: If not defined then try debug and convert
 
348
            case snmpc_lib:key1search(debug, Options, false) of
 
349
                true ->
 
350
                    log;
 
351
                false ->
 
352
                    WarningsSeverity
 
353
            end;
 
354
        silence ->
 
355
            WarningsSeverity;
 
356
        Verbosity ->
 
357
            Verbosity
 
358
    end.
 
359
 
 
360
 
 
361
%%----------------------------------------------------------------------
 
362
%% The compile process.
 
363
%%----------------------------------------------------------------------
 
364
 
 
365
init(From, MibFileName, Options) ->
 
366
    {A,B,C} = now(),
 
367
    random:seed(A,B,C),
 
368
    put(options,     Options),
 
369
    put(verbosity,   get_verbosity(Options)),
 
370
    put(description, get_description(Options)),
 
371
    File = filename:rootname(MibFileName, ".mib"),
 
372
    put(filename, filename:basename(File ++ ".mib")),
 
373
    R = case catch c_impl(File) of
 
374
            {ok, OutFile} -> {ok, OutFile};
 
375
            {'EXIT',error} -> {error, compilation_failed};
 
376
            Error -> exit(Error)
 
377
        end,
 
378
    From ! {compile_result, R}.
 
379
 
 
380
 
 
381
c_impl(File) ->
 
382
    {ok, PData} = parse(File),
 
383
    t("Syntax analysis:~n"
 
384
      "   ~p",[PData]),
 
385
    MibName = compile_parsed_data(PData),
 
386
    t("Compiler output:~n"
 
387
      "   ~p",[get(cdata)]),
 
388
    save(File, MibName, get(options)).
 
389
 
 
390
compile_parsed_data(#pdata{mib_name = MibName, 
 
391
                           imports  = Imports, 
 
392
                           defs     = Definitions}) ->
 
393
    snmpc_lib:import(Imports),
 
394
    update_imports(Imports),
 
395
    Deprecated = get_deprecated(get(options)),
 
396
    definitions_loop(Definitions, Deprecated),
 
397
    MibName.
 
398
 
 
399
update_imports(Imports) ->
 
400
    case lists:member(imports, get(options)) of
 
401
        true ->
 
402
            IMPs  = do_update_imports(Imports, []),
 
403
            CDATA = get(cdata),
 
404
            put(cdata, CDATA#cdata{imports = IMPs});
 
405
        false ->
 
406
            ok
 
407
    end.
 
408
 
 
409
do_update_imports([], Acc) ->
 
410
    lists:reverse(Acc);
 
411
do_update_imports([{{Mib, ImportsFromMib0},_Line}|Imports], Acc) ->
 
412
    ImportsFromMib = [Name || {_, Name} <- ImportsFromMib0],
 
413
    Import = {Mib, ImportsFromMib},
 
414
    do_update_imports(Imports, [Import|Acc]).
 
415
 
 
416
 
 
417
update_status(Name, Status) ->
 
418
    #cdata{status_ets = Ets} = get(cdata),
 
419
    ets:insert(Ets, {Name, Status}).
 
420
    
 
421
 
 
422
%% A deprecated object
 
423
definitions_loop([{#mc_object_type{name = ObjName, status = deprecated}, 
 
424
                   Line}|T],
 
425
                 false) ->
 
426
    %% May be implemented but the compiler chooses not to.
 
427
    i("object_type ~w is deprecated => ignored",[ObjName],Line),    
 
428
    update_status(ObjName, deprecated), 
 
429
    definitions_loop(T, false);
 
430
 
 
431
%% A obsolete object
 
432
definitions_loop([{#mc_object_type{name = ObjName, status = obsolete}, 
 
433
                   Line}|T], 
 
434
                 Deprecated) ->
 
435
    l("object_type ~w (~w) is obsolete => ignored",[ObjName,Line]),
 
436
    %% No need to implement a obsolete object
 
437
    update_status(ObjName, obsolete),
 
438
    ensure_macro_imported('OBJECT-TYPE', Line),
 
439
    definitions_loop(T, Deprecated);
 
440
 
 
441
%% Defining a table
 
442
definitions_loop([{#mc_object_type{name        = NameOfTable,
 
443
                                   syntax      = {{sequence_of, SeqName}, _},
 
444
                                   max_access  = Taccess,
 
445
                                   kind        = Kind, 
 
446
                                   status      = Tstatus,
 
447
                                   description = Desc1,
 
448
                                   units       = Tunits,
 
449
                                   name_assign = Tindex},
 
450
                   Tline},
 
451
                  {#mc_object_type{name        = NameOfEntry,
 
452
                                   syntax      = {{type, SeqName}, TEline},
 
453
                                   max_access  = 'not-accessible',
 
454
                                   kind        = {table_entry, IndexingInfo},
 
455
                                   status      = Estatus,
 
456
                                   description = Desc2,
 
457
                                   units       = Eunits, 
 
458
                                   name_assign = {NameOfTable,[1]}},
 
459
                   Eline},
 
460
                  {#mc_sequence{name   = SeqName,
 
461
                                fields = FieldList},
 
462
                   Sline}|ColsEtc],
 
463
                 Deprecated) ->
 
464
    l("defloop -> [object_type(sequence_of),object_type(type,[1]),sequence]:~n"
 
465
      "   NameOfTable:  ~p~n"
 
466
      "   SeqName:      ~p~n"
 
467
      "   Taccess:      ~p~n"
 
468
      "   Kind:         ~p~n"
 
469
      "   Tstatus:      ~p~n"
 
470
      "   Tindex:       ~p~n"
 
471
      "   Tunits:       ~p~n"
 
472
      "   Tline:        ~p~n"
 
473
      "   NameOfEntry:  ~p~n"
 
474
      "   TEline:       ~p~n"
 
475
      "   IndexingInfo: ~p~n"
 
476
      "   Estatus:      ~p~n"
 
477
      "   Eunits:       ~p~n"
 
478
      "   Eline:        ~p~n"
 
479
      "   FieldList:    ~p~n"
 
480
      "   Sline:        ~p",
 
481
      [NameOfTable,SeqName,Taccess,Kind,Tstatus,
 
482
       Tindex,Tunits,Tline,
 
483
       NameOfEntry,TEline,IndexingInfo,Estatus,Eunits,Eline,
 
484
       FieldList,Sline]),
 
485
    update_status(NameOfTable, Tstatus),
 
486
    update_status(NameOfEntry, Estatus),
 
487
    update_status(SeqName,     undefined),
 
488
    ensure_macro_imported('OBJECT-TYPE', Tline),
 
489
    test_table(NameOfTable,Taccess,Kind,Tindex,Tline),
 
490
    {Tfather,Tsubindex} = Tindex,
 
491
    snmpc_lib:register_oid(Tline,NameOfTable,Tfather,Tsubindex),
 
492
    Description1 = make_description(Desc1),
 
493
    TableME = #me{aliasname   = NameOfTable,
 
494
                  entrytype   = table, 
 
495
                  access      = 'not-accessible',
 
496
                  description = Description1,
 
497
                  units       = Tunits},
 
498
    snmpc_lib:register_oid(TEline,NameOfEntry,NameOfTable,[1]),
 
499
    Description2 = make_description(Desc2),
 
500
    TableEntryME = #me{aliasname   = NameOfEntry, 
 
501
                       entrytype   = table_entry,
 
502
                       assocList   = [{table_entry_with_sequence, SeqName}], 
 
503
                       access      = 'not-accessible',
 
504
                       description = Description2,
 
505
                       units       = Eunits},
 
506
    {ColMEs, RestObjs} = 
 
507
        define_cols(ColsEtc, 1, FieldList, NameOfEntry, NameOfTable, []),
 
508
    TableInfo = snmpc_lib:make_table_info(Eline, NameOfTable,
 
509
                                          IndexingInfo, ColMEs),
 
510
    snmpc_lib:add_cdata(#cdata.mes, 
 
511
                        [TableEntryME,
 
512
                         TableME#me{assocList=[{table_info, 
 
513
                                                TableInfo}]} |
 
514
                                ColMEs]),
 
515
    definitions_loop(RestObjs, Deprecated);
 
516
 
 
517
definitions_loop([{#mc_object_type{name        = NameOfTable,
 
518
                                   syntax      = {{sequence_of, SeqName},_},
 
519
                                   max_access  = Taccess,
 
520
                                   kind        = Kind, 
 
521
                                   status      = Tstatus,
 
522
                                   description = Desc1,
 
523
                                   units       = Tunits,
 
524
                                   name_assign = Tindex}, Tline},
 
525
                  {#mc_object_type{name        = NameOfEntry,
 
526
                                   syntax      = {{type, SeqName},_},
 
527
                                   max_access  = 'not-accessible',
 
528
                                   kind        = {table_entry,IndexingInfo}, 
 
529
                                   status      = Estatus, 
 
530
                                   description = Desc2,
 
531
                                   units       = Eunits,
 
532
                                   name_assign = BadOID}, Eline},
 
533
                  {#mc_sequence{name   = SeqName,
 
534
                                fields = FieldList}, Sline}|ColsEtc],
 
535
                 Deprecated) ->
 
536
    l("defloop -> "
 
537
      "[object_type(sequence_of),object_type(type),sequence(fieldList)]:~n"
 
538
      "   NameOfTable:  ~p~n"
 
539
      "   SeqName:      ~p~n"
 
540
      "   Taccess:      ~p~n"
 
541
      "   Kind:         ~p~n"
 
542
      "   Tstatus:      ~p~n"
 
543
      "   Tindex:       ~p~n"
 
544
      "   Tunits:       ~p~n"
 
545
      "   Tline:        ~p~n"
 
546
      "   NameOfEntry:  ~p~n"
 
547
      "   IndexingInfo: ~p~n"
 
548
      "   Estatus:      ~p~n"
 
549
      "   BadOID:       ~p~n"
 
550
      "   Eunits:       ~p~n"
 
551
      "   Eline:        ~p~n"
 
552
      "   FieldList:    ~p~n"
 
553
      "   Sline:        ~p",
 
554
      [NameOfTable,SeqName,Taccess,Kind,Tstatus,
 
555
       Tindex,Tunits,Tline,
 
556
       NameOfEntry,IndexingInfo,Estatus,BadOID,Eunits,Eline,
 
557
       FieldList,Sline]),
 
558
    update_status(NameOfTable, Tstatus),
 
559
    update_status(NameOfEntry, Estatus),
 
560
    update_status(SeqName,     undefined),
 
561
    ensure_macro_imported('OBJECT-TYPE', Tline),
 
562
    snmpc_lib:print_error("Bad TableEntry OID definition (~w)",
 
563
                          [BadOID],Eline),
 
564
    test_table(NameOfTable,Taccess,Kind,Tindex,Tline),
 
565
    {Tfather,Tsubindex} = Tindex,
 
566
    snmpc_lib:register_oid(Tline,NameOfTable,Tfather,Tsubindex),
 
567
    Description1 = make_description(Desc1),
 
568
    TableME = #me{aliasname   = NameOfTable,
 
569
                  entrytype   = table, 
 
570
                  access      = 'not-accessible',
 
571
                  description = Description1,
 
572
                  units       = Tunits},
 
573
    Description2 = make_description(Desc2),
 
574
    TableEntryME = #me{aliasname   = NameOfEntry, 
 
575
                       entrytype   = table_entry,
 
576
                       access      = 'not-accessible',
 
577
                       assocList   = [{table_entry_with_sequence,SeqName}],
 
578
                       description = Description2,
 
579
                       units       = Eunits},
 
580
    {ColMEs, RestObjs} = 
 
581
        define_cols(ColsEtc, 1, FieldList, NameOfEntry, NameOfTable, []),
 
582
    TableInfo = snmpc_lib:make_table_info(Eline, NameOfTable,
 
583
                                          IndexingInfo, ColMEs),
 
584
    snmpc_lib:add_cdata(#cdata.mes, 
 
585
                               [TableEntryME,
 
586
                                TableME#me{assocList=[{table_info, 
 
587
                                                       TableInfo}]} |
 
588
                                ColMEs]),
 
589
    definitions_loop(RestObjs, Deprecated);
 
590
 
 
591
definitions_loop([{#mc_new_type{name         = NewTypeName,
 
592
                                macro        = Macro,
 
593
                                syntax       = OldType,
 
594
                                display_hint = DisplayHint},Line}|T],
 
595
                 Deprecated) ->
 
596
    l("defloop -> new_type:~n"
 
597
      "   Macro:       ~p~n"
 
598
      "   NewTypeName: ~p~n"
 
599
      "   OldType:     ~p~n"
 
600
      "   DisplayHint: ~p~n"
 
601
      "   Line:        ~p",[Macro,NewTypeName,OldType,DisplayHint,Line]),
 
602
    ensure_macro_imported(Macro,Line),
 
603
    Types = (get(cdata))#cdata.asn1_types,
 
604
    case lists:keysearch(NewTypeName, #asn1_type.aliasname, Types) of
 
605
        {value,_} ->
 
606
            snmpc_lib:print_error("Type ~w already defined.",
 
607
                                  [NewTypeName],Line);
 
608
        false ->
 
609
            %% NameOfOldType = element(2,OldType), 
 
610
            ASN1 = snmpc_lib:make_ASN1type(OldType),
 
611
            snmpc_lib:add_cdata(#cdata.asn1_types,
 
612
                                [ASN1#asn1_type{aliasname    = NewTypeName,
 
613
                                                imported     = false,
 
614
                                                display_hint = DisplayHint}])
 
615
    end,
 
616
    definitions_loop(T, Deprecated);
 
617
 
 
618
%% Plain variable
 
619
definitions_loop([{#mc_object_type{name        = NewVarName,
 
620
                                   syntax      = Type, 
 
621
                                   max_access  = Access,
 
622
                                   kind        = {variable, DefVal}, 
 
623
                                   status      = Status,
 
624
                                   description = Desc1, 
 
625
                                   units       = Units,
 
626
                                   name_assign = {Parent,SubIndex}},Line} |T],
 
627
                 Deprecated) ->
 
628
    l("defloop -> object_type (variable):~n"
 
629
      "   NewVarName: ~p~n"
 
630
      "   Type:       ~p~n"
 
631
      "   Access:     ~p~n"
 
632
      "   DefVal:     ~p~n"
 
633
      "   Status:     ~p~n"
 
634
      "   Units:      ~p~n"
 
635
      "   Parent:     ~p~n"
 
636
      "   SubIndex:   ~p~n"
 
637
      "   Line:       ~p",
 
638
      [NewVarName, Type, Access, DefVal, Status, Units, Parent, SubIndex, Line]),
 
639
    update_status(NewVarName, Status),
 
640
    snmpc_lib:test_father(Parent, NewVarName, SubIndex, Line),
 
641
    ASN1type = snmpc_lib:make_ASN1type(Type),
 
642
    snmpc_lib:register_oid(Line, NewVarName, Parent, SubIndex),
 
643
    Description1 = make_description(Desc1),
 
644
    NewME = #me{aliasname   = NewVarName, 
 
645
                asn1_type   = ASN1type,
 
646
                entrytype   = variable,
 
647
                access      = Access,
 
648
                description = Description1, 
 
649
                units       = Units,
 
650
                assocList   = DefVal},  
 
651
    NewME2 = snmpc_lib:resolve_defval(NewME),
 
652
    %% hmm, should this be done in resolve_defval?
 
653
    VI = snmpc_lib:make_variable_info(NewME2), 
 
654
    snmpc_lib:add_cdata(#cdata.mes,
 
655
                        [NewME2#me{assocList = [{variable_info, VI}]}]),
 
656
    definitions_loop(T, Deprecated);
 
657
 
 
658
definitions_loop([{#mc_module_identity{name         = NewVarName,
 
659
                                       last_updated = LU,
 
660
                                       organization = Org,
 
661
                                       contact_info = CI,
 
662
                                       description  = Desc,
 
663
                                       revisions    = Revs0, 
 
664
                                       name_assign  = {Parent, SubIndex}},
 
665
                   Line}|T],
 
666
                 Deprecated) ->
 
667
    l("defloop -> module-identity: "
 
668
      "~n   NewVarName: ~p"
 
669
      "~n   LU:         ~p"
 
670
      "~n   Org:        ~p"
 
671
      "~n   CI:         ~p"
 
672
      "~n   Desc:       ~p"
 
673
      "~n   Revs0:      ~p"
 
674
      "~n   Parent:     ~p"
 
675
      "~n   SubIndex:   ~p"
 
676
      "~n   Line:       ~p",
 
677
      [NewVarName, LU, Org, CI, Desc, Revs0, Parent, SubIndex, Line]),
 
678
    ensure_macro_imported('MODULE-IDENTITY', Line),
 
679
    snmpc_lib:register_oid(Line, NewVarName, Parent, SubIndex),
 
680
    Revs = [{R,D}||#mc_revision{revision = R,description = D} <- Revs0],
 
681
    MI = #module_identity{last_updated = LU,
 
682
                          organization = Org,
 
683
                          contact_info = CI,
 
684
                          description  = Desc,
 
685
                          revisions    = Revs},
 
686
    CDATA = get(cdata),
 
687
    put(cdata, CDATA#cdata{module_identity = MI}),
 
688
    snmpc_lib:add_cdata(
 
689
      #cdata.mes,
 
690
      [snmpc_lib:makeInternalNode2(false, NewVarName)]),
 
691
    definitions_loop(T, Deprecated);    
 
692
 
 
693
definitions_loop([{#mc_internal{name      = NewVarName,
 
694
                                macro     = Macro,
 
695
                                parent    = Parent,
 
696
                                sub_index = SubIndex},Line}|T],
 
697
                 Deprecated) ->
 
698
    l("defloop -> internal:~n"
 
699
      "   NewVarName: ~p~n"
 
700
      "   Macro:      ~p~n"
 
701
      "   Parent:     ~p~n"
 
702
      "   SubIndex:   ~p~n"
 
703
      "   Line:       ~p",[NewVarName, Macro, Parent, SubIndex, Line]),
 
704
    ensure_macro_imported(Macro, Line),
 
705
    snmpc_lib:register_oid(Line, NewVarName, Parent, SubIndex),
 
706
    snmpc_lib:add_cdata(
 
707
      #cdata.mes,
 
708
      [snmpc_lib:makeInternalNode2(false, NewVarName)]),
 
709
    definitions_loop(T, Deprecated);    
 
710
 
 
711
%% A trap message
 
712
definitions_loop([{#mc_trap{name        = TrapName,
 
713
                            enterprise  = EnterPrise, 
 
714
                            vars        = Variables, 
 
715
                            description = Desc1,
 
716
                            num         = SpecificCode}, Line}|T],
 
717
                 Deprecated) ->
 
718
    l("defloop -> trap:~n"
 
719
      "   TrapName:     ~p~n"
 
720
      "   EnterPrise:   ~p~n"
 
721
      "   Variables:    ~p~n"
 
722
      "   SpecificCode: ~p~n"
 
723
      "   Line:         ~p",
 
724
      [TrapName,EnterPrise,Variables,SpecificCode,Line]),
 
725
    update_status(TrapName, undefined),
 
726
    CDATA = get(cdata),
 
727
    snmpc_lib:check_trap_name(EnterPrise, Line, CDATA#cdata.mes),
 
728
    Descriptions = make_description(Desc1),
 
729
    Trap = #trap{trapname      = TrapName, 
 
730
                 enterpriseoid = EnterPrise,
 
731
                 specificcode  = SpecificCode,
 
732
                 %% oidobjects: Store Variables temporary here.
 
733
                 %%             This will be replaced later in the 
 
734
                 %%             get_final_mib function by a call to
 
735
                 %%             the update_trap_objects function.
 
736
                 oidobjects    = Variables,  
 
737
                 description   = Descriptions},
 
738
    snmpc_misc:map({snmpc_lib,check_trap}, [Trap, Line], 
 
739
                  CDATA#cdata.traps),
 
740
    snmpc_lib:add_cdata(#cdata.traps, [Trap]),
 
741
    definitions_loop(T, Deprecated);    
 
742
 
 
743
definitions_loop([{#mc_object_type{name        = NameOfEntry, 
 
744
                                   syntax      = Type, 
 
745
                                   max_access  = Eaccess,
 
746
                                   kind        = {table_entry, Index},
 
747
                                   status      = Estatus,
 
748
                                   name_assign = SubIndex},Eline}|T], 
 
749
                 Deprecated) ->
 
750
    l("defloop -> object_type (table_entry):~n"
 
751
      "   NameOfEntry: ~p~n"
 
752
      "   Type:        ~p~n"
 
753
      "   Eaccess:     ~p~n"
 
754
      "   Index:       ~p~n"
 
755
      "   Estatus:     ~p~n"
 
756
      "   SubIndex:    ~p~n"
 
757
      "   SubIndex:    ~p~n"
 
758
      "   Eline:       ~p",
 
759
      [NameOfEntry,Type,Eaccess,Index,Estatus,SubIndex,Eline]),
 
760
    update_status(NameOfEntry, Estatus),
 
761
    snmpc_lib:print_error("Misplaced TableEntry definition (~w)",
 
762
                          [NameOfEntry],Eline),
 
763
    definitions_loop(T, Deprecated);
 
764
 
 
765
definitions_loop([{#mc_notification{name   = TrapName,
 
766
                                    status = deprecated}, Line}|T],
 
767
                 false) ->
 
768
    i("defloop -> notification ~w is deprecated => ignored",
 
769
      [TrapName],Line),    
 
770
    update_status(TrapName, deprecated),
 
771
    ensure_macro_imported('NOTIFICATION-TYPE', Line),
 
772
    definitions_loop(T, false);    
 
773
 
 
774
definitions_loop([{#mc_notification{name   = TrapName,
 
775
                                    status = obsolete}, Line}|T],
 
776
                 Deprecated) ->
 
777
    l("defloop -> notification ~w (~w) is obsolete => ignored", 
 
778
      [TrapName,Line]),
 
779
    update_status(TrapName, obsolete),
 
780
    ensure_macro_imported('NOTIFICATION-TYPE', Line),
 
781
    definitions_loop(T, Deprecated);    
 
782
 
 
783
definitions_loop([{#mc_notification{name        = TrapName,
 
784
                                    vars        = Variables,
 
785
                                    status      = Status,
 
786
                                    description = Desc,
 
787
                                    name_assign = {Parent, SubIndex}},Line}|T],
 
788
                 Deprecated) ->
 
789
    l("defloop -> notification:~n"
 
790
      "   TrapName:  ~p~n"
 
791
      "   Variables: ~p~n"
 
792
      "   Status:    ~p~n"
 
793
      "   Parent:    ~p~n"
 
794
      "   SubIndex:  ~p~n"
 
795
      "   Line:      ~p",
 
796
      [TrapName, Variables, Status, Parent, SubIndex, Line]),
 
797
    update_status(TrapName, Status),
 
798
    ensure_macro_imported('NOTIFICATION-TYPE', Line),
 
799
    CDATA = get(cdata),
 
800
    snmpc_lib:register_oid(Line, TrapName, Parent, SubIndex),
 
801
    Descriptions = make_description(Desc),
 
802
    Notif = #notification{trapname    = TrapName,
 
803
                          description = Descriptions,
 
804
                          %% oidobjects: Store Variables temporary here.
 
805
                          %%             This will be replaced later in the 
 
806
                          %%             get_final_mib function by a call to
 
807
                          %%             the update_trap_objects function.
 
808
                          oidobjects  = Variables}, 
 
809
    snmpc_lib:check_notification(Notif, Line, CDATA#cdata.traps),
 
810
    snmpc_lib:add_cdata(#cdata.traps, [Notif]),
 
811
    definitions_loop(T, Deprecated);    
 
812
 
 
813
definitions_loop([{#mc_module_compliance{name = Name},Line}|T], Deprecated) ->
 
814
    l("defloop -> module_compliance:~n"
 
815
      "   Name: ~p~n"
 
816
      "   Line: ~p",[Name,Line]),
 
817
    ensure_macro_imported('MODULE-COMPLIANCE', Line),
 
818
    definitions_loop(T, Deprecated);
 
819
 
 
820
definitions_loop([{#mc_object_group{name    = Name,
 
821
                                    objects = GroupObjects,
 
822
                                    status  = Status}, Line}|T],
 
823
                 Deprecated) ->
 
824
    l("defloop -> object_group ~p:~n"
 
825
      "   Status:       ~p~n"
 
826
      "   GroupObjects: ~p~n"
 
827
      "   Line:         ~p",[Name,Status,GroupObjects,Line]),
 
828
    ensure_macro_imported('OBJECT-GROUP', Line),
 
829
    GroupBool = get_group_check(get(options)),
 
830
    case GroupBool of
 
831
        true ->
 
832
            snmpc_lib:add_cdata(#cdata.objectgroups,
 
833
                                       [{Name,GroupObjects,Line}]),
 
834
            %% Check that the group members has been defined 
 
835
            %% and that they have the correct status
 
836
            snmpc_lib:check_object_group(Name, GroupObjects,
 
837
                                                Line, Status);
 
838
        _ ->
 
839
            ok
 
840
    end,
 
841
    definitions_loop(T, Deprecated);
 
842
 
 
843
definitions_loop([{#mc_notification_group{name    = Name,
 
844
                                          objects = GroupObjects,
 
845
                                          status  = Status},Line}
 
846
                  |T], Deprecated) ->
 
847
    l("defloop -> notification_group ~p: ~n"
 
848
      "   Status:       ~p~n"
 
849
      "   GroupObjects: ~p~n"
 
850
      "   Line:         ~p",[Name,Status,GroupObjects,Line]),
 
851
    ensure_macro_imported('NOTIFICATION-GROUP', Line),
 
852
    GroupBool = get_group_check(get(options)),
 
853
    case GroupBool of
 
854
        true ->
 
855
            snmpc_lib:add_cdata(#cdata.notificationgroups,
 
856
                                       [{Name,GroupObjects,Line}]),
 
857
 
 
858
            %% Check that the group members has been defined 
 
859
            %% and that they have the correct status
 
860
            snmpc_lib:check_notification_group(Name, GroupObjects,
 
861
                                               Line, Status);
 
862
        _ ->
 
863
            ok
 
864
    end,
 
865
    definitions_loop(T, Deprecated);
 
866
 
 
867
definitions_loop([{#mc_object_type{name   = NameOfTable,
 
868
                                   syntax = {{sequence_of, SeqName},_},
 
869
                                   status = Tstatus},Tline}, 
 
870
                  Entry, Seq|T],
 
871
                Deprecated) ->
 
872
    l("defloop -> object_type (sequence_of)~n"
 
873
      "   NameOfTable: ~p~n"
 
874
      "   SeqName:     ~p~n"
 
875
      "   Tline:       ~p~n"
 
876
      "   Entry:       ~p~n"
 
877
      "   Seq:         ~p",
 
878
      [NameOfTable,SeqName,Tline,Entry,Seq]),
 
879
    update_status(NameOfTable, Tstatus),
 
880
    case Entry of
 
881
        {#mc_object_type{syntax      = {{type, SeqName},_line},
 
882
                         max_access  = 'not-accessible',
 
883
                         kind        = {table_entry, _IndexingInfo},
 
884
                         name_assign = {_NameOfTable,[1]}}, _Eline} ->
 
885
            case Seq of
 
886
                {#mc_sequence{name = SeqName}, Sline} ->
 
887
                    snmpc_lib:error("Internal error. Correct incorrect "
 
888
                                           "table (~p,~w).",[SeqName,Sline],
 
889
                                    Tline);
 
890
                _ ->
 
891
                    i("defloop -> Invalid sequence: ~p",[Seq]),
 
892
                    snmpc_lib:print_error(
 
893
                      "Invalid SEQUENCE OF '~p'.",
 
894
                      [safe_elem(1,safe_elem(2,Seq))],Tline)
 
895
            end;
 
896
        Else ->
 
897
            i("defloop -> Invalid table entry: Else = ~p",[Else]),
 
898
            snmpc_lib:print_error(
 
899
              "Invalid TableEntry '~p' (check STATUS, Sequence name, Oid)",
 
900
              [safe_elem(1,safe_elem(2,Entry))],Tline)
 
901
    end,
 
902
    definitions_loop(T, Deprecated);
 
903
 
 
904
definitions_loop([{#mc_object_type{name   = NameOfTable,
 
905
                                   syntax = {{sequence_of, SeqName},_},
 
906
                                   status = Tstatus},Tline}|T],
 
907
                 Deprecated) ->
 
908
    l("defloop -> object_type (sequence_of):~n"
 
909
      "   object_type: ~p~n"
 
910
      "   sequence_of: ~p~n"
 
911
      "   Tline:       ~p",[NameOfTable,SeqName,Tline]),
 
912
    update_status(NameOfTable, Tstatus),
 
913
    snmpc_lib:print_error("Invalid statements following table ~p.",
 
914
                          [NameOfTable],Tline),
 
915
    definitions_loop(T, Deprecated);
 
916
 
 
917
definitions_loop([{#mc_sequence{name   = SeqName,
 
918
                                fields = FieldList},Line}|T],
 
919
                 Deprecated) ->
 
920
    l("defloop -> sequence (fieldList):"
 
921
      "~n   SeqName:   ~p"
 
922
      "~n   FieldList: ~p"
 
923
      "~n   Line:      ~p",[SeqName, FieldList, Line]),
 
924
    w("Unexpected SEQUENCE ~w, ignoring.",[SeqName],Line),
 
925
    definitions_loop(T, Deprecated);
 
926
 
 
927
definitions_loop([{Obj,Line}|T], Deprecated) ->
 
928
    i("defloop -> unknown Error ~n"
 
929
      "   Obj:  ~p~n"
 
930
      "   Line: ~p",[Obj,Line]),
 
931
    snmpc_lib:print_error("Unknown Error in MIB. "
 
932
         "Can't describe the error better than this: ~999p ignored."
 
933
         " Please send a trouble report to support@erlang.ericsson.se.",
 
934
                                 [Obj],Line),
 
935
    definitions_loop(T, Deprecated);
 
936
 
 
937
definitions_loop([], _Deprecated) ->
 
938
    l("defloop -> done",[]),
 
939
    ok.
 
940
 
 
941
safe_elem(N,T) ->
 
942
    case catch(element(N,T)) of
 
943
        {'EXIT',_} ->
 
944
            "no more information available";
 
945
        X -> X
 
946
    end.
 
947
 
 
948
%% A correct column
 
949
define_cols([{#mc_object_type{name        = NameOfCol,
 
950
                              syntax      = Type1,
 
951
                              max_access  = Access,
 
952
                              kind        = {variable,Defval},
 
953
                              status      = Status,
 
954
                              description = Desc,
 
955
                              units       = Units,
 
956
                              name_assign = {NameOfEntry,[SubIndex]}},
 
957
              Oline}|Rest],
 
958
            SubIndex, 
 
959
            [{NameOfCol,Type2}|Fields], NameOfEntry, TableName, ColMEs) ->
 
960
    l("defcols -> object_type (variable):~n"
 
961
      "   NameOfCol:  ~p~n"
 
962
      "   Type1:      ~p~n"
 
963
      "   Access:     ~p~n"
 
964
      "   Defval:     ~p~n"
 
965
      "   Status      ~p~n"
 
966
      "   Units       ~p~n"
 
967
      "   NameOfEntry ~p~n"
 
968
      "   Oline:      ~p",
 
969
      [NameOfCol,Type1,Access,Defval,Status,Units,NameOfEntry,Oline]),
 
970
    update_status(NameOfCol, Status),
 
971
    Deprecated = get_deprecated(get(options)),
 
972
    ASN1type = snmpc_lib:make_ASN1type(Type1),
 
973
    case (snmpc_lib:make_ASN1type(Type2))#asn1_type.bertype of
 
974
        T2 when T2 == ASN1type#asn1_type.bertype -> ok;
 
975
        _Else ->
 
976
            snmpc_lib:error(
 
977
              "Types for ~p differs from the SEQUENCE definition. ",
 
978
              [NameOfCol],Oline)
 
979
    end,
 
980
    NewAccess = % a simple way to get the obsolete behaviour
 
981
        if
 
982
            Status == obsolete ->
 
983
                %% Be quiet and don't implement
 
984
                'not-accessible';
 
985
            Status == deprecated, Deprecated == false ->
 
986
                %% The compiler chooses not to implement the column.
 
987
                i("object_type ~w is deprecated => ignored",
 
988
                  [NameOfCol],Oline),
 
989
                'not-accessible';
 
990
            true -> Access
 
991
        end,
 
992
    snmpc_lib:register_oid(Oline,NameOfCol,NameOfEntry,[SubIndex]),
 
993
    Description = make_description(Desc),
 
994
    ColumnME = snmpc_lib:resolve_defval(
 
995
                 #me{oid         = SubIndex,
 
996
                     aliasname   = NameOfCol, 
 
997
                     asn1_type   = ASN1type,
 
998
                     entrytype   = table_column, 
 
999
                     access      = NewAccess,
 
1000
                     description = Description,
 
1001
                     units       = Units,   %% Propably not usefull
 
1002
                     assocList   = [{table_name,TableName} | Defval]}),
 
1003
    define_cols(Rest,SubIndex+1,Fields,NameOfEntry,TableName,
 
1004
                [ColumnME|ColMEs]);
 
1005
 
 
1006
%% A "hole" (non-consecutive columns) in the table.
 
1007
%% Implemented as a not-accessible column so Col always is index in
 
1008
%% row tuple.
 
1009
define_cols([{#mc_object_type{name        = NameOfCol,
 
1010
                              syntax      = Type1,
 
1011
                              max_access  = Access,
 
1012
                              kind        = Kind,
 
1013
                              status      = Status,
 
1014
                              name_assign = {NameOfEntry,[SubIndex]}},
 
1015
              Oline}|Rest],
 
1016
            ExpectedSubIndex, Fields, NameOfEntry, TableName, ColMEs) 
 
1017
  when SubIndex > ExpectedSubIndex ->
 
1018
    l("defcols -> object_type (non consecutive cols):~n"
 
1019
      "   NameOfCol:  ~p~n"
 
1020
      "   Type1:      ~p~n"
 
1021
      "   Access:     ~p~n"
 
1022
      "   Status      ~p~n"
 
1023
      "   NameOfEntry ~p~n"
 
1024
      "   Oline:      ~p",
 
1025
      [NameOfCol,Type1,Access,Status,NameOfEntry,Oline]),
 
1026
    update_status(NameOfCol, Status),
 
1027
    Int = {{type, 'INTEGER'},Oline},
 
1028
    GeneratedColumn =  
 
1029
        %% be sure to use an invalid column name here!
 
1030
        {#mc_object_type{name        = '$no_name$', 
 
1031
                         syntax      = Int, 
 
1032
                         max_access  = 'not-accessible',
 
1033
                         kind        = {variable, [{defval,0}]}, 
 
1034
                         status      = current, 
 
1035
                         description = undefined,
 
1036
                         name_assign = {NameOfEntry, [ExpectedSubIndex]}}, 
 
1037
         Oline},
 
1038
    define_cols([GeneratedColumn, 
 
1039
                 {#mc_object_type{name        = NameOfCol, 
 
1040
                                  syntax      = Type1, 
 
1041
                                  max_access  = Access, 
 
1042
                                  kind        = Kind, 
 
1043
                                  status      = Status,
 
1044
                                  description = undefined,
 
1045
                                  name_assign = {NameOfEntry,[SubIndex]}},
 
1046
                  Oline}|Rest], ExpectedSubIndex,
 
1047
                 [{'$no_name$', Int}|Fields], NameOfEntry, TableName,ColMEs) ;
 
1048
 
 
1049
%% Ok. done. All fields are eaten.
 
1050
define_cols(Rest, _SubIndex, [], _NameOfEntry, _TableName, ColMEs) ->
 
1051
    {ColMEs, Rest};
 
1052
 
 
1053
 
 
1054
%% Error Handling
 
1055
 
 
1056
%% The name of the field and object is the same
 
1057
define_cols([{#mc_object_type{name        = NameOfCol,
 
1058
                              kind        = Kind,
 
1059
                              name_assign = SubIndex}, Oline}|Rest],
 
1060
            SubIndex2, [{NameOfCol, _Type2}|Fields], 
 
1061
            NameOfEntry, TableName, ColMEs) ->
 
1062
    l("defcols -> object_type (name of field and object is the same):~n"
 
1063
      "   NameOfCol:   ~p~n"
 
1064
      "   Kind:        ~p~n"
 
1065
      "   SubIndex:    ~p~n"
 
1066
      "   Oline:       ~p n"
 
1067
      "   SubIndex2:   ~p~n"
 
1068
      "   NameOfEntry  ~p~n"
 
1069
      "   TableName    ~p~n",
 
1070
      [NameOfCol,Kind,SubIndex,Oline,SubIndex2,NameOfEntry,TableName]),    
 
1071
    SIok = case SubIndex of
 
1072
               {Parent,[_SI]} when Parent =/= NameOfEntry ->
 
1073
                   snmpc_lib:print_error(
 
1074
                     "Invalid parent ~p for table column ~p (should be ~p).",
 
1075
                     [Parent,NameOfCol,NameOfEntry],Oline),
 
1076
                   error;
 
1077
               {NameOfEntry,[SubIndex2]} ->
 
1078
                   ok;
 
1079
               {NameOfEntry,[SI]} ->
 
1080
                   snmpc_lib:print_error(
 
1081
                     "Invalid column number ~p for column ~p.",
 
1082
                     [SI, NameOfCol], Oline),
 
1083
                   error;
 
1084
               _Q ->
 
1085
                   snmpc_lib:print_error(
 
1086
                     "Invalid parent for column ~p.",[NameOfCol],Oline),
 
1087
                   error
 
1088
           end,
 
1089
    Kok = case Kind of
 
1090
              {variable,_} ->
 
1091
                  ok;
 
1092
              _Q2 ->
 
1093
                  snmpc_lib:print_error(
 
1094
                    "Expected a table column.",[],Oline),
 
1095
                  error
 
1096
          end,
 
1097
    case {SIok, Kok} of
 
1098
        {ok, ok} ->
 
1099
            snmpc_lib:print_error("Invalid table column definition for"
 
1100
                                  " ~p.",[NameOfCol],Oline);
 
1101
        _Q4 ->
 
1102
            done % already reported
 
1103
    end,
 
1104
    define_cols(Rest,SubIndex2+1,Fields,NameOfEntry,TableName,ColMEs);
 
1105
 
 
1106
%% It's an object-type but everything else is wrong
 
1107
define_cols([{#mc_object_type{name = NameOfCol},Oline}|Rest],SubIndex2,Fields,
 
1108
            NameOfEntry,TableName,ColMEs) ->
 
1109
    snmpc_lib:print_error(
 
1110
      "Number of columns differs from SEQUENCE definition (object:~p).",
 
1111
      [NameOfCol],Oline),
 
1112
    define_cols(Rest,SubIndex2+1,Fields,NameOfEntry,TableName,ColMEs);
 
1113
 
 
1114
define_cols([{Obj,Line}|Tl], _SubIndex,_,_,_,ColMEs) ->
 
1115
    snmpc_lib:print_error("Corrupt table definition.",[],Line),
 
1116
    {ColMEs,[{Obj,Line}|Tl]};
 
1117
define_cols(Rest, _SubIndex,_,_,_,ColMEs) ->
 
1118
    snmpc_lib:print_error("Corrupt table definition.",[]),
 
1119
    {ColMEs,Rest}.
 
1120
 
 
1121
ensure_macro_imported(dummy, _Line) -> ok;
 
1122
ensure_macro_imported(Macro, Line) ->
 
1123
    Macros = (get(cdata))#cdata.imported_macros,
 
1124
    case lists:member(Macro, Macros) of
 
1125
        true -> ok;
 
1126
        false ->
 
1127
            snmpc_lib:print_error("Macro ~p not imported.", [Macro],
 
1128
                                         Line)
 
1129
    end.
 
1130
 
 
1131
test_table(NameOfTable, Taccess, Kind, _Tindex, Tline) ->
 
1132
    if
 
1133
        Taccess =/= 'not-accessible' ->
 
1134
            snmpc_lib:print_error(
 
1135
              "Table ~w must have STATUS not-accessible",
 
1136
              [NameOfTable],Tline),
 
1137
            error;
 
1138
        Kind =/= {variable,[]} ->
 
1139
            snmpc_lib:print_error(
 
1140
              "Bad table definition (~w).",
 
1141
              [NameOfTable],Tline),
 
1142
            error;
 
1143
        true ->
 
1144
            ok
 
1145
    end.
 
1146
 
 
1147
save(Filename, MibName, Options) ->
 
1148
    R     = filename:rootname(Filename),
 
1149
    File1 = filename:basename(R),
 
1150
    File3 = snmpc_misc:to_upper(File1),
 
1151
    case snmpc_misc:to_upper(atom_to_list(MibName)) of
 
1152
        File3 ->
 
1153
            {value, OutDirr} = snmpc_misc:assq(outdir, Options),
 
1154
            OutDir = snmpc_misc:ensure_trailing_dir_delimiter(OutDirr),
 
1155
            File2 = (OutDir ++ File1) ++ ".bin",
 
1156
            {ok, MIB} = snmpc_lib:get_final_mib(File1, Options),
 
1157
            case get(errors) of
 
1158
                undefined ->
 
1159
                    case file:write_file(File2, term_to_binary(MIB)) of
 
1160
                        ok ->
 
1161
                            {ok, File2};
 
1162
                        _Err ->
 
1163
                            snmpc_lib:error(
 
1164
                              "Couldn't write file \"~s\".",[File2])
 
1165
                    end;
 
1166
                E ->
 
1167
                    l("save failed: ~n~p", [E]),
 
1168
                    {'EXIT',error}
 
1169
            end;
 
1170
        MibNameL ->
 
1171
            snmpc_lib:error("Mibname (~s) differs from filename (~s).",
 
1172
                                   [MibNameL, File1])
 
1173
    end.
 
1174
    
 
1175
%% parse takes a text file as a input and the output is a list of tokens. 
 
1176
%% Input: FileName (file of mibs)
 
1177
%% Output: {ok, Mib} where MIB is a tuple of Tokens.
 
1178
%%         {error, {LineNbr, Mod, Msg} an error on line number LineNb.
 
1179
 
 
1180
 
 
1181
parse(FileName) ->
 
1182
    case snmpc_tok:start_link(reserved_words(),
 
1183
                              [{file, FileName ++ ".mib"},
 
1184
                               {forget_stringdata, true}]) of
 
1185
        {error,ReasonStr} ->
 
1186
            snmpc_lib:error(lists:flatten(ReasonStr),[]);
 
1187
        {ok, TokPid} ->
 
1188
            Toks = snmpc_tok:get_all_tokens(TokPid),
 
1189
            set_version(Toks),
 
1190
            %% io:format("parse -> lexical analysis: ~n~p~n", [Toks]),
 
1191
            %% t("parse -> lexical analysis: ~n~p", [Toks]),
 
1192
            CDataArg =
 
1193
                case lists:keysearch(module, 1, get(options)) of
 
1194
                    {value, {module, M}} -> {module, M};
 
1195
                    _ -> {file, FileName ++ ".funcs"}
 
1196
                end,
 
1197
            put(cdata,snmpc_lib:make_cdata(CDataArg)),
 
1198
            snmpc_tok:stop(TokPid),
 
1199
            Res = if list(Toks) ->
 
1200
                          snmpc_mib_gram:parse(Toks);
 
1201
                     true ->
 
1202
                          Toks
 
1203
                  end,
 
1204
            %% t("parse -> parsed: ~n~p", [Res]),
 
1205
            case Res of
 
1206
                {ok, PData} ->
 
1207
                    {ok, PData};
 
1208
                {error, {LineNbr, Mod, Msg}} ->
 
1209
                    case catch format_yecc_error(LineNbr, Msg) of
 
1210
                        {Line, Format, Data} -> 
 
1211
                            snmpc_lib:error(Format,Data,Line);
 
1212
                        _Q -> % sorry, have to use ugly yecc printouts
 
1213
                            Str = apply(Mod, format_error, [Msg]),
 
1214
                            snmpc_lib:error("~s",[Str],LineNbr)
 
1215
                    end
 
1216
            end
 
1217
    end.
 
1218
 
 
1219
set_version(Toks) when list(Toks) ->
 
1220
%% MODULE-IDENTITY _must_ be invoked in SNMPv2 according to RFC1908
 
1221
    case lists:keymember('MODULE-IDENTITY',1,Toks) of
 
1222
        true ->
 
1223
            put(snmp_version,2);
 
1224
        false ->
 
1225
            put(snmp_version,1)
 
1226
    end;
 
1227
set_version(_) ->
 
1228
    put(snmp_version,1).
 
1229
 
 
1230
 
 
1231
%% YeccGeneratedFile:format_error/1 is bad.
 
1232
format_yecc_error(Line, [ErrMsg, [${,Category, $,, _LineStr,$,, Value, $}]]) ->
 
1233
    {Line, "~s \"~s\" (~s).", [ErrMsg, Value, Category]}.
 
1234
 
 
1235
%% The same as the (quoted) Terminals in the snmpc_mib_gram.yrl
 
1236
reserved_words() -> 
 
1237
    [ 
 
1238
      'ACCESS', 
 
1239
      'BEGIN', 
 
1240
      'BIT', 
 
1241
      'CONTACT-INFO',
 
1242
      'Counter', 
 
1243
      'DEFINITIONS', 
 
1244
      'DEFVAL', 
 
1245
      'DESCRIPTION', 
 
1246
      'DISPLAY-HINT',
 
1247
      'END', 
 
1248
      'ENTERPRISE', 
 
1249
      'FROM', 
 
1250
      'Gauge', 
 
1251
      'IDENTIFIER', 
 
1252
      'IDENTIFIER',
 
1253
      'IMPORTS', 
 
1254
      'INDEX', 
 
1255
      'INTEGER', 
 
1256
      'IpAddress', 
 
1257
      'LAST-UPDATED',
 
1258
      'NetworkAddress', 
 
1259
      'OBJECT', 
 
1260
      'OBJECT', 
 
1261
      'OBJECT-TYPE', 
 
1262
      'OCTET', 
 
1263
      'OF',
 
1264
      'Opaque', 
 
1265
      'REFERENCE', 
 
1266
      'SEQUENCE', 
 
1267
      'SIZE', 
 
1268
      'STATUS', 
 
1269
      'STRING',
 
1270
      'SYNTAX', 
 
1271
      'TRAP-TYPE', 
 
1272
      'TimeTicks', 
 
1273
      'VARIABLES', 
 
1274
 
 
1275
      %% v2
 
1276
      'LAST-UPDATED',
 
1277
      'ORGANIZATION',
 
1278
      'CONTACT-INFO',
 
1279
      'MODULE-IDENTITY',
 
1280
      'NOTIFICATION-TYPE',
 
1281
      'MODULE-COMPLIANCE',
 
1282
      'OBJECT-GROUP',
 
1283
      'NOTIFICATION-GROUP',
 
1284
      'REVISION',
 
1285
      'OBJECT-IDENTITY',
 
1286
      'MAX-ACCESS',
 
1287
      'UNITS',
 
1288
      'AUGMENTS',
 
1289
      'IMPLIED',
 
1290
      'OBJECTS',
 
1291
      'TEXTUAL-CONVENTION',
 
1292
      'OBJECT-GROUP',
 
1293
      'NOTIFICATION-GROUP',
 
1294
      'NOTIFICATIONS',
 
1295
      'MODULE-COMPLIANCE',
 
1296
      'MODULE',
 
1297
      'MANDATORY-GROUPS',
 
1298
      'GROUP',
 
1299
      'WRITE-SYNTAX',
 
1300
      'MIN-ACCESS',
 
1301
      'BITS'
 
1302
     ].