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

« back to all changes in this revision

Viewing changes to lib/snmp/src/snmp_generic.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_generic).
19
 
 
20
 
-export([variable_func/2, variable_func/3, variable_get/1, variable_set/2]).
21
 
-export([table_func/2, table_func/4, 
22
 
         table_set_row/5, table_set_cols/3, table_set_cols/4,
23
 
         table_row_exists/2, table_foreach/2,
24
 
         table_try_row/4, table_get_row/2,
25
 
         table_get_elements/3, table_get_elements/4, table_get_element/3,
26
 
         table_set_element/4, table_set_elements/3,
27
 
         table_next/2, handle_table_next/6, 
28
 
         table_try_make_consistent/3, table_max_col/2,
29
 
         find_col/2, table_check_status/5, 
30
 
         table_find/3,split_index_to_keys/2, init_defaults/2, init_defaults/3,
31
 
         table_info/1,
32
 
         try_apply/2, get_own_indexes/2, table_create_rest/6,
33
 
         handle_table_get/4, variable_inc/2,
34
 
         get_status_col/2, get_table_info/2, get_index_types/1]).
35
 
 
36
 
-include("STANDARD-MIB.hrl").
37
 
-include("snmp_types.hrl").
38
 
-include("snmp_generic.hrl").
39
 
 
40
 
-define(VMODULE,"GENERIC").
41
 
-include("snmp_verbosity.hrl").
42
 
 
43
 
-ifndef(default_verbosity).
44
 
-define(default_verbosity,silence).
45
 
-endif.
46
 
 
47
 
 
48
 
%%%-----------------------------------------------------------------
49
 
%%% Generic functions for implementing software tables
50
 
%%% and variables. 
51
 
%%%-----------------------------------------------------------------
52
 
%% NameDb is {TableName, Db} where Db is volatile | persistent | mnesia
53
 
 
54
 
%%------------------------------------------------------------------
55
 
%% Access functions to the database.
56
 
%%------------------------------------------------------------------
57
 
variable_get({Name, mnesia}) ->
58
 
    snmp_generic_mnesia:variable_get(Name);
59
 
variable_get(NameDb) ->                   % ret {value, Val} | undefined
60
 
    snmp_local_db:variable_get(NameDb).
61
 
variable_set({Name, mnesia}, Val) ->
62
 
    snmp_generic_mnesia:variable_set(Name, Val);
63
 
variable_set(NameDb, Val) ->              % ret true
64
 
    snmp_local_db:variable_set(NameDb, Val).
65
 
 
66
 
variable_inc({Name, mnesia}, N) ->
67
 
    snmp_generic_mnesia:variable_inc(Name, N);
68
 
variable_inc(NameDb, N) ->              % ret true
69
 
    snmp_local_db:variable_inc(NameDb, N).
70
 
 
71
 
%%-----------------------------------------------------------------
72
 
%% Returns: {value, Val} | undefined
73
 
%%
74
 
%% snmp_local_db overloads (for performance reasons? (mbj?))
75
 
%%-----------------------------------------------------------------
76
 
table_get_element({Name, volatile}, RowIndex, Col) ->
77
 
    snmp_local_db:table_get_element({Name, volatile}, RowIndex, Col);
78
 
table_get_element({Name, persistent}, RowIndex, Col) ->
79
 
    snmp_local_db:table_get_element({Name, persistent}, RowIndex, Col);
80
 
table_get_element(NameDb, RowIndex, Col) ->
81
 
    TableInfo = table_info(NameDb),
82
 
    case handle_table_get(NameDb,RowIndex,[Col],
83
 
                          TableInfo#table_info.first_own_index) of
84
 
        [{value, Val}] -> {value, Val};
85
 
        _ -> undefined
86
 
    end.
87
 
 
88
 
table_get_elements(NameDb, RowIndex, Cols) ->
89
 
    TableInfo = snmp_generic:table_info(NameDb),
90
 
    table_get_elements(NameDb, RowIndex, Cols,
91
 
                       TableInfo#table_info.first_own_index).
92
 
 
93
 
%%----------------------------------------------------------------------
94
 
%% Returns: list of vals | undefined
95
 
%%----------------------------------------------------------------------
96
 
table_get_elements({Name, mnesia}, RowIndex, Cols, FirstOwnIndex) ->
97
 
    snmp_generic_mnesia:table_get_elements(Name, RowIndex, Cols, FirstOwnIndex);
98
 
table_get_elements(NameDb, RowIndex, Cols, FirstOwnIndex) -> 
99
 
    snmp_local_db:table_get_elements(NameDb, RowIndex, Cols, FirstOwnIndex).
100
 
 
101
 
 
102
 
% ret true
103
 
table_set_element({Name,mnesia}, RowIndex, Col, NewVal) -> 
104
 
    snmp_generic_mnesia:table_set_elements(Name, RowIndex,
105
 
                                           [{Col, NewVal}]);
106
 
table_set_element(NameDb, RowIndex, Col, NewVal) ->
107
 
    snmp_local_db:table_set_elements(NameDb, RowIndex, [{Col, NewVal}]).
108
 
 
109
 
table_set_elements({Name, mnesia}, RowIndex, Cols) ->
110
 
    snmp_generic_mnesia:table_set_elements(Name, RowIndex, Cols);
111
 
table_set_elements(NameDb, RowIndex, Cols) -> % ret true
112
 
    snmp_local_db:table_set_elements(NameDb, RowIndex, Cols).
113
 
 
114
 
table_next({Name, mnesia}, RestOid) ->
115
 
    snmp_generic_mnesia:table_next(Name, RestOid);
116
 
table_next(NameDb, RestOid) ->              % ret RRestOid | endOfTable
117
 
    snmp_local_db:table_next(NameDb, RestOid).
118
 
table_max_col(NameDb, Col) ->               % ret largest element in Col
119
 
                                            % in the table NameDb.
120
 
    snmp_local_db:table_max_col(NameDb, Col).
121
 
%%------------------------------------------------------------------
122
 
%% Theses functions could be in the MIB for simple 
123
 
%% variables or tables, i.e. vars without complex 
124
 
%% set-operations. If there are complex set op, an
125
 
%% extra layer-function should be added, and that
126
 
%% function should be in the MIB, and it can call these
127
 
%% functions.
128
 
%% The MIB functions just provide the table name, column
129
 
%% and a list of the keys for the table.
130
 
%%------------------------------------------------------------------
131
 
 
132
 
%%------------------------------------------------------------------
133
 
%% Variables
134
 
%%------------------------------------------------------------------
135
 
%%------------------------------------------------------------------
136
 
%% This is the default function for variables.
137
 
%%------------------------------------------------------------------
138
 
 
139
 
variable_func(new, NameDb) ->
140
 
    case variable_get(NameDb) of
141
 
        {value, _} -> ok;
142
 
        undefined ->
143
 
            {value, #variable_info{defval = Defval}} =
144
 
                variable_info(NameDb),
145
 
            variable_set(NameDb, Defval)
146
 
    end;
147
 
 
148
 
variable_func(delete, _NameDb) ->
149
 
    ok;
150
 
 
151
 
variable_func(get, NameDb) ->
152
 
    case variable_get(NameDb) of
153
 
        {value, Val} -> {value, Val};
154
 
        _ -> genErr
155
 
    end.
156
 
 
157
 
variable_func(is_set_ok, _Val, _NameDb) ->
158
 
    noError;
159
 
variable_func(set, Val, NameDb) ->
160
 
    case variable_set(NameDb, Val) of
161
 
        true -> noError;
162
 
        false -> commitFailed
163
 
    end;
164
 
variable_func(undo, _Val, _NameDb) ->
165
 
    noError.
166
 
 
167
 
%%------------------------------------------------------------------
168
 
%% Tables
169
 
%% Assumes the RowStatus is the last column in the
170
 
%% table.
171
 
%%------------------------------------------------------------------
172
 
%%------------------------------------------------------------------
173
 
%% This is the default function for tables.
174
 
%%
175
 
%% NameDb       is the name of the table (atom)
176
 
%% RowIndex   is a flat list of the indexes for the row.
177
 
%% Col        is the column number.
178
 
%%------------------------------------------------------------------
179
 
%% Each database implements its own table_func
180
 
%%------------------------------------------------------------------
181
 
table_func(Op, {Name, mnesia}) ->
182
 
    snmp_generic_mnesia:table_func(Op, Name);
183
 
 
184
 
table_func(Op, NameDb) ->
185
 
    snmp_local_db:table_func(Op, NameDb).
186
 
 
187
 
table_func(Op, RowIndex, Cols, {Name, mnesia}) ->
188
 
    snmp_generic_mnesia:table_func(Op, RowIndex, Cols, Name);
189
 
 
190
 
table_func(Op, RowIndex, Cols, NameDb) ->
191
 
    snmp_local_db:table_func(Op, RowIndex, Cols, NameDb).
192
 
 
193
 
%%----------------------------------------------------------------------
194
 
%% DB independent.
195
 
%%----------------------------------------------------------------------
196
 
handle_table_get(NameDb, RowIndex, Cols, FirstOwnIndex) ->
197
 
    case table_get_elements(NameDb, RowIndex, Cols, FirstOwnIndex) of
198
 
        undefined -> make_list(length(Cols), {noValue, noSuchInstance});
199
 
        Res -> validate_get(Cols, Res)
200
 
    end.
201
 
 
202
 
validate_get([_Col | Cols], [Res | Ress]) ->
203
 
    NewVal = 
204
 
        case Res of
205
 
            noinit -> {noValue, unSpecified};
206
 
            noacc -> {noAccess, unSpecified};
207
 
            Val -> {value, Val}
208
 
        end,
209
 
    [NewVal | validate_get(Cols, Ress)];
210
 
validate_get([], []) -> [].
211
 
 
212
 
make_list(N, X) when N > 0 -> [X | make_list(N-1, X)];
213
 
make_list(_, _) -> [].
214
 
 
215
 
table_foreach(Tab, Fun) ->
216
 
    ?vdebug("apply fun to all in table ~w",[Tab]),
217
 
    table_foreach(Tab, Fun, []).
218
 
table_foreach(Tab, Fun, Oid) ->
219
 
    case table_next(Tab, Oid) of
220
 
        endOfTable ->
221
 
            ?vdebug("end of table",[]),
222
 
            ok;
223
 
        Oid ->
224
 
            %% OOUPS, circular ref, major db fuckup
225
 
            ?vinfo("cyclic reference: ~w -> ~w",[Oid,Oid]),
226
 
            exit({cyclic_db_reference,Oid});
227
 
        NextOid ->
228
 
            ?vtrace("get row for oid ~w",[NextOid]),
229
 
            case table_get_row(Tab, NextOid) of
230
 
                undefined -> ok;
231
 
                Row -> 
232
 
                    ?vtrace("row: ~w",[Row]),
233
 
                    Fun(NextOid, Row)
234
 
            end,
235
 
            table_foreach(Tab, Fun, NextOid)
236
 
    end.
237
 
 
238
 
%%------------------------------------------------------------------
239
 
%% Used to implement next, and to find next entry's
240
 
%% keys in a table when not all of the keys are known.
241
 
%%
242
 
%% FirstCol is the first column in the search.
243
 
%% LastCol is the last column.
244
 
%% Col is the current column.
245
 
%% If Col is less than FirstCol, (or not present), the
246
 
%% search shall begin in the first row (no indexes) of
247
 
%% column FirstCol.
248
 
%% Returns: List of endOfTable | {NextOid, Value}
249
 
%%------------------------------------------------------------------
250
 
handle_table_next(_NameDb, _RowIndex, _OrgCols, _FirstCol, _FOI, undefined) ->
251
 
    [endOfTable];
252
 
handle_table_next(_NameDb, _RowIndex, [], _FirstCol, _FOI, _LastCol) ->
253
 
    [];
254
 
handle_table_next(NameDb, RowIndex, OrgCols, FirstCol, FOI, LastCol) ->
255
 
    FirstVals = 
256
 
        case split_cols(OrgCols, FirstCol, LastCol) of
257
 
            {[], Cols, LastCols} ->
258
 
                [];
259
 
            {FirstCols, Cols, LastCols} ->
260
 
                handle_table_next(NameDb, [], FirstCols, FirstCol, FOI, LastCol)
261
 
        end,
262
 
    NextVals = 
263
 
        case table_next(NameDb, RowIndex) of
264
 
            endOfTable -> 
265
 
                {NewCols, EndOfTabs} = make_new_cols(Cols, LastCol),
266
 
                NewVals = 
267
 
                    handle_table_next(NameDb, [], NewCols,FirstCol,FOI,LastCol),
268
 
                lists:append(NewVals, EndOfTabs);
269
 
            NextIndex ->  
270
 
                %% We found next Row; check if all Cols are initialized.
271
 
                Row = table_get_elements(NameDb, NextIndex, Cols, FOI),
272
 
                check_all_initalized(Row,Cols,NameDb,NextIndex,
273
 
                                     FirstCol, FOI, LastCol)
274
 
        end,
275
 
    lists:append([FirstVals, NextVals, LastCols]).
276
 
 
277
 
%% Split into three parts A,B,C; A < FirstCol =<  B =<  LastCol < C
278
 
split_cols([Col | Cols], FirstCol, LastCol) when Col < FirstCol ->
279
 
    {A, B, C} = split_cols(Cols, FirstCol, LastCol),
280
 
    {[FirstCol | A], B, C};
281
 
split_cols([Col | Cols], FirstCol, LastCol) when Col > LastCol ->
282
 
    {A, B, C} = split_cols(Cols, FirstCol, LastCol),
283
 
    {A, B, [endOfTable | C]};
284
 
split_cols([Col | Cols], FirstCol, LastCol)  ->
285
 
    {A, B, C} = split_cols(Cols, FirstCol, LastCol),
286
 
    {A, [Col | B], C};
287
 
split_cols([], _FirstCol, _LastCol) ->
288
 
    {[], [], []}.
289
 
 
290
 
%% Add 1 to each col < lastcol. Otherwise make it into
291
 
%% endOfTable.
292
 
make_new_cols([Col | Cols], LastCol) when Col < LastCol ->
293
 
    {NewCols, Ends} = make_new_cols(Cols, LastCol),
294
 
    {[Col+1 | NewCols], Ends};
295
 
make_new_cols([_Col | Cols], LastCol) ->
296
 
    {NewCols, Ends} = make_new_cols(Cols, LastCol),
297
 
    {NewCols, [endOfTable | Ends]};
298
 
make_new_cols([], _LastCol) ->
299
 
    {[], []}.
300
 
 
301
 
check_all_initalized([noinit|Vals],[Col|Cols],Name,RowIndex,
302
 
                     FirstCol, FOI, LastCol) ->
303
 
    [NextValForThisCol] = 
304
 
        handle_table_next(Name, RowIndex, [Col], FirstCol, FOI, LastCol),
305
 
    [NextValForThisCol | 
306
 
     check_all_initalized(Vals, Cols, Name, RowIndex, FirstCol, FOI, LastCol)];
307
 
check_all_initalized([noacc|Vals],[Col|Cols],Name,RowIndex,
308
 
                     FirstCol, FOI, LastCol) ->
309
 
    [NextValForThisCol] = 
310
 
        handle_table_next(Name, RowIndex, [Col], FirstCol, FOI, LastCol),
311
 
    [NextValForThisCol | 
312
 
     check_all_initalized(Vals, Cols, Name, RowIndex, FirstCol, FOI, LastCol)];
313
 
check_all_initalized([Val | Vals], [Col | Cols], Name, RowIndex, 
314
 
                     FirstCol, FOI, LastCol) ->
315
 
    [{[Col | RowIndex], Val} |
316
 
     check_all_initalized(Vals, Cols, Name, RowIndex, FirstCol, FOI, LastCol)];
317
 
check_all_initalized([], [], _Name, _RowIndex, _FirstCol, _FOI, _LastCol) ->
318
 
    [].
319
 
    
320
 
 
321
 
%%------------------------------------------------------------------
322
 
%%  Implements is_set_ok. 
323
 
%%------------------------------------------------------------------
324
 
%% TryChangeStatusFunc is a function that will be
325
 
%% called if the rowstatus column is changed.
326
 
%% Arguments: (StatusVal, RowIndex, Cols)
327
 
%% Two cases:
328
 
%% 1) Last col is RowStatus - check status
329
 
%% 2) No modification to RowStatus - check that row exists.
330
 
%%------------------------------------------------------------------
331
 
table_try_row(_NameDb, _TryChangeStatusFunc, _RowIndex, []) -> {noError, 0};
332
 
table_try_row(NameDb, TryChangeStatusFunc, RowIndex, Cols) ->
333
 
    #table_info{status_col = StatusCol} = table_info(NameDb),
334
 
    case lists:keysearch(StatusCol, 1, Cols) of
335
 
        {value, {StatusCol, Val}} ->
336
 
            case table_check_status(NameDb, StatusCol, 
337
 
                                    Val, RowIndex, Cols) of
338
 
                {noError, 0} ->
339
 
                    try_apply(TryChangeStatusFunc, [NameDb, Val,
340
 
                                                    RowIndex, Cols]);
341
 
                Error -> Error
342
 
            end;
343
 
        _ -> 
344
 
            case table_row_exists(NameDb, RowIndex) of
345
 
                true -> {noError, 0};
346
 
                false ->
347
 
                    [{ColNo, _Val}|_] = Cols,
348
 
                    {inconsistentName, ColNo}
349
 
            end
350
 
    end.
351
 
 
352
 
%%------------------------------------------------------------------
353
 
%% table_check_status can be used by the is_set_ok
354
 
%% procedure of all tables, to check the
355
 
%% status variable, if present in Cols.
356
 
%% table_check_status(NameDb, Col, Val, RowIndex, Cols) ->
357
 
%% NameDb    : the name of the table
358
 
%% Col       : the columnnumber of RowStatus
359
 
%% Val       : the value of the RowStatus Col
360
 
%%------------------------------------------------------------------
361
 
 
362
 
%% Try to make the row active. Ok if status != notReady
363
 
%% If it is notReady, make sure no row has value noinit.
364
 
table_check_status(NameDb, Col, ?'RowStatus_active', RowIndex, Cols) ->
365
 
    case table_get_row(NameDb, RowIndex) of
366
 
        Row when tuple(Row), element(Col, Row) == ?'RowStatus_notReady' ->
367
 
            case is_any_noinit(Row, Cols) of
368
 
                false -> {noError, 0};
369
 
                true -> {inconsistentValue, Col}
370
 
            end;
371
 
        undefined -> {inconsistentValue, Col};
372
 
        _Else -> {noError, 0}
373
 
    end;
374
 
 
375
 
%% Try to make the row inactive. Ok if status != notReady
376
 
table_check_status(NameDb, Col, ?'RowStatus_notInService', RowIndex, Cols) ->
377
 
    case table_get_row(NameDb, RowIndex) of
378
 
        Row when tuple(Row), element(Col, Row) == ?'RowStatus_notReady' ->
379
 
            case is_any_noinit(Row, Cols) of
380
 
                false -> {noError, 0};
381
 
                true -> {inconsistentValue, Col}
382
 
            end;
383
 
        undefined -> {inconsistentValue, Col};
384
 
        _Else -> {noError, 0}
385
 
    end;
386
 
 
387
 
%% Try to createAndGo
388
 
%% Ok if values are provided, or default values can be used for
389
 
%% all columns.
390
 
table_check_status(NameDb, Col, ?'RowStatus_createAndGo', RowIndex, Cols) ->
391
 
    case table_row_exists(NameDb, RowIndex) of
392
 
        false -> 
393
 
            % it's ok to use snmp_local_db:table_construct_row since it's
394
 
            % side effect free and we only use the result temporary.
395
 
            case catch snmp_local_db:table_construct_row(
396
 
                         NameDb, RowIndex, ?'RowStatus_createAndGo', Cols) of
397
 
                {'EXIT', _} ->
398
 
                    {noCreation, Col}; % Bad RowIndex
399
 
                Row ->
400
 
                    case lists:member(noinit, tuple_to_list(Row)) of
401
 
                        false -> {noError, 0};
402
 
                        _Found -> {inconsistentValue, Col}
403
 
                    end
404
 
            end;
405
 
        true -> {inconsistentValue, Col}
406
 
    end;
407
 
 
408
 
%% Try to createAndWait - ok if row doesn't exist.
409
 
table_check_status(NameDb, Col, ?'RowStatus_createAndWait', RowIndex, Cols) ->
410
 
    case table_row_exists(NameDb, RowIndex) of
411
 
        false ->
412
 
            case catch snmp_local_db:table_construct_row(
413
 
                         NameDb, RowIndex, ?'RowStatus_createAndGo', Cols) of
414
 
                {'EXIT', _} ->
415
 
                    {noCreation, Col}; % Bad RowIndex
416
 
                _Row ->
417
 
                    {noError, 0}
418
 
            end;
419
 
        true -> {inconsistentValue, Col}
420
 
    end;
421
 
 
422
 
%% Try to destroy
423
 
table_check_status(_NameDb, _Col, ?'RowStatus_destroy', _RowIndex, _Cols) ->
424
 
    {noError, 0};
425
 
    
426
 
%% Otherwise, notReady. It isn't possible to set a row to notReady.
427
 
table_check_status(_NameDb, Col, _, _RowIndex, _Cols) ->
428
 
    {inconsistentValue, Col}.
429
 
 
430
 
is_any_noinit(Row, Cols) ->
431
 
    is_any_noinit(tuple_to_list(Row), Cols, 1).
432
 
is_any_noinit([noinit | Vals], [{N, _Value} | Cols], N) ->
433
 
    is_any_noinit(Vals, Cols, N);
434
 
is_any_noinit([noinit | _Vals], _Cols, _N) ->
435
 
    true;
436
 
is_any_noinit([_ | Vals], [{N, _Value} | Cols], N) ->
437
 
    is_any_noinit(Vals, Cols, N+1);
438
 
is_any_noinit([_ | Vals], Cols, N) ->
439
 
    is_any_noinit(Vals, Cols, N+1);
440
 
is_any_noinit([], _, _) ->
441
 
    false.
442
 
 
443
 
%%------------------------------------------------------------------
444
 
%%  Implements set.
445
 
%% ChangedStatusFunc is a function that will be
446
 
%%   called if the rowstatus column is changed.
447
 
%%   The function is called *after* the row is created or
448
 
%%   otherwise modified, but *before* it is deleted.
449
 
%%   Arguments: (StatusVal, RowIndex, Cols)
450
 
%% ConsFunc is a consistency-check function which will
451
 
%%   be called with the RowIndex of this row, if
452
 
%%   no operation on the row is made, when
453
 
%%   all columns are set, OR when row is createAndWait:ed.
454
 
%%   This is useful when the RowStatus
455
 
%%   could change, e.g. if the manager has provided all
456
 
%%   mandatory columns in this set operation.
457
 
%%   If it is nofunc, no function will be called after all
458
 
%%   sets.
459
 
%%------------------------------------------------------------------
460
 
table_set_row(_NameDb, _, _, _RowIndex, []) -> {noError, 0};
461
 
table_set_row(NameDb, ChangedStatusFunc, ConsFunc, RowIndex, Cols) ->
462
 
    #table_info{status_col = StatusCol} = table_info(NameDb),
463
 
    case lists:keysearch(StatusCol, 1, Cols) of
464
 
        {value, {StatusCol, Val}} ->
465
 
            table_set_status(NameDb, RowIndex, Val, StatusCol, 
466
 
                             Cols, ChangedStatusFunc, ConsFunc);
467
 
        _ -> table_set_cols(NameDb, RowIndex, Cols, ConsFunc)
468
 
    end.
469
 
    
470
 
%%----------------------------------------------------------------------
471
 
%% Mnesia overloads for performance reasons.
472
 
%%----------------------------------------------------------------------
473
 
table_set_status({Name, mnesia}, RowIndex, Status, StatusCol, Cols, 
474
 
                 ChangedStatusFunc, ConsFunc) ->
475
 
    snmp_generic_mnesia:table_set_status(Name, RowIndex,
476
 
                                         Status, StatusCol, Cols, 
477
 
                                         ChangedStatusFunc, ConsFunc);
478
 
 
479
 
table_set_status(NameDb,RowIndex, Status, StatusCol, Cols,
480
 
                 ChangedStatusFunc,ConsFunc) ->
481
 
    snmp_local_db:table_set_status(NameDb, RowIndex,
482
 
                                   Status, StatusCol, Cols, 
483
 
                                   ChangedStatusFunc, ConsFunc).
484
 
 
485
 
init_defaults(Defs, InitRow) ->
486
 
    table_defaults(InitRow, Defs).
487
 
init_defaults(Defs, InitRow, StartCol) ->
488
 
    table_defaults(InitRow, StartCol, Defs).
489
 
%%-----------------------------------------------------------------
490
 
%% Get, from a list of Keys, the Keys defined in this table.
491
 
%% (e.g. if INDEX { ifIndex, myOwnIndex }, the Keys is a list
492
 
%% of two elements, and returned from this func is a list of
493
 
%% the last of the two.)
494
 
%%-----------------------------------------------------------------
495
 
get_own_indexes(0, _Keys) -> [];
496
 
get_own_indexes(1, Keys) -> Keys;
497
 
get_own_indexes(Index, [_Key | Keys]) ->
498
 
    get_own_indexes(Index - 1, Keys).
499
 
 
500
 
%%-----------------------------------------------------------------
501
 
%% Creates everything but the INDEX columns.
502
 
%% Pre: The StatusColumn is present
503
 
%% Four cases:
504
 
%% 0) If a column is 'not-accessible' => use noacc
505
 
%% 1) If no value is provided for the column and column is
506
 
%%    not StatusCol => use noinit
507
 
%% 2) If column is not StatusCol, use the provided value
508
 
%% 3) If column is StatusCol, use Status
509
 
%%-----------------------------------------------------------------
510
 
table_create_rest(Col, Max, _ , _ , [], _NoAcc) when Col > Max -> [];
511
 
table_create_rest(Col,Max,StatusCol,Status,[{Col,_Val}|Defs],[Col|NoAccs]) ->
512
 
    % case 0
513
 
    [noacc | table_create_rest(Col+1, Max, StatusCol, Status, Defs, NoAccs)];
514
 
table_create_rest(Col,Max,StatusCol,Status,Defs,[Col|NoAccs]) ->
515
 
    % case 0
516
 
    [noacc | table_create_rest(Col+1, Max, StatusCol, Status, Defs, NoAccs)];
517
 
table_create_rest(StatCol, Max, StatCol, Status, [{_Col, _Val} |Defs], NoAccs) ->
518
 
    % case 3
519
 
    [Status | table_create_rest(StatCol+1, Max, StatCol, Status,Defs,NoAccs)];
520
 
table_create_rest(Col, Max, StatusCol, Status, [{Col, Val} |Defs],NoAccs) ->
521
 
    % case 2
522
 
    [Val | table_create_rest(Col+1, Max, StatusCol, Status,Defs,NoAccs)];
523
 
table_create_rest(StatCol, Max, StatCol, Status, Cols, NoAccs) ->
524
 
    % case 3
525
 
    [Status | table_create_rest(StatCol+1, Max, StatCol, Status, Cols, NoAccs)];
526
 
table_create_rest(Col, Max, StatusCol, Status, Cols, NoAccs) when Col =< Max->
527
 
    % case 1
528
 
    [noinit | table_create_rest(Col+1, Max, StatusCol, Status, Cols, NoAccs)].
529
 
 
530
 
%%------------------------------------------------------------------
531
 
%%  Sets default values to a row.
532
 
%%  InitRow is a list of values.
533
 
%%  Defs is a list of {Col, DefVal}, in Column order.
534
 
%%  Returns a new row (a list of values) with the same values as
535
 
%%  InitRow, except if InitRow has value noinit in a column, and
536
 
%%  the corresponing Col has a DefVal in Defs, then the DefVal
537
 
%%  will be the new value.
538
 
%%------------------------------------------------------------------
539
 
table_defaults(InitRow, Defs) -> table_defaults(InitRow, 1, Defs).
540
 
 
541
 
table_defaults([], _, _Defs) -> [];
542
 
table_defaults([noinit | T], CurIndex, [{CurIndex, DefVal} | Defs]) ->
543
 
    [DefVal | table_defaults(T, CurIndex+1, Defs)];
544
 
%% 'not-accessible' columns don't get a value
545
 
table_defaults([noacc | T], CurIndex, [{CurIndex, _DefVal} | Defs]) ->
546
 
    [noacc | table_defaults(T, CurIndex+1, Defs)];
547
 
table_defaults([Val | T], CurIndex, [{CurIndex, _DefVal} | Defs]) ->
548
 
    [Val | table_defaults(T, CurIndex+1, Defs)];
549
 
table_defaults([Val | T], CurIndex, Defs) ->
550
 
    [Val | table_defaults(T, CurIndex+1, Defs)].
551
 
 
552
 
 
553
 
%%------------------------------------------------------------------
554
 
%% table_set_cols/3,4
555
 
%% can be used by the set procedure of all tables
556
 
%% to set all columns in Cols, one at a time.
557
 
%% ConsFunc is a check-consistency function, which will
558
 
%% be called with the RowIndex of this row, when
559
 
%% all columns are set. This is useful when the RowStatus
560
 
%% could change, e.g. if the manager has provided all
561
 
%% mandatory columns in this set operation.
562
 
%% If ConsFunc is nofunc, no function will be called after all
563
 
%% sets.
564
 
%% Returns: {noError, 0} | {Error, Col}
565
 
%%------------------------------------------------------------------
566
 
%% mnesia uses its own for performance reasons.
567
 
%% -----------------------------------------------------------------
568
 
table_set_cols({Name,mnesia}, RowIndex, Cols, ConsFunc) ->
569
 
    snmp_generic_mnesia:table_set_cols(Name, RowIndex,Cols,ConsFunc);
570
 
table_set_cols(NameDb, RowIndex, Cols, ConsFunc) ->
571
 
    case table_set_cols(NameDb, RowIndex, Cols) of
572
 
        {noError, 0} -> try_apply(ConsFunc, [NameDb, RowIndex, Cols]);
573
 
        Error -> Error
574
 
    end.
575
 
 
576
 
table_set_cols(_NameDb, _RowIndex, []) -> {noError, 0};
577
 
table_set_cols(NameDb, RowIndex, [{Col, Val} | Cols]) ->
578
 
    case catch table_set_element(NameDb, RowIndex, Col, Val) of
579
 
        true -> table_set_cols(NameDb, RowIndex, Cols);
580
 
        _X ->
581
 
            user_err("snmp_generic:table_set_cols set ~w to"
582
 
                     " ~w returned ~w",
583
 
                     [{NameDb, RowIndex}, {Col, Val}]),
584
 
            {undoFailed, Col}
585
 
    end.
586
 
    
587
 
%%------------------------------------------------------------------
588
 
%% This function splits RowIndex which is part
589
 
%% of a OID, into a list of the indexes for the
590
 
%% table. So a table with indexes {integer, octet string},
591
 
%% and a RowIndex [4,3,5,6,7], will be split into
592
 
%% [4, [5,6,7]].
593
 
%%------------------------------------------------------------------
594
 
split_index_to_keys(Indexes, RowIndex) ->
595
 
    collect_keys(Indexes, RowIndex).
596
 
 
597
 
collect_keys([#asn1_type{bertype = 'INTEGER'} | Indexes], [IntKey | Keys]) ->
598
 
    [IntKey | collect_keys(Indexes, Keys)];
599
 
collect_keys([#asn1_type{bertype = 'Unsigned32'} | Indexes], [IntKey | Keys]) ->
600
 
    [IntKey | collect_keys(Indexes, Keys)];
601
 
collect_keys([#asn1_type{bertype = 'Counter32'} | Indexes], [IntKey | Keys]) ->
602
 
    %% Should we allow this - counter in INDEX is strange!
603
 
    [IntKey | collect_keys(Indexes, Keys)];
604
 
collect_keys([#asn1_type{bertype = 'TimeTicks'} | Indexes], [IntKey | Keys]) ->
605
 
    %% Should we allow this - timeticks in INDEX is strange!
606
 
    [IntKey | collect_keys(Indexes, Keys)];
607
 
collect_keys([#asn1_type{bertype = 'IpAddress'} | Indexes], 
608
 
             [A, B, C, D | Keys]) ->
609
 
    [[A, B, C, D] | collect_keys(Indexes, Keys)];
610
 
%% Otherwise, check if it has constant size
611
 
collect_keys([#asn1_type{lo = X, hi = X} | Indexes], Keys)
612
 
   when integer(X), length(Keys) >= X ->
613
 
    {StrKey, Rest} = collect_length(X, Keys, []),
614
 
    [StrKey | collect_keys(Indexes, Rest)];
615
 
collect_keys([#asn1_type{lo = X, hi = X} | _Indexes], Keys)
616
 
   when integer(X) ->
617
 
    exit({error, {size_mismatch, X, Keys}});
618
 
%% Otherwise, its a dynamic-length type => its a list
619
 
%% OBJECT IDENTIFIER, OCTET STRING or BITS (or derivatives)
620
 
%% Check if it is IMPLIED (only last element can be IMPLIED)
621
 
collect_keys([#asn1_type{implied = true}], Keys) ->
622
 
    [Keys];
623
 
collect_keys([_Type | Indexes], [Length | Keys]) when length(Keys) >= Length ->
624
 
    {StrKey, Rest} = collect_length(Length, Keys, []),
625
 
    [StrKey | collect_keys(Indexes, Rest)];
626
 
collect_keys([_Type | _Indexes], [Length | Keys]) ->
627
 
    exit({error, {size_mismatch, Length, Keys}});
628
 
collect_keys([], []) -> [];
629
 
collect_keys([], Keys) ->
630
 
    exit({error, {bad_keys, Keys}});
631
 
collect_keys(_Any, Key) -> [Key].
632
 
 
633
 
collect_length(0, Rest, Rts) ->
634
 
    {lists:reverse(Rts), Rest};
635
 
collect_length(N, [El | Rest], Rts) ->
636
 
    collect_length(N-1, Rest, [El | Rts]).
637
 
 
638
 
%%------------------------------------------------------------------
639
 
%% Checks if a certain row exists.
640
 
%% Returns true or false.
641
 
%%------------------------------------------------------------------
642
 
table_row_exists(NameDb, RowIndex) ->
643
 
    case table_get_element(NameDb, RowIndex, 1) of
644
 
        undefined -> false;
645
 
        _ -> true
646
 
    end.
647
 
 
648
 
%%------------------------------------------------------------------
649
 
%% table_find(NameDb, Col, Value)
650
 
%% Finds a row (if one exists) in table NameDb
651
 
%% with column Col equals to Value.
652
 
%% Returns the RowIndex of the row, or false
653
 
%% if no row exists.
654
 
%%------------------------------------------------------------------
655
 
table_find(NameDb, Col, Value) -> table_find(NameDb, Col, Value, []).
656
 
table_find(NameDb, Col, Value, Indexes) ->
657
 
    case table_next(NameDb, Indexes) of
658
 
        endOfTable ->
659
 
            false;
660
 
        NewIndexes ->
661
 
            case table_get_element(NameDb, NewIndexes, Col) of
662
 
                {value, Value} -> NewIndexes;
663
 
                _Else -> table_find(NameDb, Col, Value, NewIndexes)
664
 
            end
665
 
    end.
666
 
 
667
 
%%------------------------------------------------------------------
668
 
%%  find_col(Col, Cols)
669
 
%%    undefined if a Col for column Col doesn't exist.
670
 
%%    {value, Val} if a Col for Col with value Val exists.
671
 
%%------------------------------------------------------------------
672
 
find_col(_Col, []) -> undefined;
673
 
find_col(Col, [{Col, Val} | _T]) -> {value, Val};
674
 
find_col(Col, [_H | T]) -> find_col(Col, T).
675
 
 
676
 
%%------------------------------------------------------------------
677
 
%%  check_mandatory_cols(ListOfCols, Cols)
678
 
%%     {noError 0}if all columns in ListOfCols are present in Cols.
679
 
%%     {inconsistentValue 0} otherwise. (Index = 0. It's hard to tell
680
 
%%        which Col is wrong, when the problem is that one is missing!)
681
 
%%------------------------------------------------------------------
682
 
% check_mandatory_cols([], _) -> {noError, 0};
683
 
% check_mandatory_cols(_, []) -> {inconsistentValue, 0};
684
 
% check_mandatory_cols([Col | Cols], [{Col, Val} | T]) ->
685
 
%     check_mandatory_cols(Cols, T);
686
 
% check_mandatory_cols([Col | Cols], [{Col2, Val} | T]) ->
687
 
%     check_mandatory_cols([Col | Cols], T).
688
 
 
689
 
 
690
 
try_apply(nofunc, _) -> {noError, 0};
691
 
try_apply(F, Args) -> apply(F, Args).
692
 
 
693
 
table_info({Name, _Db}) ->
694
 
    {value, TI} = snmp_symbolic_store:table_info(Name),
695
 
    TI;
696
 
table_info(Name) ->
697
 
    {value, TI} = snmp_symbolic_store:table_info(Name),
698
 
    TI.
699
 
 
700
 
variable_info({Name, _Db}) ->
701
 
    snmp_symbolic_store:variable_info(Name);
702
 
variable_info(NameDb) ->
703
 
    snmp_symbolic_store:variable_info(NameDb).
704
 
 
705
 
%%------------------------------------------------------------------
706
 
%% This function is a simple consistency check
707
 
%% function which could be used by the user-defined
708
 
%% table functions.
709
 
%% Check if the row has all information needed to
710
 
%% make row notInService (from notReady). This is
711
 
%% a simple check, which just checks if some col
712
 
%% in the row has the value 'noinit'.
713
 
%% If it has the information, the status is changed
714
 
%% to notInService.
715
 
%%------------------------------------------------------------------
716
 
table_try_make_consistent(Name, RowIndex, _Cols) ->
717
 
    TableInfo = table_info(Name),
718
 
    case TableInfo#table_info.status_col of
719
 
        StatusCol when integer(StatusCol) ->
720
 
            {value, StatusVal} = table_get_element(Name, RowIndex, StatusCol),
721
 
            table_try_make_consistent(Name, RowIndex, StatusVal, TableInfo);
722
 
        _ ->
723
 
            {noError, 0}
724
 
    end.
725
 
    
726
 
table_try_make_consistent(Name, RowIndex, ?'RowStatus_notReady', TableInfo) ->
727
 
%% this *should* be a generic function, but since mnesia got its own try_mk_cons
728
 
%% and I don't have time to impl table_get_row for mnesia I call snmp_local_db:
729
 
    Row = snmp_local_db:table_get_row(Name, RowIndex),
730
 
    case lists:member(noinit, tuple_to_list(Row)) of
731
 
        true -> {noError, 0};
732
 
        false -> 
733
 
            case catch table_set_element(Name, RowIndex,
734
 
                                         TableInfo#table_info.status_col,
735
 
                                         ?'RowStatus_notInService') of
736
 
                true -> {noError, 0};
737
 
                X -> 
738
 
                    user_err("snmp_generic:table_try_make_consistent "
739
 
                             "set ~w to notInService returned ~w",
740
 
                             [{Name, RowIndex}, X]),
741
 
                    {commitFailed, TableInfo#table_info.status_col}
742
 
            end
743
 
    end;
744
 
 
745
 
table_try_make_consistent(_Name, _RowIndex, _StatusVal, _TableInfo) ->
746
 
    {noError, 0}.
747
 
 
748
 
table_get_row({Name, mnesia}, RowIndex) ->
749
 
    snmp_generic_mnesia:table_get_row(Name, RowIndex);
750
 
table_get_row(NameDb, RowIndex) ->
751
 
    snmp_local_db:table_get_row(NameDb, RowIndex).
752
 
 
753
 
 
754
 
%%-----------------------------------------------------------------
755
 
%% Purpose: These functions can be used by the user's instrum func 
756
 
%%          to retrieve various table info.
757
 
%%-----------------------------------------------------------------
758
 
 
759
 
%%-----------------------------------------------------------------
760
 
%% Description:
761
 
%% Used by user's instrum func to check if mstatus column is 
762
 
%% modified.
763
 
%%-----------------------------------------------------------------
764
 
get_status_col(Name, Cols) ->
765
 
    #table_info{status_col = StatusCol} = table_info(Name),
766
 
    case lists:keysearch(StatusCol, 1, Cols) of
767
 
        {value, {StatusCol, Val}} -> {ok, Val};
768
 
        _ -> false
769
 
    end.
770
 
 
771
 
 
772
 
%%-----------------------------------------------------------------
773
 
%% Description:
774
 
%% Used by user's instrum func to get the table info. Specific parts
775
 
%% or all of it. If all is selected then the result will be a tagged
776
 
%% list of values.
777
 
%%-----------------------------------------------------------------
778
 
get_table_info(Name,nbr_of_cols) ->
779
 
    get_nbr_of_cols(Name);
780
 
get_table_info(Name,defvals) ->
781
 
    get_defvals(Name);
782
 
get_table_info(Name,status_col) ->
783
 
    get_status_col(Name);
784
 
get_table_info(Name,not_accessible) ->
785
 
    get_not_accessible(Name);
786
 
get_table_info(Name,index_types) ->
787
 
    get_index_types(Name);
788
 
get_table_info(Name,first_accessible) ->
789
 
    get_first_accessible(Name);
790
 
get_table_info(Name,first_own_index) ->
791
 
    get_first_own_index(Name);
792
 
get_table_info(Name,all) ->
793
 
    TableInfo = table_info(Name),
794
 
    [{nbr_of_cols,      TableInfo#table_info.nbr_of_cols},
795
 
     {defvals,          TableInfo#table_info.defvals},
796
 
     {status_col,       TableInfo#table_info.status_col},
797
 
     {not_accessible,   TableInfo#table_info.not_accessible},
798
 
     {index_types,      TableInfo#table_info.index_types},
799
 
     {first_accessible, TableInfo#table_info.first_accessible},
800
 
     {first_own_index,  TableInfo#table_info.first_own_index}].
801
 
 
802
 
 
803
 
%%-----------------------------------------------------------------
804
 
%% Description:
805
 
%% Used by user's instrum func to get the index types.
806
 
%%-----------------------------------------------------------------
807
 
get_index_types(Name) ->
808
 
    #table_info{index_types = IndexTypes} = table_info(Name),
809
 
    IndexTypes.
810
 
 
811
 
get_nbr_of_cols(Name) ->
812
 
    #table_info{nbr_of_cols = NumberOfCols} = table_info(Name),
813
 
    NumberOfCols.
814
 
 
815
 
get_defvals(Name) ->
816
 
    #table_info{defvals = DefVals} = table_info(Name),
817
 
    DefVals.
818
 
 
819
 
get_status_col(Name) ->
820
 
    #table_info{status_col = StatusCol} = table_info(Name),
821
 
    StatusCol.
822
 
 
823
 
get_not_accessible(Name) ->
824
 
    #table_info{not_accessible = NotAcc} = table_info(Name),
825
 
    NotAcc.
826
 
 
827
 
get_first_accessible(Name) ->
828
 
    #table_info{first_accessible = FirstAcc} = table_info(Name),
829
 
    FirstAcc.
830
 
 
831
 
get_first_own_index(Name) ->
832
 
    #table_info{first_own_index = FirstOwnIdx} = table_info(Name),
833
 
    FirstOwnIdx.
834
 
 
835
 
 
836
 
user_err(F, A) ->
837
 
    snmp_error_report:user_err(F, A).