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

« back to all changes in this revision

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