~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/r9c_tests_SUITE_data/src/mnesia/mnesia_snmp_hook.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

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: mnesia_snmp_hook.erl,v 1.1 2008/12/17 09:53:39 mikpe Exp $
 
17
%%
 
18
-module(mnesia_snmp_hook).
 
19
 
 
20
%% Hooks (called from mnesia)
 
21
-export([check_ustruct/1, create_table/3, delete_table/2,
 
22
         key_to_oid/3, update/1, start/2,
 
23
         get_row/2, get_next_index/2, get_mnesia_key/2]).
 
24
 
 
25
%% sys callback functions
 
26
-export([system_continue/3,
 
27
         system_terminate/4,
 
28
         system_code_change/4
 
29
        ]).
 
30
 
 
31
%% Internal exports
 
32
-export([b_init/2]).
 
33
 
 
34
check_ustruct([]) ->
 
35
    true;  %% default value, not SNMP'ified
 
36
check_ustruct([{key, Types}]) -> 
 
37
    is_snmp_type(to_list(Types));
 
38
check_ustruct(_) -> false.
 
39
    
 
40
to_list(Tuple) when tuple(Tuple) -> tuple_to_list(Tuple);
 
41
to_list(X) -> [X].
 
42
 
 
43
is_snmp_type([integer | T]) -> is_snmp_type(T);
 
44
is_snmp_type([string | T]) -> is_snmp_type(T);
 
45
is_snmp_type([fix_string | T]) -> is_snmp_type(T);
 
46
is_snmp_type([]) -> true;
 
47
is_snmp_type(_) -> false.
 
48
 
 
49
create_table([], MnesiaTab, _Storage) ->
 
50
    mnesia:abort({badarg, MnesiaTab, {snmp, empty_snmpstruct}});
 
51
 
 
52
create_table([{key, Us}], MnesiaTab, Storage) ->
 
53
    Tree = b_new(MnesiaTab, Us),
 
54
    mnesia_lib:db_fixtable(Storage, MnesiaTab, true),
 
55
    First = mnesia_lib:db_first(Storage, MnesiaTab),
 
56
    build_table(First, MnesiaTab, Tree, Us, Storage),
 
57
    mnesia_lib:db_fixtable(Storage, MnesiaTab, false),
 
58
    Tree.
 
59
    
 
60
build_table(MnesiaKey, MnesiaTab, Tree, Us, Storage)
 
61
  when MnesiaKey /= '$end_of_table' ->
 
62
%%    SnmpKey = key_to_oid(MnesiaTab, MnesiaKey, Us),
 
63
%%    update(write, Tree, MnesiaKey, SnmpKey),
 
64
    update(write, Tree, MnesiaKey, MnesiaKey),
 
65
    Next = mnesia_lib:db_next_key(Storage, MnesiaTab, MnesiaKey), 
 
66
    build_table(Next, MnesiaTab, Tree, Us, Storage);
 
67
build_table('$end_of_table', _MnesiaTab, _Tree, _Us, _Storage) ->
 
68
    ok.
 
69
 
 
70
delete_table(_MnesiaTab, Tree) ->
 
71
    exit(Tree, shutdown),
 
72
    ok.
 
73
 
 
74
%%-----------------------------------------------------------------
 
75
%% update({Op, MnesiaTab, MnesiaKey, SnmpKey})
 
76
%%-----------------------------------------------------------------
 
77
   
 
78
update({clear_table, MnesiaTab}) ->
 
79
    Tree = mnesia_lib:val({MnesiaTab, {index, snmp}}),
 
80
    b_clear(Tree);
 
81
    
 
82
update({Op, MnesiaTab, MnesiaKey, SnmpKey}) ->
 
83
    Tree = mnesia_lib:val({MnesiaTab, {index, snmp}}),
 
84
    update(Op, Tree, MnesiaKey, SnmpKey).
 
85
 
 
86
update(Op, Tree, MnesiaKey, _) ->
 
87
    case Op of
 
88
        write ->
 
89
            b_insert(Tree, MnesiaKey, MnesiaKey);
 
90
        update_counter ->
 
91
            ignore;
 
92
        delete ->
 
93
            b_delete(Tree, MnesiaKey);
 
94
        delete_object ->
 
95
            b_delete(Tree, MnesiaKey)
 
96
    end,
 
97
    ok.
 
98
 
 
99
%%-----------------------------------------------------------------
 
100
%% Func: key_to_oid(Tab, Key, Ustruct)
 
101
%% Args: Key ::= key()
 
102
%%         key() ::= int() | string() | {int() | string()}
 
103
%%       Type ::= {fix_string | term()}
 
104
%% Make an OBJECT IDENTIFIER out of it.
 
105
%% Variable length objects are prepended by their length.
 
106
%% Ex. Key = {"pelle", 42} AND Type = {string, integer} =>
 
107
%%        OID [5, $p, $e, $l, $l, $e, 42]
 
108
%%     Key = {"pelle", 42} AND Type = {fix_string, integer} =>
 
109
%%        OID [$p, $e, $l, $l, $e, 42]
 
110
%%-----------------------------------------------------------------
 
111
key_to_oid(Tab, Key, [{key, Types}]) ->
 
112
    MnesiaOid = {Tab, Key},
 
113
    if
 
114
        tuple(Key), tuple(Types) ->
 
115
            case {size(Key), size(Types)} of
 
116
                {Size, Size} ->
 
117
                    keys_to_oid(MnesiaOid, Size, Key, [], Types);
 
118
                _ ->
 
119
                    exit({bad_snmp_key, MnesiaOid})
 
120
            end;
 
121
        true ->
 
122
            key_to_oid_i(MnesiaOid, Key, Types)
 
123
    end.
 
124
 
 
125
key_to_oid_i(_MnesiaOid, Key, integer) when integer(Key) -> [Key];
 
126
key_to_oid_i(_MnesiaOid, Key, fix_string) when list(Key) -> Key;
 
127
key_to_oid_i(_MnesiaOid, Key, string) when list(Key) -> [length(Key) | Key];
 
128
key_to_oid_i(MnesiaOid, Key, Type) ->
 
129
    exit({bad_snmp_key, [MnesiaOid, Key, Type]}).
 
130
 
 
131
keys_to_oid(_MnesiaOid, 0, _Key, Oid, _Types) -> Oid;
 
132
keys_to_oid(MnesiaOid, N, Key, Oid, Types) ->
 
133
    Type = element(N, Types),
 
134
    KeyPart = element(N, Key),
 
135
    Oid2 = key_to_oid_i(MnesiaOid, KeyPart, Type) ++ Oid,
 
136
    keys_to_oid(MnesiaOid, N-1, Key, Oid2, Types).
 
137
 
 
138
%%-----------------------------------------------------------------
 
139
%% Func: get_row/2
 
140
%% Args: Name is the name of the table (atom)
 
141
%%       RowIndex is an Oid
 
142
%% Returns: {ok, Row} | undefined
 
143
%%          Note that the Row returned might contain columns that
 
144
%%          are not visible via SNMP. e.g. the first column may be
 
145
%%          ifIndex, and the last MFA ({ifIndex, col1, col2, MFA}).
 
146
%%          where ifIndex is used only as index (not as a real col),
 
147
%%          and MFA as extra info, used by the application.
 
148
%%-----------------------------------------------------------------
 
149
get_row(Name, RowIndex) ->
 
150
    Tree = mnesia_lib:val({Name, {index, snmp}}),
 
151
    case b_lookup(Tree, RowIndex) of
 
152
        {ok, {_RowIndex, Key}} ->
 
153
            [Row] = mnesia:dirty_read({Name, Key}),
 
154
            {ok, Row};
 
155
        _ ->
 
156
            undefined
 
157
    end.
 
158
 
 
159
%%-----------------------------------------------------------------
 
160
%% Func: get_next_index/2
 
161
%% Args: Name is the name of the table (atom)
 
162
%%       RowIndex is an Oid
 
163
%% Returns: {ok, NextIndex} | endOfTable
 
164
%%-----------------------------------------------------------------
 
165
get_next_index(Name, RowIndex) ->
 
166
    Tree = mnesia_lib:val({Name, {index, snmp}}),
 
167
    case b_lookup_next(Tree, RowIndex) of
 
168
        {ok, {NextIndex, _Key}} ->
 
169
            {ok, NextIndex};
 
170
        _ ->
 
171
            endOfTable
 
172
    end.
 
173
 
 
174
%%-----------------------------------------------------------------
 
175
%% Func: get_mnesia_key/2
 
176
%% Purpose: Get the mnesia key corresponding to the RowIndex.
 
177
%% Args: Name is the name of the table (atom)
 
178
%%       RowIndex is an Oid
 
179
%% Returns: {ok, Key} | undefiend
 
180
%%-----------------------------------------------------------------
 
181
get_mnesia_key(Name, RowIndex) ->
 
182
    Tree = mnesia_lib:val({Name, {index, snmp}}),
 
183
    case b_lookup(Tree, RowIndex) of
 
184
        {ok, {_RowIndex, Key}} ->
 
185
            {ok, Key};
 
186
        _ ->
 
187
            undefined
 
188
    end.
 
189
 
 
190
%%-----------------------------------------------------------------
 
191
%% Encapsulate a bplus_tree in a process.
 
192
%%-----------------------------------------------------------------
 
193
 
 
194
b_new(MnesiaTab, Us) ->
 
195
    case supervisor:start_child(mnesia_snmp_sup, [MnesiaTab, Us]) of
 
196
        {ok, Tree} ->
 
197
            Tree;
 
198
        {error, Reason} ->
 
199
            exit({badsnmp, MnesiaTab, Reason})
 
200
    end.
 
201
 
 
202
start(MnesiaTab, Us) ->
 
203
    Name = {mnesia_snmp, MnesiaTab},
 
204
    mnesia_monitor:start_proc(Name, ?MODULE, b_init, [self(), Us]).
 
205
 
 
206
b_insert(Tree, Key, Val) -> Tree ! {insert, Key, Val}.
 
207
b_delete(Tree, Key) -> Tree ! {delete, Key}.
 
208
b_lookup(Tree, Key) ->
 
209
    Tree ! {lookup, self(), Key},
 
210
    receive
 
211
        {bplus_res, Res} ->
 
212
            Res
 
213
    end.
 
214
b_lookup_next(Tree, Key) ->
 
215
    Tree ! {lookup_next, self(), Key},
 
216
    receive
 
217
        {bplus_res, Res} ->
 
218
            Res
 
219
    end.
 
220
 
 
221
b_clear(Tree) ->
 
222
    Tree ! clear,
 
223
    ok.
 
224
 
 
225
b_init(Parent, Us) ->
 
226
    %% Do not trap exit
 
227
    Tree = snmp_index:new(Us),
 
228
    proc_lib:init_ack(Parent, {ok, self()}),
 
229
    b_loop(Parent, Tree, Us).
 
230
 
 
231
b_loop(Parent, Tree, Us) ->
 
232
    receive
 
233
        {insert, Key, Val} ->
 
234
            NTree = snmp_index:insert(Tree, Key, Val),
 
235
            b_loop(Parent, NTree, Us);
 
236
        {delete, Key} ->
 
237
            NTree = snmp_index:delete(Tree, Key),
 
238
            b_loop(Parent, NTree, Us);
 
239
        {lookup, From, Key} ->
 
240
            Res = snmp_index:get(Tree, Key),
 
241
            From ! {bplus_res, Res},
 
242
            b_loop(Parent, Tree, Us);
 
243
        {lookup_next, From, Key} ->
 
244
            Res = snmp_index:get_next(Tree, Key),
 
245
            From ! {bplus_res, Res},
 
246
            b_loop(Parent, Tree, Us);
 
247
        clear ->
 
248
            catch snmp_index:delete(Tree), %% Catch because delete/1 is not 
 
249
            NewTree = snmp_index:new(Us),  %% available in old snmp (before R5)
 
250
            b_loop(Parent, NewTree, Us);
 
251
        
 
252
        {'EXIT', Parent, Reason} ->
 
253
            exit(Reason);
 
254
 
 
255
        {system, From, Msg} ->
 
256
            mnesia_lib:dbg_out("~p got {system, ~p, ~p}~n", [?MODULE, From, Msg]),
 
257
            sys:handle_system_msg(Msg, From, Parent, ?MODULE, [], {Tree, Us})
 
258
        
 
259
    end.
 
260
 
 
261
%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
262
%% System upgrade
 
263
 
 
264
system_continue(Parent, _Debug, {Tree, Us}) ->
 
265
    b_loop(Parent, Tree, Us).
 
266
 
 
267
system_terminate(Reason, _Parent, _Debug, _Tree) ->
 
268
    exit(Reason).
 
269
 
 
270
system_code_change(State, _Module, _OldVsn, _Extra) ->
 
271
    {ok, State}.