~statik/ubuntu/maverick/erlang/erlang-merge-testing

« back to all changes in this revision

Viewing changes to lib/snmp/src/agent/snmpa_trap.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%%<copyright>
2
 
%% <year>1996-2008</year>
3
 
%% <holder>Ericsson AB, All Rights Reserved</holder>
4
 
%%</copyright>
5
 
%%<legalnotice>
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 1996-2009. 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
 
%%
17
 
%% The Initial Developer of the Original Code is Ericsson AB.
18
 
%%</legalnotice>
 
16
%% 
 
17
%% %CopyrightEnd%
19
18
%%
20
19
-module(snmpa_trap).
21
20
 
22
21
%%%-----------------------------------------------------------------
23
 
%%% This module takes care of all trap handling.
 
22
%%% This module takes care of all trap(notification handling.
24
23
%%%-----------------------------------------------------------------
25
24
%% External exports
26
 
-export([construct_trap/2, try_initialise_vars/2, send_trap/6]).
 
25
-export([construct_trap/2, 
 
26
         try_initialise_vars/2, send_trap/6]).
 
27
-export([send_discovery/5]).
27
28
 
28
29
%% Internal exports
29
30
-export([init_v2_inform/9, init_v3_inform/9, send_inform/6]).
 
31
-export([init_discovery_inform/12, send_discovery_inform/5]).
30
32
 
31
33
-include("snmp_types.hrl").
32
34
-include("SNMPv2-MIB.hrl").
33
35
-include("SNMPv2-TM.hrl").
 
36
-include("SNMPv2-TC.hrl").
34
37
-include("SNMP-FRAMEWORK-MIB.hrl").
 
38
-include("SNMP-TARGET-MIB.hrl").
35
39
-define(enterpriseSpecific, 6).
36
40
 
37
41
 
122
126
            user_err("construct_trap got undef Trap: ~w" , [Trap]),
123
127
            error;
124
128
 
125
 
        {value, TRec} when is_record(TRec, trap) ->
 
129
        {value, #trap{oidobjects = ListOfVars} = TRec} ->
126
130
            ?vdebug("construct_trap -> trap"
127
131
                    "~n   ~p", [TRec]),
128
 
            ListOfVars = TRec#trap.oidobjects,
129
 
            OidVbs = [alias_to_oid(Vb) || Vb <- Varbinds],
130
 
            LV = initiate_vars(ListOfVars, OidVbs),
 
132
            OidVbs        = [alias_to_oid(Vb) || Vb <- Varbinds],
 
133
            LV            = initiate_vars(ListOfVars, OidVbs),
131
134
            InitiatedVars = try_initialise_vars(get(mibserver), LV),
132
135
            {ok, TRec, InitiatedVars};
133
136
 
134
 
        {value, NRec} when is_record(NRec, notification) ->
 
137
        {value, #notification{oidobjects = ListOfVars} = NRec} ->
135
138
            ?vdebug("construct_trap -> notification"
136
139
                    "~n   ~p", [NRec]),
137
 
            ListOfVars = NRec#notification.oidobjects,
138
 
            OidVbs = [alias_to_oid(Vb) || Vb <- Varbinds],
139
 
            LV = initiate_vars(ListOfVars, OidVbs),
 
140
            OidVbs        = [alias_to_oid(Vb) || Vb <- Varbinds],
 
141
            LV            = initiate_vars(ListOfVars, OidVbs),
140
142
            InitiatedVars = try_initialise_vars(get(mibserver), LV), 
141
143
            {ok, NRec, InitiatedVars}
142
144
    end.
287
289
             time_stamp    = SysUpTime,
288
290
             varbinds      = VarbindList}.
289
291
 
 
292
make_discovery_pdu(Vbs) ->
 
293
    #pdu{type         = 'inform-request',
 
294
         request_id   = snmpa_mpd:generate_req_id(),
 
295
         error_status = noError,
 
296
         error_index  = 0,
 
297
         varbinds     = Vbs}.
 
298
 
290
299
make_v2_notif_pdu(Vbs, Type) ->
291
300
    #pdu{type         = Type,
292
301
         request_id   = snmpa_mpd:generate_req_id(),
329
338
    Dests       = find_dests(NotifyName),
330
339
    send_trap_pdus(Dests, ContextName, {TrapRec, VarbindList}, [], [], [],
331
340
                   Recv, NetIf).
332
 
            
 
341
 
 
342
send_discovery(TargetName, Record, ContextName, Vbs, NetIf) ->
 
343
    case find_dest(TargetName) of
 
344
        {ok, Dest} ->
 
345
            send_discovery_pdu(Dest, Record, ContextName, Vbs, NetIf);
 
346
        Error ->
 
347
            Error
 
348
    end.
 
349
 
 
350
 
333
351
get_values(VariablesWithType) ->
334
352
    {Order, Varbinds} = extract_order(VariablesWithType, 1),
335
353
    case snmpa_agent:do_get(snmpa_acm:get_root_mib_view(), Varbinds, true) of
398
416
    throw(error);
399
417
split_variables([]) -> {[], []}.
400
418
 
 
419
 
401
420
%%-----------------------------------------------------------------
402
421
%% Func: find_dests(NotifyName) -> 
403
422
%%          [{DestAddr, TargetName, TargetParams, NotifyType}]
420
439
            Dests
421
440
    end.
422
441
 
 
442
find_dest(TargetName) ->
 
443
    AddrCols = [?snmpTargetAddrTDomain,
 
444
                ?snmpTargetAddrTAddress,
 
445
                ?snmpTargetAddrTimeout,
 
446
                ?snmpTargetAddrRetryCount,
 
447
                ?snmpTargetAddrParams,
 
448
                ?snmpTargetAddrRowStatus],
 
449
    case snmp_target_mib:snmpTargetAddrTable(get, TargetName, AddrCols) of
 
450
        [{value, TDomain},
 
451
         {value, TAddress},
 
452
         {value, Timeout},
 
453
         {value, RetryCount},
 
454
         {value, Params},
 
455
         {value, ?'RowStatus_active'}] ->
 
456
            ?vtrace("find_dest -> found snmpTargetAddrTable info:"
 
457
                    "~n   TDomain:    ~p"
 
458
                    "~n   TAddress:   ~p"
 
459
                    "~n   Timeout:    ~p"
 
460
                    "~n   RetryCount: ~p"
 
461
                    "~n   Params:     ~p", 
 
462
                    [TDomain, TAddress, Timeout, RetryCount, Params]),
 
463
            ParmCols = [?snmpTargetParamsMPModel,
 
464
                        ?snmpTargetParamsSecurityModel,
 
465
                        ?snmpTargetParamsSecurityName,
 
466
                        ?snmpTargetParamsSecurityLevel,
 
467
                        ?snmpTargetParamsRowStatus],
 
468
            case snmp_target_mib:snmpTargetParamsTable(get, Params, ParmCols) of
 
469
                [{value, ?MP_V3}, 
 
470
                 {value, SecModel}, 
 
471
                 {value, SecName}, 
 
472
                 {value, SecLevel},
 
473
                 {value, ?'RowStatus_active'}] ->
 
474
                    ?vtrace("find_dest -> found snmpTargetParamsTable info:"
 
475
                            "~n   SecModel: ~p"
 
476
                            "~n   SecModel: ~p"
 
477
                            "~n   SecLevel: ~p", 
 
478
                            [SecModel, SecName, SecLevel]),
 
479
                    DestAddr     = {TDomain, TAddress},
 
480
                    TargetParams = {SecModel, SecName, SecLevel},
 
481
                    Val = {DestAddr, TargetName, TargetParams, Timeout, RetryCount},
 
482
                    {ok, Val};
 
483
                [{value, ?MP_V3}, 
 
484
                 {value, _SecModel}, 
 
485
                 {value, _SecName}, 
 
486
                 {value, _SecLevel},
 
487
                 {value, RowStatus}] ->
 
488
                    {error, {invalid_RowStatus, RowStatus, snmpTargetParamsTable}};
 
489
                [{value, MpModel}, 
 
490
                 {value, _SecModel}, 
 
491
                 {value, _SecName}, 
 
492
                 {value, _SecLevel},
 
493
                 {value, ?'RowStatus_active'}] ->
 
494
                    {error, {invalid_MpModel, MpModel, snmpTargetParamsTable}};
 
495
                [{value, _MpModel}, 
 
496
                 {value, _SecModel}, 
 
497
                 {value, _SecName}, 
 
498
                 {value, _SecLevel},
 
499
                 {value, RowStatus}] ->
 
500
                    {error, {invalid_RowStatus, RowStatus, snmpTargetParamsTable}};
 
501
                Bad ->
 
502
                    ?vlog("find_dest -> "
 
503
                          "could not find snmpTargetParamsTable info: "
 
504
                          "~n   Bad: ~p", [Bad]),
 
505
                    {error, {not_found, snmpTargetParamsTable}}
 
506
            end;
 
507
        
 
508
        [{value, _TDomain},
 
509
         {value, _TAddress},
 
510
         {value, _Timeout},
 
511
         {value, _RetryCount},
 
512
         {value, _Params},
 
513
         {value, RowStatus}] ->
 
514
            {error, {invalid_RowStatus, RowStatus, snmpTargetAddrTable}};
 
515
        _ ->
 
516
            {error, {not_found, snmpTargetAddrTable}}
 
517
    end.
 
518
 
 
519
 
 
520
send_discovery_pdu({Dest, TargetName, {SecModel, SecName, SecLevel}, 
 
521
                    Timeout, Retry}, 
 
522
                   Record, ContextName, Vbs, NetIf) ->
 
523
    ?vdebug("send_discovery_pdu -> entry with "
 
524
            "~n   Destination address: ~p"
 
525
            "~n   Target name:         ~p"
 
526
            "~n   Sec model:           ~p"
 
527
            "~n   Sec name:            ~p"
 
528
            "~n   Sec level:           ~p"
 
529
            "~n   Timeout:             ~p"
 
530
            "~n   Retry:               ~p"
 
531
            "~n   Record:              ~p"
 
532
            "~n   ContextName:         ~p",
 
533
            [Dest, TargetName, SecModel, SecName, SecLevel, 
 
534
             Timeout, Retry, Record, ContextName]),
 
535
    case snmpa_vacm:get_mib_view(notify, SecModel, SecName, SecLevel,
 
536
                                 ContextName) of
 
537
        {ok, MibView} ->
 
538
            case check_all_varbinds(Record, Vbs, MibView) of
 
539
                true ->
 
540
                    SysUpTime = snmp_standard_mib:sys_up_time(), 
 
541
                    send_discovery_pdu(Record, Dest, Vbs, 
 
542
                                       SecModel, SecName, SecLevel, 
 
543
                                       TargetName, ContextName, 
 
544
                                       Timeout, Retry, 
 
545
                                       SysUpTime, NetIf);
 
546
                false ->
 
547
                    {error, {mibview_validation_failed, Vbs, MibView}}
 
548
            end;
 
549
        {discarded, Reason} ->
 
550
            {error, {failed_get_mibview, Reason}}
 
551
    end.
 
552
 
 
553
send_discovery_pdu(Record, Dest, Vbs, 
 
554
                   SecModel, SecName, SecLevel, TargetName, 
 
555
                   ContextName, Timeout, Retry, SysUpTime, NetIf) ->
 
556
    {_Oid, IVbs} = mk_v2_trap(Record, Vbs, SysUpTime), % v2 refers to SMIv2;
 
557
    Sender = proc_lib:spawn_link(?MODULE, init_discovery_inform,
 
558
                                 [self(), 
 
559
                                  Dest, 
 
560
                                  SecModel, SecName, SecLevel, TargetName,
 
561
                                  ContextName, 
 
562
                                  Timeout, Retry, 
 
563
                                  IVbs, NetIf, 
 
564
                                  get(verbosity)]),
 
565
    {ok, Sender, SecLevel}.
 
566
 
 
567
init_discovery_inform(Parent, 
 
568
                      Dest, 
 
569
                      SecModel, SecName, SecLevel, TargetName, 
 
570
                      ContextName, Timeout, Retry, Vbs, NetIf, Verbosity) ->
 
571
    put(verbosity, Verbosity),
 
572
    put(sname, madis),
 
573
    Pdu = make_discovery_pdu(Vbs), 
 
574
    ContextEngineId = snmp_framework_mib:get_engine_id(),
 
575
    SecLevelFlag = mk_flag(SecLevel), 
 
576
    SecData      = {SecModel, SecName, SecLevelFlag, TargetName}, 
 
577
    MsgData      = {SecData, ContextEngineId, ContextName}, 
 
578
%%     NoteTimeout = note_timeout(Timeout, Retry),
 
579
%%     Msg         = {send_discovery, Pdu, MsgData, NoteTimeout, Dest, self()},
 
580
    Msg          = {send_discovery, Pdu, MsgData, Dest, self()},
 
581
    ?MODULE:send_discovery_inform(Parent, Timeout*10, Retry, Msg, NetIf).
 
582
 
 
583
%% note_timeout(Timeout, Retry) 
 
584
%%   when ((is_integer(Timeout) andalso (Timeout > 0)) andalso 
 
585
%%      (is_integer(Retry) andalso (Retry > 0)))
 
586
%%     note_timeout(Timeout*10, Retry, 0);
 
587
%% note_timeout(Timeout, Retry) 
 
588
%%   when (is_integer(Timeout) andalso (Timeout > 0)) ->
 
589
%%     Timeout*10.
 
590
 
 
591
%% note_timeout(_Timeout, -1, NoteTimeout) ->
 
592
%%     NoteTimeout;
 
593
%% note_timeout(Timeout, Retry, NoteTimeout) when ->
 
594
%%     note_timeout(Timeout*2, Retry-1, NoteTimeout+Timeout).
 
595
 
 
596
send_discovery_inform(Parent, _Timeout, -1, _Msg, _NetIf) ->
 
597
    Parent ! {discovery_response, {error, timeout}};
 
598
send_discovery_inform(Parent, Timeout, Retry, Msg, NetIf) ->
 
599
    NetIf ! Msg,
 
600
    receive
 
601
        {snmp_discovery_response_received, Pdu, undefined} ->
 
602
            ?vtrace("received stage 2 discovery response: "
 
603
                    "~n   Pdu: ~p", [Pdu]),
 
604
            Parent ! {discovery_response, {ok, Pdu}};
 
605
        {snmp_discovery_response_received, Pdu, ManagerEngineId} ->
 
606
            ?vtrace("received stage 1 discovery response: "
 
607
                    "~n   Pdu:             ~p"
 
608
                    "~n   ManagerEngineId: ~p", [Pdu, ManagerEngineId]),
 
609
            Parent ! {discovery_response, {ok, Pdu, ManagerEngineId}}
 
610
    after
 
611
        Timeout ->
 
612
            ?MODULE:send_discovery_inform(Parent, 
 
613
                                          Timeout*2, Retry-1, Msg, NetIf)
 
614
    end.
 
615
 
 
616
    
423
617
%%-----------------------------------------------------------------
424
618
%% NOTE: This function is executed in the master agent's context
425
619
%% For each target, check if it has access to the objects in the
438
632
            "~n   V1Res:               ~p"
439
633
            "~n   V2Res:               ~p"
440
634
            "~n   V3Res:               ~p",
441
 
            [DestAddr,TargetName,MpModel,Type,V1Res,V2Res,V3Res]),
 
635
            [DestAddr, TargetName, MpModel, Type, V1Res, V2Res, V3Res]),
442
636
    case snmpa_vacm:get_mib_view(notify, SecModel, SecName, SecLevel,
443
637
                                 ContextName) of
444
638
        {ok, MibView} ->
445
639
            case check_all_varbinds(TrapRec, Vbs, MibView) of
446
 
                true when MpModel == ?MP_V1 ->
 
640
                true when MpModel =:= ?MP_V1 ->
447
641
                    ?vtrace("send_trap_pdus -> v1 mp model",[]),
448
642
                    ContextEngineId = snmp_framework_mib:get_engine_id(),
449
643
                    case snmp_community_mib:vacm2community({SecName,
462
656
                            send_trap_pdus(T, ContextName, {TrapRec, Vbs},
463
657
                                           V1Res, V2Res, V3Res, Recv, NetIf)
464
658
                    end;
465
 
                true when MpModel == ?MP_V2C ->
 
659
                true when MpModel =:= ?MP_V2C ->
466
660
                    ?vtrace("send_trap_pdus -> v2c mp model",[]),
467
661
                    ContextEngineId = snmp_framework_mib:get_engine_id(),
468
662
                    case snmp_community_mib:vacm2community({SecName,
482
676
                            send_trap_pdus(T, ContextName, {TrapRec, Vbs},
483
677
                                           V1Res, V2Res, V3Res, Recv, NetIf)
484
678
                    end;
485
 
                true when MpModel == ?MP_V3 ->
 
679
                true when MpModel =:= ?MP_V3 ->
486
680
                    ?vtrace("send_trap_pdus -> v3 mp model",[]),
487
681
                    SecLevelF = mk_flag(SecLevel),
488
682
                    MsgData = {SecModel, SecName, SecLevelF, TargetName},
703
897
           []),
704
898
    deliver_recv(Recv, snmp_notification, {no_response, Addr});
705
899
send_inform(Addr, Timeout, Retry, Msg, Recv, NetIf) ->
706
 
    ?vtrace("~n   deliver send-pdu-request to net-if when"
 
900
    ?vtrace("deliver send-pdu-request to net-if when"
707
901
            "~n   Timeout: ~p"
708
902
            "~n   Retry:   ~p",[Timeout, Retry]),
709
903
    NetIf ! Msg,
710
904
    receive
711
905
        {snmp_response_received, _Vsn, _Pdu, _From} ->
712
 
            ?vtrace("~n   received response for ~p (~p)",[Recv,Retry]),
 
906
            ?vtrace("received response for ~p (when Retry = ~p)", 
 
907
                    [Recv, Retry]),
713
908
            deliver_recv(Recv, snmp_notification, {got_response, Addr})
714
909
    after
715
910
        Timeout ->