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

« back to all changes in this revision

Viewing changes to lib/snmp/src/agent/snmpa_trap.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_trap).
 
19
 
 
20
%%%-----------------------------------------------------------------
 
21
%%% This module takes care of all trap handling.
 
22
%%%-----------------------------------------------------------------
 
23
%% External exports
 
24
-export([construct_trap/2, try_initialise_vars/2, send_trap/6]).
 
25
 
 
26
%% Internal exports
 
27
-export([init_v2_inform/9, init_v3_inform/9]).
 
28
 
 
29
-include("snmp_types.hrl").
 
30
-include("SNMPv2-MIB.hrl").
 
31
-include("SNMP-FRAMEWORK-MIB.hrl").
 
32
-define(enterpriseSpecific, 6).
 
33
 
 
34
 
 
35
-define(VMODULE,"TRAP").
 
36
-include("snmp_verbosity.hrl").
 
37
 
 
38
 
 
39
%%-----------------------------------------------------------------
 
40
%% Trap mechanism
 
41
%% ==============
 
42
%% Distributed subagent (dSA) case
 
43
%%   The MIB with the TRAP-TYPE macro is loaded in dSA.  This means
 
44
%%   that dSA has info on all variables defined in the TRAP-TYPE,
 
45
%%   even though some variables may be located in other SA:s (or
 
46
%%   in the MA). Other variables that may be sent in the trap, 
 
47
%%   must be known by either the dSA, or some of its parent agents
 
48
%%   (e.g. the master agent), if the variable should be referred
 
49
%%   to by symbolic name. It is however possible to send other
 
50
%%   variables as well, but then the entire OID must be provided.
 
51
%%   The dSA locates the asn1 type, oid and value for as many
 
52
%%   variables as possible. This information, together with the
 
53
%%   variables for which the type, value or oid isn't known, is
 
54
%%   sent to the dSA's parent. This agent performs the same
 
55
%%   operation, and so on, until eventually the MA will receive the
 
56
%%   info. The MA then fills in the gaps, and at this point all
 
57
%%   oids and types must be known, otherwise an error is signalled,
 
58
%%   and the opertaion is aborted. For the unknown values for some 
 
59
%%   oids, a get-operation is performed by the MA. This will
 
60
%%   retreive the missing values.
 
61
%%   At this point, all oid, types and values are known, so the MA
 
62
%%   can distribute the traps according to the information in the
 
63
%%   internal tables.
 
64
%% 
 
65
%% Local subagent (lSA) case
 
66
%%   This case is similar to the case above.
 
67
%%
 
68
%% Master agent (MA) case
 
69
%%   This case is similar to the case above.
 
70
%%
 
71
%% NOTE: All trap forwarding between agents is made asynchronously.
 
72
%%
 
73
%% dSA: Distributed SA  (the #trap is loaded here)
 
74
%% nSA: [many] SAs between dSA and MA
 
75
%% MA:  Master Agent. (all trap info (destiniations is here))
 
76
%% 1) application decides to send a trap.
 
77
%% 2) dSA calls send_trap which initialises vars
 
78
%% 3) dSA sends all to nSA
 
79
%% 4) nSA tries to map symbolic names to oids and find the types
 
80
%%    of all variableoids with a value (and no type).
 
81
%% 5) nSA sends all to (n-1)SA
 
82
%% 6) MA tries to initialise vars
 
83
%% 7) MA makes a trappdu, and sends it to all destination.
 
84
%%
 
85
%% Problems with this implementation
 
86
%% =================================
 
87
%% It's ok to send {Oid, Value} but not just Oid. (it should be for
 
88
%%   any Oid)
 
89
%% It's ok to send {Name, Value} but not just Name. (it should be
 
90
%%   for Names in the hierarchy)
 
91
%% This approach might be too flexible; will people use it?
 
92
%% *NOTE*
 
93
%% Therefore, in this version we *do not* allow extra variables
 
94
%% in traps.
 
95
%% *YES* In _this_ version we do.
 
96
%%-----------------------------------------------------------------
 
97
 
 
98
%%-----------------------------------------------------------------
 
99
%% Func: construct_trap/2
 
100
%% Args: Trap is an atom
 
101
%%       Varbinds is a list of {Variable, Value},
 
102
%%         where Variable is an atom or an OID. |
 
103
%%         {SymbolicTableCol, RowIndex, Value},
 
104
%%         where RowIndex is the indexes for the row.
 
105
%%         We don't check the RowIndex.
 
106
%% Purpose: This is the initially-called function. It is called
 
107
%%          by the agent that found out that a trap should be
 
108
%%          sent.
 
109
%%          Initialize as many variables as possible.
 
110
%% Returns: {ok, TrapRecord, <list of Var>} | error
 
111
%%          where Var is returned from initiate_vars.
 
112
%% NOTE: Executed at the inital SA
 
113
%%-----------------------------------------------------------------
 
114
construct_trap(Trap, Varbinds) ->
 
115
    ?vdebug("construct_trap -> entry with"
 
116
        "~n   Trap: ~p", [Trap]),
 
117
    case snmpa_symbolic_store:get_notification(Trap) of
 
118
        undefined -> 
 
119
            user_err("send_trap got undef Trap: ~w" , [Trap]),
 
120
            error;
 
121
        {value, TRec} when record(TRec, trap) ->
 
122
            ?vtrace("construct_trap -> TRec: ~n~p", [TRec]),
 
123
            ListOfVars = TRec#trap.oidobjects,
 
124
            OidVbs = [alias_to_oid(Vb) || Vb <- Varbinds],
 
125
            LV = initiate_vars(ListOfVars, OidVbs),
 
126
            InitiatedVars = try_initialise_vars(get(mibserver), LV),
 
127
            {ok, TRec, InitiatedVars};
 
128
        {value, NRec} when record(NRec, notification) ->
 
129
            ?vtrace("construct_trap -> NRec: ~n~p", [NRec]),
 
130
            ListOfVars = NRec#notification.oidobjects,
 
131
            OidVbs = [alias_to_oid(Vb) || Vb <- Varbinds],
 
132
            LV = initiate_vars(ListOfVars, OidVbs),
 
133
            {ok, NRec, try_initialise_vars(get(mibserver), LV)}
 
134
    end.
 
135
 
 
136
alias_to_oid({Alias, Val}) when atom(Alias) ->
 
137
    case snmpa_symbolic_store:aliasname_to_oid(Alias) of
 
138
        {value, Oid} -> {lists:append(Oid, [0]), {value, Val}};
 
139
        _ ->         {Alias, {value, Val}}
 
140
    end;
 
141
alias_to_oid({Alias, RowIndex, Val}) when atom(Alias) ->
 
142
    case snmpa_symbolic_store:aliasname_to_oid(Alias) of
 
143
        {value, Oid} -> {lists:append(Oid, RowIndex), {value, Val}};
 
144
        _ ->         {Alias, RowIndex, {value, Val}}
 
145
    end;
 
146
alias_to_oid({Oid, Val}) -> {Oid, {value, Val}}.
 
147
 
 
148
%%-----------------------------------------------------------------
 
149
%% Func: initiate_vars/2
 
150
%% Args: ListOfVars is a list of {Oid, #asn1_type}
 
151
%%       Varbinds is a list of 
 
152
%%          {VariableOid, Value} | 
 
153
%%          {VariableAtom, Value} |
 
154
%%          {TableColAtom, RowIndex, Value}
 
155
%% Purpose: For each variable in specified in the TRAP-TYPE macro
 
156
%%          (each in ListOfVars), check if it's got a value given
 
157
%%          in the Varbinds list.
 
158
%%          For each Oid:
 
159
%%            1) It has corresponding VariableOid. Use Value.
 
160
%%            2) No corresponding VariableOid. No value.
 
161
%% Returns: A list of
 
162
%%            {VariableOid, #asn1_type, Value} |
 
163
%%            {VariableOid, #asn1_type} |
 
164
%%            {VariableOid, Value} |
 
165
%%            {VariableAtom, Value} |
 
166
%%            {TableColAtom, RowIndex, Value}
 
167
%% NOTE: Executed at the inital SA
 
168
%%-----------------------------------------------------------------
 
169
initiate_vars([{Oid, Asn1Type} | T], Varbinds) ->
 
170
    case delete_oid_from_varbinds(Oid, Varbinds) of
 
171
        {undefined, _, _} ->
 
172
            [{Oid, Asn1Type} | initiate_vars(T, Varbinds)];
 
173
        {Value, VarOid, RestOfVarbinds} ->
 
174
            [{VarOid, Asn1Type, Value} | initiate_vars(T, RestOfVarbinds)]
 
175
    end;
 
176
initiate_vars([], Varbinds) ->
 
177
    Varbinds.
 
178
    
 
179
delete_oid_from_varbinds(Oid, [{VarOid, Value} | T]) ->
 
180
    case lists:prefix(Oid, VarOid) of
 
181
        true -> 
 
182
            {Value, VarOid, T};
 
183
        _ -> 
 
184
            {Value2, VarOid2, T2} = delete_oid_from_varbinds(Oid, T),
 
185
            {Value2, VarOid2, [{VarOid, Value} | T2]}
 
186
    end;
 
187
delete_oid_from_varbinds(Oid, [H | T]) ->
 
188
    {Value, VarOid, T2} = delete_oid_from_varbinds(Oid, T),
 
189
    {Value, VarOid, [H | T2]};
 
190
delete_oid_from_varbinds(_Oid, []) -> {undefined, undefined, []}.
 
191
 
 
192
%%-----------------------------------------------------------------
 
193
%% Func: try_initialise_vars(Mib, Varbinds)
 
194
%% Args: Mib is the local mib process
 
195
%%       Varbinds is a list returned from initiate_vars.
 
196
%% Purpose: Try to initialise uninitialised vars.
 
197
%% Returns: see initiate_vars
 
198
%% NOTE: Executed at the intermediate SAs
 
199
%%-----------------------------------------------------------------
 
200
try_initialise_vars(Mib, Varbinds) ->
 
201
    V = try_map_symbolic(Varbinds),
 
202
    try_find_type(V, Mib).
 
203
 
 
204
%%-----------------------------------------------------------------
 
205
%% Func: try_map_symbolic/1
 
206
%% Args: Varbinds is a list returned from initiate_vars.
 
207
%% Purpose: Try to map symbolic name to oid for the 
 
208
%%          symbolic names left in the Varbinds list.
 
209
%% Returns: see initiate_vars.
 
210
%% NOTE: Executed at the intermediate SAs
 
211
%%-----------------------------------------------------------------
 
212
try_map_symbolic([Varbind | Varbinds]) ->
 
213
    [localise_oid(Varbind) | try_map_symbolic(Varbinds)];
 
214
try_map_symbolic([]) -> [].
 
215
 
 
216
localise_oid({VariableName, Value}) when atom(VariableName) ->
 
217
    alias_to_oid({VariableName, Value});
 
218
localise_oid({VariableName, RowIndex, Value}) when atom(VariableName) ->
 
219
    alias_to_oid({VariableName, RowIndex, Value});
 
220
localise_oid(X) -> X.
 
221
 
 
222
%%-----------------------------------------------------------------
 
223
%% Func: try_find_type/2
 
224
%% Args: Varbinds is a list returned from initiate_vars.
 
225
%%       Mib is a ref to the Mib process corresponding to
 
226
%%         this agent.
 
227
%% Purpose: Try to find the type for each variableoid with a value
 
228
%%          but no type.
 
229
%% Returns: see initiate_vars.
 
230
%% NOTE: Executed at the intermediate SAs
 
231
%%-----------------------------------------------------------------
 
232
try_find_type([Varbind | Varbinds], Mib) ->
 
233
    [localise_type(Varbind, Mib) | try_find_type(Varbinds, Mib)];
 
234
try_find_type([], _) -> [].
 
235
 
 
236
localise_type({VariableOid, Type}, _Mib) 
 
237
  when list(VariableOid), record(Type, asn1_type) ->
 
238
    {VariableOid, Type};
 
239
localise_type({VariableOid, Value}, Mib) when list(VariableOid) ->
 
240
    case snmpa_mib:lookup(Mib, VariableOid) of
 
241
        {variable, ME} ->
 
242
            {VariableOid, ME#me.asn1_type, Value};
 
243
        {table_column, ME, _} ->
 
244
            {VariableOid, ME#me.asn1_type, Value};
 
245
        _ ->
 
246
            {VariableOid, Value}
 
247
    end;
 
248
localise_type(X, _) -> X.
 
249
 
 
250
%%-----------------------------------------------------------------
 
251
%% Func: make_v1_trap_pdu/4
 
252
%% Args: Enterprise = oid()
 
253
%%       Specific = integer()
 
254
%%       Varbinds is as returned from initiate_vars
 
255
%%         (but only {Oid, Type[, Value} permitted)
 
256
%%       SysUpTime = integer()
 
257
%% Purpose: Make a #trappdu
 
258
%%          Checks the Varbinds to see that no symbolic names are
 
259
%%          present, and that each var has a type. Performs a get
 
260
%%          to find any missing value.
 
261
%% Returns: {#trappdu, [byte()] | error
 
262
%% Fails: yes
 
263
%% NOTE: Executed at the MA
 
264
%%-----------------------------------------------------------------
 
265
make_v1_trap_pdu(Enterprise, Specific, VarbindList, SysUpTime) ->
 
266
    {Enterp,Generic,Spec} = 
 
267
        case Enterprise of
 
268
            ?snmp ->
 
269
                {sys_object_id(),Specific,0};
 
270
            _ ->
 
271
                {Enterprise,?enterpriseSpecific,Specific}
 
272
    end,
 
273
    {value, AgentIp} = snmp_framework_mib:intAgentIpAddress(get),
 
274
    #trappdu{enterprise = Enterp,
 
275
             agent_addr = AgentIp,
 
276
             generic_trap = Generic,
 
277
             specific_trap = Spec,
 
278
             time_stamp = SysUpTime,
 
279
             varbinds = VarbindList}.
 
280
 
 
281
make_v2_notif_pdu(Vbs, Type) ->
 
282
    #pdu{type = Type,
 
283
         request_id = snmpa_mpd:generate_req_id(),
 
284
         error_status = noError,
 
285
         error_index = 0,
 
286
         varbinds = Vbs}.
 
287
 
 
288
make_varbind_list(Varbinds) ->
 
289
    {VariablesWithValueAndType, VariablesWithType} =
 
290
        split_variables(order(Varbinds)),
 
291
    V = get_all(VariablesWithType),
 
292
    Vars = lists:append([V, VariablesWithValueAndType]),
 
293
    [make_varbind(Var) || Var <- unorder(lists:keysort(1, Vars))].
 
294
 
 
295
%%-----------------------------------------------------------------
 
296
%% Func: send_trap/6
 
297
%% Args: TrapRec = #trap | #notification
 
298
%%       NotifyName = string()
 
299
%%       ContextName = string()
 
300
%%       Recv = no_receiver | {Ref, Receiver}
 
301
%%       Receiver = pid() | atom() | {M,F,A}
 
302
%%       Vbs = [varbind()]
 
303
%%       NetIf = pid()
 
304
%% Purpose: Default trap sending function.
 
305
%%          Sends the trap to the targets pointed out by NotifyName.
 
306
%%          If NotifyName is ""; the normal procedure defined in 
 
307
%%          SNMP-NOTIFICATION-MIB is used, i.e. the trap is sent to
 
308
%%          all managers.
 
309
%%          Otherwise, the NotifyName is used to find an entry in the
 
310
%%          SnmpNotifyTable which define how to send the notification
 
311
%%          (as an Inform or a Trap), and to select targets from
 
312
%%          SnmpTargetAddrTable (using the Tag).
 
313
%%-----------------------------------------------------------------
 
314
send_trap(TrapRec, NotifyName, ContextName, Recv, Vbs, NetIf) ->
 
315
    VarbindList = make_varbind_list(Vbs),
 
316
    Dests = find_dests(NotifyName),
 
317
    send_trap_pdus(Dests, ContextName, {TrapRec, VarbindList}, [], [], [],
 
318
                   Recv, NetIf).
 
319
            
 
320
get_all(VariablesWithType) ->
 
321
    {Order, Varbinds} = extract_order(VariablesWithType, 1),
 
322
    case snmpa_agent:do_get(snmpa_acm:get_root_mib_view(), Varbinds, true) of
 
323
        {noError, _, NewVarbinds} ->
 
324
            contract_order(Order, NewVarbinds);
 
325
        {ErrorStatus, ErrorIndex, _} ->
 
326
            user_err("snmpa_trap: get operation failed {~w, ~w}"
 
327
                     "~n    in ~w",
 
328
                     [ErrorStatus, ErrorIndex, Varbinds]),
 
329
            throw(error)
 
330
    end.
 
331
    
 
332
make_varbind(Varbind) when record(Varbind, varbind) ->
 
333
    Varbind;
 
334
make_varbind({VarOid, ASN1Type, Value}) ->
 
335
    case snmpa_agent:make_value_a_correct_value(Value, ASN1Type, undef) of
 
336
        {value, Type, Val} ->
 
337
            #varbind{oid = VarOid, variabletype = Type, value = Val};
 
338
        {error, Reason} -> 
 
339
            user_err("snmpa_trap: Invalid value: ~w"
 
340
                     "~n   Oid:  ~w"
 
341
                     "~n   Val:  ~w"
 
342
                     "~n   Type: ~w",
 
343
                     [Reason, VarOid, Value, ASN1Type]),
 
344
            throw(error)
 
345
    end.
 
346
 
 
347
order(Varbinds) -> order(Varbinds, 1).
 
348
order([H | T], No) -> [{No, H} | order(T, No + 1)];
 
349
order([], _) -> [].
 
350
 
 
351
unorder([{_No, H} | T]) -> [H | unorder(T)];
 
352
unorder([]) -> [].
 
353
 
 
354
extract_order([{No, {VarOid, _Type}} | T], Index) ->
 
355
    {Order, V} = extract_order(T, Index+1),
 
356
    {[No | Order], [#varbind{oid = VarOid, org_index = Index} | V]};
 
357
extract_order([], _) -> {[], []}.
 
358
 
 
359
contract_order([No | Order], [Varbind | T]) ->
 
360
    [{No, Varbind} | contract_order(Order, T)];
 
361
contract_order([], []) -> [].
 
362
 
 
363
split_variables([{No, {VarOid, Type, Val}} | T]) when list(VarOid) ->
 
364
    {A, B} = split_variables(T),
 
365
    {[{No, {VarOid, Type, Val}} | A], B};
 
366
split_variables([{No, {VarOid, Type}} | T]) 
 
367
  when list(VarOid), record(Type, asn1_type) ->
 
368
    {A, B} = split_variables(T),
 
369
    {A, [{No, {VarOid, Type}} | B]};
 
370
split_variables([{_No, {VarName, Value}} | _T]) ->
 
371
    user_err("snmpa_trap: Undefined variable ~w (~w)", [VarName, Value]),
 
372
    throw(error);
 
373
split_variables([{_No, {VarName, RowIndex, Value}} | _T]) ->
 
374
    user_err("snmpa_trap: Undefined variable ~w ~w (~w)",
 
375
             [VarName, RowIndex, Value]),
 
376
    throw(error);
 
377
split_variables([]) -> {[], []}.
 
378
 
 
379
%%-----------------------------------------------------------------
 
380
%% Func: find_dests(NotifyName) -> 
 
381
%%          [{DestAddr, TargetName, TargetParams, NotifyType}]
 
382
%% Types: NotifyType = string()
 
383
%%        DestAddr = {TDomain, TAddr}
 
384
%%        TargetName = string()
 
385
%%        TargetParams = {MpModel, SecModel, SecName, SecLevel}
 
386
%%        NotifyType = trap | {inform, Timeout, Retry}
 
387
%% Returns: A list of all Destination addresses for this community.
 
388
%% NOTE: This function is executed in the master agent's context
 
389
%%-----------------------------------------------------------------
 
390
find_dests("") ->
 
391
    snmp_notification_mib:get_targets();
 
392
find_dests(NotifyName) ->
 
393
    case snmp_notification_mib:get_targets(NotifyName) of
 
394
        [] ->
 
395
            ?vlog("No dests found for snmpNotifyName: ~p",[NotifyName]),
 
396
            [];
 
397
        Dests ->
 
398
            Dests
 
399
    end.
 
400
 
 
401
%%-----------------------------------------------------------------
 
402
%% NOTE: This function is executed in the master agent's context
 
403
%% For each target, check if it has access to the objects in the
 
404
%% notification, determine which message version (v1, v2c or v3)
 
405
%% should be used for the target, and determine the message
 
406
%% specific parameters to be used.
 
407
%%-----------------------------------------------------------------
 
408
send_trap_pdus([{DestAddr, TargetName, {MpModel, SecModel, SecName, SecLevel},
 
409
                 Type} | T],
 
410
               ContextName,{TrapRec, Vbs}, V1Res, V2Res, V3Res, Recv, NetIf) ->
 
411
    ?vdebug("send trap pdus: "
 
412
            "~n   Destination address: ~p"
 
413
            "~n   Target name:         ~p"
 
414
            "~n   MP model:            ~p"
 
415
            "~n   Type:                ~p"
 
416
            "~n   V1Res:               ~p"
 
417
            "~n   V2Res:               ~p"
 
418
            "~n   V3Res:               ~p",
 
419
            [DestAddr,TargetName,MpModel,Type,V1Res,V2Res,V3Res]),
 
420
    case snmpa_vacm:get_mib_view(notify, SecModel, SecName, SecLevel,
 
421
                                 ContextName) of
 
422
        {ok, MibView} ->
 
423
            case check_all_varbinds(TrapRec, Vbs, MibView) of
 
424
                true when MpModel == ?MP_V1 ->
 
425
                    ?vtrace("v1 mp model",[]),
 
426
                    ContextEngineId = snmp_framework_mib:get_engine_id(),
 
427
                    case snmp_community_mib:vacm2community({SecName,
 
428
                                                            ContextEngineId,
 
429
                                                            ContextName},
 
430
                                                           DestAddr) of
 
431
                        {ok, Community} ->
 
432
                            ?vdebug("community found  for v1 dest: ~p",
 
433
                                    [element(2, DestAddr)]),
 
434
                            send_trap_pdus(T, ContextName, {TrapRec, Vbs},
 
435
                                           [{DestAddr, Community} | V1Res],
 
436
                                           V2Res, V3Res, Recv, NetIf);
 
437
                        undefined ->
 
438
                            ?vdebug("No community found for v1 dest: ~p", 
 
439
                                    [element(2, DestAddr)]),
 
440
                            send_trap_pdus(T, ContextName, {TrapRec, Vbs},
 
441
                                           V1Res, V2Res, V3Res, Recv, NetIf)
 
442
                    end;
 
443
                true when MpModel == ?MP_V2C ->
 
444
                    ?vtrace("v2c mp model",[]),
 
445
                    ContextEngineId = snmp_framework_mib:get_engine_id(),
 
446
                    case snmp_community_mib:vacm2community({SecName,
 
447
                                                            ContextEngineId,
 
448
                                                            ContextName},
 
449
                                                           DestAddr) of
 
450
                        {ok, Community} ->
 
451
                            ?vdebug("community found for v2c dest: ~p", 
 
452
                                    [element(2, DestAddr)]),
 
453
                            send_trap_pdus(T, ContextName, {TrapRec, Vbs},
 
454
                                           V1Res,
 
455
                                           [{DestAddr, Community, Type}|V2Res],
 
456
                                           V3Res, Recv, NetIf);
 
457
                        undefined ->
 
458
                            ?vdebug("No community found for v2c dest: ~p", 
 
459
                                    [element(2, DestAddr)]),
 
460
                            send_trap_pdus(T, ContextName, {TrapRec, Vbs},
 
461
                                           V1Res, V2Res, V3Res, Recv, NetIf)
 
462
                    end;
 
463
                true when MpModel == ?MP_V3 ->
 
464
                    ?vtrace("v3 mp model",[]),
 
465
                    SecLevelF = mk_flag(SecLevel),
 
466
                    MsgData = {SecModel, SecName, SecLevelF, TargetName},
 
467
                    send_trap_pdus(T, ContextName, {TrapRec, Vbs},
 
468
                                   V1Res, V2Res,
 
469
                                   [{DestAddr, MsgData, Type} | V3Res],
 
470
                                   Recv, NetIf);
 
471
                true ->
 
472
                    ?vlog("bad MpModel ~p for dest ~p",
 
473
                          [MpModel, element(2, DestAddr)]),
 
474
                    send_trap_pdus(T, ContextName, {TrapRec, Vbs},
 
475
                                   V1Res, V2Res, V3Res, Recv, NetIf);
 
476
                _ ->
 
477
                    ?vlog("no access for dest: "
 
478
                          "~n   ~p in target ~p",
 
479
                          [element(2, DestAddr), TargetName]),
 
480
                    send_trap_pdus(T, ContextName, {TrapRec, Vbs},
 
481
                                   V1Res, V2Res, V3Res, Recv, NetIf)
 
482
            end;
 
483
        {discarded, Reason} ->
 
484
            ?vlog("mib view error ~p for"
 
485
                  "~n   dest:    ~p"
 
486
                  "~n   SecName: ~w", 
 
487
                  [Reason, element(2, DestAddr), SecName]),
 
488
            send_trap_pdus(T, ContextName, {TrapRec, Vbs},
 
489
                           V1Res, V2Res, V3Res, Recv, NetIf)
 
490
    end;
 
491
send_trap_pdus([], ContextName, {TrapRec, Vbs}, V1Res, V2Res, V3Res,
 
492
               Recv, NetIf) ->
 
493
    SysUpTime = snmp_standard_mib:sys_up_time(),
 
494
    ?vdebug("send trap pdus with sysUpTime ~p",[SysUpTime]),
 
495
    send_v1_trap(TrapRec, V1Res, Vbs, NetIf, SysUpTime),
 
496
    send_v2_trap(TrapRec, V2Res, Vbs, Recv, NetIf, SysUpTime),
 
497
    send_v3_trap(TrapRec, V3Res, Vbs, Recv, NetIf, SysUpTime, ContextName).
 
498
 
 
499
send_v1_trap(_TrapRec, [], _Vbs, _NetIf, _SysUpTime) ->
 
500
    ok;
 
501
send_v1_trap(#trap{enterpriseoid = Enter, specificcode = Spec},
 
502
             V1Res, Vbs, NetIf, SysUpTime) ->
 
503
    ?vdebug("prepare to send v1 trap "
 
504
            "~n   '~p'"
 
505
            "~n   with"
 
506
            "~n   ~p"
 
507
            "~n   to"
 
508
            "~n   ~p",[Enter,Spec,V1Res]),
 
509
    TrapPdu = make_v1_trap_pdu(Enter, Spec, Vbs, SysUpTime),
 
510
    AddrCommunities = mk_addr_communities(V1Res),
 
511
    lists:foreach(fun({Community, Addrs}) ->
 
512
                          ?vtrace("send v1 trap pdu to ~p",[Addrs]),
 
513
                          NetIf ! {send_pdu, 'version-1', TrapPdu,
 
514
                                   {community, Community}, Addrs}
 
515
                  end, AddrCommunities);
 
516
send_v1_trap(#notification{oid = Oid}, V1Res, Vbs, NetIf, SysUpTime) ->
 
517
    %% Use alg. in rfc2089 to map a v2 trap to a v1 trap
 
518
    % delete Counter64 objects from vbs
 
519
    ?vdebug("prepare to send v1 trap '~p'",[Oid]),
 
520
    NVbs = lists:filter(fun(Vb) when Vb#varbind.variabletype =/= 'Counter64' ->
 
521
                                true;
 
522
                           (_) -> false
 
523
                        end, Vbs),
 
524
    {Enter,Spec} = 
 
525
        case Oid of
 
526
            [1,3,6,1,6,3,1,1,5,Specific] ->
 
527
                {?snmp,Specific - 1};
 
528
            _ ->
 
529
                case lists:reverse(Oid) of
 
530
                    [Last, 0 | First] ->
 
531
                        {lists:reverse(First),Last};
 
532
                    [Last | First] ->
 
533
                        {lists:reverse(First),Last}
 
534
                end
 
535
        end,
 
536
    TrapPdu = make_v1_trap_pdu(Enter, Spec, NVbs, SysUpTime),
 
537
    AddrCommunities = mk_addr_communities(V1Res),
 
538
    lists:foreach(fun({Community, Addrs}) ->
 
539
                          ?vtrace("send v1 trap to ~p",[Addrs]),
 
540
                          NetIf ! {send_pdu, 'version-1', TrapPdu,
 
541
                                   {community, Community}, Addrs}
 
542
                  end, AddrCommunities).
 
543
    
 
544
send_v2_trap(_TrapRec, [], _Vbs, _Recv, _NetIf, _SysUpTime) ->
 
545
    ok;
 
546
send_v2_trap(TrapRec, V2Res, Vbs, Recv, NetIf, SysUpTime) ->
 
547
    ?vdebug("prepare to send v2 trap",[]),
 
548
    {_Oid, IVbs} = mk_v2_trap(TrapRec, Vbs, SysUpTime),
 
549
    TrapRecvs = get_trap_recvs(V2Res),
 
550
    InformRecvs = get_inform_recvs(V2Res),
 
551
    do_send_v2_trap(TrapRecvs, IVbs, NetIf),
 
552
    do_send_v2_inform(InformRecvs, IVbs, Recv, NetIf).
 
553
    
 
554
send_v3_trap(_TrapRec, [], _Vbs, _Recv, _NetIf, _SysUpTime, _ContextName) ->
 
555
    ok;
 
556
send_v3_trap(TrapRec, V3Res, Vbs, Recv, NetIf, SysUpTime, ContextName) ->
 
557
    ?vdebug("prepare to send v3 trap",[]),
 
558
    {_Oid, IVbs} = mk_v2_trap(TrapRec, Vbs, SysUpTime), % v2 refers to SMIv2;
 
559
    TrapRecvs = get_trap_recvs(V3Res),                 % same SMI for v3
 
560
    InformRecvs = get_inform_recvs(V3Res),
 
561
    do_send_v3_trap(TrapRecvs, ContextName, IVbs, NetIf),
 
562
    do_send_v3_inform(InformRecvs, ContextName, IVbs, Recv, NetIf).
 
563
    
 
564
 
 
565
mk_v2_trap(#notification{oid = Oid}, Vbs, SysUpTime) ->
 
566
    ?vtrace("make v2 notification '~p'",[Oid]),
 
567
    mk_v2_notif(Oid, Vbs, SysUpTime);
 
568
mk_v2_trap(#trap{enterpriseoid = Enter, specificcode = Spec}, Vbs, SysUpTime) ->
 
569
    %% Use alg. in rfc1908 to map a v1 trap to a v2 trap
 
570
    ?vtrace("make v2 trap for '~p' with ~p",[Enter,Spec]),
 
571
    {Oid,Enterp} = 
 
572
        case Enter of
 
573
            ?snmp ->
 
574
                {?snmpTraps ++ [Spec + 1],sys_object_id()};
 
575
            _ ->
 
576
                {Enter ++ [0, Spec],Enter}
 
577
        end,
 
578
    ExtraVb = #varbind{oid = ?snmpTrapEnterprise_instance,
 
579
                       variabletype = 'OBJECT IDENTIFIER',
 
580
                       value = Enterp},
 
581
    mk_v2_notif(Oid, Vbs ++ [ExtraVb], SysUpTime).
 
582
    
 
583
mk_v2_notif(Oid, Vbs, SysUpTime) ->
 
584
    IVbs = [#varbind{oid = ?sysUpTime_instance,
 
585
                     variabletype = 'TimeTicks',
 
586
                     value = SysUpTime},
 
587
            #varbind{oid = ?snmpTrapOID_instance,
 
588
                     variabletype = 'OBJECT IDENTIFIER',
 
589
                     value = Oid} | Vbs],
 
590
    {Oid, IVbs}.
 
591
 
 
592
%% Addr = {Domain, DomainAddr} ; e.g. {snmpUDPDomain, {IPasList, Udp}}
 
593
%% MsgData = CommunityString (v1, v2c) |
 
594
%%           {SecModel, SecName, SecLevel, TargetAddrName} (v3)
 
595
get_trap_recvs([{Addr, MsgData, trap} | T]) ->
 
596
    [{Addr, MsgData} | get_trap_recvs(T)];
 
597
get_trap_recvs([_ | T]) ->
 
598
    get_trap_recvs(T);
 
599
get_trap_recvs([]) ->
 
600
    [].
 
601
 
 
602
get_inform_recvs([{Addr, MsgData, {inform, Timeout, Retry}} | T]) ->
 
603
    [{Addr, MsgData, Timeout, Retry} | get_inform_recvs(T)];
 
604
get_inform_recvs([_ | T]) ->
 
605
    get_inform_recvs(T);
 
606
get_inform_recvs([]) ->
 
607
    [].
 
608
 
 
609
do_send_v2_trap([], _Vbs, _NetIf) ->
 
610
    ok;
 
611
do_send_v2_trap(Recvs, Vbs, NetIf) ->
 
612
    TrapPdu = make_v2_notif_pdu(Vbs, 'snmpv2-trap'),
 
613
    AddrCommunities = mk_addr_communities(Recvs),
 
614
    lists:foreach(fun({Community, Addrs}) ->
 
615
                          ?vtrace("~n   send v2 trap to ~p",[Addrs]),
 
616
                          NetIf ! {send_pdu, 'version-2', TrapPdu,
 
617
                                   {community, Community}, Addrs}
 
618
                  end, AddrCommunities),
 
619
    ok.
 
620
 
 
621
do_send_v2_inform([], _Vbs, Recv, _NetIf) ->
 
622
    deliver_recv(Recv, snmp_targets, []);
 
623
do_send_v2_inform(Recvs, Vbs, Recv, NetIf) ->
 
624
    Targets = lists:map(fun({Addr, _Community, _Timeout, _Retry}) ->
 
625
                                Addr
 
626
                        end, Recvs),
 
627
    deliver_recv(Recv, snmp_targets, Targets),
 
628
    lists:foreach(
 
629
      fun({Addr, Community, Timeout, Retry}) ->
 
630
              ?vtrace("~n   start inform sender to send v2 inform to ~p",
 
631
                      [Addr]),
 
632
              proc_lib:spawn_link(?MODULE, init_v2_inform,
 
633
                                  [Addr, Timeout, Retry, Vbs,
 
634
                                   Recv, NetIf, Community,
 
635
                                   get(verbosity),get(sname)])
 
636
      end, 
 
637
      Recvs).
 
638
 
 
639
do_send_v3_trap([], _ContextName, _Vbs, _NetIf) ->
 
640
    ok;
 
641
do_send_v3_trap(Recvs, ContextName, Vbs, NetIf) ->
 
642
    TrapPdu = make_v2_notif_pdu(Vbs, 'snmpv2-trap'), % Yes, v2
 
643
    ContextEngineId = snmp_framework_mib:get_engine_id(),
 
644
    lists:foreach(fun(Recv) ->
 
645
                          ?vtrace("~n   send v3 notif to ~p",[Recv]),
 
646
                          NetIf ! {send_pdu, 'version-3', TrapPdu,
 
647
                                   {v3, ContextEngineId, ContextName}, [Recv]}
 
648
                  end, Recvs),
 
649
    ok.
 
650
 
 
651
do_send_v3_inform([], _ContextName, _Vbs, Recv, _NetIf) ->
 
652
    deliver_recv(Recv, snmp_targets, []);
 
653
do_send_v3_inform(Recvs, ContextName, Vbs, Recv, NetIf) ->
 
654
    Targets = lists:map(fun({Addr, _, _, _}) -> Addr end, Recvs),
 
655
    deliver_recv(Recv, snmp_targets, Targets),
 
656
    lists:foreach(
 
657
      fun({Addr, MsgData, Timeout, Retry}) ->
 
658
              ?vtrace("~n   start inform sender to send v3 inform to ~p",
 
659
                      [Addr]),
 
660
              proc_lib:spawn_link(?MODULE, init_v3_inform,
 
661
                                  [{Addr, MsgData}, Timeout, Retry, Vbs,
 
662
                                   Recv, NetIf, ContextName,
 
663
                                   get(verbosity),get(sname)])
 
664
      end, 
 
665
      Recvs).
 
666
 
 
667
%% New process
 
668
init_v2_inform(Addr, Timeout, Retry, Vbs, Recv, NetIf, Community,V,S) ->
 
669
    %% Make a new Inform for each recipient; they need unique
 
670
    %% request-ids!
 
671
    put(verbosity,V),
 
672
    put(sname,inform_sender_short_name(S)),
 
673
    ?vdebug("~n   starting with timeout = ~p and retry = ~p",
 
674
            [Timeout,Retry]),
 
675
    InformPdu = make_v2_notif_pdu(Vbs, 'inform-request'),
 
676
    Msg = {send_pdu_req, 'version-2', InformPdu, {community, Community},
 
677
           [Addr], self()},
 
678
    send_inform(Addr, Timeout*10, Retry, Msg, Recv, NetIf).
 
679
    
 
680
 
 
681
send_inform(Addr, _Timeout, -1, _Msg,  Recv, _NetIf) ->
 
682
    ?vinfo("~n   Delivery of send-pdu-request to net-if failed: reply timeout",
 
683
           []),
 
684
    deliver_recv(Recv, snmp_notification, {no_response, Addr});
 
685
send_inform(Addr, Timeout, Retry, Msg, Recv, NetIf) ->
 
686
    ?vtrace("~n   deliver send-pdu-request to net-if when"
 
687
            "~n   Timeout: ~p"
 
688
            "~n   Retry:   ~p",[Timeout, Retry]),
 
689
    NetIf ! Msg,
 
690
    receive
 
691
        {snmp_response_received, _Vsn, _Pdu, _From} ->
 
692
            ?vtrace("~n   received response for ~p (~p)",[Recv,Retry]),
 
693
            deliver_recv(Recv, snmp_notification, {got_response, Addr})
 
694
    after
 
695
        Timeout ->
 
696
            send_inform(Addr, Timeout*2, Retry-1, Msg, Recv, NetIf)
 
697
    end.
 
698
 
 
699
%% New process
 
700
init_v3_inform(Addr, Timeout, Retry, Vbs, Recv, NetIf, ContextName,V,S) ->
 
701
    %% Make a new Inform for each recipient; they need unique
 
702
    %% request-ids!
 
703
    put(verbosity,V),
 
704
    put(sname,inform_sender_short_name(S)),
 
705
    ?vdebug("~n   starting with timeout = ~p and retry = ~p",
 
706
            [Timeout,Retry]),
 
707
    InformPdu = make_v2_notif_pdu(Vbs, 'inform-request'), % Yes, v2
 
708
    ContextEngineId = snmp_framework_mib:get_engine_id(),
 
709
    Msg = {send_pdu_req, 'version-3', InformPdu,
 
710
           {v3, ContextEngineId, ContextName}, [Addr], self()},
 
711
    send_inform(Addr, Timeout*10, Retry, Msg, Recv, NetIf).
 
712
 
 
713
% A nasty bit of verbosity setup...    
 
714
inform_sender_short_name(ma)   -> mais;
 
715
inform_sender_short_name(maw)  -> mais;
 
716
inform_sender_short_name(mats) -> mais;
 
717
inform_sender_short_name(_)    -> sais.
 
718
 
 
719
deliver_recv(no_receiver, _MsgId, _Result) ->
 
720
    ?vtrace("deliver_recv -> no receiver", []),
 
721
    ok;
 
722
deliver_recv({Tag, Receiver}, MsgId, Result) ->
 
723
    ?vtrace("deliver_recv -> entry with"
 
724
        "~n   Tag:      ~p"
 
725
        "~n   Receiver: ~p"
 
726
        "~n   MsgId:    ~p"
 
727
        "~n   Result:   ~p"
 
728
        "", [Tag, Receiver, MsgId, Result]),
 
729
    Msg = {MsgId, Tag, Result},
 
730
    case Receiver of
 
731
        Pid when pid(Pid) ->
 
732
            Pid ! Msg;
 
733
        Name when atom(Name) ->
 
734
            catch Name ! Msg;
 
735
        {M, F, A} ->
 
736
            catch M:F([Msg | A]);
 
737
        Else ->
 
738
            ?vinfo("~n   Cannot deliver acknowledgment: bad receiver = '~p'",
 
739
                   [Else]),
 
740
            user_err("snmpa: bad receiver, ~w\n", [Else])
 
741
    end;
 
742
deliver_recv(Else, _MsgId, _Result) ->
 
743
    ?vinfo("~n   Cannot deliver acknowledgment: bad receiver = '~p'",
 
744
           [Else]),
 
745
    user_err("snmpa: bad receiver, ~w\n", [Else]).
 
746
 
 
747
check_all_varbinds(#notification{oid = Oid}, Vbs, MibView) ->
 
748
    case snmpa_acm:validate_mib_view(Oid, MibView) of
 
749
        true -> check_all_varbinds(Vbs, MibView);
 
750
        false -> false
 
751
    end;
 
752
check_all_varbinds(#trap{enterpriseoid = Enter, specificcode = Spec},
 
753
                   Vbs, MibView) ->
 
754
    %% Use alg. in rfc1908 to map a v1 trap to a v2 trap
 
755
    Oid = case Enter of
 
756
              ?snmp -> ?snmpTraps ++ [Spec + 1];
 
757
              _ -> Enter ++ [0, Spec]
 
758
          end,
 
759
    case snmpa_acm:validate_mib_view(Oid, MibView) of
 
760
        true -> check_all_varbinds(Vbs, MibView);
 
761
        false -> false
 
762
    end.
 
763
 
 
764
check_all_varbinds([#varbind{oid = Oid} | Vbs], MibView) ->
 
765
    case snmpa_acm:validate_mib_view(Oid, MibView) of
 
766
        true -> check_all_varbinds(Vbs, MibView);
 
767
        false -> false
 
768
    end;
 
769
check_all_varbinds([], _MibView) -> true.
 
770
 
 
771
%%--------------------------------------------------
 
772
%% Functions to access the local mib.
 
773
%%--------------------------------------------------
 
774
sys_object_id() ->
 
775
    case snmpa_agent:do_get(snmpa_acm:get_root_mib_view(),
 
776
                            [#varbind{oid = ?sysObjectID_instance}],
 
777
                            true) of
 
778
        {noError, _, [#varbind{value = Value}]} ->
 
779
            Value;
 
780
        X ->
 
781
            user_err("sysObjectID bad return value ~w", [X])
 
782
    end.
 
783
 
 
784
%% Collect all ADDRs for each community together.
 
785
%% In: [{Addr, Community}]
 
786
%% Out: [{Community, [Addr]}]
 
787
mk_addr_communities(Recvs) ->
 
788
    [{Addr, Comm} | T] = lists:keysort(2, Recvs),
 
789
    mic(T, Comm, [Addr], []).
 
790
 
 
791
mic([{Addr, Comm} | T], CurComm, AddrList, Res) when Comm == CurComm ->
 
792
    mic(T, CurComm, [Addr | AddrList], Res);
 
793
mic([{Addr, Comm} | T], CurComm, AddrList, Res) ->
 
794
    mic(T, Comm, [Addr], [{CurComm, AddrList} | Res]);
 
795
mic([], CurComm, AddrList, Res) ->
 
796
    [{CurComm, AddrList} | Res].
 
797
 
 
798
%%-----------------------------------------------------------------
 
799
%% Convert the SecurityLevel into a flag value used by snmpa_mpd
 
800
%%-----------------------------------------------------------------
 
801
mk_flag(?'SnmpSecurityLevel_noAuthNoPriv') -> 0;
 
802
mk_flag(?'SnmpSecurityLevel_authNoPriv') -> 1;
 
803
mk_flag(?'SnmpSecurityLevel_authPriv') -> 3.
 
804
     
 
805
 
 
806
 
 
807
user_err(F, A) ->
 
808
    snmpa_error:user_err(F, A).