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

« back to all changes in this revision

Viewing changes to lib/megaco/src/text/megaco_text_scanner.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:
30
30
 
31
31
-define(LOWER1(Char),
32
32
        if
33
 
            Char >= $A, Char =< $Z ->
 
33
            (Char >= $A) andalso (Char =< $Z) ->
34
34
                Char - ($A - $a);
35
35
            true ->
36
36
                Char
180
180
            comment_chars(Rest, Line);
181
181
        end_of_line ->
182
182
            sep_chars(Rest, Line);
183
 
        _ when Char == 22 ->
 
183
        _ when Char =:= 22 ->
184
184
            comment_chars(Rest, Line);
185
185
        _ ->
186
186
            %% {bad_token, {'SEP', Line, Char}, Rest, Line}
351
351
                                {'MtpAddressToken', Line, OctetString};
352
352
                            'LocalToken' ->
353
353
                                %% 'LocalToken' 'LBRKT' OctetString 'RBRKT'
354
 
                                {'LocalDescriptorToken', Line, OctetString};
 
354
                                PGs = property_groups(OctetString), 
 
355
                                {'LocalDescriptorToken', Line, PGs};
355
356
                            'RemoteToken' ->
356
357
                                %% 'RemoteToken' 'LBRKT' OctetString 'RBRKT'
357
 
                                {'RemoteDescriptorToken', Line, OctetString};
 
358
                                PGs = property_groups(OctetString), 
 
359
                                {'RemoteDescriptorToken', Line, PGs};
358
360
                            'DigitMapToken' ->
359
361
                                %% 'DigitMapToken' 'LBRKT' OctetString 'RBRKT'
360
362
                                DMV = digit_map_value(OctetString),
362
364
                                {'DigitMapDescriptorToken', Line, DMD}
363
365
                        end,
364
366
                    {token, Token, Rest6, Line4};
365
 
                _ when TokenTag == 'DigitMapToken' ->
 
367
                _ when TokenTag =:= 'DigitMapToken' ->
366
368
                    %% 'DigitMapToken'
367
369
                    {token, {'DigitMapToken', Line, SafeChars}, All, Line};
368
370
                _ ->
369
371
                    {token, {'SafeChars', Line, SafeChars}, All, Line}
370
372
            end;
371
 
        [?EqualToken | Rest2] when TokenTag == 'DigitMapToken' ->
 
373
        [?EqualToken | Rest2] when TokenTag =:= 'DigitMapToken' ->
372
374
            {Rest3, Line3} = skip_sep_chars(Rest2, Line2),
373
375
            {Rest4, DigitMapName} = collect_safe_chars(Rest3, []),
374
376
            {Rest6, Line6, DMD} = 
375
377
                if
376
 
                    DigitMapName == [] ->
 
378
                    DigitMapName =:= [] ->
377
379
                        {Rest3, Line3, #'DigitMapDescriptor'{}};
378
380
                    true ->
379
381
                        {Rest5, Line5} = skip_sep_chars(Rest4, Line3),
405
407
                    %% 'DigitMapToken'
406
408
                    {token, {'DigitMapToken', Line, SafeChars}, All, Line}
407
409
            end;
408
 
        _  when TokenTag == 'DigitMapToken' ->
 
410
        _  when TokenTag =:= 'DigitMapToken' ->
409
411
            %% 'DigitMapToken'
410
412
            {token, {'DigitMapToken', Line, SafeChars}, All, Line};
411
413
        _ ->
478
480
   case {Rest2, catch list_to_integer(Digits)} of
479
481
       {[?CommaToken | Rest3], Int} when is_integer(Int) andalso 
480
482
                                         (Int >= 0) andalso 
481
 
                                         (element(TimerPos, DMV) == asn1_NOVALUE) ->
 
483
                                         (element(TimerPos, DMV) =:= asn1_NOVALUE) ->
482
484
           {Rest4, _} = skip_sep_chars(Rest3, 0),
483
485
           DMV2 = setelement(TimerPos, DMV, Int),
484
486
           digit_map_value(Rest4, DMV2);
486
488
           DMV#'DigitMapValue'{digitMapBody = All}
487
489
   end.
488
490
 
 
491
%% ============================================================================
 
492
%% <prev-parser-stuff>
 
493
%% 
 
494
%% This stuff was originally in the parser(s), but was, 
 
495
%% for performance reasons, moved to the scanner(s). This 
 
496
%% scanner does not make it faster, but the flex scanner 
 
497
%% does, which is why the move was made.
 
498
%% 
 
499
 
 
500
property_groups(OctetString) ->
 
501
    Group  = [],
 
502
    Groups = [],
 
503
    property_name(OctetString, Group, Groups).
 
504
 
 
505
property_name([Char | Rest] = All, Group, Groups) ->
 
506
    if 
 
507
        ?white_space(Char) ->
 
508
            property_name(Rest, Group, Groups);
 
509
        ?end_of_line(Char) ->
 
510
            property_name(Rest, Group, Groups);
 
511
        true ->
 
512
            Name = [],
 
513
            do_property_name(All, Name, Group, Groups)
 
514
    end;
 
515
property_name([] = All, Group, Groups) ->
 
516
    Name = [],
 
517
    do_property_name(All, Name, Group, Groups).
 
518
 
 
519
do_property_name([Char | Rest], Name, Group, Groups) 
 
520
  when (Char =:= $=) andalso (Name =/= []) ->
 
521
    %% Now we have a complete name
 
522
    if
 
523
        (Name =:= "v") andalso (Group =/= []) ->
 
524
            %% v= is a property group delimiter,
 
525
            %% lets create yet another property group.
 
526
            Groups2 = [lists:reverse(Group) | Groups],
 
527
            Group2 = [],
 
528
            property_value(Rest, Name, Group2, Groups2);
 
529
        true ->
 
530
            %% Use current property group
 
531
            property_value(Rest, Name, Group, Groups)
 
532
    end;
 
533
do_property_name([Char | Rest], Name, Group, Groups) ->
 
534
    case ?classify_char4(Char) of
 
535
        safe_char_upper ->
 
536
            do_property_name(Rest, [Char | Name], Group, Groups);
 
537
        safe_char ->
 
538
            do_property_name(Rest, [Char | Name], Group, Groups);
 
539
        _ ->
 
540
            throw({error, {bad_prop_name, lists:reverse(Name), Char}})
 
541
    end;
 
542
do_property_name([], [], [], Groups) ->
 
543
    lists:reverse(Groups);
 
544
do_property_name([], [], Group, Groups) ->
 
545
    Group2 = lists:reverse(Group),
 
546
    lists:reverse([Group2 | Groups]);
 
547
do_property_name([], Name, Group, Groups) when Name =/= [] ->
 
548
    %% Assume end of line
 
549
    Value  = [],
 
550
    PP     = make_property_parm(Name, Value),
 
551
    Group2 = lists:reverse([PP | Group]),
 
552
    lists:reverse([Group2 | Groups]).
 
553
 
 
554
-ifdef(megaco_scanner_inline).
 
555
-compile({inline,[{property_value,4}]}).
 
556
-endif.
 
557
property_value(Chars, Name, Group, Groups) ->
 
558
    Value = [],
 
559
    do_property_value(Chars, Name, Value, Group, Groups).
 
560
 
 
561
do_property_value([Char | Rest], Name, Value, Group, Groups) ->
 
562
    if
 
563
        ?end_of_line(Char) ->
 
564
            %% Now we have a complete "name=value" pair
 
565
            PP = make_property_parm(Name, Value),
 
566
            property_name(Rest, [PP | Group], Groups);
 
567
        true ->
 
568
            do_property_value(Rest, Name, [Char | Value], Group, Groups)
 
569
    end;
 
570
do_property_value([], Name, Value, Group, Groups) ->
 
571
    %% Assume end of line
 
572
    PP = make_property_parm(Name, Value),
 
573
    Group2 = lists:reverse([PP | Group]),
 
574
    lists:reverse([Group2 | Groups]).
 
575
 
 
576
-ifdef(megaco_scanner_inline).
 
577
-compile({inline,[{make_property_parm,2}]}).
 
578
-endif.
 
579
make_property_parm(Name, Value) ->
 
580
    %% Record name, name field, value field, extraInfo field
 
581
    {'PropertyParm', 
 
582
     lists:reverse(Name), 
 
583
     [lists:reverse(Value)], 
 
584
     asn1_NOVALUE}.
 
585
 
 
586
 
 
587
%% </prev-parser-stuff>
 
588
%% ===========================================================================
 
589
 
489
590
select_token([$o, $- | LowerText], Version) ->
490
591
    select_token(LowerText, Version);
491
592
select_token([$w, $- | LowerText], Version) ->