~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/snmp/src/misc/snmp_pdus.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%<copyright>
2
 
%% <year>1996-2007</year>
 
2
%% <year>1996-2008</year>
3
3
%% <holder>Ericsson AB, All Rights Reserved</holder>
4
4
%%</copyright>
5
5
%%<legalnotice>
46
46
 
47
47
dec_message([48 | Bytes]) ->
48
48
    Bytes2 = get_data_bytes(Bytes),
49
 
    {SNMPversion, Rest1} = dec_int_tag(Bytes2),
50
 
    case dec_snmp_ver(SNMPversion) of
51
 
        'version-3' ->
52
 
            dec_rest_v3_msg(Rest1);
53
 
        Vsn -> % 1 or 2
54
 
            dec_rest_v1_v2_msg(Vsn, Rest1)
 
49
    case dec_snmp_version(Bytes2) of
 
50
        {'version-3', Rest} ->
 
51
            dec_rest_v3_msg(Rest);
 
52
        {Vsn, Rest} -> % 1 or 2
 
53
            dec_rest_v1_v2_msg(Vsn, Rest)
55
54
    end.
56
55
 
57
56
dec_message_only([48 | Bytes]) ->
58
57
    Bytes2 = get_data_bytes(Bytes),
59
 
    {SNMPversion, Rest1} = dec_int_tag(Bytes2),
60
 
    case dec_snmp_ver(SNMPversion) of
61
 
        'version-3' ->
62
 
            dec_rest_v3_msg_only(Rest1);
63
 
        Vsn -> % 1 or 2
64
 
            dec_rest_v1_v2_msg_only(Vsn, Rest1)
 
58
    case dec_snmp_version(Bytes2) of
 
59
        {'version-3', Rest} ->
 
60
            dec_rest_v3_msg_only(Rest);
 
61
        {Vsn, Rest} -> % 1 or 2
 
62
            dec_rest_v1_v2_msg_only(Vsn, Rest)
65
63
    end.
66
64
 
 
65
dec_snmp_version(Bytes) ->
 
66
    case (catch dec_int_tag(Bytes, 10)) of
 
67
        {error, {bad_integer, BadInt}} ->
 
68
            exit({bad_version, BadInt});
 
69
        {SNMPversion, Rest} when is_integer(SNMPversion) andalso is_list(Rest) ->
 
70
            {dec_snmp_ver(SNMPversion), Rest};
 
71
        {'EXIT', Reason} ->
 
72
            exit(Reason)
 
73
    end.
 
74
            
 
75
            
67
76
dec_snmp_ver(0) ->
68
77
    'version-1';
69
78
dec_snmp_ver(1) ->
303
312
get_data_bytes(Bytes) ->
304
313
    {Size, Tail} = dec_len(Bytes),
305
314
    if
306
 
        length(Tail) == Size ->
 
315
        length(Tail) =:= Size ->
307
316
            Tail;
308
317
        true ->
309
318
            exit({error, {wrong_length, Bytes}})
320
329
 
321
330
dec_int_tag([2 | Bytes]) ->
322
331
    dec_integer_notag(Bytes).
 
332
dec_int_tag([2 | Bytes], SizeLimit) ->
 
333
    dec_integer_notag(Bytes, SizeLimit).
323
334
 
324
335
dec_integer_notag(Ints) ->
325
 
    {Size, Ints2} = dec_len(Ints),
326
 
    if hd(Ints2) band 128 == 0 -> %% Positive number
327
 
            dec_pos_int(Ints2, Size, 8 * (Size - 1));
 
336
    dec_integer_notag(Ints, infinity).
 
337
dec_integer_notag(Ints, SizeLimit) ->
 
338
    case dec_len(Ints) of
 
339
        {Size, Ints2} when SizeLimit =:= infinity ->
 
340
            do_dec_integer_notag(Size, Ints2);
 
341
        {Size, Ints2} when (is_integer(SizeLimit) andalso 
 
342
                            (Size =< SizeLimit)) ->
 
343
            do_dec_integer_notag(Size, Ints2);
 
344
        {BadSize, _BadInts2} ->
 
345
            throw({error, {bad_integer, {BadSize, SizeLimit}}})
 
346
    end.
 
347
 
 
348
do_dec_integer_notag(Size, Ints) ->
 
349
    if hd(Ints) band 128 == 0 -> %% Positive number
 
350
            dec_pos_int(Ints, Size, 8 * (Size - 1));
328
351
       true -> %% Negative
329
 
            dec_neg_int(Ints2, Size, 8 * (Size - 1))
 
352
            dec_neg_int(Ints, Size, 8 * (Size - 1))
330
353
    end.
331
354
 
332
355
 
368
391
dec_oid_element([Dig|Tail],Neaten, Num) ->
369
392
    dec_oid_element(Tail, Neaten+1, Num*128 + (Dig band 127)).
370
393
 
371
 
chk_msg_id(MsgId) when MsgId >= 0, MsgId =< 2147483647 -> ok;
 
394
chk_msg_id(MsgId) when (MsgId >= 0) andalso (MsgId =< 2147483647) -> ok;
372
395
chk_msg_id(MsgId) -> exit({bad_msg_id, MsgId}).
373
396
    
374
 
chk_msg_max_size(MMS) when MMS >= 484, MMS =< 2147483647 -> ok;
 
397
chk_msg_max_size(MMS) when (MMS >= 484) andalso (MMS =< 2147483647) -> ok;
375
398
chk_msg_max_size(MMS) -> exit({bad_msg_max_size, MMS}).
376
399
    
377
400
chk_msg_sec_model(MsgSecurityModel) when MsgSecurityModel >= 0,
401
424
        true ->
402
425
            %% Long form
403
426
            No = Hd band 127,  % clear 8th bit
404
 
            {DigList,Rest} = head(No,Tl),
 
427
            {DigList, Rest} = head(No, Tl),
405
428
            Size = dec_integer_len(DigList),
406
 
            {Size,Rest}
 
429
            {Size, Rest}
407
430
    end.
408
431
 
409
432
dec_integer_len([D]) ->
502
525
    [48 | Len] ++ Bytes.
503
526
 
504
527
 
505
 
enc_pdu(PDU) when PDU#pdu.type == 'get-request' ->
 
528
enc_pdu(PDU) when PDU#pdu.type =:= 'get-request' ->
506
529
    enc_pdu(160, PDU);
507
 
enc_pdu(PDU) when PDU#pdu.type == 'get-next-request' ->
 
530
enc_pdu(PDU) when PDU#pdu.type =:= 'get-next-request' ->
508
531
    enc_pdu(161, PDU);
509
 
enc_pdu(PDU) when PDU#pdu.type == 'get-response' ->
 
532
enc_pdu(PDU) when PDU#pdu.type =:= 'get-response' ->
510
533
    enc_pdu(162, PDU);
511
 
enc_pdu(PDU) when PDU#pdu.type == 'set-request' ->
 
534
enc_pdu(PDU) when PDU#pdu.type =:= 'set-request' ->
512
535
    enc_pdu(163, PDU);
513
 
enc_pdu(PDU) when PDU#pdu.type == 'get-bulk-request' ->
 
536
enc_pdu(PDU) when PDU#pdu.type =:= 'get-bulk-request' ->
514
537
    enc_pdu(165, PDU);
515
 
enc_pdu(PDU) when PDU#pdu.type == 'inform-request' ->
 
538
enc_pdu(PDU) when PDU#pdu.type =:= 'inform-request' ->
516
539
    enc_pdu(166, PDU);
517
 
enc_pdu(PDU) when PDU#pdu.type == 'snmpv2-trap' ->
 
540
enc_pdu(PDU) when PDU#pdu.type =:= 'snmpv2-trap' ->
518
541
    enc_pdu(167, PDU);
519
 
enc_pdu(PDU) when PDU#pdu.type == report ->
 
542
enc_pdu(PDU) when PDU#pdu.type =:= report ->
520
543
    enc_pdu(168, PDU);
521
 
enc_pdu(TrapPDU) when record(TrapPDU, trappdu) ->
 
544
enc_pdu(TrapPDU) when is_record(TrapPDU, trappdu) ->
522
545
    enc_Trap(TrapPDU).
523
546
 
524
547
 
553
576
    Len = elength(length(Bytes7)),
554
577
    [48 | Len] ++ Bytes7.
555
578
 
556
 
err_val(Int,'get-bulk-request') when integer(Int) -> Int;
 
579
err_val(Int,'get-bulk-request') when is_integer(Int) -> Int;
557
580
err_val(ErrStat, _) ->
558
581
    {value, {_ErrStat, Val}} = lists:keysearch(ErrStat, 1, errMsgs()),
559
582
    Val.
567
590
     {resourceUnavailable,13},{commitFailed,14},{undoFailed,15},
568
591
     {authorizationError,16},{notWritable,17},{inconsistentName,18}].
569
592
 
570
 
enc_VarBindList(EncodedVBs) when integer(hd(EncodedVBs)) ->
 
593
enc_VarBindList(EncodedVBs) when is_integer(hd(EncodedVBs)) ->
571
594
    Len1 = elength(length(EncodedVBs)),
572
595
    lists:append([48 | Len1],EncodedVBs);
573
596
enc_VarBindList(VBs) ->
615
638
    Len2 = elength(length(Bytes2)),
616
639
    lists:append([enc_val_tag(Type,Val) | Len2],Bytes2).
617
640
 
618
 
enc_val_tag('Counter32',Val) when Val >= 0, Val =< 4294967295 ->
 
641
enc_val_tag('Counter32',Val) when (Val >= 0) andalso (Val =< 4294967295) ->
619
642
    65;
620
 
enc_val_tag('Unsigned32', Val) when Val >= 0, Val =< 4294967295 ->
 
643
enc_val_tag('Unsigned32', Val) when (Val >= 0) andalso (Val =< 4294967295) ->
621
644
    66;
622
 
enc_val_tag('TimeTicks', Val) when Val >= 0, Val =< 4294967295 ->
 
645
enc_val_tag('TimeTicks', Val) when (Val >= 0) andalso (Val =< 4294967295) ->
623
646
    67;
624
 
enc_val_tag('Counter64', Val) when Val >= 0, Val =< 18446744073709551615 ->
 
647
enc_val_tag('Counter64', Val) when ((Val >= 0) andalso 
 
648
                                    (Val =< 18446744073709551615)) ->
625
649
    70.
626
650
 
 
651
 
627
652
%%----------------------------------------------------------------------
628
653
%% Impl according to RFC1906, section 8
629
654
%% For example: the number 1010 0000 (=160)   0100 0001 (=65) is represented as
650
675
    Mul*rev_int8(Byte)+octet_str_to_bits(Bytes,Mul*256).
651
676
    
652
677
 
653
 
enc_Trap(TrapPdu) when record(TrapPdu, trappdu) ->
 
678
enc_Trap(TrapPdu) when is_record(TrapPdu, trappdu) ->
654
679
    Bytes1 = enc_trap_data(TrapPdu),
655
680
    Len1 = elength(length(Bytes1)),
656
681
    lists:append([164 | Len1],Bytes1).