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

« back to all changes in this revision

Viewing changes to lib/snmp/src/agent/snmpa_vacm.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(snmpa_vacm).
 
19
 
 
20
-export([get_mib_view/5]).
 
21
-export([init/1, init/2, backup/1]).
 
22
-export([delete/1, get_row/1, get_next_row/1, insert/1, insert/2,
 
23
         dump_table/0]).
 
24
 
 
25
-include("SNMPv2-TC.hrl").
 
26
-include("SNMP-VIEW-BASED-ACM-MIB.hrl").
 
27
-include("SNMP-FRAMEWORK-MIB.hrl").
 
28
-include("snmp_types.hrl").
 
29
-include("snmpa_vacm.hrl").
 
30
 
 
31
-define(VMODULE,"VACM").
 
32
-include("snmp_verbosity.hrl").
 
33
 
 
34
 
 
35
%%%-----------------------------------------------------------------
 
36
%%% Access Control Module for VACM  (see also snmpa_acm)
 
37
%%% This module implements:
 
38
%%%   1. access control functions for VACM
 
39
%%%   2. vacmAccessTable as an ordered ets table
 
40
%%%
 
41
%%% This version of VACM handles v1, v2c and v3.
 
42
%%%-----------------------------------------------------------------
 
43
 
 
44
%%%-----------------------------------------------------------------
 
45
%%%   1.  access control functions for VACM
 
46
%%%-----------------------------------------------------------------
 
47
%%-----------------------------------------------------------------
 
48
%% Func: get_mib_view/5 -> {ok, ViewName} | 
 
49
%%                         {discarded, Reason}
 
50
%% Types: ViewType    = read | write | notify
 
51
%%        SecModel    = ?SEC_*  (see snmp_types.hrl)
 
52
%%        SecName     = string()
 
53
%%        SecLevel    = ?'SnmpSecurityLevel_*' (see SNMP-FRAMEWORK-MIB.hrl)
 
54
%%        ContextName = string()
 
55
%% Purpose: This function is used to map VACM parameters to a mib
 
56
%%          view.
 
57
%%-----------------------------------------------------------------
 
58
get_mib_view(ViewType, SecModel, SecName, SecLevel, ContextName) ->
 
59
    check_auth(catch auth(ViewType, SecModel, SecName, SecLevel, ContextName)).
 
60
 
 
61
 
 
62
%% Follows the procedure in rfc2275
 
63
auth(ViewType, SecModel, SecName, SecLevel, ContextName) ->
 
64
    % 3.2.1 - Check that the context is known to us
 
65
    ?vdebug("check that the context (~p) is known to us",[ContextName]),
 
66
    case snmp_view_based_acm_mib:vacmContextTable(get, ContextName,
 
67
                                                  [?vacmContextName]) of
 
68
        [_Found] ->
 
69
            ok;
 
70
        _ ->
 
71
            snmpa_mpd:inc(snmpUnknownContexts),
 
72
            throw({discarded, noSuchContext})
 
73
    end,
 
74
    % 3.2.2 - Check that the SecModel and SecName is valid
 
75
    ?vdebug("check that SecModel (~p) and SecName (~p) is valid",
 
76
            [SecModel,SecName]),
 
77
    GroupName = 
 
78
        case snmp_view_based_acm_mib:get(vacmSecurityToGroupTable, 
 
79
                                         [SecModel, length(SecName) | SecName],
 
80
                 [?vacmGroupName, ?vacmSecurityToGroupStatus]) of
 
81
            [{value, GN}, {value, ?'RowStatus_active'}] ->
 
82
                GN;
 
83
            [{value, _GN}, {value, RowStatus}] ->
 
84
                ?vlog("valid SecModel and SecName but wrong row status:"
 
85
                      "~n   RowStatus: ~p", [RowStatus]),
 
86
                throw({discarded, noGroupName});
 
87
            _ ->
 
88
                throw({discarded, noGroupName})
 
89
        end,
 
90
    % 3.2.3-4 - Find an access entry and its view name
 
91
    ?vdebug("find an access entry and its view name",[]),
 
92
    ViewName =
 
93
        case get_view_name(ViewType, GroupName, ContextName,
 
94
                           SecModel, SecLevel) of
 
95
            {ok, VN} -> VN;
 
96
            Error -> throw(Error)
 
97
        end,
 
98
    % 3.2.5a - Find the corresponding mib view
 
99
    ?vdebug("find the corresponding mib view (for ~p)",[ViewName]),
 
100
    get_mib_view(ViewName).
 
101
 
 
102
check_auth({'EXIT',    Error})  -> exit(Error);
 
103
check_auth({discarded, Reason}) -> {discarded, Reason};
 
104
check_auth(Res)                 -> {ok, Res}.
 
105
 
 
106
%%-----------------------------------------------------------------
 
107
%% Returns a list of {ViewSubtree, ViewMask, ViewType}
 
108
%% The view table is index by ViewIndex, ViewSubtree,
 
109
%% so a next on ViewIndex returns the first
 
110
%% key in the table >= ViewIndex.
 
111
%%-----------------------------------------------------------------
 
112
get_mib_view(ViewName) ->
 
113
    ViewKey = [length(ViewName) | ViewName],
 
114
    case snmp_view_based_acm_mib:table_next(vacmViewTreeFamilyTable,
 
115
                                            ViewKey) of
 
116
        endOfTable ->
 
117
            {discarded, noSuchView};
 
118
        Indexes ->
 
119
            case split_prefix(ViewKey, Indexes) of
 
120
                {ok, Subtree} ->
 
121
                    loop_mib_view(ViewKey, Subtree, Indexes, []);
 
122
                false ->
 
123
                    {discarded, noSuchView}
 
124
            end
 
125
    end.
 
126
 
 
127
split_prefix([H|T], [H|T2]) -> split_prefix(T,T2);
 
128
split_prefix([], Rest) -> {ok, Rest};
 
129
split_prefix(_, _) -> false.
 
130
    
 
131
 
 
132
%% ViewName is including length from now on
 
133
loop_mib_view(ViewName, Subtree, Indexes, MibView) ->
 
134
    [{value, Mask}, {value, Type}, {value, Status}] = 
 
135
        snmp_view_based_acm_mib:vacmViewTreeFamilyTable(
 
136
          get, Indexes,
 
137
          [?vacmViewTreeFamilyMask, 
 
138
           ?vacmViewTreeFamilyType,
 
139
           ?vacmViewTreeFamilyStatus]),
 
140
    NextMibView = 
 
141
        case Status of
 
142
            ?'RowStatus_active' ->
 
143
                [_Length | Tree] = Subtree,
 
144
                [{Tree, Mask, Type} | MibView];
 
145
            _ ->
 
146
                MibView
 
147
        end,
 
148
    case snmp_view_based_acm_mib:table_next(vacmViewTreeFamilyTable, 
 
149
                                            Indexes) of
 
150
        endOfTable -> NextMibView;
 
151
        NextIndexes ->
 
152
            case split_prefix(ViewName, NextIndexes) of
 
153
                {ok, NextSubTree} ->
 
154
                    loop_mib_view(ViewName, NextSubTree, NextIndexes,
 
155
                                  NextMibView);
 
156
                false ->
 
157
                    NextMibView
 
158
            end
 
159
    end.
 
160
 
 
161
%%%-----------------------------------------------------------------
 
162
%%%  1b.  The ordered ets table that implements vacmAccessTable
 
163
%%%-----------------------------------------------------------------
 
164
 
 
165
init(Dir) ->
 
166
    init(Dir, terminate).
 
167
 
 
168
init(Dir, InitError) ->
 
169
    FName = filename:join(Dir, "snmpa_vacm.db"),
 
170
    case file:read_file_info(FName) of
 
171
        {ok, _} -> 
 
172
            %% File exists - we must check this, since ets doesn't tell
 
173
            %% us the reason in case of error...
 
174
            case ets:file2tab(FName) of
 
175
                {ok, _Tab} -> 
 
176
                    gc_tab([]);
 
177
                {error, Reason} ->
 
178
                    user_err("Corrupt VACM database ~p", [FName]),
 
179
                    case InitError of
 
180
                        terminate ->
 
181
                            throw({error, {file2tab, FName, Reason}});
 
182
                        _ ->
 
183
                            %% Rename old file (for later analyzes)
 
184
                            Saved = FName ++ ".saved",
 
185
                            file:rename(FName, Saved),
 
186
                            ets:new(snmpa_vacm, 
 
187
                                    [public, ordered_set, named_table])
 
188
                    end
 
189
            end;
 
190
        {error, _} ->
 
191
            ets:new(snmpa_vacm, [public, ordered_set, named_table])
 
192
    end,
 
193
    ets:insert(snmp_agent_table, {snmpa_vacm_file, FName}),
 
194
    {ok, FName}.
 
195
 
 
196
 
 
197
backup(BackupDir) ->
 
198
    BackupFile = filename:join(BackupDir, "snmpa_vacm.db"),
 
199
    ets:tab2file(snmpa_vacm, BackupFile).
 
200
 
 
201
 
 
202
%% Ret: {ok, ViewName} | {error, Reason}
 
203
get_view_name(ViewType, GroupName, ContextName, SecModel, SecLevel) ->
 
204
    GroupKey = [length(GroupName) | GroupName],
 
205
    case get_access_row(GroupKey, ContextName, SecModel, SecLevel) of
 
206
        undefined ->
 
207
            {discarded, noAccessEntry};
 
208
        Row ->
 
209
            ?vtrace("get_view_name -> Row: ~n   ~p", [Row]),
 
210
            ViewName =
 
211
                case ViewType of
 
212
                    read -> element(?vacmAReadViewName, Row);
 
213
                    write -> element(?vacmAWriteViewName, Row);
 
214
                    notify -> element(?vacmANotifyViewName, Row)
 
215
                end,
 
216
            case ViewName of
 
217
                "" -> 
 
218
                    ?vtrace("get_view_name -> not found when"
 
219
                            "~n   ViewType:    ~p"
 
220
                            "~n   GroupName:   ~p"
 
221
                            "~n   ContextName: ~p"
 
222
                            "~n   SecModel:    ~p"
 
223
                            "~n   SecLevel:    ~p", [ViewType, GroupName, 
 
224
                                                     ContextName, SecModel, 
 
225
                                                     SecLevel]),
 
226
                    {discarded, noSuchView};
 
227
                _ -> {ok, ViewName}
 
228
            end
 
229
    end.
 
230
 
 
231
 
 
232
get_row(Key) -> 
 
233
    case ets:lookup(snmpa_vacm, Key) of
 
234
        [{_Key, Row}] -> {ok, Row};
 
235
        _ -> false
 
236
    end.
 
237
 
 
238
get_next_row(Key) ->
 
239
    case ets:next(snmpa_vacm, Key) of
 
240
        '$end_of_table' -> false;
 
241
        NextKey  ->
 
242
            case ets:lookup(snmpa_vacm, NextKey) of
 
243
                [Entry] -> Entry;
 
244
                _ -> false
 
245
            end
 
246
    end.
 
247
 
 
248
insert(Entries) -> insert(Entries, true).
 
249
 
 
250
insert(Entries, Dump) ->
 
251
    lists:foreach(fun(Entry) -> ets:insert(snmpa_vacm, Entry) end, Entries),
 
252
    dump_table(Dump).
 
253
 
 
254
delete(Key) ->
 
255
    ets:delete(snmpa_vacm, Key),
 
256
    dump_table().
 
257
 
 
258
dump_table(true) ->
 
259
    dump_table();
 
260
dump_table(_) ->
 
261
    ok.
 
262
 
 
263
dump_table() ->
 
264
    [{_, FName}] = ets:lookup(snmp_agent_table, snmpa_vacm_file),
 
265
    TmpName = FName ++ ".tmp",
 
266
    case ets:tab2file(snmpa_vacm, TmpName) of
 
267
        ok ->
 
268
            case file:rename(TmpName, FName) of
 
269
                ok ->
 
270
                    ok;
 
271
                Else -> % What is this? Undocumented return code...
 
272
                    user_err("Warning: could not move VACM db ~p"
 
273
                             " (~p)", [FName, Else])
 
274
            end;
 
275
        {error, Reason} ->
 
276
            user_err("Warning: could not save vacm db ~p (~p)",
 
277
                     [FName, Reason])
 
278
    end.
 
279
 
 
280
 
 
281
%%-----------------------------------------------------------------
 
282
%% Alg.
 
283
%% Procedure is defined in the descr. of vacmAccessTable.
 
284
%%
 
285
%% for (each entry with matching group name, context, secmodel and seclevel)
 
286
%% {
 
287
%%   rate the entry; if it's score is > prev max score, keep it
 
288
%% }
 
289
%%
 
290
%% Rating:  The procedure says to keep entries in order
 
291
%%    1.  matching secmodel  ('any'(0) or same(1) is ok)
 
292
%%    2.  matching contextprefix (exact(1) or prefix(0) is ok)
 
293
%%    3.  longest prefix (0..32)
 
294
%%    4.  highest secLevel (noAuthNoPriv(0) < authNoPriv(1) < authPriv(2))
 
295
%%  We give each entry a single rating number according to this order.
 
296
%%  The number is chosen so that a higher number gives a better
 
297
%%  entry, according to the order above.
 
298
%%  The number is:
 
299
%%    secLevel + (3 * prefix_len) + (99 * match_prefix) + (198 * match_secmodel)
 
300
%%
 
301
%% Optimisation:  Maybe the most common case is that there
 
302
%% is just one matching entry, and it matches exact.  We could do
 
303
%% an exact lookup for this entry; if we find one, use it, otherwise
 
304
%% perform this alg.
 
305
%%-----------------------------------------------------------------
 
306
get_access_row(GroupKey, ContextName, SecModel, SecLevel) ->
 
307
    %% First, try the optimisation...
 
308
    ExactKey =
 
309
        GroupKey ++ [length(ContextName) | ContextName] ++ [SecModel,SecLevel],
 
310
    case ets:lookup(snmpa_vacm, ExactKey) of
 
311
        [{_Key, Row}] ->
 
312
            Row;
 
313
        _ -> % Otherwise, perform the alg
 
314
            get_access_row(GroupKey, GroupKey, ContextName,
 
315
                           SecModel, SecLevel, 0, undefined)
 
316
    end.
 
317
 
 
318
get_access_row(Key, GroupKey, ContextName, SecModel, SecLevel, Score, Found) ->
 
319
    case get_next_row(Key) of
 
320
        {NextKey, Row}
 
321
        when element(?vacmAStatus, Row) == ?'RowStatus_active'->
 
322
            case catch score(NextKey, GroupKey, ContextName,
 
323
                             element(?vacmAContextMatch, Row), 
 
324
                             SecModel, SecLevel) of
 
325
                {ok, NScore} when NScore > Score ->
 
326
                    get_access_row(NextKey, GroupKey, ContextName,
 
327
                                   SecModel, SecLevel, NScore, Row);
 
328
                {ok, _} -> % e.g. a throwed {ok, 0}
 
329
                    get_access_row(NextKey, GroupKey, ContextName,
 
330
                                   SecModel, SecLevel, Score, Found);
 
331
                false ->
 
332
                    Found
 
333
            end;
 
334
        {NextKey, _InvalidRow} ->
 
335
            get_access_row(NextKey, GroupKey, ContextName, SecModel,
 
336
                           SecLevel, Score, Found);
 
337
        false ->
 
338
            Found
 
339
    end.
 
340
                
 
341
                
 
342
 
 
343
score(Key, GroupKey, ContextName, Match, SecModel, SecLevel) ->
 
344
    [CtxLen | Rest1] = chop_off_group(GroupKey, Key),
 
345
    {NPrefix, [VSecModel, VSecLevel]} =
 
346
        chop_off_context(ContextName, Rest1, 0, CtxLen, Match),
 
347
    %% Make sure the vacmSecModel is valid (any or matching)
 
348
    NSecModel = case VSecModel of
 
349
                    SecModel -> 198;
 
350
                    ?SEC_ANY -> 0;
 
351
                    _        -> throw({ok, 0})
 
352
                end,
 
353
    %% Make sure the vacmSecLevel is less than the requested
 
354
    NSecLevel = if 
 
355
                    VSecLevel =< SecLevel -> VSecLevel - 1;
 
356
                    true                  -> throw({ok, 0})
 
357
                end,
 
358
    {ok, NSecLevel + 3*CtxLen + NPrefix + NSecModel}.
 
359
    
 
360
 
 
361
 
 
362
chop_off_group([H|T], [H|T2]) -> chop_off_group(T, T2);
 
363
chop_off_group([], Rest) -> Rest;
 
364
chop_off_group(_, _) -> throw(false).
 
365
 
 
366
chop_off_context([H|T], [H|T2], Cnt, Len, Match) when Cnt < Len ->
 
367
    chop_off_context(T, T2, Cnt+1, Len, Match);
 
368
chop_off_context([], Rest, _Len, _Len, _Match) ->
 
369
    %% We have exact match; don't care about Match
 
370
    {99, Rest};
 
371
chop_off_context(_, Rest, Len, Len, ?vacmAccessContextMatch_prefix) ->
 
372
    %% We have a prefix match
 
373
    {0, Rest};
 
374
chop_off_context(_Ctx, _Rest, _Cnt, _Len, _Match) ->    
 
375
    %% Otherwise, it didn't match!
 
376
    throw({ok, 0}).
 
377
 
 
378
 
 
379
gc_tab(Oid) ->
 
380
    case get_next_row(Oid) of
 
381
        {NextOid, Row} ->
 
382
            case element(?vacmAStorageType, Row) of
 
383
                ?'StorageType_volatile' ->
 
384
                    ets:delete(snmpa_vacm, NextOid),
 
385
                    gc_tab(NextOid);
 
386
                _ ->
 
387
                    gc_tab(NextOid)
 
388
            end;
 
389
        false ->
 
390
            ok
 
391
    end.
 
392
 
 
393
 
 
394
user_err(F, A) ->
 
395
    snmpa_error:user_err(F, A).
 
396
 
 
397
% config_err(F, A) ->
 
398
%     snmpa_error:config_err(F, A).