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

« back to all changes in this revision

Viewing changes to lib/snmp/src/agent/snmp_generic_mnesia.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_mnesia).
 
19
 
 
20
-export([variable_get/1, variable_set/2, variable_inc/2]).
 
21
-export([table_func/2, table_func/4, 
 
22
         table_set_cols/4, table_set_element/4, table_set_elements/3,
 
23
         table_get_elements/4, table_get_row/2, table_get_row/3,
 
24
         table_next/2,table_set_status/7,
 
25
         table_try_make_consistent/2,
 
26
         table_delete_row/2]).
 
27
 
 
28
-include("STANDARD-MIB.hrl").
 
29
-include("snmp_types.hrl").
 
30
%% -include("snmp_generic.hrl").
 
31
 
 
32
%%%-----------------------------------------------------------------
 
33
%%% Generic functions for implementing software tables
 
34
%%% and variables.  Mnesia is used.
 
35
%%%-----------------------------------------------------------------
 
36
 
 
37
%%------------------------------------------------------------------
 
38
%% Theses functions could be in the MIB for simple 
 
39
%% variables or tables, i.e. vars without complex 
 
40
%% set-operations. If there are complex set op, an
 
41
%% extra layer-function should be added, and that
 
42
%% function should be in the MIB, and it can call these
 
43
%% functions.
 
44
%%------------------------------------------------------------------
 
45
 
 
46
%%------------------------------------------------------------------
 
47
%% Variables
 
48
%%------------------------------------------------------------------
 
49
%%------------------------------------------------------------------
 
50
%% This is the default function for variables.
 
51
%%------------------------------------------------------------------
 
52
variable_get(Name) ->
 
53
    case mnesia:dirty_read({snmp_variables, Name}) of
 
54
        [{_Db, _Name, Val}] -> {value, Val};
 
55
        _ -> undefined
 
56
    end.
 
57
 
 
58
variable_set(Name, Val) ->
 
59
    mnesia:dirty_write({snmp_variables, Name, Val}),
 
60
    true.
 
61
 
 
62
variable_inc(Name, N) ->
 
63
    case mnesia:dirty_update_counter({snmp_variables, Name}, N) of
 
64
        NewVal when NewVal < 4294967296 ->
 
65
            ok;
 
66
        NewVal ->
 
67
            mnesia:dirty_write({snmp_variables, Name, NewVal rem 4294967296})
 
68
    end.
 
69
 
 
70
%%------------------------------------------------------------------
 
71
%% Tables
 
72
%% Assumes the RowStatus is the last column in the
 
73
%% table.
 
74
%%------------------------------------------------------------------
 
75
%%------------------------------------------------------------------
 
76
%% This is the default function for tables.
 
77
%%
 
78
%% Name       is the name of the table (atom)
 
79
%% RowIndex   is a flat list of the indexes for the row.
 
80
%% Cols       is a list of column numbers.
 
81
%%------------------------------------------------------------------
 
82
table_func(new, _Name) ->
 
83
    ok;
 
84
 
 
85
table_func(delete, _Name) ->
 
86
    ok.
 
87
 
 
88
table_func(get, RowIndex, Cols, Name) ->
 
89
    TableInfo = snmp_generic:table_info(Name),
 
90
    snmp_generic:handle_table_get({Name, mnesia}, RowIndex, Cols,
 
91
                                  TableInfo#table_info.first_own_index);
 
92
 
 
93
%%------------------------------------------------------------------
 
94
%% Returns: List of endOfTable | {NextOid, Value}.
 
95
%% Implements the next operation, with the function
 
96
%% handle_table_next. Next should return the next accessible
 
97
%% instance, which cannot be a key (well, it could, but it
 
98
%% shouldn't).
 
99
%%------------------------------------------------------------------
 
100
table_func(get_next, RowIndex, Cols, Name) ->
 
101
    #table_info{first_accessible = FirstCol, first_own_index = FOI,
 
102
                nbr_of_cols = LastCol} = snmp_generic:table_info(Name),
 
103
    snmp_generic:handle_table_next({Name,mnesia},RowIndex,Cols,
 
104
                                   FirstCol, FOI, LastCol);
 
105
 
 
106
table_func(is_set_ok, RowIndex, Cols, Name) ->
 
107
    snmp_generic:table_try_row({Name, mnesia}, nofunc, RowIndex, Cols);
 
108
 
 
109
%%------------------------------------------------------------------
 
110
%% Cols is here a list of {ColumnNumber, NewValue}
 
111
%% This function must only be used by tables with a RowStatus col!
 
112
%% Other tables should use table_set_cols/4.
 
113
%% All set functionality is handled within a transaction.
 
114
%%
 
115
%% GenericMnesia uses its own table_set_status and own table_try_make_consistent
 
116
%% for performance reasons.
 
117
%%------------------------------------------------------------------
 
118
table_func(set, RowIndex, Cols, Name) ->
 
119
    case mnesia:transaction(
 
120
           fun() ->
 
121
                   snmp_generic:table_set_row(
 
122
                     {Name, mnesia}, nofunc,
 
123
                     {snmp_generic_mnesia, table_try_make_consistent},
 
124
                     RowIndex, Cols)
 
125
           end) of
 
126
        {atomic, Value} ->
 
127
            Value;
 
128
        {aborted, Reason} ->
 
129
            user_err("set transaction aborted. Tab ~w, RowIndex"
 
130
                     " ~w, Cols ~w. Reason ~w",
 
131
                     [Name, RowIndex, Cols, Reason]),
 
132
            {Col, _Val} = hd(Cols),
 
133
            {commitFailed, Col}
 
134
    end;
 
135
 
 
136
table_func(undo, _RowIndex, _Cols, _Name) ->
 
137
    {noError, 0}.
 
138
 
 
139
 
 
140
table_get_row(Name, RowIndex) ->
 
141
    case mnesia:snmp_get_row(Name, RowIndex) of
 
142
        {ok, DbRow} ->
 
143
            TableInfo = snmp_generic:table_info(Name),
 
144
            make_row(DbRow, TableInfo#table_info.first_own_index);
 
145
        undefined ->
 
146
            undefined
 
147
    end.
 
148
table_get_row(Name, RowIndex, FOI) ->
 
149
    case mnesia:snmp_get_row(Name, RowIndex) of
 
150
        {ok, DbRow} ->
 
151
            make_row(DbRow, FOI);
 
152
        undefined ->
 
153
            undefined
 
154
    end.
 
155
 
 
156
%%-----------------------------------------------------------------
 
157
%% Returns: [Val | noacc | noinit] | undefined
 
158
%%-----------------------------------------------------------------
 
159
table_get_elements(Name, RowIndex, Cols, FirstOwnIndex) ->
 
160
    case mnesia:snmp_get_row(Name, RowIndex) of
 
161
        {ok, DbRow} ->
 
162
            Row = make_row(DbRow, FirstOwnIndex),
 
163
            get_elements(Cols, Row);
 
164
        undefined ->
 
165
            undefined
 
166
    end.
 
167
 
 
168
get_elements([Col | Cols], Row) ->
 
169
    [element(Col, Row) | get_elements(Cols, Row)];
 
170
get_elements([], _Row) -> [].
 
171
 
 
172
%%-----------------------------------------------------------------
 
173
%% Args: DbRow is a mnesia row ({name, Keys, Cols, ...}).
 
174
%% Returns: A tuple with a SNMP-table row. Each SNMP-col is one
 
175
%%          element, list or int.
 
176
%%-----------------------------------------------------------------
 
177
make_row(DbRow, 0) ->
 
178
    [_Name, _Keys | Cols] = tuple_to_list(DbRow),
 
179
    list_to_tuple(Cols);
 
180
make_row(DbRow, FirstOwnIndex) ->
 
181
    list_to_tuple(make_row2(make_row_list(DbRow), FirstOwnIndex)).
 
182
make_row2(RowList, 1) -> RowList;
 
183
make_row2([_OtherIndex | RowList], N) ->
 
184
    make_row2(RowList, N-1).
 
185
 
 
186
make_row_list(Row) ->
 
187
    make_row_list(size(Row), Row, []).
 
188
make_row_list(N, Row, Acc) when N > 2 ->
 
189
    make_row_list(N-1, Row, [element(N, Row) | Acc]);
 
190
make_row_list(2, Row, Acc) ->
 
191
    case element(2, Row) of
 
192
        Keys when tuple(Keys) ->
 
193
            lists:append(tuple_to_list(Keys), Acc);
 
194
        Key ->
 
195
            [Key | Acc]
 
196
    end.
 
197
 
 
198
%% createAndGo
 
199
table_set_status(Name, RowIndex, ?'RowStatus_createAndGo', _StatusCol, Cols, 
 
200
                 ChangedStatusFunc, _ConsFunc) ->
 
201
    Row = table_construct_row(Name, RowIndex, ?'RowStatus_active', Cols),
 
202
    mnesia:write(Row),
 
203
    snmp_generic:try_apply(ChangedStatusFunc, [Name, ?'RowStatus_createAndGo',
 
204
                                               RowIndex, Cols]);
 
205
 
 
206
%%------------------------------------------------------------------
 
207
%% createAndWait - set status to notReady, and try to 
 
208
%% make row consistent.
 
209
%%------------------------------------------------------------------
 
210
table_set_status(Name, RowIndex, ?'RowStatus_createAndWait', _StatusCol, 
 
211
                 Cols, ChangedStatusFunc, ConsFunc) ->
 
212
    Row = table_construct_row(Name, RowIndex, ?'RowStatus_notReady', Cols),
 
213
    mnesia:write(Row),
 
214
    case snmp_generic:try_apply(ConsFunc, [RowIndex, Row]) of
 
215
        {noError, 0} -> snmp_generic:try_apply(ChangedStatusFunc, 
 
216
                                               [Name, ?'RowStatus_createAndWait',
 
217
                                                RowIndex, Cols]);
 
218
        Error -> Error
 
219
    end;
 
220
    
 
221
%% destroy
 
222
table_set_status(Name, RowIndex, ?'RowStatus_destroy', _StatusCol, Cols,
 
223
                 ChangedStatusFunc, _ConsFunc) ->
 
224
    case snmp_generic:try_apply(ChangedStatusFunc,
 
225
                                [Name, ?'RowStatus_destroy', RowIndex, Cols]) of
 
226
        {noError, 0} ->
 
227
            #table_info{index_types = Indexes} = snmp_generic:table_info(Name),
 
228
            Key = 
 
229
                case snmp_generic:split_index_to_keys(Indexes, RowIndex) of
 
230
                    [Key1] -> Key1;
 
231
                    KeyList -> list_to_tuple(KeyList)
 
232
                end,
 
233
            mnesia:delete({Name, Key}),
 
234
            {noError, 0};
 
235
        Error -> Error
 
236
    end;
 
237
 
 
238
%% Otherwise, active or notInService
 
239
table_set_status(Name, RowIndex, Val, _StatusCol, Cols,
 
240
                 ChangedStatusFunc, ConsFunc) ->
 
241
    table_set_cols(Name, RowIndex, Cols, ConsFunc),
 
242
    snmp_generic:try_apply(ChangedStatusFunc, [Name, Val, RowIndex, Cols]).
 
243
 
 
244
table_delete_row(Name, RowIndex) ->
 
245
    case mnesia:snmp_get_mnesia_key(Name, RowIndex) of
 
246
        {ok, Key} ->
 
247
            mnesia:delete({Name, Key});
 
248
        undefined ->
 
249
            ok
 
250
    end.
 
251
 
 
252
 
 
253
%%------------------------------------------------------------------
 
254
%% This function is a simple consistency check
 
255
%% function which could be used by the user-defined
 
256
%% table functions.
 
257
%% Check if the row has all information needed to
 
258
%% make row notInService (from notReady). This is
 
259
%% a simple check, which just checks if some col
 
260
%% in the row has the value 'noinit'.
 
261
%% If it has the information, the status is changed
 
262
%% to notInService.
 
263
%%------------------------------------------------------------------
 
264
table_try_make_consistent(RowIndex, NewDbRow) ->
 
265
    Name = element(1, NewDbRow),
 
266
    #table_info{first_own_index = FirstOwnIndex,
 
267
                status_col = StatusCol, index_types = IT} = 
 
268
        snmp_generic:table_info(Name),
 
269
    if
 
270
        integer(StatusCol) ->
 
271
            NewRow = make_row(NewDbRow, FirstOwnIndex),
 
272
            StatusVal = element(StatusCol, NewRow),
 
273
            AddCol = if
 
274
                         FirstOwnIndex == 0 -> 2;
 
275
                         true -> 1 + FirstOwnIndex - length(IT)
 
276
                     end,
 
277
            table_try_make_consistent(Name, RowIndex, NewRow, NewDbRow, 
 
278
                                      AddCol, StatusCol, StatusVal);
 
279
        true ->
 
280
            {noError, 0}
 
281
    end.
 
282
 
 
283
    
 
284
table_try_make_consistent(Name, RowIndex, NewRow, NewDbRow, 
 
285
                          AddCol, StatusCol, ?'RowStatus_notReady') ->
 
286
    case lists:member(noinit, tuple_to_list(NewRow)) of
 
287
        true -> {noError, 0};
 
288
        false -> 
 
289
            table_set_element(Name, RowIndex, StatusCol,
 
290
                              ?'RowStatus_notInService'),
 
291
            NewDbRow2 = set_new_row([{StatusCol, ?'RowStatus_notInService'}],
 
292
                                    AddCol, NewDbRow),
 
293
            mnesia:write(NewDbRow2),
 
294
            {noError, 0}
 
295
    end;
 
296
 
 
297
table_try_make_consistent(_Name, _RowIndex, _NewRow, _NewDBRow,
 
298
                          _AddCol, _StatusCol, _StatusVal) ->
 
299
    {noError, 0}.
 
300
 
 
301
%%------------------------------------------------------------------
 
302
%%  Constructs a row that is to be stored in Mnesia, i.e.
 
303
%%  {Name, Key, Col1, ...} |
 
304
%%  {Name, {Key1, Key2, ..}, ColN, ColN+1...}
 
305
%%  dynamic key values are stored without length first.
 
306
%%  RowIndex is a list of the first elements. RowStatus is needed,
 
307
%%  because the provided value may not be stored, e.g. createAndGo
 
308
%%  should be active. If a value isn't specified in the Col list,
 
309
%%  then the corresponding value will be noinit.
 
310
%%------------------------------------------------------------------
 
311
table_construct_row(Name, RowIndex, Status, Cols) ->
 
312
    #table_info{nbr_of_cols = LastCol, index_types = Indexes,
 
313
                defvals = Defs, status_col = StatusCol,
 
314
                first_own_index = FirstOwnIndex, not_accessible = NoAccs} =
 
315
        snmp_generic:table_info(Name),
 
316
    KeyList = snmp_generic:split_index_to_keys(Indexes, RowIndex),
 
317
    OwnKeyList = snmp_generic:get_own_indexes(FirstOwnIndex, KeyList),
 
318
    StartCol = length(OwnKeyList) + 1,
 
319
    RowList = snmp_generic:table_create_rest(StartCol, LastCol, 
 
320
                                             StatusCol, Status, Cols, NoAccs),
 
321
    L = snmp_generic:init_defaults(Defs, RowList, StartCol),
 
322
    Keys = case KeyList of
 
323
               [H] -> H;
 
324
               _ -> list_to_tuple(KeyList)
 
325
           end,
 
326
    list_to_tuple([Name, Keys | L]).
 
327
 
 
328
%%------------------------------------------------------------------
 
329
%% table_set_cols/4
 
330
%% can be used by the set procedure of all tables
 
331
%% to set all columns in Cols, one at a time.
 
332
%% ConsFunc is a check-consistency function, which will
 
333
%% be called with the RowIndex of this row, when
 
334
%% all columns are set. This is useful when the RowStatus
 
335
%% could change, e.g. if the manager has provided all
 
336
%% mandatory columns in this set operation.
 
337
%% If ConsFunc is nofunc, no function will be called after all
 
338
%% sets.
 
339
%% Returns: {noError, 0} | {Error, Col}
 
340
%%------------------------------------------------------------------
 
341
table_set_cols(Name, RowIndex, Cols, ConsFunc) ->
 
342
    table_set_elements(Name, RowIndex, Cols, ConsFunc).
 
343
    
 
344
%%-----------------------------------------------------------------
 
345
%% Col is _not_ a key column. A row in the db is stored as
 
346
%% {Name, {Key1, Key2,...}, Col1, Col2, ...}
 
347
%%-----------------------------------------------------------------
 
348
table_set_element(Name, RowIndex, Col, NewVal) ->
 
349
    #table_info{index_types = Indexes, first_own_index = FirstOwnIndex} =
 
350
        snmp_generic:table_info(Name),
 
351
    DbCol = if
 
352
                FirstOwnIndex == 0 -> Col + 2;
 
353
                true -> 1 + FirstOwnIndex - length(Indexes) + Col
 
354
            end,
 
355
    case mnesia:snmp_get_row(Name, RowIndex) of
 
356
        {ok, DbRow} ->
 
357
            NewDbRow = setelement(DbCol, DbRow, NewVal),
 
358
            mnesia:write(NewDbRow),
 
359
            true;
 
360
        undefined ->
 
361
            false
 
362
    end.
 
363
 
 
364
table_set_elements(Name, RowIndex, Cols) ->
 
365
    case table_set_elements(Name, RowIndex, Cols, nofunc) of
 
366
        {noError, 0} -> true;
 
367
        _ -> false
 
368
    end.
 
369
table_set_elements(Name, RowIndex, Cols, ConsFunc) ->
 
370
    #table_info{index_types = Indexes, first_own_index = FirstOwnIndex} =
 
371
        snmp_generic:table_info(Name),
 
372
    AddCol = if
 
373
                 FirstOwnIndex == 0 -> 2;
 
374
                 true -> 1 + FirstOwnIndex - length(Indexes)
 
375
             end,
 
376
    case mnesia:snmp_get_row(Name, RowIndex) of
 
377
        {ok, DbRow} ->
 
378
            NewDbRow = set_new_row(Cols, AddCol, DbRow),
 
379
            mnesia:write(NewDbRow),
 
380
            snmp_generic:try_apply(ConsFunc, [RowIndex, NewDbRow]);
 
381
        undefined ->
 
382
            {Col, _Val} = hd(Cols),
 
383
            {commitFailed, Col}
 
384
    end.
 
385
 
 
386
set_new_row([{Col, Val} | Cols], AddCol, Row) ->
 
387
    set_new_row(Cols, AddCol, setelement(Col+AddCol, Row, Val));
 
388
set_new_row([], _AddCol, Row) ->
 
389
    Row.
 
390
 
 
391
table_next(Name, RestOid) ->
 
392
    case mnesia:snmp_get_next_index(Name, RestOid) of
 
393
        {ok, NextIndex} -> NextIndex;
 
394
        endOfTable -> endOfTable
 
395
    end.
 
396
 
 
397
 
 
398
user_err(F, A) ->
 
399
    snmpa_error:user_err(F, A).