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

« back to all changes in this revision

Viewing changes to lib/snmp/src/snmp_acm.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_acm).
19
 
 
20
 
-export([init_check_access/2, get_root_mib_view/0,
21
 
         error2status/1,
22
 
         validate_mib_view/2, validate_all_mib_view/2,
23
 
         is_definitely_not_in_mib_view/2]).
24
 
 
25
 
-include("snmp_types.hrl").
26
 
-include("STANDARD-MIB.hrl").
27
 
-include("SNMP-FRAMEWORK-MIB.hrl").
28
 
-include("SNMPv2-TM.hrl").
29
 
 
30
 
-define(VMODULE,"ACM").
31
 
-include("snmp_verbosity.hrl").
32
 
 
33
 
 
34
 
%%%-----------------------------------------------------------------
35
 
%%% This module implements the Access Control Model part of the
36
 
%%% multi-lingual SNMP agent.  It contains generic function not
37
 
%%% tied to a specific model, but in this version it uses VACM.
38
 
%%%
39
 
%%% Note that we don't follow the isAccessAllowed Abstract Service
40
 
%%% Interface defined in rfc2271.  We implement an optimization
41
 
%%% of that ASI.  Since the mib view is the same for all variable
42
 
%%% bindings in a PDU, there is no need to recalculate the mib
43
 
%%% view for each variable.  Therefore, one function
44
 
%%% (init_check_access/2) is used to find the mib view, and then
45
 
%%% each variable is checked against this mib view.
46
 
%%%
47
 
%%% Access checking is done in several steps.  First, the version-
48
 
%%% specific MPD (see snmp_mpd) creates data used by VACM.  This
49
 
%%% means that the format of this data is known by both the MPD and
50
 
%%% the ACM.  When the master agent wants to check the access to a
51
 
%%% Pdu, it first calls init_check_access/2, which returns a MibView
52
 
%%% that can be used to check access of individual variables.
53
 
%%%-----------------------------------------------------------------
54
 
 
55
 
%%-----------------------------------------------------------------
56
 
%% Func: init_check_access(Pdu, ACMData) ->
57
 
%%       {ok, MibView, ContextName} |
58
 
%%       {error, Reason} |
59
 
%%       {discarded, Variable, Reason}
60
 
%% Types: Pdu = #pdu
61
 
%%        ACMData = acm_data() = {community, Community, Address} |
62
 
%%                               {v3, MsgID, SecModel, SecName, SecLevel,
63
 
%%                                    ContextEngineID, ContextName, SecData}
64
 
%%        Community       = string()
65
 
%%        Address         = ip() ++ udp() (list)
66
 
%%        MsgID           = integer() <not used>
67
 
%%        SecModel        = ?SEC_*  (see snmp_types.hrl)
68
 
%%        SecName         = string()
69
 
%%        SecLevel        = ?'SnmpSecurityLevel_*' (see SNMP-FRAMEWORK-MIB.hrl)
70
 
%%        ContextEngineID = string() <not used>
71
 
%%        ContextName     = string()
72
 
%%        SecData         = <not used>
73
 
%%        Variable        = snmpInBadCommunityNames |
74
 
%%                          snmpInBadCommunityUses |
75
 
%%                          snmpInASNParseErrs
76
 
%%        Reason          = snmp_message_decoding |
77
 
%%                          {bad_community_name, Address, Community}} |
78
 
%%                          {invalid_access, Access, Op}
79
 
%% 
80
 
%% Purpose: Called once for each Pdu.  Returns a MibView
81
 
%%          which is later used for each variable in the pdu.
82
 
%%          The authenticationFailure trap is sent (maybe) when the auth.
83
 
%%          procedure evaluates to unauthentic,
84
 
%%
85
 
%% NOTE: This function is executed in the Master agents's context
86
 
%%-----------------------------------------------------------------
87
 
init_check_access(Pdu, ACMData) ->
88
 
    case init_ca(Pdu, ACMData) of
89
 
        {ok, MibView, ContextName} ->
90
 
            {ok, MibView, ContextName};
91
 
        {discarded, Reason} ->
92
 
            {error, Reason};
93
 
        {authentication_failure, Variable, Reason} ->
94
 
            handle_authentication_failure(),
95
 
            {discarded, Variable, Reason}
96
 
    end.
97
 
 
98
 
error2status(noSuchView) -> authorizationError;
99
 
error2status(noAccessEntry) -> authorizationError;
100
 
error2status(noGroupName) -> authorizationError;
101
 
error2status(_) -> genErr.
102
 
     
103
 
%%-----------------------------------------------------------------
104
 
%% Func: init_ca(Pdu, ACMData) ->
105
 
%%       {ok, MibView} |
106
 
%%       {discarded, Reason} |
107
 
%%       {authentication_failure, Variable, Reason}
108
 
%%
109
 
%% error: an error response will be sent
110
 
%% discarded: no error response is sent
111
 
%% authentication_failure: no error response is sent, a trap is generated
112
 
%%-----------------------------------------------------------------
113
 
init_ca(Pdu, {community, SecModel, Community, TAddr}) ->
114
 
    %% This is a v1 or v2c request.   Use SNMP-COMMUNITY-MIB to
115
 
    %% map the community to vacm parameters.
116
 
    ?vtrace("check access for ~n"
117
 
            "   Pdu:            ~p~n"
118
 
            "   Security model: ~p~n"
119
 
            "   Community:      ~s",[Pdu,SecModel,Community]),
120
 
    ViewType = case Pdu#pdu.type of
121
 
                   'set-request' -> write;
122
 
                   _ -> read
123
 
               end,
124
 
    ?vtrace("View type: ~p",[ViewType]),
125
 
    case snmp_community_mib:community2vacm(Community, {?snmpUDPDomain,TAddr}) of
126
 
        {SecName, _ContextEngineId, ContextName} ->
127
 
            %% Maybe we should check that the contextEngineID matches the
128
 
            %% local engineID?  It better, since we don't impl. proxy.
129
 
            ?vtrace("get mib view"
130
 
                    "~n   Security name: ~p"
131
 
                    "~n   Context name:  ~p",[SecName,ContextName]),
132
 
            case snmp_vacm:get_mib_view(ViewType, SecModel, SecName,
133
 
                                        ?'SnmpSecurityLevel_noAuthNoPriv',
134
 
                                        ContextName) of
135
 
                {ok, MibView} ->
136
 
                    put(sec_model, SecModel),
137
 
                    put(sec_name, SecName),
138
 
                    {ok, MibView, ContextName};
139
 
                {discarded, Reason} ->
140
 
                    snmp_mpd:inc(snmpInBadCommunityUses),
141
 
                    {discarded, Reason}
142
 
            end;
143
 
        undefined ->
144
 
            {authentication_failure, snmpInBadCommunityNames,
145
 
             {bad_community_name, TAddr, Community}}
146
 
    end;
147
 
init_ca(Pdu, {v3, _MsgID, SecModel, SecName, SecLevel,
148
 
              _ContextEngineID, ContextName, _SecData}) ->
149
 
    ?vtrace("check v3 access for ~n"
150
 
            "   Pdu:            ~p~n"
151
 
            "   Security model: ~p~n"
152
 
            "   Security name:  ~p~n"
153
 
            "   Security level: ~p",[Pdu,SecModel,SecName,SecLevel]),
154
 
    ViewType = case Pdu#pdu.type of
155
 
                   'set-request' -> write;
156
 
                   _ -> read
157
 
               end,
158
 
    ?vtrace("View type: ~p",[ViewType]),
159
 
    %% Convert the msgflag value to a ?'SnmpSecurityLevel*'
160
 
    SL = case SecLevel of
161
 
             0 -> ?'SnmpSecurityLevel_noAuthNoPriv';
162
 
             1 -> ?'SnmpSecurityLevel_authNoPriv';
163
 
             3 -> ?'SnmpSecurityLevel_authPriv'
164
 
         end,
165
 
    put(sec_model, SecModel),
166
 
    put(sec_name, SecName),
167
 
    case snmp_vacm:get_mib_view(ViewType, SecModel, SecName, SL, ContextName) of
168
 
        {ok, MibView} ->
169
 
            {ok, MibView, ContextName};
170
 
        Else ->
171
 
            Else
172
 
    end.
173
 
 
174
 
%%-----------------------------------------------------------------
175
 
%% Func: check(Res) -> {ok, MibView} | {discarded, Variable, Reason}
176
 
%% Args: Res = {ok, AccessFunc} | {authentication_failure, Variable, Reason
177
 
%%-----------------------------------------------------------------
178
 
 
179
 
%%-----------------------------------------------------------------
180
 
%% NOTE: This function is executed in the Master agents's context
181
 
%% Do a GET to retrieve the value for snmpEnableAuthenTraps.  A
182
 
%% user may have another impl. than default for this variable.
183
 
%%-----------------------------------------------------------------
184
 
handle_authentication_failure() ->
185
 
    case snmp_agent:do_get(get_root_mib_view(),
186
 
                           [#varbind{oid = ?snmpEnableAuthenTraps_instance}],
187
 
                           true) of
188
 
        {noError, _, [#varbind{value = ?snmpEnableAuthenTraps_enabled}]} ->
189
 
            snmp:send_notification(self(), authenticationFailure, no_receiver);
190
 
        _ ->
191
 
            ok
192
 
    end.
193
 
 
194
 
%%%-----------------------------------------------------------------
195
 
%%% MIB View handling
196
 
%%%-----------------------------------------------------------------
197
 
 
198
 
get_root_mib_view() ->
199
 
    [{[1], [], ?view_included}].
200
 
 
201
 
%%-----------------------------------------------------------------
202
 
%% Returns true if Oid is in the MibView, false
203
 
%% otherwise.
204
 
%% Alg: (defined in SNMP-VIEW-BASED-ACM-MIB)
205
 
%% For each family (= {SubTree, Mask, Type}), check if Oid
206
 
%% belongs to that family. For each family that Oid belong to,
207
 
%% get the longest. If two or more are longest, get the
208
 
%% lexicografically greatest. Check the type of this family. If
209
 
%% included, then Oid belongs to the MibView, otherwise it
210
 
%% does not.
211
 
%% Optimisation: Do only one loop, and kepp the largest sofar.
212
 
%% When we find a family that Oid belongs to, check if it is
213
 
%% larger than the largest.
214
 
%%-----------------------------------------------------------------
215
 
validate_mib_view(Oid, MibView) ->
216
 
    case get_largest_family(MibView, Oid, undefined) of
217
 
        {_, _, ?view_included} -> true;
218
 
        _ -> false
219
 
    end.
220
 
 
221
 
get_largest_family([{SubTree, Mask, Type} | T], Oid, Res) ->
222
 
    case check_mask(Oid, SubTree, Mask) of
223
 
        true -> get_largest_family(T, Oid, add_res(length(SubTree), SubTree,
224
 
                                                   Type, Res));
225
 
        false -> get_largest_family(T, Oid, Res)
226
 
    end;
227
 
get_largest_family([], _Oid, Res) -> Res.
228
 
 
229
 
%%-----------------------------------------------------------------
230
 
%% We keep only the largest (first longest SubTree, and then 
231
 
%% lexicografically greatest) SubTree.
232
 
%%-----------------------------------------------------------------
233
 
add_res(Len, SubTree, Type, undefined) ->
234
 
    {Len, SubTree, Type};
235
 
add_res(Len, SubTree, Type, {MaxLen, _MaxS, _MaxT}) when Len > MaxLen ->
236
 
    {Len, SubTree, Type};
237
 
add_res(Len, SubTree, Type, {MaxLen, MaxS, MaxT}) when Len == MaxLen ->
238
 
    if
239
 
        SubTree > MaxS -> {Len, SubTree, Type};
240
 
        true -> {MaxLen, MaxS, MaxT}
241
 
    end;
242
 
add_res(_Len, _SubTree, _Type, MaxRes) -> MaxRes.
243
 
 
244
 
 
245
 
%% 1 in mask is exact match, 0 is wildcard.
246
 
%% If mask is shorter than SubTree, its regarded
247
 
%% as being all ones.
248
 
check_mask(_Oid, [], _Mask) -> true;
249
 
check_mask([X | Xs], [X | Ys], [1 | Ms]) ->
250
 
    check_mask(Xs, Ys, Ms);
251
 
check_mask([X | Xs], [X | Ys], []) ->
252
 
    check_mask(Xs, Ys, []);
253
 
check_mask([_X | Xs], [_Y | Ys], [0 | Ms]) ->
254
 
    check_mask(Xs, Ys, Ms);
255
 
check_mask(_, _, _) -> false.
256
 
 
257
 
%%-----------------------------------------------------------------
258
 
%% Validates all oids in the Varbinds list towards the MibView.
259
 
%%-----------------------------------------------------------------
260
 
validate_all_mib_view([#varbind{oid = Oid, org_index = Index} | Varbinds],
261
 
                      MibView) ->
262
 
    case validate_mib_view(Oid, MibView) of
263
 
        true -> validate_all_mib_view(Varbinds, MibView);
264
 
        false -> {false, Index}
265
 
    end;
266
 
validate_all_mib_view([], _MibView) ->
267
 
    true.
268
 
 
269
 
%%-----------------------------------------------------------------
270
 
%% This function is used to optimize the next operation in
271
 
%% snmp_mib_data. If we get to a node in the tree where we can
272
 
%% determine that we are guaranteed to be outside the mibview,
273
 
%% we don't have to continue the search in the that tree (Actually
274
 
%% we will, because we only check this at leafs. But we won't
275
 
%% go into tables or subagents, and that's the important
276
 
%% optimization.) For now, this function isn't that sophisticated;
277
 
%% it just checks that there is really no family in the mibview
278
 
%% that the Oid (or any other oids with Oid as prefix) may be
279
 
%% included in. Perhaps this function easily could be more
280
 
%% intelligent.
281
 
%%-----------------------------------------------------------------
282
 
is_definitely_not_in_mib_view(Oid, [{SubTree, Mask,?view_included}|T]) ->
283
 
    case check_maybe_mask(Oid, SubTree, Mask) of
284
 
        true -> false;
285
 
        false -> is_definitely_not_in_mib_view(Oid, T)
286
 
    end;
287
 
is_definitely_not_in_mib_view(Oid, [{_SubTree, _Mask,?view_excluded}|T]) ->
288
 
    is_definitely_not_in_mib_view(Oid, T);
289
 
is_definitely_not_in_mib_view(_Oid, []) ->
290
 
    true.
291
 
    
292
 
%%-----------------------------------------------------------------
293
 
%% As check_mask, BUT if Oid < SubTree and sofar good, we
294
 
%% return true. As Oid get larger we may decide.
295
 
%%-----------------------------------------------------------------
296
 
check_maybe_mask(_Oid, [], _Mask) -> true;
297
 
check_maybe_mask([X | Xs], [X | Ys], [1 | Ms]) ->
298
 
    check_maybe_mask(Xs, Ys, Ms);
299
 
check_maybe_mask([X | Xs], [X | Ys], []) ->
300
 
    check_maybe_mask(Xs, Ys, []);
301
 
check_maybe_mask([_X | Xs], [_Y | Ys], [0 | Ms]) ->
302
 
    check_maybe_mask(Xs, Ys, Ms);
303
 
check_maybe_mask([_X | _Xs], [_Y | _Ys], _) ->
304
 
    false;
305
 
check_maybe_mask(_, _, _) -> 
306
 
    true.