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

« back to all changes in this revision

Viewing changes to lib/snmp/src/agent/snmpa_agent.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 1996-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1996-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_agent).
30
30
-export([subagent_set/2, 
31
31
         load_mibs/2, unload_mibs/2, which_mibs/1, whereis_mib/2, info/1,
32
32
         register_subagent/3, unregister_subagent/2,
33
 
         send_trap/6, 
 
33
         send_trap/6, send_trap/7, 
34
34
         register_notification_filter/5,
35
35
         unregister_notification_filter/2,
36
36
         which_notification_filter/1,
48
48
         get/2, get/3, get_next/2, get_next/3]).
49
49
-export([mib_of/1, mib_of/2, me_of/1, me_of/2,
50
50
         invalidate_mibs_cache/1,
 
51
         which_mibs_cache_size/1, 
51
52
         enable_mibs_cache/1, disable_mibs_cache/1,
52
53
         gc_mibs_cache/1, gc_mibs_cache/2, gc_mibs_cache/3,
53
54
         enable_mibs_cache_autogc/1, disable_mibs_cache_autogc/1,
58
59
-export([get_log_type/1,      set_log_type/2]).
59
60
-export([get_request_limit/1, set_request_limit/2]).
60
61
-export([invalidate_ca_cache/0]).
 
62
-export([increment_counter/3]).
61
63
-export([restart_worker/1, restart_set_worker/1]).
62
64
 
63
65
%% Internal exports
64
66
-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
65
67
         terminate/2, code_change/3, tr_var/2, tr_varbind/1,
66
 
         handle_pdu/7, worker/2, worker_loop/1, do_send_trap/6]).
 
68
         handle_pdu/7, worker/2, worker_loop/1, do_send_trap/7]).
67
69
 
68
70
-ifndef(default_verbosity).
69
71
-define(default_verbosity,silence).
244
246
    call(Agent, {mibs_cache_request, disable_cache}).
245
247
 
246
248
 
 
249
which_mibs_cache_size(Agent) ->
 
250
    call(Agent, {mibs_cache_request, cache_size}).
 
251
 
 
252
 
247
253
enable_mibs_cache_autogc(Agent) ->
248
254
    call(Agent, {mibs_cache_request, enable_autogc}).
249
255
 
259
265
    call(Agent, {mibs_cache_request, {update_age, Age}}).
260
266
 
261
267
 
 
268
increment_counter(Counter, Initial, Max) ->
 
269
    %% This is to make sure no one else increments our counter
 
270
    Key = {Counter, self()}, 
 
271
 
 
272
    %% Counter data
 
273
    Position  = 2, 
 
274
    Increment = 1, 
 
275
    Threshold = Max,
 
276
    SetValue  = Initial, 
 
277
    UpdateOp  = {Position, Increment, Threshold, SetValue},
 
278
    
 
279
    %% And now for the actual increment
 
280
    Tab = snmp_agent_table, 
 
281
    case (catch ets:update_counter(Tab, Key, UpdateOp)) of
 
282
        {'EXIT', {badarg, _}} ->
 
283
            %% Oups, first time
 
284
            ets:insert(Tab, {Key, Initial}),
 
285
            Initial;
 
286
        Next when is_integer(Next) ->
 
287
            Next
 
288
    end.
 
289
 
 
290
 
262
291
init([Prio, Parent, Ref, Options]) ->
263
292
    ?d("init -> entry with"
264
293
        "~n   Prio:    ~p"
500
529
 
501
530
send_trap(Agent, Trap, NotifyName, CtxName, Recv, Varbinds) ->
502
531
    ?d("send_trap -> entry with"
503
 
       "~n   self():     ~p"
504
 
       "~n   Agent:      ~p [~p]"
505
 
       "~n   Trap:       ~p"
506
 
       "~n   NotifyName: ~p"
507
 
       "~n   CtxName:    ~p"
508
 
       "~n   Recv:       ~p"
509
 
       "~n   Varbinds:   ~p", 
510
 
       [self(), Agent, wis(Agent), Trap, NotifyName, CtxName, Recv, Varbinds]),
 
532
       "~n   self():        ~p"
 
533
       "~n   Agent:         ~p [~p]"
 
534
       "~n   Trap:          ~p"
 
535
       "~n   NotifyName:    ~p"
 
536
       "~n   CtxName:       ~p"
 
537
       "~n   Recv:          ~p"
 
538
       "~n   Varbinds:      ~p", 
 
539
       [self(), Agent, wis(Agent), 
 
540
        Trap, NotifyName, CtxName, Recv, Varbinds]),
511
541
    Msg = {send_trap, Trap, NotifyName, CtxName, Recv, Varbinds}, 
512
542
    case (wis(Agent) =:= self()) of
513
543
        false ->
516
546
            Agent ! Msg
517
547
    end.
518
548
 
 
549
send_trap(Agent, Trap, NotifyName, CtxName, Recv, Varbinds, LocalEngineID) ->
 
550
    ?d("send_trap -> entry with"
 
551
       "~n   self():        ~p"
 
552
       "~n   Agent:         ~p [~p]"
 
553
       "~n   Trap:          ~p"
 
554
       "~n   NotifyName:    ~p"
 
555
       "~n   CtxName:       ~p"
 
556
       "~n   Recv:          ~p"
 
557
       "~n   Varbinds:      ~p" 
 
558
       "~n   LocalEngineID: ~p", 
 
559
       [self(), Agent, wis(Agent), 
 
560
        Trap, NotifyName, CtxName, Recv, Varbinds, LocalEngineID]),
 
561
    Msg = 
 
562
        {send_trap, Trap, NotifyName, CtxName, Recv, Varbinds, LocalEngineID}, 
 
563
    case (wis(Agent) =:= self()) of
 
564
        false ->
 
565
            call(Agent, Msg);
 
566
        true ->
 
567
            Agent ! Msg
 
568
    end.
 
569
 
519
570
 
520
571
%% -- Discovery functions --
521
572
 
602
653
wis(Atom) when is_atom(Atom) ->
603
654
    whereis(Atom).
604
655
 
 
656
 
605
657
forward_trap(Agent, TrapRecord, NotifyName, CtxName, Recv, Varbinds) ->
606
658
    Agent ! {forward_trap, TrapRecord, NotifyName, CtxName, Recv, Varbinds}.
607
659
 
695
747
 
696
748
handle_info({send_trap, Trap, NotifyName, ContextName, Recv, Varbinds}, S) ->
697
749
    ?vlog("[handle_info] send trap request:"
698
 
          "~n   Trap:        ~p"
699
 
          "~n   NotifyName:  ~p"
700
 
          "~n   ContextName: ~p"
701
 
          "~n   Recv:        ~p" 
702
 
          "~n   Varbinds:    ~p", 
703
 
          [Trap,NotifyName,ContextName,Recv,Varbinds]),
704
 
    case catch handle_send_trap(S, Trap, NotifyName, ContextName,
705
 
                                Recv, Varbinds) of
706
 
        {ok, NewS} ->
707
 
            {noreply, NewS};
708
 
        {'EXIT', R} ->
709
 
            ?vinfo("Trap not sent:~n   ~p", [R]),
710
 
            {noreply, S};
711
 
        _ ->
712
 
            {noreply, S}
713
 
    end;
714
 
 
715
 
handle_info({forward_trap, TrapRecord, NotifyName, ContextName,
716
 
             Recv, Varbinds},S) ->
 
750
          "~n   Trap:          ~p"
 
751
          "~n   NotifyName:    ~p"
 
752
          "~n   ContextName:   ~p"
 
753
          "~n   Recv:          ~p" 
 
754
          "~n   Varbinds:      ~p", 
 
755
          [Trap, NotifyName, ContextName, Recv, Varbinds]),
 
756
    LocalEngineID = ?DEFAULT_LOCAL_ENGINE_ID, 
 
757
    case catch handle_send_trap(S, Trap, NotifyName, ContextName,
 
758
                                Recv, Varbinds, LocalEngineID) of
 
759
        {ok, NewS} ->
 
760
            {noreply, NewS};
 
761
        {'EXIT', R} ->
 
762
            ?vinfo("Trap not sent:~n   ~p", [R]),
 
763
            {noreply, S};
 
764
        _ ->
 
765
            {noreply, S}
 
766
    end;
 
767
 
 
768
handle_info({send_trap, Trap, NotifyName, ContextName, Recv, Varbinds, 
 
769
             LocalEngineID}, S) ->
 
770
    ?vlog("[handle_info] send trap request:"
 
771
          "~n   Trap:          ~p"
 
772
          "~n   NotifyName:    ~p"
 
773
          "~n   ContextName:   ~p"
 
774
          "~n   Recv:          ~p" 
 
775
          "~n   Varbinds:      ~p" 
 
776
          "~n   LocalEngineID: ~p", 
 
777
          [Trap, NotifyName, ContextName, Recv, Varbinds, LocalEngineID]),
 
778
    case catch handle_send_trap(S, Trap, NotifyName, ContextName,
 
779
                                Recv, Varbinds, LocalEngineID) of
 
780
        {ok, NewS} ->
 
781
            {noreply, NewS};
 
782
        {'EXIT', R} ->
 
783
            ?vinfo("Trap not sent:~n   ~p", [R]),
 
784
            {noreply, S};
 
785
        _ ->
 
786
            {noreply, S}
 
787
    end;
 
788
 
 
789
handle_info({forward_trap, TrapRecord, NotifyName, ContextName, 
 
790
             Recv, Varbinds}, S) ->
717
791
    ?vlog("[handle_info] forward trap request:"
718
 
          "~n   TrapRecord:  ~p"
719
 
          "~n   NotifyName:  ~p"
720
 
          "~n   ContextName: ~p"
721
 
          "~n   Recv:        ~p"
722
 
          "~n   Varbinds:    ~p", 
723
 
          [TrapRecord,NotifyName,ContextName,Recv,Varbinds]),
 
792
          "~n   TrapRecord:    ~p"
 
793
          "~n   NotifyName:    ~p"
 
794
          "~n   ContextName:   ~p"
 
795
          "~n   Recv:          ~p"
 
796
          "~n   Varbinds:      ~p", 
 
797
          [TrapRecord, NotifyName, ContextName, Recv, Varbinds]),
 
798
    LocalEngineID = ?DEFAULT_LOCAL_ENGINE_ID, 
724
799
    case (catch maybe_send_trap(S, TrapRecord, NotifyName, ContextName,
725
 
                                Recv, Varbinds)) of
 
800
                                Recv, Varbinds, LocalEngineID)) of
726
801
        {ok, NewS} ->
727
802
            {noreply, NewS};
728
803
        {'EXIT', R} ->
832
907
            ok
833
908
    end,
834
909
    {reply, ok, S};
 
910
 
835
911
handle_call({send_trap, Trap, NotifyName, ContextName, Recv, Varbinds}, 
836
912
            _From, S) ->
837
913
    ?vlog("[handle_call] send trap request:"
838
 
          "~n   Trap:        ~p"
839
 
          "~n   NotifyName:  ~p"
840
 
          "~n   ContextName: ~p"
841
 
          "~n   Recv:        ~p" 
842
 
          "~n   Varbinds:    ~p", 
843
 
          [Trap,NotifyName,ContextName,Recv,Varbinds]),
844
 
    case (catch handle_send_trap(S, Trap, NotifyName, ContextName,
845
 
                                 Recv, Varbinds)) of
846
 
        {ok, NewS} ->
847
 
            {reply, ok, NewS};
848
 
        {'EXIT', Reason} ->
849
 
            ?vinfo("Trap not sent:~n   ~p", [Reason]),
850
 
            {reply, {error, {send_failed, Reason}}, S};
851
 
        _ ->
852
 
            ?vinfo("Trap not sent", []),
853
 
            {reply, {error, send_failed}, S}
854
 
    end;
 
914
          "~n   Trap:          ~p"
 
915
          "~n   NotifyName:    ~p"
 
916
          "~n   ContextName:   ~p"
 
917
          "~n   Recv:          ~p" 
 
918
          "~n   Varbinds:      ~p", 
 
919
          [Trap, NotifyName, ContextName, Recv, Varbinds]),
 
920
    LocalEngineID = 
 
921
        case S#state.type of
 
922
            master_agent ->
 
923
                ?DEFAULT_LOCAL_ENGINE_ID;
 
924
            _ -> 
 
925
                %% subagent - 
 
926
                %% we don't need this, eventually the trap sent request 
 
927
                %% will reach the master-agent and then it will look up 
 
928
                %% the proper engine id.
 
929
                ignore
 
930
        end,
 
931
    case (catch handle_send_trap(S, Trap, NotifyName, ContextName,
 
932
                                 Recv, Varbinds, LocalEngineID)) of
 
933
        {ok, NewS} ->
 
934
            {reply, ok, NewS};
 
935
        {'EXIT', Reason} ->
 
936
            ?vinfo("Trap not sent:~n   ~p", [Reason]),
 
937
            {reply, {error, {send_failed, Reason}}, S};
 
938
        _ ->
 
939
            ?vinfo("Trap not sent", []),
 
940
            {reply, {error, send_failed}, S}
 
941
    end;
 
942
 
 
943
handle_call({send_trap, Trap, NotifyName, 
 
944
             ContextName, Recv, Varbinds, LocalEngineID}, 
 
945
            _From, S) ->
 
946
    ?vlog("[handle_call] send trap request:"
 
947
          "~n   Trap:          ~p"
 
948
          "~n   NotifyName:    ~p"
 
949
          "~n   ContextName:   ~p"
 
950
          "~n   Recv:          ~p" 
 
951
          "~n   Varbinds:      ~p" 
 
952
          "~n   LocalEngineID: ~p", 
 
953
          [Trap, NotifyName, ContextName, Recv, Varbinds, LocalEngineID]),
 
954
    case (catch handle_send_trap(S, Trap, NotifyName, ContextName,
 
955
                                 Recv, Varbinds, LocalEngineID)) of
 
956
        {ok, NewS} ->
 
957
            {reply, ok, NewS};
 
958
        {'EXIT', Reason} ->
 
959
            ?vinfo("Trap not sent:~n   ~p", [Reason]),
 
960
            {reply, {error, {send_failed, Reason}}, S};
 
961
        _ ->
 
962
            ?vinfo("Trap not sent", []),
 
963
            {reply, {error, send_failed}, S}
 
964
    end;
 
965
 
855
966
handle_call({discovery, 
856
 
             TargetName, Notification, ContextName, Vbs, DiscoHandler, ExtraInfo}, 
 
967
             TargetName, Notification, ContextName, Vbs, DiscoHandler, 
 
968
             ExtraInfo}, 
857
969
            From, 
858
970
            #state{disco = undefined} = S) ->
859
971
    ?vlog("[handle_call] initiate discovery process:"
1195
1307
                              snmpa_mib:gc_cache(MibServer, Age);
1196
1308
                          {gc_cache, Age, GcLimit} ->
1197
1309
                              snmpa_mib:gc_cache(MibServer, Age, GcLimit);
 
1310
                          cache_size ->
 
1311
                              snmpa_mib:which_cache_size(MibServer);
1198
1312
                          enable_cache ->
1199
1313
                              snmpa_mib:enable_cache(MibServer);
1200
1314
                          disable_cache ->
1223
1337
 
1224
1338
%% Downgrade
1225
1339
%%
1226
 
code_change({down, _Vsn}, S, downgrade_to_pre_4_13) ->
1227
 
    S1 = workers_restart(S),
1228
 
    case S1#state.disco of
1229
 
        undefined ->
1230
 
            ok;
1231
 
        #disco{from   = From,
1232
 
               sender = Sender,
1233
 
               stage  = Stage} ->
1234
 
            gen_server:reply(From, {error, {upgrade, Stage, Sender}}),
1235
 
            exit(Sender, kill)
1236
 
    end,
1237
 
    S2 = {state, 
1238
 
          S1#state.type,
1239
 
          S1#state.parent, 
1240
 
          S1#state.worker, 
1241
 
          S1#state.worker_state,
1242
 
          S1#state.set_worker, 
1243
 
          S1#state.multi_threaded, 
1244
 
          S1#state.ref, 
1245
 
          S1#state.vsns,
1246
 
          S1#state.nfilters,
1247
 
          S1#state.note_store,
1248
 
          S1#state.mib_server,   
1249
 
          S1#state.net_if,       
1250
 
          S1#state.net_if_mod,   
1251
 
          S1#state.backup,
1252
 
          S1#state.disco}, 
1253
 
    {ok, S2};
 
1340
%% code_change({down, _Vsn}, S, downgrade_to_pre_4_13) ->
 
1341
%%     {ok, S2};
1254
1342
 
1255
1343
%% Upgrade
1256
1344
%%
1257
 
code_change(_Vsn, S, upgrade_from_pre_4_13) ->
1258
 
    {state, 
1259
 
     Type, 
1260
 
     Parent, 
1261
 
     Worker, 
1262
 
     WorkerState,
1263
 
     SetWorker, 
1264
 
     MultiThreaded, 
1265
 
     Ref, 
1266
 
     Vsns,
1267
 
     NFilters = [],
1268
 
     NoteStore,
1269
 
     MibServer,   %% Currently unused
1270
 
     NetIf,       %% Currently unused
1271
 
     NetIfMod,   
1272
 
     Backup} = S,
1273
 
    S1 = #state{type           = Type, 
1274
 
                parent         = Parent, 
1275
 
                worker         = Worker, 
1276
 
                worker_state   = WorkerState,
1277
 
                set_worker     = SetWorker, 
1278
 
                multi_threaded = MultiThreaded, 
1279
 
                ref            = Ref, 
1280
 
                vsns           = Vsns,
1281
 
                nfilters       = NFilters,
1282
 
                note_store     = NoteStore,
1283
 
                mib_server     = MibServer, 
1284
 
                net_if         = NetIf, 
1285
 
                net_if_mod     = NetIfMod,   
1286
 
                backup         = Backup},
1287
 
    S2 = workers_restart(S1),
1288
 
    {ok, S2};
 
1345
%% code_change(_Vsn, S, upgrade_from_pre_4_13) ->
 
1346
%%     {ok, S2};
1289
1347
 
1290
1348
code_change(_Vsn, S, _Extra) ->
1291
1349
    {ok, S}.
1292
1350
 
1293
1351
 
1294
 
workers_restart(#state{worker = W, set_worker = SW} = S) ->
1295
 
    Worker    = worker_restart(W),
1296
 
    SetWorker = set_worker_restart(SW),
1297
 
    S#state{worker     = Worker, 
1298
 
            set_worker = SetWorker}.
 
1352
%% workers_restart(#state{worker = W, set_worker = SW} = S) ->
 
1353
%%     Worker    = worker_restart(W),
 
1354
%%     SetWorker = set_worker_restart(SW),
 
1355
%%     S#state{worker     = Worker, 
 
1356
%%          set_worker = SetWorker}.
1299
1357
 
1300
1358
 
1301
1359
%%-----------------------------------------------------------------
1321
1379
worker_start(Dict) ->
1322
1380
    proc_lib:spawn_link(?MODULE, worker, [self(), Dict]).
1323
1381
 
1324
 
worker_stop(Pid) ->
1325
 
    worker_stop(Pid, infinity).
 
1382
%% worker_stop(Pid) ->
 
1383
%%     worker_stop(Pid, infinity).
1326
1384
 
1327
1385
worker_stop(Pid, Timeout) when is_pid(Pid) ->
1328
1386
    Pid ! terminate, 
1336
1394
worker_stop(_, _) ->
1337
1395
    ok.
1338
1396
 
1339
 
set_worker_restart(Pid) ->
1340
 
    worker_restart(Pid, [{master, self()} | get()]).
1341
 
 
1342
 
worker_restart(Pid) ->
1343
 
    worker_restart(Pid, get()).
1344
 
 
1345
 
worker_restart(Pid, Dict) when is_pid(Pid) -> 
1346
 
    worker_stop(Pid),
1347
 
    worker_start(Dict);
1348
 
worker_restart(Any, _Dict) ->
1349
 
    Any.
 
1397
%% set_worker_restart(Pid) ->
 
1398
%%     worker_restart(Pid, [{master, self()} | get()]).
 
1399
 
 
1400
%% worker_restart(Pid) ->
 
1401
%%     worker_restart(Pid, get()).
 
1402
 
 
1403
%% worker_restart(Pid, Dict) when is_pid(Pid) -> 
 
1404
%%     worker_stop(Pid),
 
1405
%%     worker_start(Dict);
 
1406
%% worker_restart(Any, _Dict) ->
 
1407
%%     Any.
1350
1408
 
1351
1409
 
1352
1410
%%-----------------------------------------------------------------
1464
1522
    Args = [Vsn, Pdu, PduMS, ACMData, Address, Extra, Dict], 
1465
1523
    proc_lib:spawn_link(?MODULE, handle_pdu, Args).
1466
1524
 
1467
 
spawn_trap_thread(TrapRec, NotifyName, ContextName, Recv, V) ->
 
1525
spawn_trap_thread(TrapRec, NotifyName, ContextName, Recv, Vbs, 
 
1526
                  LocalEngineID) ->
1468
1527
    Dict = get(),
1469
1528
    proc_lib:spawn_link(?MODULE, do_send_trap,
1470
 
                        [TrapRec, NotifyName, ContextName, Recv, V, Dict]).
 
1529
                        [TrapRec, NotifyName, ContextName, 
 
1530
                         Recv, Vbs, LocalEngineID, Dict]).
1471
1531
 
1472
 
do_send_trap(TrapRec, NotifyName, ContextName, Recv, V, Dict) ->
 
1532
do_send_trap(TrapRec, NotifyName, ContextName, Recv, Vbs, 
 
1533
             LocalEngineID, Dict) ->
1473
1534
    lists:foreach(fun({Key, Val}) -> put(Key, Val) end, Dict),
1474
1535
    put(sname,trap_sender_short_name(get(sname))),
1475
1536
    ?vlog("starting",[]),
1476
 
    snmpa_trap:send_trap(TrapRec, NotifyName, ContextName, Recv, V, 
1477
 
                         get(net_if)).
 
1537
    snmpa_trap:send_trap(TrapRec, NotifyName, ContextName, Recv, Vbs, 
 
1538
                         LocalEngineID, get(net_if)).
1478
1539
 
1479
1540
worker(Master, Dict) ->
1480
1541
    lists:foreach(fun({Key, Val}) -> put(Key, Val) end, Dict),
1489
1550
            handle_pdu(Vsn, Pdu, PduMS, ACMData, Address, Extra),
1490
1551
            Master ! worker_available;
1491
1552
 
1492
 
        %% Old style message
1493
 
        {MibView, Vsn, Pdu, PduMS, ACMData, AgentData, Extra} ->
1494
 
            ?vtrace("worker_loop -> received (old) request", []),
1495
 
            do_handle_pdu(MibView, Vsn, Pdu, PduMS, ACMData, AgentData, Extra),
 
1553
        %% We don't trap exits!
 
1554
        {TrapRec, NotifyName, ContextName, Recv, Vbs} -> 
 
1555
            ?vtrace("worker_loop -> send trap:"
 
1556
                    "~n   ~p", [TrapRec]),
 
1557
            snmpa_trap:send_trap(TrapRec, NotifyName, 
 
1558
                                 ContextName, Recv, Vbs, get(net_if)),
1496
1559
            Master ! worker_available;
1497
1560
 
1498
 
        {TrapRec, NotifyName, ContextName, Recv, V} -> % We don't trap exits!
 
1561
        %% We don't trap exits!
 
1562
        {send_trap, 
 
1563
         TrapRec, NotifyName, ContextName, Recv, Vbs, LocalEngineID} -> 
1499
1564
            ?vtrace("worker_loop -> send trap:"
1500
1565
                    "~n   ~p", [TrapRec]),
1501
1566
            snmpa_trap:send_trap(TrapRec, NotifyName, 
1502
 
                                 ContextName, Recv, V, get(net_if)),
 
1567
                                 ContextName, Recv, Vbs, LocalEngineID, 
 
1568
                                 get(net_if)),
1503
1569
            Master ! worker_available;
1504
1570
 
1505
1571
        {verbosity, Verbosity} ->
1648
1714
    end.
1649
1715
 
1650
1716
 
1651
 
handle_send_trap(S, TrapName, NotifyName, ContextName, Recv, Varbinds) ->
 
1717
handle_send_trap(S, TrapName, NotifyName, ContextName, Recv, Varbinds, 
 
1718
                 LocalEngineID) ->
1652
1719
    ?vtrace("handle_send_trap -> entry with"
1653
 
        "~n   S#state.type: ~p"
1654
 
        "~n   TrapName:     ~p"
1655
 
        "~n   NotifyName:   ~p"
1656
 
        "~n   ContextName:  ~p", 
1657
 
        [S#state.type, TrapName, NotifyName, ContextName]),
 
1720
        "~n   S#state.type:  ~p"
 
1721
        "~n   TrapName:      ~p"
 
1722
        "~n   NotifyName:    ~p"
 
1723
        "~n   ContextName:   ~p"
 
1724
        "~n   LocalEngineID: ~p", 
 
1725
        [S#state.type, TrapName, NotifyName, ContextName, LocalEngineID]),
1658
1726
    case snmpa_trap:construct_trap(TrapName, Varbinds) of
1659
1727
        {ok, TrapRecord, VarList} ->
1660
1728
            ?vtrace("handle_send_trap -> construction complete: "
1671
1739
                    ?vtrace("handle_send_trap -> "
1672
1740
                            "[master] handle send trap",[]),
1673
1741
                    maybe_send_trap(S, TrapRecord, NotifyName,
1674
 
                                    ContextName, Recv, VarList)
 
1742
                                    ContextName, Recv, VarList,
 
1743
                                    LocalEngineID)
1675
1744
            end;
1676
1745
        error ->
1677
1746
            error
1708
1777
 
1709
1778
 
1710
1779
maybe_send_trap(#state{nfilters = NFs} = S, 
1711
 
                TrapRec, NotifyName, ContextName, Recv, Varbinds) ->
 
1780
                TrapRec, NotifyName, ContextName, Recv, Varbinds, 
 
1781
                LocalEngineID) ->
1712
1782
    ?vtrace("maybe_send_trap -> entry with"
1713
1783
            "~n   NFs: ~p", [NFs]),
1714
1784
    case filter_notification(NFs, [], TrapRec) of
1725
1795
            ?vtrace("maybe_send_trap -> send trap:"
1726
1796
                    "~n   ~p", [TrapRec2]),
1727
1797
            do_handle_send_trap(S, TrapRec2, 
1728
 
                                NotifyName, ContextName, Recv, Varbinds);
 
1798
                                NotifyName, ContextName, Recv, Varbinds, 
 
1799
                                LocalEngineID);
1729
1800
        
1730
1801
        {send, Removed, TrapRec2} ->
1731
1802
            ?vtrace("maybe_send_trap -> send trap:"
1732
1803
                    "~n   ~p", [TrapRec2]),
1733
1804
            NFs2 = del_notification_filter(Removed, NFs),
1734
1805
            do_handle_send_trap(S#state{nfilters = NFs2}, TrapRec2, 
1735
 
                                NotifyName, ContextName, Recv, Varbinds)
 
1806
                                NotifyName, ContextName, Recv, Varbinds,
 
1807
                                LocalEngineID)
1736
1808
    end.
1737
1809
   
1738
 
do_handle_send_trap(S, TrapRec, NotifyName, ContextName, Recv, Varbinds) ->
1739
 
    V = snmpa_trap:try_initialise_vars(get(mibserver), Varbinds),
 
1810
do_handle_send_trap(S, TrapRec, NotifyName, ContextName, Recv, Varbinds,
 
1811
                   LocalEngineID) ->
 
1812
    Vbs = snmpa_trap:try_initialise_vars(get(mibserver), Varbinds),
1740
1813
    case S#state.type of
1741
1814
        subagent ->
1742
1815
            forward_trap(S#state.parent, TrapRec, NotifyName, ContextName,
1743
 
                         Recv, V),
 
1816
                         Recv, Vbs),
1744
1817
            {ok, S};
1745
1818
        master_agent when S#state.multi_threaded =:= false ->
1746
1819
            ?vtrace("do_handle_send_trap -> send trap:"
1747
1820
                    "~n   ~p", [TrapRec]),
1748
1821
            snmpa_trap:send_trap(TrapRec, NotifyName, ContextName,
1749
 
                                 Recv, V, get(net_if)),
 
1822
                                 Recv, Vbs, LocalEngineID, get(net_if)),
1750
1823
            {ok, S};
1751
1824
        master_agent when S#state.worker_state =:= busy ->
1752
1825
            %% Main worker busy => create new worker
1753
1826
            ?vtrace("do_handle_send_trap -> main worker busy: "
1754
1827
                    "spawn a trap sender", []),
1755
 
            spawn_trap_thread(TrapRec, NotifyName, ContextName, Recv, V),
 
1828
            spawn_trap_thread(TrapRec, NotifyName, ContextName, Recv, Vbs,
 
1829
                              LocalEngineID),
1756
1830
            {ok, S};
1757
1831
        master_agent ->
1758
1832
            %% Send to main worker
1759
1833
            ?vtrace("do_handle_send_trap -> send to main worker",[]),
1760
 
            S#state.worker ! {TrapRec, NotifyName, ContextName, Recv, V},
 
1834
            S#state.worker ! {send_trap, 
 
1835
                              TrapRec, NotifyName, ContextName, Recv, Vbs,
 
1836
                              LocalEngineID},
1761
1837
            {ok, S#state{worker_state = busy}}
1762
1838
    end.
1763
1839