~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): Sergei Golovan
  • Date: 2009-06-11 12:18:07 UTC
  • mfrom: (1.2.2 upstream)
  • Revision ID: james.westby@ubuntu.com-20090611121807-ks7eb4xrt7dsysgx
Tags: 1:13.b.1-dfsg-1
* New upstream release.
* Removed unnecessary dependency of erlang-os-mon on erlang-observer and
  erlang-tools and added missing dependency of erlang-nox on erlang-os-mon
  (closes: #529512).
* Removed a patch to eunit application because the bug was fixed upstream.

Show diffs side-by-side

added added

removed removed

Lines of Context:
21
21
-export([
22
22
         process_incoming_msg/4, 
23
23
         generate_outgoing_msg/5,
24
 
         generate_discovery_msg/5
 
24
         generate_discovery_msg/5, generate_discovery_msg/6
25
25
        ]).
26
26
 
27
27
-define(SNMP_USE_V3, true).
55
55
%% Types: Reason -> term()
56
56
%% Purpose: 
57
57
%%-----------------------------------------------------------------
 
58
 
58
59
process_incoming_msg(Packet, Data, SecParams, SecLevel) ->
 
60
    TermDiscoEnabled = is_terminating_discovery_enabled(), 
59
61
    %% 3.2.1
60
62
    ?vtrace("process_incoming_msg -> check security parms: 3.2.1",[]),
61
63
    UsmSecParams =
67
69
                Res
68
70
        end,
69
71
    case UsmSecParams of
70
 
        #usmSecurityParameters{msgAuthoritativeEngineID = "",
71
 
                               msgUserName              = ""} ->
 
72
        #usmSecurityParameters{msgAuthoritativeEngineID = MsgAuthEngineID,
 
73
                               msgUserName              = ""} when TermDiscoEnabled =:= true ->
72
74
            %% Step 1 discovery message
73
75
            ?vtrace("process_incoming_msg -> discovery step 1", []),
74
 
            process_discovery_msg(Data, SecLevel);
 
76
            process_discovery_msg(MsgAuthEngineID, Data, SecLevel);
75
77
        
76
 
        #usmSecurityParameters{msgAuthoritativeEngineID = "",
77
 
                               msgUserName              = "initial"} ->
 
78
        #usmSecurityParameters{msgAuthoritativeEngineID = MsgAuthEngineID,
 
79
                               msgUserName              = "initial"} when TermDiscoEnabled =:= true ->
78
80
            %% Step 1 discovery message
79
81
            ?vtrace("process_incoming_msg -> [initial] discovery step 1", []),
80
 
            process_discovery_msg(Data, SecLevel);
 
82
            process_discovery_msg(MsgAuthEngineID, Data, SecLevel);
81
83
        
82
84
        #usmSecurityParameters{msgAuthoritativeEngineID = MsgAuthEngineID,
83
85
                               msgUserName = MsgUserName} ->
147
149
    end.
148
150
    
149
151
%% Process a step 1 discovery message
150
 
process_discovery_msg(Data, SecLevel) ->
 
152
process_discovery_msg(MsgAuthEngineID, Data, SecLevel) ->
151
153
    ?vtrace("process_discovery_msg -> entry with"
152
154
            "~n   Data:     ~p"
153
155
            "~n   SecLevel: ~p", [Data, SecLevel]),
159
161
            NewData = {SecData,
160
162
                       ?usmStatsUnknownEngineIDs_instance, 
161
163
                       get_counter(usmStatsUnknownEngineIDs)}, 
162
 
            {ok, {"", "", ScopedPDUBytes, NewData, discovery}};
 
164
            {ok, {MsgAuthEngineID, "", ScopedPDUBytes, NewData, discovery}};
163
165
        false ->
164
166
            error(usmStatsUnknownEngineIDs, 
165
167
                  ?usmStatsUnknownEngineIDs_instance, 
176
178
                           msgAuthoritativeEngineTime  = MsgAuthEngineTime,
177
179
                           msgAuthenticationParameters = MsgAuthParams} = 
178
180
        UsmSecParams,
 
181
    ?vtrace("authenticate_incoming -> Sec params: "
 
182
            "~n   MsgAuthEngineID:    ~p"
 
183
            "~n   MsgAuthEngineBoots: ~p"
 
184
            "~n   MsgAuthEngineTime:  ~p",
 
185
            [MsgAuthEngineID, MsgAuthEngineBoots, MsgAuthEngineTime]),
179
186
    case snmp_misc:is_auth(SecLevel) of
180
187
        true ->
181
188
            SecName = element(?usmUserSecurityName, UsmUser),
201
208
            plain
202
209
    end.
203
210
            
 
211
authoritative(SecName, MsgAuthEngineBoots, MsgAuthEngineTime) ->
 
212
    ?vtrace("authoritative -> entry with"
 
213
            "~n   SecName:            ~p"
 
214
            "~n   MsgAuthEngineBoots: ~p"
 
215
            "~n   MsgAuthEngineTime:  ~p", 
 
216
            [SecName, MsgAuthEngineBoots, MsgAuthEngineTime]),
 
217
    SnmpEngineBoots = snmp_framework_mib:get_engine_boots(),
 
218
    ?vtrace("authoritative -> SnmpEngineBoots: ~p", [SnmpEngineBoots]),
 
219
    SnmpEngineTime = snmp_framework_mib:get_engine_time(),
 
220
    ?vtrace("authoritative -> SnmpEngineTime: ~p", [SnmpEngineTime]),
 
221
    InTimeWindow =
 
222
        if
 
223
            SnmpEngineBoots =:= 2147483647 -> false;
 
224
            MsgAuthEngineBoots =/= SnmpEngineBoots -> false;
 
225
            MsgAuthEngineTime + 150 < SnmpEngineTime -> false;
 
226
            MsgAuthEngineTime - 150 > SnmpEngineTime -> false;
 
227
            true -> true
 
228
        end,
 
229
    case InTimeWindow of
 
230
        true -> 
 
231
            true;
 
232
        false -> 
 
233
            %% OTP-4090 (OTP-3542)
 
234
            ?vinfo("NOT in time window: "
 
235
                   "~n   SecName:            ~p"
 
236
                   "~n   SnmpEngineBoots:    ~p"
 
237
                   "~n   MsgAuthEngineBoots: ~p"
 
238
                   "~n   SnmpEngineTime:     ~p"
 
239
                   "~n   MsgAuthEngineTime:  ~p",
 
240
                   [SecName,
 
241
                    SnmpEngineBoots, MsgAuthEngineBoots,
 
242
                    SnmpEngineTime, MsgAuthEngineTime]),
 
243
            error(usmStatsNotInTimeWindows,
 
244
                  ?usmStatsNotInTimeWindows_instance,
 
245
                  SecName,
 
246
                  [{securityLevel, 1}]) % authNoPriv
 
247
    end.
 
248
 
 
249
non_authoritative(SecName, 
 
250
                  MsgAuthEngineID, MsgAuthEngineBoots, MsgAuthEngineTime) ->
 
251
    ?vtrace("non_authoritative -> entry with"
 
252
            "~n   SecName:            ~p"
 
253
            "~n   MsgAuthEngineID:    ~p"
 
254
            "~n   MsgAuthEngineBoots: ~p"
 
255
            "~n   MsgAuthEngineTime:  ~p", 
 
256
            [SecName, 
 
257
             MsgAuthEngineID, MsgAuthEngineBoots, MsgAuthEngineTime]),
 
258
    SnmpEngineBoots = get_engine_boots(MsgAuthEngineID),
 
259
    ?vtrace("non_authoritative -> SnmpEngineBoots: ~p", [SnmpEngineBoots]),
 
260
    SnmpEngineTime = get_engine_time(MsgAuthEngineID),
 
261
    LatestRecvTime = get_engine_latest_time(MsgAuthEngineID),
 
262
    UpdateLCD =
 
263
        if
 
264
            MsgAuthEngineBoots > SnmpEngineBoots -> true;
 
265
            ((MsgAuthEngineBoots =:= SnmpEngineBoots) andalso 
 
266
             (MsgAuthEngineTime > LatestRecvTime)) -> true;
 
267
            true -> false
 
268
        end,
 
269
    case UpdateLCD of
 
270
        true -> %% 3.2.7b1
 
271
            ?vtrace("non_authoritative -> "
 
272
                    "update msgAuthoritativeEngineID: 3.2.7b1",
 
273
                    []),
 
274
            set_engine_boots(MsgAuthEngineID, MsgAuthEngineBoots),
 
275
            set_engine_time(MsgAuthEngineID, MsgAuthEngineTime),
 
276
            set_engine_latest_time(MsgAuthEngineID, MsgAuthEngineTime);
 
277
        false ->
 
278
            ok
 
279
    end,
 
280
    %% 3.2.7.b2
 
281
    ?vtrace("non_authoritative -> "
 
282
            "check if message is outside time window: 3.2.7b2",
 
283
            []),
 
284
    InTimeWindow =
 
285
        if
 
286
            SnmpEngineBoots == 2147483647 ->
 
287
                false;
 
288
            MsgAuthEngineBoots < SnmpEngineBoots ->
 
289
                false;
 
290
            MsgAuthEngineBoots =:= SnmpEngineBoots,
 
291
            MsgAuthEngineTime < (SnmpEngineTime - 150) ->
 
292
                false;
 
293
            true -> true
 
294
        end,
 
295
    case InTimeWindow of
 
296
        false ->
 
297
            ?vinfo("NOT in time window: "
 
298
                   "~n   SecName:            ~p"
 
299
                   "~n   SnmpEngineBoots:    ~p"
 
300
                   "~n   MsgAuthEngineBoots: ~p"
 
301
                   "~n   SnmpEngineTime:     ~p"
 
302
                   "~n   MsgAuthEngineTime:  ~p",
 
303
                   [SecName,
 
304
                    SnmpEngineBoots, MsgAuthEngineBoots,
 
305
                    SnmpEngineTime, MsgAuthEngineTime]),
 
306
            error(notInTimeWindow, []);
 
307
        true ->
 
308
            ok
 
309
    end,
 
310
    true.
 
311
 
 
312
      
204
313
is_auth(?usmNoAuthProtocol, _, _, _, SecName, _, _, _) -> % 3.2.5
205
314
    error(usmStatsUnsupportedSecLevels,
206
315
          ?usmStatsUnsupportedSecLevels_instance, SecName); % OTP-5464
207
316
is_auth(AuthProtocol, AuthKey, AuthParams, Packet, SecName,
208
317
        MsgAuthEngineID, MsgAuthEngineBoots, MsgAuthEngineTime) ->
 
318
    TermDiscoEnabled = is_terminating_discovery_enabled(), 
 
319
    TermDiscoStage2  = terminating_discovery_stage2(), 
209
320
    IsAuth = auth_in(AuthProtocol, AuthKey, AuthParams, Packet),
210
321
    case IsAuth of
211
322
        true ->
213
324
            ?vtrace("is_auth -> "
214
325
                    "retrieve EngineBoots and EngineTime: 3.2.7",[]),
215
326
            SnmpEngineID = snmp_framework_mib:get_engine_id(),
216
 
            ?vtrace("is_auth -> SnmpEngineID: ~p",[SnmpEngineID]),
 
327
            ?vtrace("is_auth -> SnmpEngineID: ~p", [SnmpEngineID]),
217
328
            case MsgAuthEngineID of
218
329
                SnmpEngineID when ((MsgAuthEngineBoots =:= 0) andalso 
219
 
                                   (MsgAuthEngineTime =:= 0)) -> %% 3.2.7a
 
330
                                   (MsgAuthEngineTime =:= 0) andalso 
 
331
                                   (TermDiscoEnabled =:= true) andalso 
 
332
                                   (TermDiscoStage2 =:= discovery)) -> %% 3.2.7a
 
333
                    ?vtrace("is_auth -> discovery stage 2 - discovery",[]),
220
334
                    discovery;
 
335
                SnmpEngineID when ((MsgAuthEngineBoots =:= 0) andalso 
 
336
                                   (MsgAuthEngineTime =:= 0) andalso 
 
337
                                   (TermDiscoEnabled =:= true) andalso 
 
338
                                   (TermDiscoStage2 =:= plain)) -> %% 3.2.7a
 
339
                    ?vtrace("is_auth -> discovery stage 2 - plain",[]),
 
340
                    %% This will *always* result in the manager *not* 
 
341
                    %% beeing in timewindow
 
342
                    authoritative(SecName, 
 
343
                                  MsgAuthEngineBoots, MsgAuthEngineTime);
 
344
 
221
345
                SnmpEngineID -> %% 3.2.7a
222
 
                    ?vtrace("is_auth -> we are authoritative: 3.2.7a",[]),
223
 
                    SnmpEngineBoots = snmp_framework_mib:get_engine_boots(),
224
 
                    ?vtrace("is_auth -> SnmpEngineBoots: ~p",
225
 
                            [SnmpEngineBoots]),
226
 
                    SnmpEngineTime = snmp_framework_mib:get_engine_time(),
227
 
                    InTimeWindow =
228
 
                        if
229
 
                            SnmpEngineBoots =:= 2147483647 -> false;
230
 
                            MsgAuthEngineBoots =/= SnmpEngineBoots -> false;
231
 
                            MsgAuthEngineTime + 150 < SnmpEngineTime -> false;
232
 
                            MsgAuthEngineTime - 150 > SnmpEngineTime -> false;
233
 
                            true -> true
234
 
                        end,
235
 
                    case InTimeWindow of
236
 
                        true -> 
237
 
                            true;
238
 
                        false -> 
239
 
                            %% OTP-4090 (OTP-3542)
240
 
                            ?vinfo("NOT in time window: "
241
 
                                   "~n   SecName:            ~p"
242
 
                                   "~n   SnmpEngineBoots:    ~p"
243
 
                                   "~n   MsgAuthEngineBoots: ~p"
244
 
                                   "~n   SnmpEngineTime:     ~p"
245
 
                                   "~n   MsgAuthEngineTime:  ~p",
246
 
                                   [SecName,
247
 
                                    SnmpEngineBoots, MsgAuthEngineBoots,
248
 
                                    SnmpEngineTime, MsgAuthEngineTime]),
249
 
                            error(usmStatsNotInTimeWindows,
250
 
                                  ?usmStatsNotInTimeWindows_instance,
251
 
                                  SecName,
252
 
                                  [{securityLevel, 1}]) % authNoPriv
253
 
                    end;
 
346
                    ?vtrace("is_auth -> we are authoritative: 3.2.7a", []),
 
347
                    authoritative(SecName, 
 
348
                                  MsgAuthEngineBoots, MsgAuthEngineTime);
 
349
 
254
350
                _ -> %% 3.2.7b - we're non-authoritative
255
351
                    ?vtrace("is_auth -> we are non-authoritative: 3.2.7b",[]),
256
 
                    SnmpEngineBoots = get_engine_boots(MsgAuthEngineID),
257
 
                    ?vtrace("is_auth -> SnmpEngineBoots: ~p",
258
 
                            [SnmpEngineBoots]),
259
 
                    SnmpEngineTime = get_engine_time(MsgAuthEngineID),
260
 
                    LatestRecvTime = get_engine_latest_time(MsgAuthEngineID),
261
 
                    UpdateLCD =
262
 
                        if
263
 
                            MsgAuthEngineBoots > SnmpEngineBoots -> true;
264
 
                            ((MsgAuthEngineBoots =:= SnmpEngineBoots) andalso 
265
 
                             (MsgAuthEngineTime > LatestRecvTime)) -> true;
266
 
                            true -> false
267
 
                        end,
268
 
                    case UpdateLCD of
269
 
                        true -> %% 3.2.7b1
270
 
                            ?vtrace("is_auth -> "
271
 
                                    "update msgAuthoritativeEngineID: 3.2.7b1",
272
 
                                    []),
273
 
                            set_engine_boots(MsgAuthEngineID,
274
 
                                             MsgAuthEngineBoots),
275
 
                            set_engine_time(MsgAuthEngineID,
276
 
                                            MsgAuthEngineTime),
277
 
                            set_engine_latest_time(MsgAuthEngineID,
278
 
                                                   MsgAuthEngineTime);
279
 
                        false ->
280
 
                            ok
281
 
                    end,
282
 
                    %% 3.2.7.b2
283
 
                    ?vtrace("is_auth -> "
284
 
                            "check if message is outside time window: 3.2.7b2",
285
 
                            []),
286
 
                    InTimeWindow =
287
 
                        if
288
 
                            SnmpEngineBoots == 2147483647 ->
289
 
                                false;
290
 
                            MsgAuthEngineBoots < SnmpEngineBoots ->
291
 
                                false;
292
 
                            MsgAuthEngineBoots == SnmpEngineBoots,
293
 
                            MsgAuthEngineTime < (SnmpEngineTime - 150) ->
294
 
                                false;
295
 
                            true -> true
296
 
                        end,
297
 
                    case InTimeWindow of
298
 
                        false ->
299
 
                            ?vinfo("NOT in time window: "
300
 
                                   "~n   SecName:            ~p"
301
 
                                   "~n   SnmpEngineBoots:    ~p"
302
 
                                   "~n   MsgAuthEngineBoots: ~p"
303
 
                                   "~n   SnmpEngineTime:     ~p"
304
 
                                   "~n   MsgAuthEngineTime:  ~p",
305
 
                                   [SecName,
306
 
                                    SnmpEngineBoots, MsgAuthEngineBoots,
307
 
                                    SnmpEngineTime, MsgAuthEngineTime]),
308
 
                            error(notInTimeWindow, []);
309
 
                        true ->
310
 
                            ok
311
 
                    end,
312
 
                    true
 
352
                    non_authoritative(SecName, 
 
353
                                      MsgAuthEngineID, 
 
354
                                      MsgAuthEngineBoots, MsgAuthEngineTime)
313
355
            end;
 
356
 
314
357
        false -> 
315
358
            false
316
359
    end.
329
372
            SecName      = element(?usmUserSecurityName, UsmUser),
330
373
            PrivP        = element(?usmUserPrivProtocol, UsmUser),
331
374
            PrivKey      = element(?usmUserPrivKey,      UsmUser), 
 
375
    ?vtrace("do_decrypt -> try decrypt with: "
 
376
            "~n   SecName: ~p"
 
377
            "~n   PrivP:   ~p", [SecName, PrivP]),
332
378
    try_decrypt(PrivP, PrivKey, UsmSecParams, EncryptedPDU, SecName).
333
379
 
334
380
try_decrypt(?usmNoPrivProtocol, _, _, _, SecName) -> % 3.2.5
433
479
 
434
480
generate_discovery_msg(Message, SecEngineID, ManagerEngineID, 
435
481
                       SecName, SecLevel) ->
436
 
    ?vtrace("generate_discovery_msg -> entry with"
 
482
    generate_discovery_msg(Message, SecEngineID, ManagerEngineID, 
 
483
                           SecName, SecLevel, "").
 
484
 
 
485
generate_discovery_msg(Message, SecEngineID, ManagerEngineID, 
 
486
                       SecName, SecLevel, InitialUserName) ->
 
487
   ?vtrace("generate_discovery_msg -> entry with"
437
488
            "~n   SecEngineID:     ~p"
438
489
            "~n   ManagerEngineID: ~p"
439
490
            "~n   SecName:         ~p"
440
 
            "~n   SecLevel:        ~p", 
441
 
            [SecEngineID, ManagerEngineID, SecName, SecLevel]),
 
491
            "~n   SecLevel:        ~p"
 
492
            "~n   InitialUserName: ~p", 
 
493
            [SecEngineID, ManagerEngineID, SecName, SecLevel, 
 
494
             InitialUserName]),
442
495
    {UserName, AuthProtocol, AuthKey, PrivProtocol, PrivKey} = 
443
496
        case ManagerEngineID of
444
497
            "" ->
446
499
                %% Nothing except the user name will be used in this
447
500
                %% tuple in this step, but since we need some values,
448
501
                %% we fill in proper ones just in case
449
 
                {"initial", usmNoAuthProtocol, "", usmNoPrivProtocol, ""}; 
 
502
                %% {"initial", usmNoAuthProtocol, "", usmNoPrivProtocol, ""}; 
 
503
                %% {"", usmNoAuthProtocol, "", usmNoPrivProtocol, ""}; 
 
504
                {InitialUserName, 
 
505
                 usmNoAuthProtocol, "", usmNoPrivProtocol, ""}; 
 
506
 
 
507
%%          _ ->
 
508
%%              %% Discovery step 2
 
509
%%              case snmp_user_based_sm_mib:get_user_from_security_name(
 
510
%%                     SecEngineID, SecName) of
 
511
%%                  User when element(?usmUserStatus, User) =:=
 
512
%%                            ?'RowStatus_active' ->
 
513
%%                      {element(?usmUserName, User),
 
514
%%                       element(?usmUserAuthProtocol, User),
 
515
%%                       element(?usmUserAuthKey, User),
 
516
%%                       usmNoPrivProtocol, ""};
 
517
%%                  {_, Name,_,_,_,_,_,_,_,_,_,_,_, RowStatus,_,_} ->
 
518
%%                      ?vdebug("generate_discovery_msg -> "
 
519
%%                              "found user ~p with wrong row status: ~p", 
 
520
%%                              [Name, RowStatus]),
 
521
%%                      error(unknownSecurityName);
 
522
%%                  _ ->
 
523
%%                      error(unknownSecurityName)
 
524
%%              end
 
525
 
450
526
 
451
527
            _ ->
452
528
                %% Discovery step 2
456
532
                              ?'RowStatus_active' ->
457
533
                        {element(?usmUserName, User),
458
534
                         element(?usmUserAuthProtocol, User),
 
535
                         element(?usmUserAuthKey, User),
459
536
                         element(?usmUserPrivProtocol, User),
460
 
                         element(?usmUserAuthKey, User),
461
537
                         element(?usmUserPrivKey, User)};
462
538
                    {_, Name,_,_,_,_,_,_,_,_,_,_,_, RowStatus,_,_} ->
463
539
                        ?vdebug("generate_discovery_msg -> "
496
572
                    {snmp_pdus:enc_oct_str_tag(ScopedPduData), MsgPrivParams};
497
573
                {error, Reason} ->
498
574
                    error(Reason);
499
 
                _ ->
 
575
                _Error ->
500
576
                    error(encryptionError)
501
577
            end
502
578
    end.
547
623
        case catch ets:update_counter(snmp_agent_table, usm_des_salt, 1) of
548
624
            N when N =< 4294967295 ->
549
625
                N;
550
 
            N when integer(N) -> % wrap
 
626
            N when is_integer(N) -> % wrap
551
627
                ets:insert(snmp_agent_table, {usm_des_salt, 0}),
552
628
                0;
553
629
            _ -> % it doesn't exist, initialize
576
652
        case catch ets:update_counter(snmp_agent_table, usm_aes_salt, 1) of
577
653
            N when N =< 36893488147419103231  ->
578
654
                N;
579
 
            N when integer(N) -> % wrap
 
655
            N when is_integer(N) -> % wrap
580
656
                ets:insert(snmp_agent_table, {usm_aes_salt, 0}),
581
657
                0;
582
658
            _ -> % it doesn't exist, initialize
591
667
 
592
668
 
593
669
%%-----------------------------------------------------------------
 
670
%% Discovery wrapper functions
 
671
%%-----------------------------------------------------------------
 
672
 
 
673
is_terminating_discovery_enabled() ->
 
674
    snmpa_agent:is_terminating_discovery_enabled().
 
675
 
 
676
terminating_discovery_stage2() ->
 
677
    snmpa_agent:terminating_discovery_stage2().
 
678
 
 
679
 
 
680
%%-----------------------------------------------------------------
594
681
%% We cache the local values of all non-auth engines we know.
595
682
%% Keep the values in the snmp_agent_table.
596
683
%% See section 2.3 of the RFC.