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

« back to all changes in this revision

Viewing changes to lib/snmp/src/agent/snmpa_usm.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
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 1999-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1999-2010. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
-module(snmpa_usm).
20
20
 
 
21
%% Avoid warning for local function error/1 clashing with autoimported BIF.
 
22
-compile({no_auto_import,[error/1]}).
 
23
%% Avoid warning for local function error/2 clashing with autoimported BIF.
 
24
-compile({no_auto_import,[error/2]}).
21
25
-export([
22
 
         process_incoming_msg/4, 
23
 
         generate_outgoing_msg/5,
 
26
         process_incoming_msg/4, process_incoming_msg/5, 
 
27
         generate_outgoing_msg/5, generate_outgoing_msg/6,
24
28
         generate_discovery_msg/4, generate_discovery_msg/5,
25
29
         current_statsNotInTimeWindows_vb/0
26
30
        ]).
33
37
 
34
38
-define(VMODULE,"A-USM").
35
39
-include("snmp_verbosity.hrl").
 
40
-include("snmpa_internal.hrl").
36
41
 
37
42
 
38
43
%%-----------------------------------------------------------------
58
63
%%-----------------------------------------------------------------
59
64
 
60
65
process_incoming_msg(Packet, Data, SecParams, SecLevel) ->
61
 
    TermDiscoEnabled = is_terminating_discovery_enabled(), 
 
66
    LocalEngineID = ?DEFAULT_LOCAL_ENGINE_ID, 
 
67
    process_incoming_msg(Packet, Data, SecParams, SecLevel, LocalEngineID).
 
68
 
 
69
process_incoming_msg(Packet, Data, SecParams, SecLevel, LocalEngineID) ->
 
70
    TermDiscoEnabled    = is_terminating_discovery_enabled(), 
62
71
    TermTriggerUsername = terminating_trigger_username(), 
63
72
    %% 3.2.1
64
73
    ?vtrace("process_incoming_msg -> check security parms: 3.2.1",[]),
124
133
                    "~n   ~p",[UsmUser]),
125
134
            DiscoOrPlain = authenticate_incoming(Packet, 
126
135
                                                 UsmSecParams, UsmUser, 
127
 
                                                 SecLevel), 
 
136
                                                 SecLevel, LocalEngineID), 
128
137
            %% 3.2.8
129
138
            ?vtrace("process_incoming_msg -> "
130
139
                    "decrypt scoped data: 3.2.8",[]),
166
175
    end.
167
176
            
168
177
 
169
 
authenticate_incoming(Packet, UsmSecParams, UsmUser, SecLevel) ->
 
178
authenticate_incoming(Packet, UsmSecParams, UsmUser, SecLevel, 
 
179
                      LocalEngineID) ->
170
180
    %% 3.2.6
171
181
    ?vtrace("authenticate_incoming -> 3.2.6", []),
172
182
    AuthProtocol = element(?usmUserAuthProtocol, UsmUser),
190
200
                         SecName,
191
201
                         MsgAuthEngineID,
192
202
                         MsgAuthEngineBoots, 
193
 
                         MsgAuthEngineTime) of
 
203
                         MsgAuthEngineTime,
 
204
                         LocalEngineID) of
194
205
                discovery ->
195
206
                    discovery;
196
207
                true -> 
205
216
            plain
206
217
    end.
207
218
            
208
 
authoritative(SecName, MsgAuthEngineBoots, MsgAuthEngineTime) ->
 
219
authoritative(SecName, MsgAuthEngineBoots, MsgAuthEngineTime, LocalEngineID) ->
209
220
    ?vtrace("authoritative -> entry with"
210
221
            "~n   SecName:            ~p"
211
222
            "~n   MsgAuthEngineBoots: ~p"
212
223
            "~n   MsgAuthEngineTime:  ~p", 
213
224
            [SecName, MsgAuthEngineBoots, MsgAuthEngineTime]),
214
 
    SnmpEngineBoots = snmp_framework_mib:get_engine_boots(),
 
225
    SnmpEngineBoots = get_local_engine_boots(LocalEngineID),
215
226
    ?vtrace("authoritative -> SnmpEngineBoots: ~p", [SnmpEngineBoots]),
216
 
    SnmpEngineTime = snmp_framework_mib:get_engine_time(),
 
227
    SnmpEngineTime = get_local_engine_time(LocalEngineID),
217
228
    ?vtrace("authoritative -> SnmpEngineTime: ~p", [SnmpEngineTime]),
218
229
    InTimeWindow =
219
230
        if
320
331
    end.
321
332
 
322
333
      
323
 
is_auth(?usmNoAuthProtocol, _, _, _, SecName, _, _, _) -> % 3.2.5
 
334
is_auth(?usmNoAuthProtocol, _, _, _, SecName, _, _, _, _) -> % 3.2.5
324
335
    error(usmStatsUnsupportedSecLevels,
325
336
          ?usmStatsUnsupportedSecLevels_instance, SecName); % OTP-5464
326
337
is_auth(AuthProtocol, AuthKey, AuthParams, Packet, SecName,
327
 
        MsgAuthEngineID, MsgAuthEngineBoots, MsgAuthEngineTime) ->
 
338
        MsgAuthEngineID, MsgAuthEngineBoots, MsgAuthEngineTime, 
 
339
        LocalEngineID) ->
328
340
    TermDiscoEnabled = is_terminating_discovery_enabled(), 
329
341
    TermDiscoStage2  = terminating_discovery_stage2(), 
330
342
    IsAuth = auth_in(AuthProtocol, AuthKey, AuthParams, Packet),
334
346
            %% 3.2.7
335
347
            ?vtrace("is_auth -> "
336
348
                    "retrieve EngineBoots and EngineTime: 3.2.7",[]),
337
 
            SnmpEngineID = snmp_framework_mib:get_engine_id(),
 
349
            SnmpEngineID = LocalEngineID,
338
350
            ?vtrace("is_auth -> SnmpEngineID: ~p", [SnmpEngineID]),
339
351
            case MsgAuthEngineID of
340
352
                SnmpEngineID when ((MsgAuthEngineBoots =:= 0) andalso 
351
363
                    %% This will *always* result in the manager *not* 
352
364
                    %% beeing in timewindow
353
365
                    authoritative(SecName, 
354
 
                                  MsgAuthEngineBoots, MsgAuthEngineTime);
 
366
                                  MsgAuthEngineBoots, MsgAuthEngineTime, 
 
367
                                  LocalEngineID);
355
368
 
356
369
                SnmpEngineID -> %% 3.2.7a
357
370
                    ?vtrace("is_auth -> we are authoritative: 3.2.7a", []),
358
371
                    authoritative(SecName, 
359
 
                                  MsgAuthEngineBoots, MsgAuthEngineTime);
 
372
                                  MsgAuthEngineBoots, MsgAuthEngineTime, 
 
373
                                  LocalEngineID);
360
374
 
361
375
                _ -> %% 3.2.7b - we're non-authoritative
362
376
                    ?vtrace("is_auth -> we are non-authoritative: 3.2.7b",[]),
396
410
    case (catch des_decrypt(PrivKey, UsmSecParams, EncryptedPDU)) of
397
411
        {ok, DecryptedData} ->
398
412
            DecryptedData;
399
 
        _ ->
 
413
        Error ->
 
414
            ?vlog("try_decrypt -> failed DES decrypt"
 
415
                  "~n   Error: ~p", [Error]),
400
416
            error(usmStatsDecryptionErrors, 
401
417
                  ?usmStatsDecryptionErrors_instance, % OTP-5464
402
418
                  SecName)
406
422
    case (catch aes_decrypt(PrivKey, UsmSecParams, EncryptedPDU)) of
407
423
        {ok, DecryptedData} ->
408
424
            DecryptedData;
409
 
        _ ->
 
425
        Error ->
 
426
            ?vlog("try_decrypt -> failed AES decrypt"
 
427
                  "~n   Error: ~p", [Error]),
410
428
            error(usmStatsDecryptionErrors, 
411
429
                  ?usmStatsDecryptionErrors_instance, % OTP-5464
412
430
                  SecName)
414
432
 
415
433
 
416
434
generate_outgoing_msg(Message, SecEngineID, SecName, SecData, SecLevel) ->
 
435
    LocalEngineID = ?DEFAULT_LOCAL_ENGINE_ID, 
 
436
    generate_outgoing_msg(Message, SecEngineID, SecName, SecData, SecLevel, 
 
437
                          LocalEngineID).
 
438
 
 
439
generate_outgoing_msg(Message, SecEngineID, SecName, SecData, SecLevel, 
 
440
                      LocalEngineID) ->
417
441
    %% 3.1.1
418
442
    ?vtrace("generate_outgoing_msg -> [3.1.1] entry with"
419
 
            "~n   SecEngineID: ~p"
420
 
            "~n   SecName:     ~p"
421
 
            "~n   SecLevel:    ~w", 
422
 
            [SecEngineID, SecName, SecLevel]),
 
443
            "~n   SecEngineID:   ~p"
 
444
            "~n   SecName:       ~p"
 
445
            "~n   SecLevel:      ~w" 
 
446
            "~n   LocalEngineID: ~p", 
 
447
            [SecEngineID, SecName, SecLevel, LocalEngineID]),
423
448
    {UserName, AuthProtocol, PrivProtocol, AuthKey, PrivKey} =
424
449
        case SecData of
425
450
            [] -> % 3.1.1b
435
460
                         element(?usmUserPrivKey, User)};
436
461
                    {_, Name,_,_,_,_,_,_,_,_,_,_,_, RowStatus,_,_} ->
437
462
                        ?vdebug("generate_outgoing_msg -> "
438
 
                                "found user ~p with wrong row status: ~p", 
 
463
                                "found not active user ~p: ~p", 
439
464
                                [Name, RowStatus]),
440
465
                        error(unknownSecurityName);
441
466
                    _ ->
456
481
    ScopedPduBytes = Message#message.data,
457
482
    {ScopedPduData, MsgPrivParams} =
458
483
        encrypt(ScopedPduBytes, PrivProtocol, PrivKey, SecLevel),
459
 
    SnmpEngineID = snmp_framework_mib:get_engine_id(),
 
484
    SnmpEngineID = LocalEngineID, 
460
485
    ?vtrace("generate_outgoing_msg -> SnmpEngineID: ~p [3.1.6]",
461
486
            [SnmpEngineID]),
462
487
    %% 3.1.6
470
495
                {get_engine_boots(SecEngineID),
471
496
                 get_engine_time(SecEngineID)};
472
497
            _ ->
473
 
                {snmp_framework_mib:get_engine_boots(),
474
 
                 snmp_framework_mib:get_engine_time()}
 
498
                {get_local_engine_boots(SnmpEngineID),
 
499
                 get_local_engine_time(SnmpEngineID)}
475
500
        end,
476
501
    %% 3.1.5 - 3.1.7
477
502
    ?vtrace("generate_outgoing_msg -> [3.1.5 - 3.1.7]",[]),
556
581
            ?vtrace("encrypt -> 3.1.4a",[]),
557
582
            case (catch try_encrypt(PrivProtocol, PrivKey, Data)) of
558
583
                {ok, ScopedPduData, MsgPrivParams} ->
559
 
                    ?vtrace("encrypt -> encode tag",[]),
 
584
                    ?vtrace("encrypt -> encrypted - now encode tag",[]),
560
585
                    {snmp_pdus:enc_oct_str_tag(ScopedPduData), MsgPrivParams};
561
586
                {error, Reason} ->
 
587
                    ?vtrace("encrypt -> error: "
 
588
                            "~n   Reason: ~p", [Reason]),
562
589
                    error(Reason);
563
 
                _Error ->
 
590
                Error ->
 
591
                    ?vtrace("encrypt -> other: "
 
592
                            "~n   Error: ~p", [Error]),
564
593
                    error(encryptionError)
565
594
            end
566
595
    end.
673
702
             value        = get_counter(usmStatsNotInTimeWindows)}.
674
703
 
675
704
 
 
705
 
 
706
%%-----------------------------------------------------------------
 
707
%% Future profing...
 
708
%%-----------------------------------------------------------------
 
709
 
 
710
get_local_engine_boots(_LocalEngineID) ->
 
711
    snmp_framework_mib:get_engine_boots().
 
712
 
 
713
get_local_engine_time(_LocalEngineID) ->
 
714
    snmp_framework_mib:get_engine_time().
 
715
 
 
716
 
 
717
 
676
718
%%-----------------------------------------------------------------
677
719
%% We cache the local values of all non-auth engines we know.
678
720
%% Keep the values in the snmp_agent_table.