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

« back to all changes in this revision

Viewing changes to lib/snmp/test/snmp_test_mgr_misc.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-07 15:07:37 UTC
  • mfrom: (1.2.1 upstream) (5.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090507150737-i4yb5elwinm7r0hc
Tags: 1:13.b-dfsg1-1
* Removed another bunch of non-free RFCs from original tarball
  (closes: #527053).
* Fixed build-dependencies list by adding missing comma. This requires
  libsctp-dev again. Also, added libsctp1 dependency to erlang-base and
  erlang-base-hipe packages because the shared library is loaded via
  dlopen now and cannot be added using dh_slibdeps (closes: #526682).
* Weakened dependency of erlang-webtool on erlang-observer to recommends
  to avoid circular dependencies (closes: #526627).
* Added solaris-i386 to HiPE enabled architectures.
* Made script sources in /usr/lib/erlang/erts-*/bin directory executable,
  which is more convenient if a user wants to create a target Erlang system.
* Shortened extended description line for erlang-dev package to make it
  fit 80x25 terminals.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%%<copyright>
2
 
%% <year>1996-2007</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%
 
18
%% 
 
19
 
19
20
%%
20
21
%% ts:run(snmp, snmp_agent_test, [batch]).
21
22
%% 
24
25
%% API
25
26
-export([start_link_packet/8, start_link_packet/9, 
26
27
         stop/1, 
27
 
         send_discovery_pdu/2, send_pdu/2, send_msg/4, send_bytes/2,
 
28
         send_discovery_pdu/2, 
 
29
         send_pdu/2, send_msg/4, send_bytes/2,
28
30
         error/2,
29
31
         get_pdu/1, set_pdu/2, format_hdr/1]).
30
32
 
63
65
    end.
64
66
        
65
67
 
66
 
send_discovery_pdu(Pdu, PacketPid) when record(Pdu, pdu) ->
 
68
send_discovery_pdu(Pdu, PacketPid) when is_record(Pdu, pdu) ->
67
69
    PacketPid ! {send_discovery_pdu, self(), Pdu},
68
70
    await_discovery_response_pdu().
69
71
 
70
72
await_discovery_response_pdu() ->
71
73
    receive
72
 
        {discovery_response,Reply} ->
73
 
            Reply;
74
 
        _ ->
75
 
            await_discovery_response_pdu()
 
74
        {discovery_response, Reply} ->
 
75
            Reply
76
76
    end.
77
77
    
78
78
 
79
 
send_pdu(Pdu, PacketPid) when record(Pdu, pdu) ->
 
79
send_pdu(Pdu, PacketPid) when is_record(Pdu, pdu) ->
80
80
    PacketPid ! {send_pdu, Pdu}.
81
81
 
82
 
send_msg(Msg, PacketPid, Ip, Udp) when record(Msg, message) ->
 
82
send_msg(Msg, PacketPid, Ip, Udp) when is_record(Msg, message) ->
83
83
    PacketPid ! {send_msg, Msg, Ip, Udp}.
84
84
 
85
85
send_bytes(Bytes, PacketPid) ->
128
128
            case mk_discovery_msg(Version, Pdu, VsnHdr, "") of
129
129
                error ->
130
130
                    ok;
131
 
                {M, B} when list(B) -> 
132
 
                    put(discovery,{M,From}),
 
131
                {M, B} when is_list(B) -> 
 
132
                    put(discovery, {M, From}),
133
133
                    display_outgoing_message(M),
134
134
                    udp_send(UdpId, AgentIp, UdpPort, B)
135
135
            end,
136
 
            packet_loop(SnmpMgr,UdpId,AgentIp,UdpPort,VsnHdr,Version,[]);
 
136
            packet_loop(SnmpMgr, UdpId, AgentIp, UdpPort, VsnHdr, Version, []);
 
137
 
137
138
        {send_pdu, Pdu} ->
138
139
            d("packet_loop -> received send_pdu with"
139
140
              "~n   Pdu:  ~p", [Pdu]),
144
145
                    udp_send(UdpId, AgentIp, UdpPort, B)
145
146
            end,
146
147
            packet_loop(SnmpMgr,UdpId,AgentIp,UdpPort,VsnHdr,Version,[]);
 
148
 
147
149
        {send_msg, Msg, Ip, Udp} ->
148
150
            d("packet_loop -> received send_msg with"
149
151
              "~n   Msg:  ~p"
164
166
              "~n   Ip:        ~p"
165
167
              "~n   UdpPort:   ~p"
166
168
              "~n   sz(Bytes): ~p", [UdpId, Ip, UdpPort, sz(Bytes)]),       
167
 
            MsgData3 = handle_udp_packet(Version,erase(discovery),
 
169
            MsgData3 = handle_udp_packet(Version, erase(discovery),
168
170
                                         UdpId, Ip, UdpPort, Bytes,
169
171
                                         SnmpMgr, AgentIp),
170
172
            packet_loop(SnmpMgr,UdpId,AgentIp,UdpPort,VsnHdr,Version,
269
271
                []
270
272
        end,
271
273
    MsgData3;
272
 
handle_udp_packet(V,{DiscoReqMsg,From},_UdpId,_Ip,_UdpPort,Bytes,_,_AgentIp) ->
 
274
handle_udp_packet(V, {DiscoReqMsg, From}, _UdpId, _Ip, _UdpPort, 
 
275
                  Bytes, _, _AgentIp) ->
273
276
    DiscoRspMsg = (catch snmp_pdus:dec_message(Bytes)),
274
277
    display_incomming_message(DiscoRspMsg),
275
 
    Reply = (catch check_discovery_result(V,DiscoReqMsg,DiscoRspMsg)),
276
 
    From ! {discovery_response,Reply},
277
 
    [].
 
278
    _Reply = (catch check_discovery_result(V, DiscoReqMsg, DiscoRspMsg)),
 
279
    case (catch check_discovery_result(V, DiscoReqMsg, DiscoRspMsg)) of
 
280
        {ok, AgentEngineID} when is_list(AgentEngineID) ->
 
281
            %% Ok, step 1 complete, now for step 2
 
282
            %% Which we skip for now
 
283
            OK = {ok, AgentEngineID}, 
 
284
            From ! {discovery_response, OK},
 
285
            [];
 
286
        Error ->
 
287
            From ! {discovery_response, Error},
 
288
            []
 
289
    end.
 
290
 
278
291
 
279
292
%% This function assumes that the agent and the manager (thats us) 
280
293
%% has the same version.
281
 
check_discovery_result('version-3',DiscoReqMsg,DiscoRspMsg) ->
 
294
check_discovery_result('version-3', DiscoReqMsg, DiscoRspMsg) ->
282
295
    ReqMsgID = getMsgID(DiscoReqMsg),
283
296
    RspMsgID = getMsgID(DiscoRspMsg),
284
 
    check_msgID(ReqMsgID,RspMsgID),
285
 
    ReqRequestId = getRequestId('version-3',DiscoReqMsg),
286
 
    RspRequestId = getRequestId('version-3',DiscoRspMsg),
287
 
    check_requestId(ReqRequestId,RspRequestId),
288
 
    {ok,getMsgAuthEngineID(DiscoRspMsg)};
289
 
check_discovery_result(Version,DiscoReqMsg,DiscoRspMsg) ->
290
 
    ReqRequestId = getRequestId(Version,DiscoReqMsg),
291
 
    RspRequestId = getRequestId(Version,DiscoRspMsg),
292
 
    check_requestId(ReqRequestId,RspRequestId),
293
 
    {ok,getSysDescr(DiscoRspMsg)}.
 
297
    check_msgID(ReqMsgID, RspMsgID),
 
298
    ReqRequestId = getRequestId('version-3', DiscoReqMsg),
 
299
    RspRequestId = getRequestId('version-3', DiscoRspMsg),
 
300
    check_requestId(ReqRequestId, RspRequestId),
 
301
    {ok, getMsgAuthEngineID(DiscoRspMsg)};
 
302
check_discovery_result(Version, DiscoReqMsg, DiscoRspMsg) ->
 
303
    ReqRequestId = getRequestId(Version, DiscoReqMsg),
 
304
    RspRequestId = getRequestId(Version, DiscoRspMsg),
 
305
    check_requestId(ReqRequestId, RspRequestId),
 
306
    {ok, getSysDescr(DiscoRspMsg)}.
294
307
 
295
 
check_msgID(ID,ID) ->
 
308
check_msgID(ID, ID) ->
296
309
    ok;
297
 
check_msgID(ReqMsgID,RspMsgID) ->
298
 
    throw({error,{invalid_msgID,ReqMsgID,RspMsgID}}).
 
310
check_msgID(ReqMsgID, RspMsgID) ->
 
311
    throw({error, {invalid_msgID, ReqMsgID, RspMsgID}}).
299
312
 
300
313
check_requestId(Id,Id) ->
301
314
    ok;
302
 
check_requestId(ReqRequestId,RspRequestId) ->
303
 
    throw({error,{invalid_requestId,ReqRequestId,RspRequestId}}).
 
315
check_requestId(ReqRequestId, RspRequestId) ->
 
316
    throw({error, {invalid_requestId, ReqRequestId, RspRequestId}}).
304
317
 
305
 
getMsgID(M) when record(M,message) ->
 
318
getMsgID(M) when is_record(M, message) ->
306
319
    (M#message.vsn_hdr)#v3_hdr.msgID.
307
320
 
308
 
getRequestId('version-3',M) when record(M,message) ->
 
321
getRequestId('version-3',M) when is_record(M, message) ->
309
322
    ((M#message.data)#scopedPdu.data)#pdu.request_id;
310
 
getRequestId(_Version,M) when record(M,message) ->
 
323
getRequestId(_Version,M) when is_record(M, message) ->
311
324
    (M#message.data)#pdu.request_id;
312
325
getRequestId(Version,M) ->
313
326
    io:format("************* ERROR ****************"
315
328
              "~n   M:       ~w~n", [Version,M]),
316
329
    throw({error, {unknown_request_id, Version, M}}).
317
330
    
318
 
getMsgAuthEngineID(M) when record(M,message) ->
 
331
getMsgAuthEngineID(M) when is_record(M, message) ->
319
332
    SecParams1 = (M#message.vsn_hdr)#v3_hdr.msgSecurityParameters,
320
333
    SecParams2 = snmp_pdus:dec_usm_security_parameters(SecParams1),
321
334
    SecParams2#usmSecurityParameters.msgAuthoritativeEngineID.
322
335
    
323
 
getSysDescr(M) when record(M,message) ->
 
336
getSysDescr(M) when is_record(M, message) ->
324
337
    getSysDescr((M#message.data)#pdu.varbinds);
325
338
getSysDescr([]) ->
326
339
    not_found;
344
357
    IsReportable = snmp_misc:is_reportable(MsgFlags),
345
358
    SecRes = (catch SecModule:process_incoming_msg(list_to_binary(Packet), 
346
359
                                                   Data,SecParams,SecLevel)),
347
 
    {_SecEngineID, SecName, ScopedPDUBytes, SecData} =
 
360
    {_SecEngineID, SecName, ScopedPDUBytes, SecData, _} =
348
361
        check_sec_module_result(SecRes, V3Hdr, Data, IsReportable),
349
 
    case catch snmp_pdus:dec_scoped_pdu(ScopedPDUBytes) of
350
 
        ScopedPDU when record(ScopedPDU, scopedPdu) -> 
 
362
    case (catch snmp_pdus:dec_scoped_pdu(ScopedPDUBytes)) of
 
363
        ScopedPDU when is_record(ScopedPDU, scopedPdu) -> 
351
364
            {ok, ScopedPDU, {MsgId, SecName, SecData}};
352
365
        {'EXIT', Reason} ->
353
 
            throw({error, Reason})
354
 
    end.
 
366
            throw({error, Reason});
 
367
        Error ->
 
368
            throw({error, {scoped_pdu_decode_failed, Error}})
 
369
    end;
 
370
handle_v3_msg(_Packet, BadMessage) ->
 
371
    throw({error, bad_message, BadMessage}).
355
372
 
356
373
get_security_module(?SEC_USM) ->
357
374
    snmpa_usm;
409
426
 
410
427
mk_discovery_msg('version-3', Pdu, _VsnHdr, UserName) ->
411
428
    ScopedPDU = #scopedPdu{contextEngineID = "",
412
 
                           contextName = "",
413
 
                           data = Pdu},
 
429
                           contextName     = "",
 
430
                           data            = Pdu},
414
431
    Bytes = snmp_pdus:enc_scoped_pdu(ScopedPDU),
415
432
    MsgID = get(msg_id),
416
 
    put(msg_id,MsgID+1),
 
433
    put(msg_id, MsgID+1),
417
434
    UsmSecParams = 
418
435
        #usmSecurityParameters{msgAuthoritativeEngineID = "",
419
436
                               msgAuthoritativeEngineBoots = 0,
423
440
                               msgAuthenticationParameters = ""},
424
441
    SecBytes = snmp_pdus:enc_usm_security_parameters(UsmSecParams),
425
442
    PduType = Pdu#pdu.type,
426
 
    Hdr = #v3_hdr{msgID = MsgID, 
427
 
                  msgMaxSize = 1000,
428
 
                  msgFlags = snmp_misc:mk_msg_flags(PduType, 0),
429
 
                  msgSecurityModel = ?SEC_USM,
 
443
    Hdr = #v3_hdr{msgID                 = MsgID, 
 
444
                  msgMaxSize            = 1000,
 
445
                  msgFlags              = snmp_misc:mk_msg_flags(PduType, 0),
 
446
                  msgSecurityModel      = ?SEC_USM,
430
447
                  msgSecurityParameters = SecBytes},
431
448
    Msg = #message{version = 'version-3', vsn_hdr = Hdr, data = Bytes},
432
449
    case (catch snmp_pdus:enc_message_only(Msg)) of
435
452
                  "~n   Pdu:    ~w"
436
453
                  "~n   Reason: ~w",[Pdu, Reason]),
437
454
            error;
438
 
        L when list(L) ->
 
455
        L when is_list(L) ->
439
456
            {Msg#message{data = ScopedPDU}, L}
440
457
    end;
441
458
mk_discovery_msg(Version, Pdu, {Com, _, _, _, _}, _UserName) ->
446
463
                  "~n   Pdu:    ~w"
447
464
                  "~n   Reason: ~w",[Pdu, Reason]),
448
465
            error;
449
 
        L when list(L) -> 
 
466
        L when is_list(L) -> 
450
467
            {Msg, L}
451
468
    end.
452
469
 
464
481
    %% Code copied from snmp_mpd.erl
465
482
    {MsgId, SecName, SecData} =
466
483
        if
467
 
            tuple(MsgData), Pdu#pdu.type == 'get-response' ->
 
484
            is_tuple(MsgData) andalso (Pdu#pdu.type =:= 'get-response') ->
468
485
                MsgData;
469
486
            true -> 
470
487
                Md = get(msg_id),
569
586
    display_message("Incomming",M).
570
587
 
571
588
display_outgoing_message(M) ->
572
 
    display_message("Outgoing",M).
 
589
    display_message("Outgoing", M).
573
590
 
574
 
display_message(Direction,M) when record(M,message) ->
575
 
    io:format("~s SNMP message:~n",[Direction]),
 
591
display_message(Direction, M) when is_record(M, message) ->
 
592
    io:format("~s SNMP message:~n", [Direction]),
576
593
    V = M#message.version,
577
594
    display_version(V),
578
 
    display_hdr(V,M#message.vsn_hdr),
579
 
    display_msg_data(V,Direction,M#message.data);
580
 
display_message(Direction,M) ->
581
 
    io:format("~s message unknown: ~n~p",[Direction,M]).
 
595
    display_hdr(V, M#message.vsn_hdr),
 
596
    display_msg_data(V, Direction, M#message.data);
 
597
display_message(Direction, M) ->
 
598
    io:format("~s message unknown: ~n~p", [Direction, M]).
582
599
 
583
600
display_version('version-3') ->
584
601
    display_prop("Version",'SNMPv3');
683
700
display_scoped_pdu_data(_Direction,D) ->
684
701
    display_prop("Unknown scoped pdu data",D).
685
702
 
686
 
display_pdu(Direction,P) ->
687
 
    io:format("~s PDU:~n",[Direction]),
 
703
display_pdu(Direction, P) ->
 
704
    io:format("~s PDU:~n", [Direction]),
688
705
    display_type(P#pdu.type),
689
706
    display_request_id(P#pdu.request_id),
690
707
    display_error_status(P#pdu.error_status),