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

« back to all changes in this revision

Viewing changes to lib/megaco/src/engine/megaco_digit_map.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:
30
30
%% digitMapLetter     = DIGIT   ; Basic event symbols 
31
31
%%                    / %x41-4B ; a-k
32
32
%%                    / %x61-6B ; A-K 
 
33
%%                    / "T"     ; Start inter-event timers
 
34
%%                    / "S"     ; Short inter-event timers
33
35
%%                    / "L"     ; Long  inter-event timers, e.g. 16 sec
34
 
%%                    / "S"     ; Short inter-event timers
35
36
%%                    / "Z"     ; Long duration modifier
36
37
%% DIGIT              = %x30-39 ; 0-9 
37
38
%%                   
39
40
%% Example of a digit map:
40
41
%% 
41
42
%% (0| 00|[1-7]xxx|8xxxxxxx|Fxxxxxxx|Exx|91xxxxxxxxxx|9011x.) 
 
43
%% 
 
44
%% DM = "(0| 00|[1-7]xxx|8xxxxxxx|Fxxxxxxx|Exx|91xxxxxxxxxx|9011x.)".
 
45
%% DM = "xxx | xxL3 | xxS4".
 
46
%% megaco:parse_digit_map(DM).
 
47
%% megaco:test_digit_event(DM, "1234").
 
48
%% megaco:test_digit_event(DM, "12ssss3").
 
49
%% megaco:test_digit_event(DM, "12ssss4").
 
50
%% megaco:test_digit_event(DM, "12ssss5").
 
51
%% 
42
52
%%----------------------------------------------------------------------
43
53
 
44
54
-module(megaco_digit_map).
46
56
-export([parse/1, eval/1, eval/2, report/2, test/2]). % Public
47
57
-export([test_eval/2]).                               % Internal
48
58
 
 
59
-include("megaco_internal.hrl").
49
60
-include("megaco_message_internal.hrl").
50
61
-include_lib("megaco/src/text/megaco_text_tokens.hrl").
51
62
 
53
64
 
54
65
-record(timers, {mode       = state_dependent,
55
66
                 start      = 0,
56
 
                 short      = timer_to_millis(3),
 
67
                 short      = timer_to_millis(3), 
57
68
                 long       = timer_to_millis(9),
 
69
                 duration   = 100,      % (not used) 100 ms <-> 9.9 sec
58
70
                 unexpected = reject}). % ignore | reject
59
71
 
60
72
%%----------------------------------------------------------------------
62
74
%% into a list of state transitions.
63
75
%% 
64
76
%% Returns {ok, StateTransitionList} | {error, Reason}
 
77
%% 
65
78
%%----------------------------------------------------------------------
66
79
 
67
80
parse(DigitMapBody) when list(DigitMapBody) ->
 
81
    ?d("parse -> entry with"
 
82
       "~n   DigitMapBody: ~p", [DigitMapBody]),
68
83
    case parse_digit_map(DigitMapBody) of
69
84
        {ok, STL} ->
70
 
            {ok, STL};
 
85
            {ok, duration_cleanup(STL, [])};
71
86
        {error, Reason} ->
72
87
            {error, Reason}
73
88
    end;
74
89
parse(_DigitMapBody) ->
75
90
    {error, not_a_digit_map_body}.
76
91
 
 
92
duration_cleanup([], Acc) ->
 
93
    Acc;
 
94
duration_cleanup([STL|T], Acc) ->
 
95
    #state_transition{cont = Events} = STL,
 
96
    Events2 = duration_events_cleanup(Events, []),
 
97
    duration_cleanup(T, [STL#state_transition{cont = Events2}|Acc]).
 
98
 
 
99
duration_events_cleanup([], Acc) ->
 
100
    lists:reverse(Acc);
 
101
duration_events_cleanup([duration_event, Event|Events], Acc) ->
 
102
    duration_events_cleanup(Events, [{duration_event, Event}|Acc]);
 
103
duration_events_cleanup([Event|Events], Acc) ->
 
104
    duration_events_cleanup(Events, [Event|Acc]).
 
105
    
77
106
parse_digit_map(Chars) ->
78
107
    parse_digit_map(Chars, 1, [], []).
79
108
 
80
109
parse_digit_map(Chars, Line, DS, STL) ->
 
110
    ?d("parse_digit_map -> entry with"
 
111
       "~n   Chars: ~p"
 
112
       "~n   DS:    ~p", [Chars, DS]),
81
113
    case megaco_text_scanner:skip_sep_chars(Chars, Line) of
82
114
        {[], _Line2} when DS /= [] ->
83
115
            case parse_digit_string(DS) of
131
163
    end.
132
164
 
133
165
parse_digit_string(Chars) ->
 
166
    ?d("parse_digit_string -> entry with"
 
167
       "~n   Chars: ~p", [Chars]),
134
168
    parse_digit_string(Chars, []).
135
169
 
136
170
parse_digit_string([Char | Chars], DS) ->
 
171
    ?d("parse_digit_string -> entry with"
 
172
       "~n   Char:  ~p"
 
173
       "~n   Chars: ~p"
 
174
       "~n   DS:    ~p", [[Char], Chars, DS]),
137
175
    case Char of
138
176
        $] ->
139
177
            parse_digit_letter(Chars, [], DS);
143
181
            parse_digit_string(Chars, [{range, $0, $9} | DS]);
144
182
        $. ->
145
183
            parse_digit_string(Chars, [zero_or_more | DS]);
 
184
 
146
185
        I when I >= $0, I =< $9 ->
147
186
            parse_digit_string(Chars, [{single, I} | DS]);
 
187
 
148
188
        A when A >= $a, A =< $k ->
149
189
            parse_digit_string(Chars, [{single, A} | DS]);
150
190
        A when A >= $A, A =< $K ->
151
191
            parse_digit_string(Chars, [{single, A} | DS]);
 
192
 
152
193
        $S ->
153
194
            parse_digit_string(Chars, [use_short_timer | DS]);
 
195
        $s ->
 
196
            parse_digit_string(Chars, [use_short_timer | DS]);
 
197
 
154
198
        $L ->
155
199
            parse_digit_string(Chars, [use_long_timer | DS]);
156
 
        $Z ->
157
 
            parse_digit_string(Chars, [inter_event_timeout | DS]);
158
 
        $s ->
159
 
            parse_digit_string(Chars, [use_short_timer | DS]);
160
200
        $l ->
161
201
            parse_digit_string(Chars, [use_long_timer | DS]);
162
 
        $z ->
163
 
            parse_digit_string(Chars, [inter_event_timeout | DS]);
 
202
 
 
203
        $Z when length(Chars) > 0 ->
 
204
            parse_digit_string(Chars, [duration_event | DS]);
 
205
        $z when length(Chars) > 0 ->
 
206
            parse_digit_string(Chars, [duration_event | DS]);
 
207
 
 
208
        $Z ->
 
209
            {error, duration_not_allowed_as_last_char};
 
210
        $z ->
 
211
            {error, duration_not_allowed_as_last_char};
 
212
 
164
213
        BadChar ->
165
214
            {error, {illegal_char_in_digit_string, BadChar}}
166
215
    end;
167
216
parse_digit_string([], DM) ->
 
217
    ?d("parse_digit_string -> entry when done with"
 
218
       "~n   DM: ~p", [DM]),
168
219
    {ok, DM}.
169
 
    
 
220
 
 
221
 
170
222
parse_digit_letter([Char | Chars], DL, DS) ->
 
223
    ?d("parse_digit_letter -> entry with"
 
224
       "~n   Char:  ~p"
 
225
       "~n   Chars: ~p"
 
226
       "~n   DL:    ~p"
 
227
       "~n   DS:    ~p", [[Char], Chars, DL, DS]),
171
228
    case Char of
172
229
        $[ ->
173
230
            parse_digit_string(Chars, [DL | DS]);
180
237
                _ ->
181
238
                    parse_digit_letter(Chars, [{single, To} | DL], DS)
182
239
            end;
 
240
 
183
241
        A when A >= $a, A =< $k ->
184
242
            parse_digit_letter(Chars, [{single, A} | DL], DS);
185
243
        A when A >= $A, A =< $K ->
186
244
            parse_digit_letter(Chars, [{single, A} | DL], DS);
 
245
 
187
246
        $S ->
188
247
            parse_digit_letter(Chars, [use_short_timer | DL], DS);
 
248
        $s ->
 
249
            parse_digit_letter(Chars, [use_short_timer | DL], DS);
 
250
 
189
251
        $L ->
190
252
            parse_digit_letter(Chars, [use_long_timer | DL], DS);
 
253
        $l ->
 
254
            parse_digit_letter(Chars, [use_long_timer | DL], DS);
 
255
 
191
256
        $Z ->
192
 
            parse_digit_letter(Chars, [inter_event_timeout | DL], DS);
193
 
        $s ->
194
 
            parse_digit_letter(Chars, [use_short_timer | DL], DS);
195
 
        $l ->
196
 
            parse_digit_letter(Chars, [use_long_timer | DL], DS);
 
257
            parse_digit_letter(Chars, [duration_event | DL], DS);
197
258
        $z ->
198
 
            parse_digit_letter(Chars, [inter_event_timeout | DL], DS);
 
259
            parse_digit_letter(Chars, [duration_event | DL], DS);
 
260
 
199
261
        BadChar ->
200
262
            {error, {illegal_char_between_square_brackets, BadChar}}
201
263
    end;
202
264
parse_digit_letter([], _DL, _DS) ->
203
265
    {error, square_bracket_mismatch}.
204
266
 
 
267
 
205
268
%%----------------------------------------------------------------------
206
269
%% Collect digit map letters according to digit map
207
270
%% Returns {ok, Letters} | {error, Reason}
217
280
eval(STL) when list(STL) ->
218
281
     eval(STL, #timers{}).
219
282
        
220
 
eval(STL, DMV) when record(DMV, 'DigitMapValue') ->
221
 
    Timers = #timers{start = timer_to_millis(DMV#'DigitMapValue'.startTimer),
222
 
                     short = timer_to_millis(DMV#'DigitMapValue'.shortTimer),
223
 
                     long  = timer_to_millis(DMV#'DigitMapValue'.longTimer)},
 
283
eval(STL, #'DigitMapValue'{startTimer    = Start,
 
284
                           shortTimer    = Short,
 
285
                           longTimer     = Long,
 
286
                           durationTimer = Duration}) ->
 
287
    Timers = #timers{start    = timer_to_millis(Start),
 
288
                     short    = timer_to_millis(Short),
 
289
                     long     = timer_to_millis(Long),
 
290
                     duration = duration_to_millis(Duration)},
224
291
    eval(STL, Timers);
225
 
eval(STL, {ignore, DMV}) when record(DMV, 'DigitMapValue') ->
226
 
    Timers = #timers{start = timer_to_millis(DMV#'DigitMapValue'.startTimer),
227
 
                     short = timer_to_millis(DMV#'DigitMapValue'.shortTimer),
228
 
                     long  = timer_to_millis(DMV#'DigitMapValue'.longTimer),
 
292
eval(STL, {ignore, #'DigitMapValue'{startTimer    = Start,
 
293
                                    shortTimer    = Short,
 
294
                                    longTimer     = Long,
 
295
                                    durationTimer = Duration}}) ->
 
296
    Timers = #timers{start      = timer_to_millis(Start),
 
297
                     short      = timer_to_millis(Short),
 
298
                     long       = timer_to_millis(Long),
 
299
                     duration   = duration_to_millis(Duration),
229
300
                     unexpected = ignore},
230
301
    eval(STL, Timers);
231
 
eval(STL, {reject, DMV}) when record(DMV, 'DigitMapValue') ->
232
 
    Timers = #timers{start = timer_to_millis(DMV#'DigitMapValue'.startTimer),
233
 
                     short = timer_to_millis(DMV#'DigitMapValue'.shortTimer),
234
 
                     long  = timer_to_millis(DMV#'DigitMapValue'.longTimer),
 
302
eval(STL, {reject, #'DigitMapValue'{startTimer    = Start,
 
303
                                    shortTimer    = Short,
 
304
                                    longTimer     = Long,
 
305
                                    durationTimer = Duration}}) ->
 
306
    Timers = #timers{start      = timer_to_millis(Start),
 
307
                     short      = timer_to_millis(Short),
 
308
                     long       = timer_to_millis(Long),
 
309
                     duration   = duration_to_millis(Duration),
235
310
                     unexpected = reject},
236
311
    eval(STL, Timers);
237
312
eval(STL, Timers) when list(STL),
238
313
                       record(hd(STL), state_transition),
239
314
                       record(Timers, timers) ->
240
 
    collect(start, mandatory_event, Timers, STL, []);
 
315
    ?d("eval -> entry with"
 
316
       "~n   STL:    ~p"
 
317
       "~n   Timers: ~p", [STL, Timers]),
 
318
    case collect(start, mandatory_event, Timers, lists:reverse(STL), []) of
 
319
        {error, _} = Error ->
 
320
            ?d("eval -> error:"
 
321
               "~n   Error: ~p", [Error]),
 
322
            Error;
 
323
        OK ->
 
324
            ?d("eval -> ok:"
 
325
               "~n   OK: ~p", [OK]),
 
326
            OK
 
327
    end;
241
328
eval(DigitMapBody, ignore) ->
242
329
    eval(DigitMapBody, #timers{unexpected = ignore});
243
330
eval(DigitMapBody, reject) ->
250
337
            {error, Reason}
251
338
    end.
252
339
 
 
340
%% full | unambiguous
 
341
 
253
342
collect(Event, State, Timers, STL, Letters) ->
 
343
    ?d("collect -> entry with"
 
344
       "~n   Event:  ~p"
 
345
       "~n   State:  ~p"
 
346
       "~n   Timers: ~p"
 
347
       "~n   STL:    ~p", [Event, State, Timers, STL]),
254
348
    case handle_event(Event, State, Timers, STL, Letters) of
 
349
        {completed_full, _Timers2, _STL2, Letters2} ->
 
350
            completed(full, Letters2);
255
351
        {completed, _Timers2, _STL2, Letters2} ->
256
 
            completed(Letters2);
 
352
            completed(unambiguous, Letters2);
257
353
        {State2, Timers2, STL2, Letters2} ->
 
354
            ?d("collect -> "
 
355
               "~n   State2:   ~p"
 
356
               "~n   Timers2:  ~p"
 
357
               "~n   Letters2: ~p", [State2, Timers2, Letters2]),
258
358
            MaxWait = choose_timer(State2, Event, Timers2),
259
 
            %% ok = io:format("Timer: ~p ~p~n~p~n~p~n",
260
 
            %%                [State2, MaxWait, Timers2, STL2]),
 
359
            ?d("collect -> Timer choosen: "
 
360
               "~n   MaxWait: ~p", [MaxWait]),
261
361
            receive
262
362
                {?MODULE, _FromPid, Event2} ->
263
 
                    %% ok = io:format("Got event: ~p~n", [Event2]),
 
363
                    ?d("collect -> Got event: "
 
364
                       "~n   ~p", [Event2]),
264
365
                    collect(Event2, State2, Timers2, STL2, Letters2)
265
366
            after MaxWait ->
266
 
                    collect(inter_event_timeout, State2, Timers2, STL2, Letters2)
 
367
                    ?d("collect -> timeout after ~w", [MaxWait]),
 
368
                    collect(inter_event_timeout, 
 
369
                            State2, Timers2, STL2, Letters2)
267
370
            end;
 
371
 
268
372
        {error, Reason} ->
 
373
            ?d("collect -> error: "
 
374
               "~n   Reason: ~p", [Reason]),
269
375
            {error, Reason}
270
376
    end.
271
377
 
272
 
choose_timer(State, start, T) ->
273
 
    Extra = T#timers.start,
274
 
    Timer = do_choose_timer(State, T),
275
 
    if
276
 
        Timer == infinity -> infinity;
277
 
        Extra == infinity -> infinity;
278
 
        true              -> Timer + Extra
279
 
    end;
 
378
choose_timer(_State, start, #timers{start = 0}) ->
 
379
    ?d("choose_timer(start) -> entry", []),
 
380
    infinity;
 
381
choose_timer(_State, start, #timers{start = T}) ->
 
382
    ?d("choose_timer(start) -> entry with"
 
383
       "~n   T: ~p", [T]),
 
384
    T;
280
385
choose_timer(State, _Event, T) ->
 
386
    ?d("choose_timer(~p) -> entry with"
 
387
       "~n   State: ~p"
 
388
       "~n   T:     ~p", [_Event, State, T]),
281
389
    do_choose_timer(State, T).
282
390
 
283
 
do_choose_timer(State, T) ->
284
 
    case T#timers.mode of
285
 
        state_dependent ->
286
 
            case State of
287
 
                mandatory_event -> T#timers.long;
288
 
                optional_event  -> T#timers.short
289
 
            end;
290
 
        use_short_timer -> 
291
 
            T#timers.short;
292
 
        use_long_timer -> 
293
 
            T#timers.long
294
 
    end.
 
391
do_choose_timer(mandatory_event, #timers{mode = state_dependent, long = T}) ->
 
392
    T;
 
393
do_choose_timer(optional_event, #timers{mode = state_dependent, short = T}) ->
 
394
    T;
 
395
do_choose_timer(_State, #timers{mode = use_short_timer, short = T}) ->
 
396
    T;
 
397
do_choose_timer(_State, #timers{mode = use_long_timer, long = T}) ->
 
398
    T.
295
399
 
296
 
timer_to_millis(asn1_NOVALUE) -> 0;
 
400
timer_to_millis(asn1_NOVALUE) -> infinity; 
297
401
timer_to_millis(infinity)     -> infinity;
298
402
timer_to_millis(Seconds)      -> timer:seconds(Seconds).
299
403
    
300
 
completed(Letters) ->
301
 
    {ok, lists:reverse(Letters)}.
 
404
%% Time for duration is in hundreds of milliseconds
 
405
duration_to_millis(asn1_NOVALUE) -> 100;
 
406
duration_to_millis(Time) when is_integer(Time) -> Time*100.
 
407
 
 
408
completed(Kind, {Letters, Event}) when is_list(Letters) ->
 
409
    ?d("completed -> entry with"
 
410
       "~n   Kind:  ~p"
 
411
       "~n   Event: ~s", [Kind, [Event]]),
 
412
    {ok, {Kind, duration_letter_cleanup(Letters, []), Event}};
 
413
completed(Kind, Letters) when is_list(Letters) ->
 
414
    ?d("completed -> entry with"
 
415
       "~n   Kind: ~p", [Kind]),
 
416
    {ok, {Kind, duration_letter_cleanup(Letters, [])}}.
 
417
 
 
418
duration_letter_cleanup([], Acc) ->
 
419
    Acc;
 
420
duration_letter_cleanup([{long, Letter}|Letters], Acc) ->
 
421
    duration_letter_cleanup(Letters, [$Z,Letter|Acc]);
 
422
duration_letter_cleanup([Letter|Letters], Acc) ->
 
423
    duration_letter_cleanup(Letters, [Letter|Acc]).
302
424
 
303
425
unexpected_event(Event, STL, Letters) ->
304
 
    Expected = [ST#state_transition.next || ST <- STL],
305
 
    SoFar = lists:reverse(Letters),
306
 
    Reason = {unexpected_event, Event, SoFar, Expected},
 
426
    Expected = [Next || #state_transition{next = Next} <- STL],
 
427
    SoFar    = lists:reverse(Letters),
 
428
    Reason   = {unexpected_event, Event, SoFar, Expected},
307
429
    {error, Reason}.
308
430
    
 
431
 
309
432
%%----------------------------------------------------------------------
310
433
%% Handles a received event according to digit map
311
434
%% State ::= optional_event | mandatory_event
313
436
%% Returns {State, NewSTL, Letters} | {error, Reason}
314
437
%%----------------------------------------------------------------------
315
438
handle_event(inter_event_timeout, optional_event, Timers, STL, Letters) ->
316
 
    {completed, Timers, STL, Letters};
 
439
    {completed_full, Timers, STL, Letters}; % 7.1.14.5 2
317
440
handle_event(cancel, _State, _Timers, STL, Letters) ->
318
441
    unexpected_event(cancel, STL, Letters);
319
442
handle_event(start, _State, Timers, STL, Letters) ->
320
443
    {State2, Timers2, STL2} = compute(Timers, STL),
321
444
    {State2, Timers2, STL2, Letters};
322
445
handle_event(Event, State, Timers, STL, Letters) ->
323
 
    {STL2, Collect} = match_event(Event, STL, [], false),
 
446
    ?d("handle_event -> entry when"
 
447
       "~n   Event:   ~p"
 
448
       "~n   State:   ~p"
 
449
       "~n   Timers:  ~p"
 
450
       "~n   Letters: ~p", [Event, State, Timers, Letters]),
 
451
    {STL2, Collect, KeepDur} = match_event(Event, STL), 
 
452
    ?d("handle_event -> match event result: "
 
453
       "~n   Collect: ~p"
 
454
       "~n   KeepDur: ~p"
 
455
       "~n   STL2:    ~p", [Collect, KeepDur, STL2]),
324
456
    case STL2 of
325
 
        [] ->
326
 
            case Timers#timers.unexpected of
327
 
                ignore ->
328
 
                    ok = io:format("<WARNING> Ignoring unexpected event: ~p~n"
329
 
                                   "Expected: ~p~n",
330
 
                                   [Event, STL]),
331
 
                    {State, Timers, STL, Letters};
332
 
                reject ->
333
 
                    unexpected_event(Event, STL, Letters)
334
 
            end;
335
 
        STL2 ->
 
457
        [] when State == optional_event -> % 7.1.14.5 5
 
458
            ?d("handle_event -> complete-full with event - 7.1.14.5 5", []),
 
459
            {completed_full, Timers, [], {Letters, Event}};
 
460
        [] when Timers#timers.unexpected == ignore ->
 
461
            ok = io:format("<WARNING> Ignoring unexpected event: ~p~n"
 
462
                           "Expected: ~p~n",
 
463
                           [Event, STL]),
 
464
            {State, Timers, STL, Letters};
 
465
        [] when Timers#timers.unexpected == reject ->
 
466
            ?d("handle_event -> unexpected (reject)", []),
 
467
            unexpected_event(Event, STL, Letters);
 
468
        _ ->
336
469
            {State3, Timers2, STL3} = compute(Timers, STL2),
 
470
            ?d("handle_event -> computed: "
 
471
               "~n   State3:  ~p"
 
472
               "~n   Timers2: ~p"
 
473
               "~n   STL3:    ~p", [State3, Timers2, STL3]),
337
474
            case Collect of
338
 
                true  -> {State3, Timers2, STL3, [Event | Letters]};
339
 
                false -> {State3, Timers2, STL3, Letters}
 
475
                true when KeepDur == true -> 
 
476
                    {State3, Timers2, STL3, [Event | Letters]};
 
477
                true -> 
 
478
                    case Event of
 
479
                        {long, ActualEvent} ->
 
480
                            {State3, Timers2, STL3, [ActualEvent | Letters]};
 
481
                        _ ->
 
482
                            {State3, Timers2, STL3, [Event | Letters]}
 
483
                    end;
 
484
                false -> 
 
485
                    {State3, Timers2, STL3, Letters}
340
486
            end
341
487
    end.
342
488
 
343
 
match_event(Event, [ST | OldSTL], NewSTL, Collect)
 
489
match_event(Event, STL) ->
 
490
    MatchingDuration = matching_duration_event(Event, STL),
 
491
    match_event(Event, STL, [], false, false, MatchingDuration).
 
492
 
 
493
match_event(Event, [ST | OldSTL], NewSTL, Collect, KeepDur, MatchingDuration)
344
494
  when record(ST, state_transition) ->
 
495
    ?d("match_event -> entry with"
 
496
       "~n   Event:            ~p"
 
497
       "~n   ST:               ~p"
 
498
       "~n   NewSTL:           ~p"
 
499
       "~n   Collect:          ~p"
 
500
       "~n   KeepDur:          ~p"
 
501
       "~n   MatchingDuration: ~p", 
 
502
       [Event, ST, NewSTL, Collect, KeepDur, MatchingDuration]),
345
503
    case ST#state_transition.next of
346
504
        {single, Event} ->
347
 
            match_event(Event, OldSTL, [ST | NewSTL], true);
 
505
            ?d("match_event -> keep ST (1)", []),
 
506
            match_event(Event, OldSTL, [ST | NewSTL], true, KeepDur,
 
507
                        MatchingDuration);
 
508
        {single, Single} when (Event == {long, Single}) and 
 
509
                              (MatchingDuration == false) ->
 
510
            %% Chap 7.1.14.5 point 4
 
511
            ?d("match_event -> keep ST - change to ordinary event (2)", []),
 
512
            match_event(Event, OldSTL, [ST | NewSTL], true, KeepDur,
 
513
                        MatchingDuration);
 
514
 
348
515
        {range, From, To} when Event >= From, Event =< To ->
 
516
            ?d("match_event -> keep ST (3)", []),
349
517
            ST2 = ST#state_transition{next = {single, Event}},
350
 
            match_event(Event, OldSTL, [ST2 | NewSTL], true);
 
518
            match_event(Event, OldSTL, [ST2 | NewSTL], true, KeepDur,
 
519
                        MatchingDuration);
 
520
 
 
521
        {range, From, To} ->
 
522
            case Event of
 
523
                {long, R} when (R >= From) and (R =< To) and (MatchingDuration == false) ->
 
524
                    ?d("match_event -> keep ST (4)", []),
 
525
                    ST2 = ST#state_transition{next = {single, R}},
 
526
                    match_event(Event, OldSTL, [ST2 | NewSTL], true, true,
 
527
                                MatchingDuration);
 
528
                _ ->
 
529
                    ?d("match_event -> drop ST - change to ordinary event (5)", []),
 
530
                    match_event(Event, OldSTL, NewSTL, Collect, KeepDur,
 
531
                                MatchingDuration) 
 
532
            end;
 
533
 
 
534
        {duration_event, {single, Single}} when Event == {long, Single} ->
 
535
            ?d("match_event -> keep ST (5)", []),
 
536
            match_event(Event, OldSTL, [ST | NewSTL], true, true,
 
537
                        MatchingDuration);
 
538
 
 
539
        {duration_event, {range, From, To}} ->
 
540
            case Event of
 
541
                {long, R} when R >= From, R =< To ->
 
542
                    ?d("match_event -> keep ST (6)", []),
 
543
                    match_event(Event, OldSTL, [ST | NewSTL], true, true,
 
544
                                MatchingDuration);
 
545
                _ ->
 
546
                    ?d("match_event -> drop ST (7)", []),
 
547
                    match_event(Event, OldSTL, NewSTL, Collect, KeepDur,
 
548
                                MatchingDuration) 
 
549
            end;
 
550
 
351
551
        Event ->
352
 
            match_event(Event, OldSTL, [ST | NewSTL], Collect);
 
552
            ?d("match_event -> keep ST (8)", []),
 
553
            match_event(Event, OldSTL, [ST | NewSTL], Collect, KeepDur,
 
554
                        MatchingDuration);
 
555
 
353
556
        _ ->
354
 
            match_event(Event, OldSTL, NewSTL, Collect)
 
557
            ?d("match_event -> drop ST (9)", []),
 
558
            match_event(Event, OldSTL, NewSTL, Collect, KeepDur,
 
559
                        MatchingDuration)
355
560
    end;
356
 
match_event(Event, [H | T], NewSTL, Collect) when list(H) ->
357
 
    {NewSTL2, _Letters} = match_event(Event, H, NewSTL, Collect),
358
 
    match_event(Event, T, NewSTL2, Collect);
359
 
match_event(_Event, [], NewSTL, Collect) ->
360
 
    {NewSTL, Collect}.
 
561
match_event(Event, [H | T], NewSTL, Collect, KeepDur0, MatchingDuration) 
 
562
  when list(H) ->
 
563
    ?d("match_event -> entry with"
 
564
       "~n   Event:            ~p"
 
565
       "~n   H:                ~p"
 
566
       "~n   NewSTL:           ~p"
 
567
       "~n   Collect:          ~p"
 
568
       "~n   KeepDur0:         ~p"
 
569
       "~n   MatchingDuration: ~p", 
 
570
       [Event, H, NewSTL, Collect, KeepDur0, MatchingDuration]),
 
571
    {NewSTL2, _Letters, KeepDur} = 
 
572
        match_event(Event, H, NewSTL, Collect, KeepDur0, MatchingDuration),
 
573
    ?d("compute -> "
 
574
       "~n   NewSTLs: ~p", [NewSTL2]),
 
575
    match_event(Event, T, NewSTL2, Collect, KeepDur,
 
576
                MatchingDuration);
 
577
match_event(_Event, [], NewSTL, Collect, KeepDur, _MatchingDuration) ->
 
578
    ?d("match_event -> entry with"
 
579
       "~n   NewSTL:  ~p"
 
580
       "~n   Collect: ~p"
 
581
       "~n   KeepDur: ~p", [NewSTL, Collect, KeepDur]),
 
582
    {lists:reverse(NewSTL), Collect, KeepDur}.
361
583
    
 
584
 
 
585
matching_duration_event({long, Event}, STL) ->
 
586
    Nexts = [Next || #state_transition{next = Next} <- STL],
 
587
    mde(Event, Nexts);
 
588
matching_duration_event(_Event, _STL) ->
 
589
    false.
 
590
 
 
591
 
 
592
mde(_, []) ->
 
593
    false;
 
594
mde(Event, [{duration_event, {single, Event}}|_]) ->
 
595
    true;
 
596
mde(Event, [{duration_event, {range, From, To}}|_]) 
 
597
  when Event >= From, Event =< To ->
 
598
    true;
 
599
mde(Event, [_|Nexts]) ->
 
600
    mde(Event, Nexts).
 
601
 
 
602
 
362
603
%%----------------------------------------------------------------------
363
604
%% Compute new state transitions
364
605
%% Returns {State, Timers, NewSTL}
365
606
%%----------------------------------------------------------------------
366
607
compute(Timers, OldSTL) ->
367
 
    {State, GlobalMode, NewSTL} = compute(mandatory_event, state_dependent, OldSTL, []),
 
608
    ?d("compute -> entry with"
 
609
       "~n   Timers: ~p"
 
610
       "~n   OldSTL: ~p", [Timers, OldSTL]),
 
611
    {State, GlobalMode, NewSTL} = 
 
612
        compute(mandatory_event, state_dependent, OldSTL, []),
 
613
    ?d("compute -> "
 
614
       "~n   State:      ~p"
 
615
       "~n   GlobalMode: ~p"
 
616
       "~n   NewSTL:     ~p", [State, GlobalMode, NewSTL]),
368
617
    Timers2 = Timers#timers{mode = GlobalMode},
 
618
    ?d("compute -> "
 
619
       "~n   Timers2: ~p", [Timers2]),
369
620
    {State, Timers2, NewSTL}.
370
621
 
371
 
compute(State, GlobalMode, [ST | OldSTL], NewSTL) when record(ST, state_transition) ->
 
622
compute(State, GlobalMode, [ST | OldSTL], NewSTL) 
 
623
  when record(ST, state_transition) ->
 
624
    ?d("compute(~w) -> entry with"
 
625
       "~n   GlobalMode: ~p"
 
626
       "~n   ST:         ~p"
 
627
       "~n   NewSTL:     ~p", [State, GlobalMode, ST, NewSTL]),
372
628
    Cont = ST#state_transition.cont,
373
629
    Mode = ST#state_transition.mode,
374
630
    {State2, GlobalMode2, NewSTL2} =
375
631
        compute_cont(Cont, Mode, GlobalMode, State, NewSTL),
376
632
    compute(State2, GlobalMode2, OldSTL, NewSTL2);
377
633
compute(State, GlobalMode, [H | T], NewSTL) when list(H) ->
 
634
    ?d("compute(~w) -> entry with"
 
635
       "~n   GlobalMode: ~p"
 
636
       "~n   H:          ~p"
 
637
       "~n   NewSTL:     ~p", [State, GlobalMode, H, NewSTL]),
378
638
    {State2, GlobalMode2, NewSTL2} = compute(State, GlobalMode, H, NewSTL),
379
639
    compute(State2, GlobalMode2, T, NewSTL2);
380
640
compute(State, GlobalMode, [], NewSTL) ->
 
641
    ?d("compute(~w) -> entry with"
 
642
       "~n   GlobalMode: ~p"
 
643
       "~n   NewSTL:     ~p", [State, GlobalMode, NewSTL]),
381
644
    case NewSTL of
382
645
        [] -> {completed, GlobalMode, NewSTL};
383
646
        _  -> {State,     GlobalMode, NewSTL}
384
647
    end.
385
648
 
386
649
compute_cont([Next | Cont] = All, Mode, GlobalMode, State, STL) ->
 
650
    ?d("compute_cont -> entry with"
 
651
       "~n   Next:       ~p"
 
652
       "~n   Mode:       ~p"
 
653
       "~n   GlobalMode: ~p", [Next, Mode, GlobalMode]),
387
654
    case Next of
 
655
        %% Retain long timer if that has already been choosen
 
656
        use_short_timer when GlobalMode == use_long_timer ->
 
657
            compute_cont(Cont, Mode, GlobalMode, State, STL);
388
658
        use_short_timer ->
389
659
            Mode2 = use_short_timer,
390
660
            compute_cont(Cont, Mode2, GlobalMode, State, STL);
422
692
make_cont(Mode, Next, Cont) ->
423
693
    #state_transition{mode = Mode, next = Next, cont = Cont}.
424
694
 
 
695
 
425
696
%%----------------------------------------------------------------------
426
697
%% Send one or more events to event collector process
427
698
%% 
450
721
        cancel                  -> cast(Pid, Event);
451
722
        $Z                      -> cast(Pid, cancel);
452
723
        $z                      -> cast(Pid, cancel);
453
 
        $S                      -> sleep(1);
454
 
        $s                      -> sleep(1);
455
 
        $L                      -> sleep(10);
456
 
        $l                      -> sleep(10);
457
 
        _                       -> {error, {illegal_event, Event}}
 
724
        $R                      -> timer:sleep(100);  % 100 ms
 
725
        $r                      -> timer:sleep(100);  % 100 ms
 
726
        $S                      -> sleep(1);  % 1 sec (1000 ms)
 
727
        $s                      -> sleep(1);  % 1 sec (1000 ms)
 
728
        $L                      -> sleep(10); % 10 sec (10000 ms)
 
729
        $l                      -> sleep(10); % 10 sec (10000 ms)
 
730
        {long, I} when (I >= $0) and (I =< $9) -> cast(Pid, {long, I});
 
731
        {long, A} when (A >= $a) and (A =< $k) -> cast(Pid, {long, A});
 
732
        {long, A} when (A >= $A) and (A =< $K) -> cast(Pid, {long, A});
 
733
%%         {long, I} when (I >= $0) and (I =< $9) -> long(Pid, I);
 
734
%%         {long, A} when (A >= $a) and (A =< $k) -> long(Pid, A);
 
735
%%         {long, A} when (A >= $A) and (A =< $K) -> long(Pid, A);
 
736
        _                       -> {error, {illegal_event, Event}}
458
737
    end.
459
738
 
 
739
%% long(Pid, Event) ->
 
740
%%     cast(Pid, long),
 
741
%%     cast(Pid, Event).
 
742
%% 
460
743
sleep(Sec) ->
461
744
    timer:sleep(timer:seconds(Sec)),
462
745
    ok.