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

« back to all changes in this revision

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