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

« back to all changes in this revision

Viewing changes to lib/megaco/src/engine/megaco_digit_map.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>2000-2007</year>
 
2
%% <year>2000-2008</year>
3
3
%% <holder>Ericsson AB, All Rights Reserved</holder>
4
4
%%</copyright>
5
5
%%<legalnotice>
80
80
%% 
81
81
%%----------------------------------------------------------------------
82
82
 
83
 
parse(DigitMapBody) when list(DigitMapBody) ->
 
83
parse(DigitMapBody) when is_list(DigitMapBody) ->
84
84
    ?d("parse -> entry with"
85
85
       "~n   DigitMapBody: ~p", [DigitMapBody]),
86
86
    case parse_digit_map(DigitMapBody) of
114
114
       "~n   Chars: ~p"
115
115
       "~n   DS:    ~p", [Chars, DS]),
116
116
    case megaco_text_scanner:skip_sep_chars(Chars, Line) of
117
 
        {[], _Line2} when DS /= [] ->
 
117
        {[], _Line2} when (DS =/= []) ->
118
118
            case parse_digit_string(DS) of
119
119
                {ok, DS2} ->
120
120
                    ST = #state_transition{mode = state_dependent,
127
127
            end;
128
128
        {[Char | Chars2], Line2} ->
129
129
            case Char of
130
 
                $( when DS == [], STL == [] ->
 
130
                $( when (DS =:= []) andalso (STL =:= []) ->
131
131
                    parse_digit_map(Chars2, Line2, DS, STL);
132
 
                $) when DS /= [] ->
 
132
                $) when (DS =/= []) ->
133
133
                    case megaco_text_scanner:skip_sep_chars(Chars2, Line2) of
134
134
                        {[], _Line3} ->
135
135
                            case parse_digit_string(DS) of
146
146
                            Trash =  lists:reverse(Chars3),
147
147
                            {error, {round_bracket_mismatch, Trash, Line3}}
148
148
                    end;
149
 
                $| when DS /= [] ->
 
149
                $| when (DS =/= []) ->
150
150
                    case parse_digit_string(DS) of
151
151
                        {ok, DS2} ->
152
152
                            ST = #state_transition{mode = state_dependent,
156
156
                        {error, Reason} ->
157
157
                            {error, Reason}
158
158
                    end;
159
 
                _ when Char /= $(, Char /= $|, Char /= $) ->
 
159
                _ when ( Char =/= $( ) andalso 
 
160
                       ( Char =/= $| ) andalso 
 
161
                       ( Char =/= $) ) ->
160
162
                    parse_digit_map(Chars2, Line2, [Char | DS], STL);
161
163
                _ ->
162
164
                    {error, {round_bracket_mismatch, Line2}}
185
187
        $. ->
186
188
            parse_digit_string(Chars, [zero_or_more | DS]);
187
189
 
188
 
        I when I >= $0, I =< $9 ->
 
190
        I when (I >= $0) andalso (I =< $9) ->
189
191
            parse_digit_string(Chars, [{single, I} | DS]);
190
192
 
191
 
        A when A >= $a, A =< $k ->
 
193
        A when (A >= $a) andalso (A =< $k) ->
192
194
            parse_digit_string(Chars, [{single, A} | DS]);
193
 
        A when A >= $A, A =< $K ->
 
195
        A when (A >= $A) andalso (A =< $K) ->
194
196
            parse_digit_string(Chars, [{single, A} | DS]);
195
197
 
196
198
        $S ->
230
232
       "~n   DS:    ~p", [[Char], Chars, DL, DS]),
231
233
    case Char of
232
234
        $[ ->
233
 
            parse_digit_string(Chars, [DL | DS]);
 
235
            parse_digit_string(Chars, [{letter, DL} | DS]);
234
236
        $] ->
235
237
            {error, square_bracket_mismatch};
236
 
        To when To >= $0, To =< $9 ->
 
238
        To when (To >= $0) andalso (To =< $9) ->
237
239
            case Chars of
238
 
                [$-, From | Chars2] when From >= $0, From =< $9 ->
 
240
                [$-, From | Chars2] when (From >= $0) andalso (From =< $9) ->
239
241
                    parse_digit_letter(Chars2, [{range, From, To} | DL], DS);
240
242
                _ ->
241
243
                    parse_digit_letter(Chars, [{single, To} | DL], DS)
242
244
            end;
243
245
 
244
 
        A when A >= $a, A =< $k ->
 
246
        A when (A >= $a) andalso (A =< $k) ->
245
247
            parse_digit_letter(Chars, [{single, A} | DL], DS);
246
 
        A when A >= $A, A =< $K ->
 
248
        A when (A >= $A) andalso (A =< $K) ->
247
249
            parse_digit_letter(Chars, [{single, A} | DL], DS);
248
250
 
249
251
        $S ->
273
275
%% Returns {ok, Letters} | {error, Reason}
274
276
%%----------------------------------------------------------------------
275
277
     
276
 
eval(DMV) when record(DMV, 'DigitMapValue') ->
 
278
eval(DMV) when is_record(DMV, 'DigitMapValue') ->
277
279
    case parse(DMV#'DigitMapValue'.digitMapBody) of
278
280
        {ok, DigitMapBody} ->
279
281
            eval(DigitMapBody, DMV);
280
282
        {error, Reason} ->
281
283
            {error, Reason}
282
284
    end;
283
 
eval(STL) when list(STL) ->
 
285
eval(STL) when is_list(STL) ->
284
286
     eval(STL, #timers{}).
285
287
        
286
288
eval(STL, #'DigitMapValue'{startTimer    = Start,
312
314
                     duration   = duration_to_millis(Duration),
313
315
                     unexpected = reject},
314
316
    eval(STL, Timers);
315
 
eval(STL, Timers) when list(STL),
316
 
                       record(hd(STL), state_transition),
317
 
                       record(Timers, timers) ->
 
317
eval(STL, Timers) when is_list(STL) andalso 
 
318
                       is_record(hd(STL), state_transition) andalso
 
319
                       is_record(Timers, timers) ->
318
320
    ?d("eval -> entry with"
319
321
       "~n   STL:    ~p"
320
322
       "~n   Timers: ~p", [STL, Timers]),
457
459
       "~n   KeepDur: ~p"
458
460
       "~n   STL2:    ~p", [Collect, KeepDur, STL2]),
459
461
    case STL2 of
460
 
        [] when State == optional_event -> % 7.1.14.5 5
 
462
        [] when (State =:= optional_event) -> % 7.1.14.5 5
461
463
            ?d("handle_event -> complete-full with event - 7.1.14.5 5", []),
462
464
            {completed_full, Timers, [], {Letters, Event}};
463
 
        [] when Timers#timers.unexpected == ignore ->
 
465
        [] when (Timers#timers.unexpected =:= ignore) ->
464
466
            ok = io:format("<WARNING> Ignoring unexpected event: ~p~n"
465
467
                           "Expected: ~p~n",
466
468
                           [Event, STL]),
467
469
            {State, Timers, STL, Letters};
468
 
        [] when Timers#timers.unexpected == reject ->
 
470
        [] when (Timers#timers.unexpected =:= reject) ->
469
471
            ?d("handle_event -> unexpected (reject)", []),
470
472
            unexpected_event(Event, STL, Letters);
471
473
        _ ->
475
477
               "~n   Timers2: ~p"
476
478
               "~n   STL3:    ~p", [State3, Timers2, STL3]),
477
479
            case Collect of
478
 
                true when KeepDur == true -> 
 
480
                true when (KeepDur =:= true) -> 
479
481
                    {State3, Timers2, STL3, [Event | Letters]};
480
482
                true -> 
481
483
                    case Event of
494
496
    match_event(Event, STL, [], false, false, MatchingDuration).
495
497
 
496
498
match_event(Event, [ST | OldSTL], NewSTL, Collect, KeepDur, MatchingDuration)
497
 
  when record(ST, state_transition) ->
 
499
  when is_record(ST, state_transition) ->
498
500
    ?d("match_event -> entry with"
499
501
       "~n   Event:            ~p"
500
502
       "~n   ST:               ~p"
508
510
            ?d("match_event -> keep ST (1)", []),
509
511
            match_event(Event, OldSTL, [ST | NewSTL], true, KeepDur,
510
512
                        MatchingDuration);
511
 
        {single, Single} when (Event == {long, Single}) and 
512
 
                              (MatchingDuration == false) ->
 
513
 
 
514
        {single, Single} when (Event =:= {long, Single}) andalso 
 
515
                              (MatchingDuration =:= false) ->
513
516
            %% Chap 7.1.14.5 point 4
514
517
            ?d("match_event -> keep ST - change to ordinary event (2)", []),
515
518
            match_event(Event, OldSTL, [ST | NewSTL], true, KeepDur,
516
519
                        MatchingDuration);
517
520
 
518
 
        {range, From, To} when Event >= From, Event =< To ->
 
521
        {range, From, To} when (Event >= From) andalso (Event =< To) ->
519
522
            ?d("match_event -> keep ST (3)", []),
520
523
            ST2 = ST#state_transition{next = {single, Event}},
521
524
            match_event(Event, OldSTL, [ST2 | NewSTL], true, KeepDur,
523
526
 
524
527
        {range, From, To} ->
525
528
            case Event of
526
 
                {long, R} when (R >= From) and (R =< To) and (MatchingDuration == false) ->
 
529
                {long, R} when (R >= From) andalso 
 
530
                               (R =< To)   andalso 
 
531
                               (MatchingDuration =:= false) ->
527
532
                    ?d("match_event -> keep ST (4)", []),
528
533
                    ST2 = ST#state_transition{next = {single, R}},
529
534
                    match_event(Event, OldSTL, [ST2 | NewSTL], true, true,
530
535
                                MatchingDuration);
531
536
                _ ->
532
 
                    ?d("match_event -> drop ST - change to ordinary event (5)", []),
 
537
                    ?d("match_event -> drop ST - "
 
538
                       "change to ordinary event (5)", []),
533
539
                    match_event(Event, OldSTL, NewSTL, Collect, KeepDur,
534
540
                                MatchingDuration) 
535
541
            end;
536
542
 
537
 
        {duration_event, {single, Single}} when Event == {long, Single} ->
 
543
        {duration_event, {single, Single}} when (Event =:= {long, Single}) ->
538
544
            ?d("match_event -> keep ST (5)", []),
539
545
            match_event(Event, OldSTL, [ST | NewSTL], true, true,
540
546
                        MatchingDuration);
541
547
 
542
548
        {duration_event, {range, From, To}} ->
543
549
            case Event of
544
 
                {long, R} when R >= From, R =< To ->
 
550
                {long, R} when (R >= From) andalso (R =< To) ->
545
551
                    ?d("match_event -> keep ST (6)", []),
546
552
                    match_event(Event, OldSTL, [ST | NewSTL], true, true,
547
553
                                MatchingDuration);
556
562
            match_event(Event, OldSTL, [ST | NewSTL], Collect, KeepDur,
557
563
                        MatchingDuration);
558
564
 
 
565
        {letter, Letters} ->
 
566
            case match_letter(Event, Letters, MatchingDuration) of
 
567
                {true, ChangedEvent} ->
 
568
                    ?d("match_event -> keep ST (9)", []),
 
569
                    ST2 = ST#state_transition{next = ChangedEvent},
 
570
                    match_event(Event, OldSTL, [ST2 | NewSTL], true, KeepDur,
 
571
                                MatchingDuration);
 
572
                true ->
 
573
                    ?d("match_event -> keep ST (10)", []),
 
574
                    match_event(Event, OldSTL, [ST | NewSTL], true, KeepDur,
 
575
                                MatchingDuration);
 
576
                false ->
 
577
                    ?d("match_event -> drop ST (11)", []),
 
578
                    match_event(Event, OldSTL, NewSTL, Collect, KeepDur,
 
579
                                MatchingDuration)
 
580
            end;
 
581
 
559
582
        _ ->
560
 
            ?d("match_event -> drop ST (9)", []),
 
583
            ?d("match_event -> drop ST (12)", []),
561
584
            match_event(Event, OldSTL, NewSTL, Collect, KeepDur,
562
585
                        MatchingDuration)
563
586
    end;
564
587
match_event(Event, [H | T], NewSTL, Collect, KeepDur0, MatchingDuration) 
565
 
  when list(H) ->
 
588
  when is_list(H) ->
566
589
    ?d("match_event -> entry with"
567
590
       "~n   Event:            ~p"
568
591
       "~n   H:                ~p"
573
596
       [Event, H, NewSTL, Collect, KeepDur0, MatchingDuration]),
574
597
    {NewSTL2, _Letters, KeepDur} = 
575
598
        match_event(Event, H, NewSTL, Collect, KeepDur0, MatchingDuration),
576
 
    ?d("compute -> "
 
599
    ?d("match_event -> "
577
600
       "~n   NewSTLs: ~p", [NewSTL2]),
578
601
    match_event(Event, T, NewSTL2, Collect, KeepDur,
579
602
                MatchingDuration);
585
608
    {lists:reverse(NewSTL), Collect, KeepDur}.
586
609
    
587
610
 
 
611
match_letter(_Event, [], _MatchingDuration) ->
 
612
    false;
 
613
match_letter(Event, [Letter | Letters], MatchingDuration) ->
 
614
    ?d("match_letter -> entry with"
 
615
       "~n   Event:            ~p"
 
616
       "~n   Letter:           ~p", 
 
617
       [Event, Letter]),
 
618
    case Letter of
 
619
        {single, Event} ->
 
620
            ?d("match_letter -> keep ST (1)", []),
 
621
            true;
 
622
 
 
623
        {single, Single} when (Event =:= {long, Single}) andalso 
 
624
                              (MatchingDuration =:= false) ->
 
625
            %% Chap 7.1.14.5 point 4
 
626
            ?d("match_letter -> keep ST - change to ordinary event (2)", []),
 
627
            true;
 
628
 
 
629
        {range, From, To} when (Event >= From) andalso (Event =< To) ->
 
630
            ?d("match_letter -> keep ST (3)", []),
 
631
            {true, {single, Event}};
 
632
 
 
633
        {range, From, To} ->
 
634
            case Event of
 
635
                {long, R} when (R >= From) andalso 
 
636
                               (R =< To)   andalso 
 
637
                               (MatchingDuration =:= false) ->
 
638
                    ?d("match_letter -> keep ST (4)", []),
 
639
                    {true, {single, R}};
 
640
                _ ->
 
641
                    ?d("match_letter -> drop ST - "
 
642
                       "change to ordinary event (5)", []),
 
643
                    match_letter(Event, Letters, MatchingDuration)
 
644
            end;
 
645
 
 
646
        {duration_event, {single, Single}} when (Event =:= {long, Single}) ->
 
647
            ?d("match_letter -> keep ST (5)", []),
 
648
            true;
 
649
 
 
650
        {duration_event, {range, From, To}} ->
 
651
            case Event of
 
652
                {long, R} when (R >= From) andalso (R =< To) ->
 
653
                    ?d("match_letter -> keep ST (6)", []),
 
654
                    true;
 
655
                _ ->
 
656
                    ?d("match_letter -> drop ST (7)", []),
 
657
                    match_letter(Event, Letters, MatchingDuration)
 
658
            end;
 
659
        
 
660
        _ ->
 
661
            ?d("match_letter -> drop ST (8)", []),          
 
662
            match_letter(Event, Letters, MatchingDuration)
 
663
 
 
664
    end.
 
665
        
 
666
 
 
667
    
 
668
 
588
669
matching_duration_event({long, Event}, STL) ->
589
670
    Nexts = [Next || #state_transition{next = Next} <- STL],
590
671
    mde(Event, Nexts);
623
704
    {State, Timers2, NewSTL}.
624
705
 
625
706
compute(State, GlobalMode, [ST | OldSTL], NewSTL) 
626
 
  when record(ST, state_transition) ->
 
707
  when is_record(ST, state_transition) ->
627
708
    ?d("compute(~w) -> entry with"
628
709
       "~n   GlobalMode: ~p"
629
710
       "~n   ST:         ~p"
633
714
    {State2, GlobalMode2, NewSTL2} =
634
715
        compute_cont(Cont, Mode, GlobalMode, State, NewSTL),
635
716
    compute(State2, GlobalMode2, OldSTL, NewSTL2);
636
 
compute(State, GlobalMode, [H | T], NewSTL) when list(H) ->
 
717
compute(State, GlobalMode, [H | T], NewSTL) when is_list(H) ->
637
718
    ?d("compute(~w) -> entry with"
638
719
       "~n   GlobalMode: ~p"
639
720
       "~n   H:          ~p"
656
737
       "~n   GlobalMode: ~p", [Next, Mode, GlobalMode]),
657
738
    case Next of
658
739
        %% Retain long timer if that has already been choosen
659
 
        use_short_timer when GlobalMode == use_long_timer ->
 
740
        use_short_timer when GlobalMode =:= use_long_timer ->
660
741
            compute_cont(Cont, Mode, GlobalMode, State, STL);
661
742
        use_short_timer ->
662
743
            Mode2 = use_short_timer,
716
797
    end;
717
798
report(_Pid, [])->
718
799
    ok;
719
 
report(Pid, Event) when pid(Pid) ->
 
800
report(Pid, Event) when is_pid(Pid) ->
720
801
    case Event of
721
802
        I when I >= $0, I =< $9 -> cast(Pid, Event);
722
803
        A when A >= $a, A =< $k -> cast(Pid, Event);