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

« back to all changes in this revision

Viewing changes to lib/megaco/src/engine/megaco_messenger.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:
39
39
         test_reply/5
40
40
        ]).
41
41
 
 
42
%% MIB stat functions
42
43
-export([
43
44
         get_stats/0, get_stats/1, get_stats/2,
44
45
         reset_stats/0, reset_stats/1
45
46
        ]).
46
47
 
 
48
%% Misc functions
 
49
-export([
 
50
         cleanup/2, 
 
51
         which_requests/1, which_replies/1
 
52
        ]).
 
53
 
47
54
%% Module internal export
48
55
-export([
49
56
         process_received_message/5,
89
96
          timer_ref,
90
97
          version,
91
98
          bytes,
92
 
          ack_action           % discard_ack | {handle_ack, Data}
 
99
          ack_action,          % discard_ack | {handle_ack, Data}
 
100
          send_handle
93
101
         }).
94
102
 
95
103
-record(trans_id,
118
126
-define(report_pending_limit_exceeded(ConnData),
119
127
        ?report_important(ConnData, "<ERROR> pending limit exceeded", [])).
120
128
 
 
129
-ifdef(megaco_extended_trace).
 
130
-define(rt1(T,F,A),?report_trace(T,F,A)).
 
131
-define(rt2(F,A),  ?rt1(ignore,F,A)).
 
132
-define(rt3(F),    ?rt2(F,[])).
 
133
-else.
 
134
-define(rt1(T,F,A),ok).
 
135
-define(rt2(F,A),  ok).
 
136
-define(rt3(F),    ok).
 
137
-endif.
 
138
 
 
139
 
121
140
%%----------------------------------------------------------------------
122
141
%% SNMP statistics handling functions
123
142
%%----------------------------------------------------------------------
126
145
%% Func: get_stats/0, get_stats/1, get_stats/2
127
146
%% Description: Retreive statistics (counters) for TCP
128
147
%%-----------------------------------------------------------------
 
148
 
129
149
get_stats() ->
130
150
    megaco_stats:get_stats(megaco_stats).
131
151
 
140
160
%% Func: reset_stats/0, reaet_stats/1
141
161
%% Description: Reset statistics (counters)
142
162
%%-----------------------------------------------------------------
 
163
 
143
164
reset_stats() ->
144
165
    megaco_stats:reset_stats(megaco_stats).
145
166
 
147
168
    megaco_stats:reset_stats(megaco_stats, ConnHandleOrCounter).
148
169
 
149
170
 
 
171
 
 
172
%%----------------------------------------------------------------------
 
173
%% cleanup utility functions
 
174
%%----------------------------------------------------------------------
 
175
 
 
176
cleanup(#megaco_conn_handle{local_mid = LocalMid}, Force) 
 
177
  when (Force == true) or (Force == false) ->
 
178
    Pat = #reply{trans_id  = '$1', 
 
179
                 local_mid = LocalMid, 
 
180
                 state     = '$2',
 
181
                 _         = '_'},
 
182
    do_cleanup(Pat, Force);
 
183
cleanup(LocalMid, Force) 
 
184
  when (Force == true) or (Force == false) ->
 
185
    Pat = #reply{trans_id  = '$1', 
 
186
                 local_mid = LocalMid, 
 
187
                 state     = '$2',
 
188
                 _         = '_'},
 
189
    do_cleanup(Pat, Force).
 
190
    
 
191
do_cleanup(Pat, Force) ->
 
192
    Match = megaco_monitor:which_replies(Pat),
 
193
    Reps  = [{V1, V2} || [V1, V2] <- Match],
 
194
    do_cleanup2(Reps, Force).
 
195
 
 
196
do_cleanup2([], _) ->
 
197
    ok;
 
198
do_cleanup2([{TransId, aborted}|T], Force = false) ->
 
199
    megaco_monitor:delete_reply(TransId),
 
200
    do_cleanup2(T, Force);
 
201
do_cleanup2([_|T], Force = false) ->
 
202
    do_cleanup2(T, Force);
 
203
do_cleanup2([{TransId, _State}|T], Force = true) ->
 
204
    megaco_monitor:delete_reply(TransId),
 
205
    do_cleanup2(T, Force).
 
206
                  
 
207
 
 
208
%%----------------------------------------------------------------------
 
209
%% which_requests and which_replies utility functions
 
210
%%----------------------------------------------------------------------
 
211
 
 
212
which_requests(#megaco_conn_handle{local_mid  = LocalMid, 
 
213
                                   remote_mid = RemoteMid}) ->
 
214
    Pat1 = #trans_id{mid    = LocalMid, 
 
215
                     serial = '$1', _ = '_'},
 
216
    Pat2 = #request{trans_id   = Pat1, 
 
217
                    remote_mid = RemoteMid, 
 
218
                    _ = '_'},
 
219
    Match = megaco_monitor:which_requests(Pat2),
 
220
    [S || [S] <- Match];
 
221
which_requests(LocalMid) ->
 
222
    Pat1 = #trans_id{mid    = LocalMid, 
 
223
                     serial = '$1', _ = '_'},
 
224
    Pat2 = #request{trans_id   = Pat1, 
 
225
                    remote_mid = '$2', _ = '_'},
 
226
    Match0 = megaco_monitor:which_requests(Pat2),
 
227
    Match1 = [{mk_ch(LocalMid, V2), V1} || [V1, V2] <- Match0],
 
228
    which_requests1(lists:sort(Match1)).
 
229
 
 
230
which_requests1([]) ->
 
231
    [];
 
232
which_requests1([{CH, S}|T]) ->
 
233
    which_requests2(T, CH, [S], []).
 
234
 
 
235
which_requests2([], CH, Serials, Reqs) ->
 
236
    lists:reverse([{CH, Serials}|Reqs]);
 
237
which_requests2([{CH, S}|T], CH, Serials, Reqs) ->
 
238
    which_requests2(T, CH, [S|Serials], Reqs);
 
239
which_requests2([{CH1, S}|T], CH2, Serials, Reqs) ->
 
240
    which_requests2(T, CH1, [S], [{CH2, lists:reverse(Serials)}| Reqs]).
 
241
    
 
242
 
 
243
which_replies(#megaco_conn_handle{local_mid  = LocalMid, 
 
244
                                  remote_mid = RemoteMid}) ->
 
245
    Pat1 = #trans_id{mid    = RemoteMid, 
 
246
                     serial = '$1', _ = '_'},
 
247
    Pat2 = #reply{trans_id  = Pat1, 
 
248
                  local_mid = LocalMid, 
 
249
                  state     = '$2', 
 
250
                  handler   = '$3', _ = '_'},
 
251
    Match = megaco_monitor:which_replies(Pat2),
 
252
    [{V1, V2, V3} || [V1, V2, V3] <- Match];
 
253
which_replies(LocalMid) ->
 
254
    Pat1 = #trans_id{mid    = '$1', 
 
255
                     serial = '$2', _ = '_'},
 
256
    Pat2 = #reply{trans_id  = Pat1, 
 
257
                  local_mid = LocalMid, 
 
258
                  state     = '$3', 
 
259
                  handler   = '$4', _ = '_'},
 
260
    Match0 = megaco_monitor:which_replies(Pat2),
 
261
    Match1 = [{mk_ch(LocalMid,V1),{V2,V3,V4}} || [V1, V2, V3, V4] <- Match0],
 
262
    which_replies1(lists:sort(Match1)).
 
263
 
 
264
which_replies1([]) ->
 
265
    [];
 
266
which_replies1([{CH, Data}|T]) ->
 
267
    which_replies2(T, CH, [Data], []).
 
268
 
 
269
which_replies2([], CH, Data, Reps) ->
 
270
    lists:reverse([{CH, Data}|Reps]);
 
271
which_replies2([{CH, Data}|T], CH, Datas, Reps) ->
 
272
    which_replies2(T, CH, [Data|Datas], Reps);
 
273
which_replies2([{CH1, Data}|T], CH2, Datas, Reps) ->
 
274
    which_replies2(T, CH1, [Data], [{CH2, lists:reverse(Datas)}| Reps]).
 
275
    
 
276
    
 
277
mk_ch(LM, RM) ->
 
278
    #megaco_conn_handle{local_mid = LM, remote_mid = RM}.
 
279
    
 
280
 
150
281
%%----------------------------------------------------------------------
151
282
%% Register/unreister connections
152
283
%%----------------------------------------------------------------------
153
284
 
154
285
%% Returns {ok, ConnHandle} | {error, Reason}
155
286
connect(RH, RemoteMid, SendHandle, ControlPid)
156
 
  when record(RH, megaco_receive_handle) ->
 
287
  when is_record(RH, megaco_receive_handle) ->
157
288
    case megaco_config:connect(RH, RemoteMid, SendHandle, ControlPid) of
158
289
        {ok, ConnData} ->
159
290
            do_connect(ConnData);
175
306
        ok ->
176
307
            ?SIM(ok, do_encode),
177
308
            monitor_process(CH, CD#conn_data.control_pid);
178
 
        {error, ED} when record(ED,'ErrorDescriptor') ->
 
309
        error ->
 
310
            megaco_config:disconnect(CH),
 
311
            {error, {connection_refused, CD, error}};
 
312
        {error, ED} when is_record(ED,'ErrorDescriptor') ->
179
313
            megaco_config:disconnect(CH),
180
314
            {error, {connection_refused, CD, ED}};
181
 
        Error ->
 
315
        _Error ->
 
316
            warning_msg("connect callback failed: ~w", [Res]),
182
317
            megaco_config:disconnect(CH),
183
 
            {error, {connection_refused, CD, Error}}
 
318
            {error, {connection_refused, CD, Res}}
184
319
    end.
185
320
 
186
321
 
243
378
    end.
244
379
 
245
380
disconnect(ConnHandle, DiscoReason)
246
 
  when record(ConnHandle, megaco_conn_handle) ->
 
381
  when is_record(ConnHandle, megaco_conn_handle) ->
247
382
    case megaco_config:disconnect(ConnHandle) of
248
383
        {ok, ConnData, RemoteConnData} ->
249
384
            ControlRef = ConnData#conn_data.monitor_ref,
310
445
            {error, {no_connection, ConnHandle}}
311
446
    end.
312
447
 
 
448
 
313
449
%%----------------------------------------------------------------------
314
450
%% Handle incoming message
315
451
%%----------------------------------------------------------------------
331
467
process_received_message(ReceiveHandle, ControlPid, SendHandle, Bin) ->
332
468
    Flag = process_flag(trap_exit, true),
333
469
    case prepare_message(ReceiveHandle, SendHandle, Bin, ControlPid) of
334
 
        {ok, ConnData, MegaMsg} when record(MegaMsg, 'MegacoMessage') ->
 
470
        {ok, ConnData, MegaMsg} when is_record(MegaMsg, 'MegacoMessage') ->
 
471
            ?rt1(ConnData, "message prepared", [MegaMsg]),
335
472
            Mess = MegaMsg#'MegacoMessage'.mess,
336
473
            case Mess#'Message'.messageBody of
337
474
                {transactions, Transactions} ->
340
477
                    handle_acks(AckList),
341
478
                    case ReqList of
342
479
                        [] ->
 
480
                            ?rt3("no requests"),
343
481
                            ignore;
344
 
                        [Req|Reqs] when ConnData#conn_data.threaded ->
 
482
                        [Req|Reqs] when (ConnData#conn_data.threaded == true) ->
 
483
%                           lists:foreach(
 
484
%                             fun() -> 
 
485
%                                     spawn(?MODULE,handle_request,[R]) 
 
486
%                             end, 
 
487
%                             Reqs),
345
488
                            [spawn(?MODULE,handle_request,[R]) || R <- Reqs],
346
489
                            handle_request(Req);
347
490
                        _ ->
 
491
                            ?rt3("handle requests"),
348
492
                            case handle_requests(ReqList, []) of
349
493
                                [] ->
350
494
                                    ignore;
368
512
    ok.
369
513
 
370
514
prepare_message(RH, SH, Bin, Pid)
371
 
  when record(RH, megaco_receive_handle), pid(Pid) ->
 
515
  when is_record(RH, megaco_receive_handle) and is_pid(Pid) ->
372
516
    ?report_trace(RH, "receive bytes", [{bytes, Bin}]),
373
517
    EncodingMod    = RH#megaco_receive_handle.encoding_mod,
374
518
    EncodingConfig = RH#megaco_receive_handle.encoding_config,
375
519
    ProtVersion    = RH#megaco_receive_handle.protocol_version,
376
520
    case (catch EncodingMod:decode_message(EncodingConfig, ProtVersion, Bin)) of
377
 
        {ok, MegaMsg} when record(MegaMsg, 'MegacoMessage') ->
 
521
        {ok, MegaMsg} when is_record(MegaMsg, 'MegacoMessage') ->
378
522
            ?report_trace(RH, "receive message", [{message, MegaMsg}]),
379
523
            Mess       = MegaMsg#'MegacoMessage'.mess,
380
524
            RemoteMid  = Mess#'Message'.mId,
383
527
            CH         = #megaco_conn_handle{local_mid  = LocalMid,
384
528
                                             remote_mid = RemoteMid},
385
529
            case megaco_config:lookup_local_conn(CH) of
 
530
                %% 
 
531
                %% Message is not of the negotiated version
 
532
                %% 
 
533
 
 
534
                [#conn_data{protocol_version = NegVersion, 
 
535
                            strict_version   = true} = ConnData] 
 
536
                when NegVersion /= Version ->
 
537
                    %% Use already established connection, 
 
538
                    %% but incorrect version
 
539
                    ?rt1(ConnData, "not negotiated version", [Version]),
 
540
                    Error = {error, {not_negotiated_version, 
 
541
                                     NegVersion, Version}}, 
 
542
                    handle_syntax_error_callback(RH, ConnData, 
 
543
                                                 prepare_error(Error));
 
544
 
 
545
 
386
546
                [ConnData] ->
387
547
                    %% Use already established connection
388
 
                    ConnData2 = ConnData#conn_data{send_handle = SH,
 
548
                    ?rt1(ConnData, "use already established connection", []),
 
549
                    ConnData2 = ConnData#conn_data{send_handle      = SH,
389
550
                                                   protocol_version = Version},
390
551
                    check_message_auth(CH, ConnData2, MegaMsg, Bin);
 
552
 
 
553
 
391
554
                [] ->
392
555
                    %% Setup a temporary connection
 
556
                    ?rt3("setup a temporary connection"),
393
557
                    case connect(RH, RemoteMid, SH, Pid) of
394
558
                        {ok, _} ->
395
559
                            do_prepare_message(RH, CH, SH, MegaMsg, Pid, Bin);
406
570
                    end
407
571
            end;
408
572
        Error ->
409
 
            incNumErrors(),
410
 
            ConnData = fake_conn_data(RH, SH, Pid),
 
573
            ?rt2("decode error", [Error]),
 
574
            ConnData = handle_decode_error(Error, 
 
575
                                           RH, SH, Bin, Pid, 
 
576
                                           EncodingMod, 
 
577
                                           EncodingConfig, 
 
578
                                           ProtVersion),
411
579
            handle_syntax_error_callback(RH, ConnData, prepare_error(Error))
412
580
    end;
413
581
prepare_message(RH, SendHandle, _Bin, ControlPid) ->
415
583
    Error    = prepare_error({'EXIT', {bad_receive_handle, RH}}),
416
584
    {verbose_fail, ConnData, Error}.
417
585
 
 
586
 
 
587
handle_decode_error({error, {unsupported_version, _}},
 
588
                    #megaco_receive_handle{local_mid = LocalMid} = RH, SH, 
 
589
                    Bin, Pid,
 
590
                    EM, EC, V) ->
 
591
    case (catch EM:decode_mini_message(EC, V, Bin)) of
 
592
        {ok, #'MegacoMessage'{mess = #'Message'{version = _Ver, mId = RemoteMid}}} ->
 
593
            ?rt2("erroneous message received", [SH, RemoteMid, _Ver]),
 
594
            CH = #megaco_conn_handle{local_mid  = LocalMid,
 
595
                                     remote_mid = RemoteMid},
 
596
            incNumErrors(CH),
 
597
            %% We cannot put the version into conn-data, that will
 
598
            %% make the resulting error message impossible to sent
 
599
            %% (unsupported version)
 
600
            case megaco_config:lookup_local_conn(CH) of
 
601
                [ConnData] ->
 
602
                    ?rt3("known to us"),
 
603
                    ConnData#conn_data{send_handle = SH};
 
604
                [] ->
 
605
                    ?rt3("unknown to us"),
 
606
                    ConnData = fake_conn_data(RH, SH, Pid),
 
607
                    ConnData#conn_data{conn_handle = CH}
 
608
            end;
 
609
 
 
610
        _ ->
 
611
            ?rt2("erroneous message received", [SH]),
 
612
            incNumErrors(),
 
613
            fake_conn_data(RH, SH, Pid)
 
614
    end;
 
615
 
 
616
handle_decode_error(_,
 
617
                    #megaco_receive_handle{local_mid = LocalMid} = RH, SH, 
 
618
                    Bin, Pid,
 
619
                    EM, EC, V) ->
 
620
    case (catch EM:decode_mini_message(EC, V, Bin)) of
 
621
        {ok, #'MegacoMessage'{mess = #'Message'{version = Ver, mId = RemoteMid}}} ->
 
622
            ?rt2("erroneous message received", [SH, Ver, RemoteMid]),
 
623
            CH = #megaco_conn_handle{local_mid  = LocalMid,
 
624
                                     remote_mid = RemoteMid},
 
625
            incNumErrors(CH),
 
626
            case megaco_config:lookup_local_conn(CH) of
 
627
                [ConnData] ->
 
628
                    ?rt3("known to us"),
 
629
                    ConnData#conn_data{send_handle      = SH,
 
630
                                       protocol_version = Ver};
 
631
                [] ->
 
632
                    ?rt3("unknown to us"),
 
633
                    ConnData = fake_conn_data(RH, SH, Pid),
 
634
                    ConnData#conn_data{conn_handle      = CH,
 
635
                                       protocol_version = Ver}
 
636
            end;
 
637
 
 
638
        _ ->
 
639
            ?rt2("erroneous message received", [SH]),
 
640
            incNumErrors(),
 
641
            fake_conn_data(RH, SH, Pid)
 
642
    end.
 
643
 
 
644
 
418
645
do_prepare_message(RH, CH, SendHandle, MegaMsg, ControlPid, Bin) ->
419
646
    case megaco_config:lookup_local_conn(CH) of
420
647
        [ConnData] ->
455
682
handle_syntax_error_callback(ReceiveHandle, ConnData, PrepError) ->
456
683
    {Code, Reason, Error} = PrepError,
457
684
    ErrorDesc = #'ErrorDescriptor'{errorCode = Code, errorText = Reason},
458
 
    Version   = ConnData#conn_data.protocol_version,
 
685
    Version   = 
 
686
        case Error of
 
687
            {error, {unsupported_version, UV}} ->
 
688
                UV;
 
689
            _ ->
 
690
                ConnData#conn_data.protocol_version
 
691
        end,
459
692
    UserMod   = ConnData#conn_data.user_mod,
460
693
    UserArgs  = ConnData#conn_data.user_args,
461
694
    ?report_trace(ReceiveHandle, "callback: syntax error", [ErrorDesc, Error]),
469
702
        no_reply ->
470
703
            {silent_fail, ConnData, PrepError};
471
704
        {no_reply,#'ErrorDescriptor'{errorCode=Code2,errorText=Reason2}} ->
472
 
            {silent_fail, ConnData, {Code2,Reason2,Error}}; %%% OTP-XXXX
473
 
        _Bad ->
 
705
            {silent_fail, ConnData, {Code2,Reason2,Error}}; %%% OTP-????
 
706
        _ ->
 
707
            warning_msg("syntax error callback failed: ~w", [Res]),
474
708
            {verbose_fail, ConnData, PrepError}
475
709
    end.
476
710
 
477
 
fake_conn_data(CH) when record(CH, megaco_conn_handle) ->
478
 
    case catch megaco_config:conn_info(CH, receive_handle) of
479
 
        RH when record(RH, megaco_receive_handle) ->
 
711
fake_conn_data(CH) when is_record(CH, megaco_conn_handle) ->
 
712
    case (catch megaco_config:conn_info(CH, receive_handle)) of
 
713
        RH when is_record(RH, megaco_receive_handle) ->
480
714
            RemoteMid = CH#megaco_conn_handle.remote_mid,
481
715
            ConnData = 
482
716
                fake_conn_data(RH, RemoteMid, no_send_handle, no_control_pid),
494
728
                               encoding_mod       = no_encoding_mod,
495
729
                               encoding_config    = no_encoding_config,
496
730
                               reply_action       = undefined,
497
 
                               orig_pending_limit = infinity};
 
731
                               sent_pending_limit = infinity,
 
732
                               recv_pending_limit = infinity};
498
733
                RH ->
499
734
                    ConnData = 
500
735
                        fake_conn_data(RH, no_send_handle, no_control_pid),
532
767
                       encoding_mod       = EncodingMod,
533
768
                       encoding_config    = EncodingConfig,
534
769
                       reply_action       = undefined,
535
 
                       orig_pending_limit = infinity};
 
770
                       sent_pending_limit = infinity,
 
771
                       recv_pending_limit = infinity};
536
772
        ConnData ->
537
773
            ConnData
538
774
    end.
539
775
 
540
776
prepare_error(Error) ->
541
777
    case Error of
542
 
        {error, ED} when record(ED, 'ErrorDescriptor') ->
 
778
        {error, ED} when is_record(ED, 'ErrorDescriptor') ->
543
779
            Code   = ED#'ErrorDescriptor'.errorCode,
544
780
            Reason = ED#'ErrorDescriptor'.errorText,
545
781
            {Code, Reason, Error};
546
 
        {error, [{reason, {bad_token, _}, Line}]} when integer(Line) ->
 
782
        {error, [{reason, {bad_token, _}, Line}]} when is_integer(Line) ->
547
783
            Reason = lists:concat(["Illegal token on line ", Line]),
548
784
            Code = ?megaco_bad_request,
549
785
            {Code, Reason, Error};
550
 
        {error, [{reason, {Line, _, _}} | _]} when integer(Line) ->
 
786
        {error, [{reason, {Line, _, _}} | _]} when is_integer(Line) ->
551
787
            Reason = lists:concat(["Syntax error on line ", Line]),
552
788
            Code = ?megaco_bad_request,
553
789
            {Code, Reason, Error};
554
 
        {error, {connection_refused, ED}} when record(ED,'ErrorDescriptor') ->
 
790
        {error, {connection_refused, ED}} when is_record(ED,'ErrorDescriptor') ->
555
791
            Code   = ED#'ErrorDescriptor'.errorCode,
556
792
            Reason = ED#'ErrorDescriptor'.errorText,
557
793
            {Code, Reason, Error};
559
795
            Reason = "Connection refused by user",
560
796
            Code = ?megaco_unauthorized,
561
797
            {Code, Reason, Error};
 
798
        {error, {unsupported_version, V}} ->
 
799
            Reason = 
 
800
                lists:flatten(io_lib:format("Unsupported version: ~w",[V])),
 
801
            Code = ?megaco_version_not_supported, 
 
802
            {Code, Reason, Error};
 
803
        {error, {not_negotiated_version, NegV, MsgV}} ->
 
804
            Reason = 
 
805
                lists:flatten(
 
806
                  io_lib:format("Not negotiated version: ~w [negotiated ~w]",
 
807
                                [MsgV, NegV])),
 
808
            Code = ?megaco_version_not_supported, 
 
809
            {Code, Reason, Error};
562
810
        {error, _} ->
563
811
            Reason = "Syntax error",
564
812
            Code = ?megaco_bad_request,
565
813
            {Code, Reason, Error};
566
 
        {ok, MegaMsg} when record (MegaMsg, 'MegacoMessage') ->
 
814
        {ok, MegaMsg} when is_record (MegaMsg, 'MegacoMessage') ->
567
815
            Reason = "MID does not match config",
568
816
            Code = ?megaco_incorrect_identifier,
569
817
            {Code, Reason, Error};
582
830
    %% function has not yet returned before the eager MG
583
831
    %% re-sends its initial service change message.
584
832
    case Trans of
585
 
        {transactionRequest, T} when record(T, 'TransactionRequest') ->
 
833
        {transactionRequest, T} when is_record(T, 'TransactionRequest') ->
586
834
            
587
835
            Serial = T#'TransactionRequest'.transactionId,
588
836
            ConnData2 = ConnData#conn_data{serial = Serial},
594
842
            %% 
595
843
            %% ------------------------------------------
596
844
 
597
 
            Limit = ConnData#conn_data.orig_pending_limit,
 
845
            Limit = ConnData#conn_data.sent_pending_limit,
598
846
            TransId = to_remote_trans_id(ConnData2),
599
 
            case check_and_maybe_incr_pending_limit(Limit, TransId) of
 
847
            case check_and_maybe_incr_pending_limit(Limit, sent, TransId) of
600
848
                ok ->
601
849
                    send_pending(ConnData2);
602
850
                error ->
615
863
            prepare_trans(ConnData, Rest, AckList, ReqList)
616
864
    end;
617
865
prepare_trans(ConnData, [Trans | Rest], AckList, ReqList) ->
 
866
    ?rt1(ConnData, "prepare trans", [Trans]),
618
867
    case Trans of
619
868
        {transactionRequest, #'TransactionRequest'{transactionId = asn1_NOVALUE}} ->
620
869
            ConnData2 = ConnData#conn_data{serial = 0},
622
871
            Reason = "Syntax error in message: transaction id missing",
623
872
            send_trans_error(ConnData2, Code, Reason),
624
873
            prepare_trans(ConnData2, Rest, AckList, ReqList);
625
 
        {transactionRequest, T} when record(T, 'TransactionRequest') ->
 
874
        {transactionRequest, T} when is_record(T, 'TransactionRequest') ->
626
875
            Serial = T#'TransactionRequest'.transactionId,
627
876
            ConnData2 = ConnData#conn_data{serial = Serial},
628
877
            prepare_request(ConnData2, T, Rest, AckList, ReqList);
629
 
        {transactionPending, T} when record(T, 'TransactionPending') ->
 
878
        {transactionPending, T} when is_record(T, 'TransactionPending') ->
630
879
            Serial = T#'TransactionPending'.transactionId,
631
880
            ConnData2 = ConnData#conn_data{serial = Serial},
632
881
            handle_pending(ConnData2, T),
633
882
            prepare_trans(ConnData2, Rest, AckList, ReqList);
634
 
        {transactionReply, T} when record(T, 'TransactionReply') ->
 
883
        {transactionReply, T} when is_record(T, 'TransactionReply') ->
635
884
            Serial = T#'TransactionReply'.transactionId,
636
885
            ConnData2 = ConnData#conn_data{serial = Serial},
637
886
            handle_reply(ConnData2, T),
638
887
            prepare_trans(ConnData2, Rest, AckList, ReqList);
639
 
        {transactionResponseAck, List} when list(List) ->
 
888
        {transactionResponseAck, List} when is_list(List) ->
640
889
            prepare_ack(ConnData, List, Rest, AckList, ReqList)
641
890
 
642
891
    end;
644
893
    ?SIM({AckList, ReqList}, prepare_trans_done).
645
894
 
646
895
prepare_request(ConnData, T, Rest, AckList, ReqList) ->
647
 
%     d("prepare_request -> entry with"
648
 
%       "~n   T: ~p", [T]),
 
896
    ?rt2("prepare request", [T]),
649
897
    LocalMid = (ConnData#conn_data.conn_handle)#megaco_conn_handle.local_mid,
650
898
    TransId = to_remote_trans_id(ConnData),
 
899
    ?rt2("prepare request", [LocalMid, TransId]),
651
900
    case megaco_monitor:lookup_reply(TransId) of
652
901
        [] ->
 
902
            ?rt3("brand new request"),
 
903
 
653
904
            %% Brand new request
654
905
 
655
906
            %% Check pending limit:
663
914
            %% monitor_ref == undefined_monitor_ref).
664
915
            %% 
665
916
 
666
 
            #conn_data{pending_timer    = InitTimer,
 
917
            #conn_data{send_handle      = SendHandle,
 
918
                       pending_timer    = InitTimer,
667
919
                       protocol_version = Version} = ConnData,
668
920
            {WaitFor, CurrTimer} = init_timer(InitTimer),
669
921
            M = ?MODULE,
670
922
            F = pending_timeout,
671
923
            A = [ConnData, TransId, CurrTimer],     
672
924
            PendingRef = megaco_monitor:apply_after(M, F, A, WaitFor),
673
 
            Rep = #reply{% state             = eval_request,
 
925
            Rep = #reply{send_handle       = SendHandle,
674
926
                         trans_id          = TransId,
675
927
                         local_mid         = LocalMid,
676
928
                         pending_timer_ref = PendingRef,
683
935
        [#reply{state             = State, 
684
936
                handler           = Pid,
685
937
                pending_timer_ref = Ref} = Rep] 
686
 
        when State == prepare; State == eval_request ->
 
938
        when (State == prepare) or (State == eval_request) ->
 
939
 
 
940
            ?rt2("request resend", [State, Pid, Ref]),
687
941
 
688
942
            %% Pending limit:
689
943
            %% We are still preparing/evaluating the request
693
947
            %% the pending timer, but that we cannot do).
694
948
            %% Don't care about Msg and Rep version diff
695
949
 
696
 
            #conn_data{orig_pending_limit = Limit} = ConnData,
 
950
            %% ?report_trace(ignore, "still preparing/evaluating request", []),
 
951
 
 
952
            #conn_data{sent_pending_limit = Limit} = ConnData,
697
953
            
698
 
            case check_and_maybe_incr_pending_limit(Limit, TransId) of
 
954
            case check_and_maybe_incr_pending_limit(Limit, sent, TransId) of
699
955
                ok ->
700
956
 
701
957
                    %% ------------------------------------------
729
985
 
730
986
                    %% 
731
987
                    %% State == eval_request:
732
 
                    %%   This means that the reply timer has been 
733
 
                    %%   started. The reply record will be deleted
734
 
                    %%   eventually by the reply timer, so there is 
735
 
                    %%   no need to do it here.
 
988
                    %%   This means that the request is currently beeing 
 
989
                    %%   evaluated by the user, and the reply timer has 
 
990
                    %%   not yet been started. 
 
991
                    %%   Either:
 
992
                    %%   a) The "other side" will resend (which will 
 
993
                    %%      trigger a pending message send) until we pass the 
 
994
                    %%      pending limit 
 
995
                    %%   b) We will send pending messages (when the pending 
 
996
                    %%      timer expire) until we pass the pending limit.
 
997
                    %%   In any event, we cannot delete the reply record
 
998
                    %%   or the pending counter in this case. Is there
 
999
                    %%   a risk we accumulate aborted reply records?
736
1000
                    %% 
737
1001
                    %% State == prepare:
738
 
                    %%   The reply timer has not yet been started,
739
 
                    %%   so we must do the cleanup here.
 
1002
                    %%   The user does not know about this request
 
1003
                    %%   so we can safely perform cleanup.
740
1004
                    %% 
741
 
                    ?report_pending_limit_exceeded(ConnData),
742
1005
                    megaco_monitor:cancel_apply_after(Ref),
743
1006
                    send_pending_limit_error(ConnData),
744
1007
                    if 
745
1008
                        State == eval_request ->
 
1009
                            %% 
 
1010
                            %% What if the user never replies?
 
1011
                            %% In that case we will have a record
 
1012
                            %% (and counters) that is never cleaned up...
746
1013
                            Rep2 = Rep#reply{state             = aborted,
747
1014
                                             pending_timer_ref = undefined},
748
1015
                            megaco_monitor:insert_reply(Rep2),
749
1016
                            handle_request_abort_callback(ConnData, 
750
 
                                                          TransId, 
751
 
                                                          Pid);
 
1017
                                                          TransId, Pid);
752
1018
                        true ->
753
1019
                            %% Since the user does not know about
754
 
                            %% this call yet, should we inform?
755
 
                            megaco_monitor:delete_reply(TransId),
 
1020
                            %% this call yet, it is safe to cleanup.
 
1021
                            %% Should we inform?
 
1022
                            Rep2 = Rep#reply{state = aborted},
 
1023
                            cancel_reply(ConnData, Rep2, aborted),
756
1024
                            ok
757
1025
                    end,
758
1026
                    prepare_trans(ConnData, Rest, AckList, ReqList);
764
1032
                    %% 
765
1033
                    %%   Pending limit already exceeded
766
1034
                    %% 
767
 
                    %%    ( can we really get here ? )
 
1035
                    %%   Cleanup, just to make sure:
 
1036
                    %%     reply record & pending counter
768
1037
                    %% 
769
1038
                    %% -------------------------------------------
 
1039
 
 
1040
                    Rep2 = Rep#reply{state = aborted},
 
1041
                    cancel_reply(ConnData, Rep2, aborted),
770
1042
                    prepare_trans(ConnData, Rest, AckList, ReqList)
771
1043
 
772
1044
            end;
773
1045
 
774
 
        [#reply{state = waiting_for_ack, bytes = Bin, version = Version}] ->
 
1046
        [#reply{state   = waiting_for_ack, 
 
1047
                bytes   = Bin, 
 
1048
                version = Version} = Rep] ->
 
1049
            ?rt3("request resend when waiting for ack"),
775
1050
 
776
1051
            %% We have already sent a reply, but the receiver
777
1052
            %% has obviously not got it. Resend the reply but
780
1055
            ?report_trace(ConnData2, 
781
1056
                          "re-send trans reply", [T | {bytes, Bin}]),
782
1057
            case megaco_messenger_misc:send_message(ConnData2, Bin) of
783
 
                {ok, _} ->
784
 
                    prepare_trans(ConnData2, Rest, AckList, ReqList);
785
 
                {error, Reason} ->
786
 
                    ?report_important(ConnData2, 
787
 
                                      "<ERROR> re-send trans reply failed",
788
 
                                      [{bytes, Bin}, {error, Reason}]),
789
 
                    error_msg("re-send transaction reply failed: ~w", 
790
 
                              [Reason]),
791
 
                    prepare_trans(ConnData2, Rest, AckList, ReqList)
792
 
            end;
793
 
 
794
 
        [#reply{state = aborted}] ->
 
1058
                ok ->
 
1059
                    ok;
 
1060
                {ok, _} ->
 
1061
                    ok;
 
1062
                {error, Reason} ->
 
1063
                    %% Pass it on to the user (via handle_ack)
 
1064
                    cancel_reply(ConnData2, Rep, Reason)
 
1065
            end,
 
1066
            prepare_trans(ConnData2, Rest, AckList, ReqList);
 
1067
 
 
1068
        [#reply{state = aborted} = Rep] ->
 
1069
            ?rt3("request resend when already in aborted state"),
 
1070
 
795
1071
            %% OTP-4956:
796
1072
            %% Already aborted so ignore.
797
 
            %% This furtermore means that the abnoxious user at the
 
1073
            %% This furthermore means that the abnoxious user at the
798
1074
            %% other end has already been informed (pending-limit
799
 
            %% passed), but keeps sending...
800
 
            %% d("prepare_request -> aborted"),
 
1075
            %% passed => error descriptor sent), but keeps sending...
 
1076
            %% 
 
1077
            %% Shall we perform a cleanup?
 
1078
            cancel_reply(ConnData, Rep, aborted),
801
1079
            prepare_trans(ConnData, Rest, AckList, ReqList)
802
1080
        end.
803
1081
 
804
1082
prepare_ack(ConnData, [TA | T], Rest, AckList, ReqList) 
805
 
  when record(TA, 'TransactionAck') ->
 
1083
  when is_record(TA, 'TransactionAck') ->
806
1084
    First     = TA#'TransactionAck'.firstAck,
807
1085
    Last      = TA#'TransactionAck'.lastAck,
808
1086
    TA2       = TA#'TransactionAck'{lastAck = asn1_NOVALUE},
843
1121
    end.
844
1122
 
845
1123
 
846
 
check_pending_limit(infinity, _) ->
 
1124
check_and_maybe_create_pending_limit(infinity, _, _) ->
847
1125
    ok;
848
 
check_pending_limit(Limit, TransId) ->
849
 
    case (catch megaco_config:get_pending_counter(TransId)) of
 
1126
check_and_maybe_create_pending_limit(Limit, Direction, TransId) ->
 
1127
    case (catch megaco_config:get_pending_counter(Direction, TransId)) of
850
1128
        {'EXIT', _} ->
851
1129
            %% Has not been created yet (connect).
852
 
            megaco_config:cre_pending_counter(TransId),
 
1130
            megaco_config:cre_pending_counter(Direction, TransId, 0),
853
1131
            ok;
854
1132
        Val when Val =< Limit ->
855
1133
            %% Since we have no intention to increment here, it
859
1137
            aborted
860
1138
    end.
861
1139
 
862
 
 
863
 
check_and_maybe_incr_pending_limit(infinity, _) ->
 
1140
check_pending_limit(infinity, _, _) ->
 
1141
    {ok, 0};
 
1142
check_pending_limit(Limit, Direction, TransId) ->
 
1143
    ?rt2("check pending limit", [Direction, Limit, TransId]),
 
1144
    case (catch megaco_config:get_pending_counter(Direction, TransId)) of
 
1145
        {'EXIT', _} ->
 
1146
            %% This function is only called when we "know" the 
 
1147
            %% counter to exist. So, the only reason that this 
 
1148
            %% would happen is of the counter has been removed.
 
1149
            %% This only happen if the pending limit has been 
 
1150
            %% reached. In any case, this is basically the same 
 
1151
            %% as aborted!
 
1152
            ?rt2("check pending limit - exit", []),
 
1153
            aborted;
 
1154
        Val when Val =< Limit ->
 
1155
            %% Since we have no intention to increment here, it
 
1156
            %% is ok to be _at_ the limit
 
1157
            ?rt2("check pending limit - ok", [Val]),
 
1158
            {ok, Val};
 
1159
        _Val ->
 
1160
            ?rt2("check pending limit - aborted", [_Val]),
 
1161
            aborted
 
1162
    end.
 
1163
 
 
1164
 
 
1165
check_and_maybe_incr_pending_limit(infinity, _, _) ->
864
1166
    ok;
865
 
check_and_maybe_incr_pending_limit(Limit, TransId) ->
 
1167
check_and_maybe_incr_pending_limit(Limit, Direction, TransId) ->
866
1168
    %% 
867
1169
    %% We need this kind of test to detect when we _pass_ the limit
868
1170
    %% 
869
 
    case (catch megaco_config:get_pending_counter(TransId)) of
 
1171
    ?rt2("check and maybe incr pending limit", [Direction, Limit, TransId]),
 
1172
    case (catch megaco_config:get_pending_counter(Direction, TransId)) of
870
1173
        {'EXIT', _} ->
871
1174
            %% Has not been created yet (connect).
872
 
            megaco_config:cre_pending_counter(TransId),
 
1175
            megaco_config:cre_pending_counter(Direction, TransId, 1),
873
1176
            ok;
874
1177
        Val when Val > Limit ->
 
1178
            ?rt2("check and maybe incr - aborted", [Direction, Val, Limit]),
875
1179
            aborted;      % Already passed the limit
876
1180
        Val ->
877
 
            megaco_config:incr_pending_counter(TransId),
 
1181
            ?rt2("check and maybe incr - incr", [Direction, Val, Limit]),
 
1182
            megaco_config:incr_pending_counter(Direction, TransId),
878
1183
            if 
879
1184
                Val < Limit ->
880
1185
                    ok;   % Still within the limit
881
1186
                true ->
 
1187
                    ?rt2("check and maybe incr - error", 
 
1188
                         [Direction, Val, Limit]),
882
1189
                    error % Passed the limit
883
1190
            end
884
1191
    end.
905
1212
    %% has not been aborted. I.e. exceeded the pending 
906
1213
    %% limit, so go check it...
907
1214
 
908
 
    #conn_data{orig_pending_limit = Limit} = ConnData,
 
1215
    #conn_data{sent_pending_limit = Limit} = ConnData,
909
1216
 
910
 
    case check_pending_limit(Limit, TransId) of
 
1217
    case check_and_maybe_create_pending_limit(Limit, sent, TransId) of
911
1218
        ok ->
912
1219
            %% Ok so far, now update state
913
1220
            case megaco_monitor:lookup_reply(TransId) of
914
 
                [Rep] when record(Rep, reply) ->
 
1221
                [Rep] when is_record(Rep, reply) ->
915
1222
                    Rep2 = Rep#reply{state = eval_request},
916
1223
                    megaco_monitor:insert_reply(Rep2),
917
1224
                    
918
1225
                    Actions = T#'TransactionRequest'.actions,
919
1226
                    {AckAction, SendReply} = 
920
1227
                        handle_request_callback(ConnData, TransId, Actions, T),
921
 
            
 
1228
 
922
1229
                    %% Next step, while we where in the callback function,
923
1230
                    %% the pending limit could have been exceeded, so check
924
1231
                    %% it again...
925
1232
                    do_handle_request(AckAction, SendReply, 
926
1233
                                      ConnData, TransId);
 
1234
 
927
1235
                _ ->
928
1236
                    %% Ugh?
929
1237
                    ignore
934
1242
            %% Already exceeded the limit
935
1243
            %% The user does not yet know about this request, so
936
1244
            %% don't bother telling that it has been aborted...
937
 
            %% 
 
1245
            %% Furthermore, the reply timer has not been started,
 
1246
            %% so do the cleanup now
 
1247
            ?rt1(ConnData, "pending limit already passed", [TransId]),
 
1248
            case megaco_monitor:lookup_reply(TransId) of
 
1249
                [Rep] ->
 
1250
                    cancel_reply(ConnData, Rep, aborted);
 
1251
                _ ->
 
1252
                    ok
 
1253
            end,
938
1254
            ignore
939
1255
    end.
940
1256
 
 
1257
do_handle_request(_, ignore, _ConnData, _TransId) ->
 
1258
    ?rt1(_ConnData, "ignore: don't reply", [_TransId]),
 
1259
    ignore;
 
1260
do_handle_request(_, ignore_trans_request, ConnData, TransId) ->
 
1261
    ?rt1(ConnData, "ignore trans request: don't reply", [TransId]),
 
1262
    case megaco_monitor:lookup_reply(TransId) of
 
1263
        [#reply{} = Rep] ->
 
1264
            cancel_reply(ConnData, Rep, ignore);
 
1265
        _ ->
 
1266
            ignore
 
1267
    end;
941
1268
do_handle_request({pending, _RequestData}, {aborted, ignore}, _, _) ->
 
1269
    ?rt2("handle request: pending - aborted - ignore => don't reply", []),
942
1270
    ignore;
943
1271
do_handle_request({pending, _RequestData}, {aborted, _SendReply}, _, _) ->
 
1272
    ?rt2("handle request: pending - aborted => don't reply", []),
944
1273
    ignore;
945
1274
do_handle_request({pending, RequestData}, _SendReply, _ConnData, _) ->
 
1275
    ?rt2("handle request: pending", [RequestData]),
946
1276
    {pending, RequestData};
947
1277
do_handle_request(AckAction, {ok, Bin}, ConnData, TransId) ->
 
1278
    ?rt1(ConnData, "handle request - ok", [AckAction, TransId]),
948
1279
    case megaco_monitor:lookup_reply(TransId) of
949
1280
        [#reply{pending_timer_ref = PendingRef} = Rep] ->
950
1281
 
 
1282
%%          d("do_handle_request -> found reply record:"
 
1283
%%            "~n   Rep: ~p", [Rep]),
 
1284
            
951
1285
            #conn_data{reply_timer = InitTimer,
952
1286
                       conn_handle = ConnHandle} = ConnData,
953
1287
 
955
1289
            %%   - Cancel the pending timer, if running
956
1290
            %%   - Delete the pending counter
957
1291
            %% 
958
 
            
 
1292
 
959
1293
            megaco_monitor:cancel_apply_after(PendingRef),
960
 
            megaco_config:del_pending_counter(TransId),
 
1294
            megaco_config:del_pending_counter(sent, TransId),
961
1295
 
962
1296
            Method = timer_method(AckAction),
963
1297
            {WaitFor, CurrTimer} = init_timer(InitTimer),
968
1302
            Ref = megaco_monitor:apply_after(Method, M, F, A, 
969
1303
                                             WaitFor),
970
1304
            Rep2 = Rep#reply{pending_timer_ref = undefined,
971
 
                             handler    = undefined,
972
 
                             bytes      = OptBin,
973
 
                             state      = waiting_for_ack,
974
 
                             timer_ref  = Ref,
975
 
                             ack_action = AckAction},
 
1305
                             handler           = undefined,
 
1306
                             bytes             = OptBin,
 
1307
                             state             = waiting_for_ack,
 
1308
                             timer_ref         = Ref,
 
1309
                             ack_action        = AckAction},
976
1310
            megaco_monitor:insert_reply(Rep2), % Timing problem?
 
1311
 
 
1312
%%          d("do_handle_request -> "
 
1313
%%            "~n   Rep2: ~p", [Rep2]),
 
1314
 
977
1315
            ignore;
978
1316
        _ ->
979
1317
            %% Been removed already?
980
1318
            ignore
981
1319
    end;
982
 
do_handle_request(_, {error, Reason}, ConnData, TransId) ->
983
 
    ?report_trace(ConnData, "send trans reply", [TransId, {error, Reason}]),
 
1320
do_handle_request(_, {error, aborted}, ConnData, TransId) ->
 
1321
    ?report_trace(ConnData, "aborted during our absence", [TransId]),
 
1322
    case megaco_monitor:lookup_reply(TransId) of
 
1323
        [Rep] ->
 
1324
            cancel_reply(ConnData, Rep, aborted);
 
1325
        _ ->
 
1326
            ok
 
1327
    end,
 
1328
    ignore;
 
1329
do_handle_request(AckAction, {error, Reason}, ConnData, TransId) ->
 
1330
    ?report_trace(ConnData, "error", [TransId, Reason]),
 
1331
    case megaco_monitor:lookup_reply(TransId) of
 
1332
        [Rep] ->
 
1333
            Rep2 = Rep#reply{state      = waiting_for_ack,
 
1334
                             ack_action = AckAction},
 
1335
            cancel_reply(ConnData, Rep2, Reason);
 
1336
        _ ->
 
1337
            ok
 
1338
    end,
 
1339
    ignore;
 
1340
do_handle_request(AckAction, SendReply, ConnData, TransId) ->
 
1341
    ?report_trace(ConnData, "unknown send trans reply result", 
 
1342
                  [TransId, AckAction, SendReply]),
984
1343
    ignore.
985
1344
    
986
1345
 
987
1346
handle_requests([{ConnData, TransId, T} | Rest], Pending) ->
 
1347
    ?rt2("handle requests", [TransId]),
988
1348
    case handle_request(ConnData, TransId, T) of
989
1349
        {pending, RequestData} ->
990
1350
            handle_requests(Rest, [{ConnData,TransId,RequestData} | Pending]);
992
1352
            handle_requests(Rest, Pending)
993
1353
    end;
994
1354
handle_requests([], Pending) ->
 
1355
    ?rt2("handle requests - done", [Pending]),
995
1356
    Pending.
996
1357
 
997
 
%%opt_garb_binary(timeout, Bin) -> garb_binary; % Need msg at restart of timer
998
 
opt_garb_binary(_Timer, Bin)   -> Bin.
 
1358
%% opt_garb_binary(timeout, _Bin) -> garb_binary; % Need msg at restart of timer
 
1359
opt_garb_binary(_Timer,   Bin) -> Bin.
999
1360
 
1000
1361
timer_method(discard_ack) ->
1001
1362
    apply_method;
1005
1366
 
1006
1367
handle_long_request({ConnData, TransId, RequestData}) ->
1007
1368
 
 
1369
    ?rt2("handle long request", [TransId, RequestData]),
 
1370
 
1008
1371
    %% Pending limit:
1009
1372
    %% We need to check the pending limit, in case it was
1010
1373
    %% exceeded before we got this far...
1011
 
 
1012
 
    #conn_data{orig_pending_limit = Limit} = ConnData,
1013
 
 
1014
 
    case check_pending_limit(Limit, TransId) of
1015
 
        ok ->
 
1374
    %% We dont need to be able to create the counter here,
 
1375
    %% since that was done in the handle_request function.
 
1376
 
 
1377
    #conn_data{sent_pending_limit = Limit} = ConnData,
 
1378
 
 
1379
    case check_pending_limit(Limit, sent, TransId) of
 
1380
        {ok, _} ->
1016
1381
            handle_long_request(ConnData, TransId, RequestData);
1017
 
        aborted ->
 
1382
        _ ->
1018
1383
            %% Already exceeded the limit
1019
1384
            ignore
1020
1385
    end.
1024
1389
                  [TransId, {request_data, RequestData}]),
1025
1390
    
1026
1391
    case megaco_monitor:lookup_reply(TransId) of
1027
 
        [Rep] when record(Rep, reply) ->
 
1392
        [Rep] when is_record(Rep, reply) ->
1028
1393
            %% Update (possibly) new handler
1029
1394
            megaco_monitor:insert_reply(Rep#reply{handler = self()}),
1030
1395
            {AckAction, Res} = 
1038
1403
 
1039
1404
do_handle_long_request(AckAction, {ok, Bin}, ConnData, TransId) ->
1040
1405
    case megaco_monitor:lookup_reply(TransId) of
1041
 
        [Rep] when record(Rep, reply) ->
 
1406
        [Rep] when is_record(Rep, reply) ->
1042
1407
            Method = timer_method(AckAction),
1043
1408
            InitTimer = ConnData#conn_data.reply_timer,
1044
1409
            {WaitFor, CurrTimer} = init_timer(InitTimer),
1073
1438
    Res = (catch apply(UserMod, handle_trans_request_abort, [ConnHandle, Version, Serial, Pid | UserArgs])),
1074
1439
    ?report_debug(ConnData, "return: trans request aborted", 
1075
1440
                  [TransId, {return, Res}]),
1076
 
    ok.
 
1441
    case Res of
 
1442
        ok ->
 
1443
            ok;
 
1444
        _ ->
 
1445
            warning_msg("transaction request abort callback failed: ~w", 
 
1446
                        [Res]),
 
1447
            ok
 
1448
    end.
1077
1449
 
1078
1450
handle_request_callback(ConnData, TransId, Actions, T) ->
1079
1451
    ?report_trace(ConnData, "callback: trans request", [T]),
1084
1456
    Res = (catch apply(UserMod, handle_trans_request, [ConnHandle, Version, Actions | UserArgs])),
1085
1457
    ?report_debug(ConnData, "return: trans request", [T, {return, Res}]),
1086
1458
    case Res of
1087
 
        ignore ->
 
1459
        ignore ->  %% NOTE: Only used for testing!!
1088
1460
            {discard_ack, ignore};
1089
 
        
1090
 
        {discard_ack, Replies} when list(Replies) ->
1091
 
            Reply = {actionReplies, Replies},
1092
 
            SendReply = 
1093
 
                maybe_send_reply(ConnData, TransId, Reply, asn1_NOVALUE),
1094
 
            {discard_ack, SendReply};
1095
 
        {discard_ack, Error} when record(Error, 'ErrorDescriptor') ->
1096
 
            Reply = {transactionError, Error},
1097
 
            SendReply = 
1098
 
                maybe_send_reply(ConnData, TransId, Reply, asn1_NOVALUE),
1099
 
            {discard_ack, SendReply};
1100
 
        {{handle_ack, AckData}, Replies} when list(Replies) ->
1101
 
            Reply = {actionReplies, Replies},
1102
 
            SendReply = 
1103
 
                maybe_send_reply(ConnData, TransId, Reply, 'NULL'),
 
1461
 
 
1462
        ignore_trans_request -> 
 
1463
            {discard_ack, ignore_trans_request};
 
1464
 
 
1465
        {discard_ack, Replies} when is_list(Replies) ->
 
1466
            Reply     = {actionReplies, Replies},
 
1467
            SendReply = maybe_send_reply(ConnData, TransId, Reply, 
 
1468
                                         [], asn1_NOVALUE),
 
1469
            {discard_ack, SendReply};
 
1470
        {discard_ack, Error} when is_record(Error, 'ErrorDescriptor') ->
 
1471
            Reply     = {transactionError, Error},
 
1472
            SendReply = maybe_send_reply(ConnData, TransId, Reply, 
 
1473
                                         [], asn1_NOVALUE),
 
1474
            {discard_ack, SendReply};
 
1475
        {discard_ack, Replies, SendOpts} when is_list(Replies) and 
 
1476
                                              is_list(SendOpts) ->
 
1477
            Reply     = {actionReplies, Replies},
 
1478
            SendReply = maybe_send_reply(ConnData, TransId, Reply, 
 
1479
                                         SendOpts, asn1_NOVALUE),
 
1480
            {discard_ack, SendReply};
 
1481
        {discard_ack, Error, SendOpts} 
 
1482
        when is_record(Error, 'ErrorDescriptor') and 
 
1483
             is_list(SendOpts) ->
 
1484
            Reply     = {transactionError, Error},
 
1485
            SendReply = maybe_send_reply(ConnData, TransId, Reply, 
 
1486
                                         SendOpts, asn1_NOVALUE),
 
1487
            {discard_ack, SendReply};
 
1488
 
 
1489
        {{handle_pending_ack, AckData}, Replies} when is_list(Replies) ->
 
1490
            Reply     = {actionReplies, Replies},
 
1491
            SendReply = maybe_send_reply(ConnData, TransId, Reply, 
 
1492
                                         [], when_pending_sent),
 
1493
            {{handle_ack, AckData}, SendReply};
 
1494
        {{handle_pending_ack, AckData}, Error} 
 
1495
        when is_record(Error, 'ErrorDescriptor') ->
 
1496
            Reply     = {transactionError, Error},
 
1497
            SendReply = maybe_send_reply(ConnData, TransId, Reply, 
 
1498
                                         [], when_pending_sent),
 
1499
            {{handle_ack, AckData}, SendReply};
 
1500
        {{handle_pending_ack, AckData}, Replies, SendOpts} 
 
1501
        when is_list(Replies) and 
 
1502
             is_list(SendOpts) ->
 
1503
            Reply     = {actionReplies, Replies},
 
1504
            SendReply = maybe_send_reply(ConnData, TransId, Reply, 
 
1505
                                         SendOpts, when_pending_sent),
 
1506
            {{handle_ack, AckData}, SendReply};
 
1507
        {{handle_pending_ack, AckData}, Error, SendOpts} 
 
1508
        when is_record(Error, 'ErrorDescriptor') and 
 
1509
             is_list(SendOpts) ->
 
1510
            Reply     = {transactionError, Error},
 
1511
            SendReply = maybe_send_reply(ConnData, TransId, Reply, 
 
1512
                                         SendOpts, when_pending_sent),
 
1513
            {{handle_ack, AckData}, SendReply};
 
1514
 
 
1515
        {{handle_ack, AckData}, Replies} when is_list(Replies) ->
 
1516
            Reply     = {actionReplies, Replies},
 
1517
            SendReply = maybe_send_reply(ConnData, TransId, Reply, 
 
1518
                                         [], 'NULL'),
1104
1519
            {{handle_ack, AckData}, SendReply};
1105
1520
        {{handle_ack, AckData}, Error} 
1106
 
        when record(Error, 'ErrorDescriptor') ->
1107
 
            Reply = {transactionError, Error},
1108
 
            SendReply = 
1109
 
                maybe_send_reply(ConnData, TransId, Reply, 'NULL'),
1110
 
            {{handle_ack, AckData}, SendReply};
1111
 
        {{handle_sloppy_ack, AckData}, Replies} when list(Replies) ->
1112
 
            Reply = {actionReplies, Replies},
1113
 
            SendReply = 
1114
 
                maybe_send_reply(ConnData, TransId, Reply, asn1_NOVALUE),
 
1521
        when is_record(Error, 'ErrorDescriptor') ->
 
1522
            Reply     = {transactionError, Error},
 
1523
            SendReply = maybe_send_reply(ConnData, TransId, Reply, 
 
1524
                                         [], 'NULL'),
 
1525
            {{handle_ack, AckData}, SendReply};
 
1526
        {{handle_ack, AckData}, Replies, SendOpts} 
 
1527
        when is_list(Replies) and 
 
1528
             is_list(SendOpts) ->
 
1529
            Reply     = {actionReplies, Replies},
 
1530
            SendReply = maybe_send_reply(ConnData, TransId, Reply, 
 
1531
                                         SendOpts, 'NULL'),
 
1532
            {{handle_ack, AckData}, SendReply};
 
1533
        {{handle_ack, AckData}, Error, SendOpts} 
 
1534
        when is_record(Error, 'ErrorDescriptor') and 
 
1535
             is_list(SendOpts) ->
 
1536
            Reply     = {transactionError, Error},
 
1537
            SendReply = maybe_send_reply(ConnData, TransId, Reply, 
 
1538
                                         SendOpts, 'NULL'),
 
1539
            {{handle_ack, AckData}, SendReply};
 
1540
 
 
1541
        {{handle_sloppy_ack, AckData}, Replies} when is_list(Replies) ->
 
1542
            Reply     = {actionReplies, Replies},
 
1543
            SendReply = maybe_send_reply(ConnData, TransId, Reply, 
 
1544
                                         [], asn1_NOVALUE),
1115
1545
            {{handle_ack, AckData}, SendReply};
1116
1546
        {{handle_sloppy_ack, AckData}, Error} 
1117
 
        when record(Error, 'ErrorDescriptor') ->
1118
 
            Reply = {transactionError, Error},
1119
 
            SendReply = 
1120
 
                maybe_send_reply(ConnData, TransId, Reply, asn1_NOVALUE),
 
1547
        when is_record(Error, 'ErrorDescriptor') ->
 
1548
            Reply     = {transactionError, Error},
 
1549
            SendReply = maybe_send_reply(ConnData, TransId, Reply, 
 
1550
                                         [], asn1_NOVALUE),
 
1551
            {{handle_ack, AckData}, SendReply};
 
1552
        {{handle_sloppy_ack, AckData}, Replies, SendOpts} 
 
1553
        when is_list(Replies) and 
 
1554
             is_list(SendOpts) ->
 
1555
            Reply     = {actionReplies, Replies},
 
1556
            SendReply = maybe_send_reply(ConnData, TransId, Reply, 
 
1557
                                         SendOpts, asn1_NOVALUE),
 
1558
            {{handle_ack, AckData}, SendReply};
 
1559
        {{handle_sloppy_ack, AckData}, Error, SendOpts} 
 
1560
        when is_record(Error, 'ErrorDescriptor') and 
 
1561
             is_list(SendOpts) ->
 
1562
            Reply     = {transactionError, Error},
 
1563
            SendReply = maybe_send_reply(ConnData, TransId, Reply, 
 
1564
                                         SendOpts, asn1_NOVALUE),
1121
1565
            {{handle_ack, AckData}, SendReply};
1122
1566
        
1123
1567
        {pending, RequestData} ->
1129
1573
        
1130
1574
        Error ->
1131
1575
            ErrorText = atom_to_list(UserMod),
1132
 
            ED = #'ErrorDescriptor'{errorCode = ?megaco_internal_gateway_error,
1133
 
                                    errorText = ErrorText},
1134
 
            ?report_important(ConnData, "callback: <ERROR> trans request",
 
1576
            ED = #'ErrorDescriptor'{
 
1577
              errorCode = ?megaco_internal_gateway_error,
 
1578
              errorText = ErrorText},
 
1579
            ?report_important(ConnData, 
 
1580
                              "callback: <ERROR> trans request",
1135
1581
                              [ED, {error, Error}]),
1136
 
            error_msg("trans request callback failed: ~w", [Error]),
 
1582
            error_msg("transaction request callback failed: ~w", [Error]),
1137
1583
            Reply = {transactionError, ED},
1138
 
            SendReply = 
1139
 
                maybe_send_reply(ConnData, TransId, Reply, asn1_NOVALUE),
 
1584
            SendReply = maybe_send_reply(ConnData, TransId, Reply, 
 
1585
                                         [], asn1_NOVALUE),
1140
1586
            {discard_ack, SendReply}
1141
1587
    end.
1142
1588
 
1143
 
 
1144
1589
handle_long_request_callback(ConnData, TransId, RequestData) ->
1145
1590
    ?report_trace(ConnData, "callback: trans long request", [RequestData]),
1146
1591
    ConnHandle = ConnData#conn_data.conn_handle,
1154
1599
    case Res of
1155
1600
        ignore ->
1156
1601
            {discard_ack, ignore};
1157
 
 
1158
 
        {discard_ack, Replies} when list(Replies) ->
1159
 
            Reply = {actionReplies, Replies},
1160
 
            SendReply = 
1161
 
                maybe_send_reply(ConnData, TransId, Reply, asn1_NOVALUE),
1162
 
            {discard_ack, SendReply};
1163
 
 
1164
 
        {{handle_ack, AckData}, Replies} when list(Replies) ->
1165
 
            Reply = {actionReplies, Replies},
1166
 
            SendReply = 
1167
 
                maybe_send_reply(ConnData, TransId, Reply, 'NULL'),
1168
 
            {{handle_ack, AckData}, SendReply};
1169
 
 
1170
 
        Error ->
 
1602
        
 
1603
        {discard_ack, Replies} when is_list(Replies) ->
 
1604
            Reply     = {actionReplies, Replies},
 
1605
            SendReply = maybe_send_reply(ConnData, TransId, Reply, 
 
1606
                                         [], asn1_NOVALUE),
 
1607
            {discard_ack, SendReply};
 
1608
        {discard_ack, Replies, SendOpts} when is_list(Replies) and 
 
1609
                                              is_list(SendOpts) ->
 
1610
            Reply     = {actionReplies, Replies},
 
1611
            SendReply = maybe_send_reply(ConnData, TransId, Reply, 
 
1612
                                         SendOpts, asn1_NOVALUE),
 
1613
            {discard_ack, SendReply};
 
1614
        
 
1615
        {{handle_ack, AckData}, Replies} when is_list(Replies) ->
 
1616
            Reply     = {actionReplies, Replies},
 
1617
            SendReply = maybe_send_reply(ConnData, TransId, Reply, 
 
1618
                                         [], 'NULL'),
 
1619
            {{handle_ack, AckData}, SendReply};
 
1620
        {{handle_ack, AckData}, Replies, SendOpts} when is_list(Replies) and 
 
1621
                                                        is_list(SendOpts) ->
 
1622
            Reply     = {actionReplies, Replies},
 
1623
            SendReply = maybe_send_reply(ConnData, TransId, Reply, 
 
1624
                                         SendOpts, 'NULL'),
 
1625
            {{handle_ack, AckData}, SendReply};
 
1626
        
 
1627
        Error ->
1171
1628
            ErrorText = atom_to_list(UserMod),
1172
1629
            ED = #'ErrorDescriptor'{errorCode = ?megaco_internal_gateway_error,
1173
1630
                                    errorText = ErrorText},
1174
 
            ?report_important(ConnData, "callback: <ERROR> trans long request",
 
1631
            ?report_important(ConnData, "callback: <ERROR> trans long request",
1175
1632
                              [ED, {error, Error}]),
1176
 
            error_msg("long trans request callback failed: ~w", [Error]),
1177
 
            Reply = {transactionError, ED},
1178
 
            SendReply = 
1179
 
                maybe_send_reply(ConnData, TransId, Reply, asn1_NOVALUE),
1180
 
            {discard_ack, SendReply}
 
1633
            error_msg("long transaction request callback failed: ~w", [Error]),
 
1634
            Reply     = {transactionError, ED},
 
1635
            SendReply = maybe_send_reply(ConnData, TransId, Reply, 
 
1636
                                         [], asn1_NOVALUE),
 
1637
            {discard_ack, SendReply}
1181
1638
    end.
1182
1639
 
1183
1640
handle_pending(ConnData, T) ->
1184
1641
    TransId = to_local_trans_id(ConnData),
 
1642
    ?rt2("handle pending", [T, TransId]),
1185
1643
    case megaco_monitor:lookup_request(TransId) of
1186
 
        [#request{timer_ref       = {short, Ref},
1187
 
                  init_long_timer = InitTimer} = Req] ->
1188
 
 
1189
 
            %% The request seems to take a while,
1190
 
            %% let's reset our transmission timer.
1191
 
            %% We now know the other side has got
1192
 
            %% the request and is working on it,
1193
 
            %% so there is no need to keep the binary
1194
 
            %% message for re-transmission.
1195
 
 
1196
 
            %% Start using the long timer. 
1197
 
            %% We can now drop the "bytes", since we will
1198
 
            %% not resend from now on.
1199
 
 
1200
 
            megaco_monitor:cancel_apply_after(Ref),
1201
 
            {WaitFor, CurrTimer} = init_timer(InitTimer),
1202
 
            ConnHandle = ConnData#conn_data.conn_handle,
1203
 
            M = ?MODULE,
1204
 
            F = request_timeout,
1205
 
            A = [ConnHandle, TransId],
1206
 
            Ref2 = megaco_monitor:apply_after(M, F, A, WaitFor),
1207
 
            Req2 = Req#request{bytes      = {no_send, garb_binary},
1208
 
                               timer_ref  = {long, Ref2},
1209
 
                               curr_timer = CurrTimer},
1210
 
            ?report_trace(ConnData, 
1211
 
                          "trans pending (timer restarted)", [T]),
1212
 
            megaco_monitor:insert_request(Req2); % Timing problem?
1213
 
 
1214
 
        [#request{timer_ref  = {long, _Ref},
1215
 
                  curr_timer = timeout}] ->
1216
 
 
1217
 
            %% The request seems to take a while,
1218
 
            %% let's reset our transmission timer.
1219
 
            %% We now know the other side has got
1220
 
            %% the request and is working on it,
1221
 
            %% so there is no need to keep the binary
1222
 
            %% message for re-transmission.
1223
 
 
1224
 
            %% This can happen if the timer is running for the last 
1225
 
            %% time. I.e. next time it expires, will be the last.
1226
 
            %% Therefor we really do not need to do anything here.
1227
 
            %% The cleanup will be done in request_timeout.
1228
 
 
1229
 
            ok;
1230
 
 
1231
 
        [#request{timer_ref  = {long, Ref},
1232
 
                  curr_timer = CurrTimer} = Req] ->
1233
 
 
1234
 
            %% The request seems to take a while,
1235
 
            %% let's reset our transmission timer.
1236
 
            %% We now know the other side has got
1237
 
            %% the request and is working on it,
1238
 
            %% so there is no need to keep the binary
1239
 
            %% message for re-transmission.
1240
 
 
1241
 
            %% We just need to recalculate the timer, i.e. 
1242
 
            %% increment the timer (one "slot" has been consumed).
1243
 
 
1244
 
            megaco_monitor:cancel_apply_after(Ref),
1245
 
            {WaitFor, Timer2} = recalc_timer(CurrTimer),
1246
 
            ConnHandle = ConnData#conn_data.conn_handle,
1247
 
            M = ?MODULE,
1248
 
            F = request_timeout,
1249
 
            A = [ConnHandle, TransId],
1250
 
            Ref2 = megaco_monitor:apply_after(M, F, A, WaitFor),
1251
 
            Req2 = Req#request{timer_ref  = {long, Ref2},
1252
 
                               curr_timer = Timer2},
1253
 
            ?report_trace(ConnData, 
1254
 
                          "long trans pending"
1255
 
                          " (timer restarted)", [T]),
1256
 
            %% Timing problem?
1257
 
            megaco_monitor:insert_request(Req2);
 
1644
        [Req] ->
 
1645
 
 
1646
            %% ------------------------------------------
 
1647
            %% 
 
1648
            %%   Check received pending limit
 
1649
            %% 
 
1650
            %% ------------------------------------------
 
1651
 
 
1652
            Limit = ConnData#conn_data.recv_pending_limit,
 
1653
            case check_and_maybe_incr_pending_limit(Limit, 
 
1654
                                                    recv, TransId) of
 
1655
                
 
1656
                ok ->
 
1657
                    %% ----------------------------------------------------
 
1658
                    %% 
 
1659
                    %%      Received pending limit not exceeded     
 
1660
                    %% 
 
1661
                    %% ----------------------------------------------------
 
1662
 
 
1663
                    handle_recv_pending(ConnData, TransId, Req, T);
 
1664
                
 
1665
                error ->
 
1666
                    %% ----------------------------------------------------
 
1667
                    %% 
 
1668
                    %%      Received pending limit exceeded     
 
1669
                    %% 
 
1670
                    %%      Time to give up on this transaction
 
1671
                    %%      1) Delete request record
 
1672
                    %%      2) Cancel timers
 
1673
                    %%      3) Delete the (receive) pending counter
 
1674
                    %%      4) Inform the user (handle_trans_reply)
 
1675
                    %% 
 
1676
                    %% ----------------------------------------------------
 
1677
 
 
1678
                    handle_recv_pending_error(ConnData, TransId, Req, T);
 
1679
 
 
1680
                
 
1681
                aborted ->
 
1682
                    %% ----------------------------------------------------
 
1683
                    %% 
 
1684
                    %%      Received pending limit already exceeded     
 
1685
                    %% 
 
1686
                    %% BMK BMK BMK -- can this really happen?
 
1687
                    %% 
 
1688
                    %%      The user has already been notified about this
 
1689
                    %%      (see error above)
 
1690
                    %% 
 
1691
                    %% ----------------------------------------------------
 
1692
 
 
1693
                    ok
 
1694
 
 
1695
            end;
1258
1696
 
1259
1697
        [] ->
1260
 
            ?report_trace(ConnData, 
1261
 
                          "remote pending (no receiver)", [T]),
 
1698
            ?report_trace(ConnData, "remote pending (no receiver)", [T]),
1262
1699
            return_unexpected_trans(ConnData, T)
1263
1700
    end.
1264
1701
 
 
1702
handle_recv_pending(#conn_data{long_request_resend = LRR,
 
1703
                               conn_handle         = ConnHandle} = ConnData, 
 
1704
                    TransId,
 
1705
                    #request{timer_ref       = {short, Ref},
 
1706
                             init_long_timer = InitTimer} = Req, T) ->
 
1707
 
 
1708
    ?rt2("handle pending - long request", [LRR, InitTimer]),
 
1709
 
 
1710
    %% The request seems to take a while,
 
1711
    %% let's reset our transmission timer.
 
1712
    %% We now know the other side has got
 
1713
    %% the request and is working on it,
 
1714
    %% so there is no need to keep the binary
 
1715
    %% message for re-transmission.
 
1716
    
 
1717
    %% Start using the long timer. 
 
1718
    %% We can now drop the "bytes", since we will
 
1719
    %% not resend from now on.
 
1720
    
 
1721
    megaco_monitor:cancel_apply_after(Ref),
 
1722
    {WaitFor, CurrTimer} = init_timer(InitTimer),
 
1723
    ConnHandle = ConnData#conn_data.conn_handle,
 
1724
    M = ?MODULE,
 
1725
    F = request_timeout,
 
1726
    A = [ConnHandle, TransId],
 
1727
    Ref2 = megaco_monitor:apply_after(M, F, A, WaitFor),
 
1728
    Req2 = 
 
1729
        case LRR of
 
1730
            true ->
 
1731
                Req#request{timer_ref  = {long, Ref2},
 
1732
                            curr_timer = CurrTimer};
 
1733
            false ->
 
1734
                Req#request{bytes      = {no_send, garb_binary}, 
 
1735
                            timer_ref  = {long, Ref2},
 
1736
                            curr_timer = CurrTimer}
 
1737
        end,
 
1738
    ?report_trace(ConnData, "trans pending (timer restarted)", [T]),
 
1739
    megaco_monitor:insert_request(Req2); % Timing problem?
 
1740
    
 
1741
handle_recv_pending(_ConnData, _TransId,
 
1742
                    #request{timer_ref  = {long, _Ref},
 
1743
                             curr_timer = timeout}, _T) ->
 
1744
 
 
1745
    ?rt3("handle pending - timeout"),
 
1746
 
 
1747
    %% The request seems to take a while,
 
1748
    %% let's reset our transmission timer.
 
1749
    %% We now know the other side has got
 
1750
    %% the request and is working on it,
 
1751
    %% so there is no need to keep the binary
 
1752
    %% message for re-transmission.
 
1753
    
 
1754
    %% This can happen if the timer is running for the last 
 
1755
    %% time. I.e. next time it expires, will be the last.
 
1756
    %% Therefor we really do not need to do anything here.
 
1757
    %% The cleanup will be done in request_timeout.
 
1758
    
 
1759
    ok;
 
1760
 
 
1761
handle_recv_pending(#conn_data{conn_handle = ConnHandle} = ConnData, TransId,
 
1762
                    #request{timer_ref  = {long, Ref},
 
1763
                             curr_timer = CurrTimer} = Req, T) ->
 
1764
    
 
1765
    ?rt2("handle pending - still waiting", [CurrTimer]),
 
1766
 
 
1767
    %% The request seems to take a while,
 
1768
    %% let's reset our transmission timer.
 
1769
    %% We now know the other side has got
 
1770
    %% the request and is working on it,
 
1771
    %% so there is no need to keep the binary
 
1772
    %% message for re-transmission.
 
1773
    
 
1774
    %% We just need to recalculate the timer, i.e. 
 
1775
    %% increment the timer (one "slot" has been consumed).
 
1776
    
 
1777
    megaco_monitor:cancel_apply_after(Ref),
 
1778
    {WaitFor, Timer2} = recalc_timer(CurrTimer),
 
1779
    ConnHandle = ConnData#conn_data.conn_handle,
 
1780
    M = ?MODULE,
 
1781
    F = request_timeout,
 
1782
    A = [ConnHandle, TransId],
 
1783
    Ref2 = megaco_monitor:apply_after(M, F, A, WaitFor),
 
1784
    Req2 = Req#request{timer_ref  = {long, Ref2},
 
1785
                       curr_timer = Timer2},
 
1786
    ?report_trace(ConnData, 
 
1787
                  "long trans pending"
 
1788
                  " (timer restarted)", [T]),
 
1789
    %% Timing problem?
 
1790
    megaco_monitor:insert_request(Req2).
 
1791
    
 
1792
 
 
1793
handle_recv_pending_error(ConnData, TransId, Req, T) ->
 
1794
    %% 1) Delete the request record
 
1795
    megaco_monitor:delete_request(TransId),
 
1796
 
 
1797
    %% 2) Possibly cancel the timer
 
1798
    case Req#request.timer_ref of
 
1799
        {_, Ref} ->
 
1800
            megaco_monitor:cancel_apply_after(Ref);
 
1801
        _ ->
 
1802
            ok
 
1803
    end,
 
1804
    
 
1805
    %% 3) Delete the (receive) pending counter
 
1806
    megaco_config:del_pending_counter(recv, TransId),
 
1807
    
 
1808
    %% 4) Inform the user that his/her request reached 
 
1809
    %%    the receive pending limit
 
1810
    UserMod   = Req#request.user_mod,
 
1811
    UserArgs  = Req#request.user_args,
 
1812
    Action    = Req#request.reply_action,
 
1813
    UserData  = Req#request.reply_data,
 
1814
    UserReply = {error, exceeded_recv_pending_limit},
 
1815
    ConnData2 = ConnData#conn_data{user_mod     = UserMod,
 
1816
                                   user_args    = UserArgs,
 
1817
                                   reply_action = Action,
 
1818
                                   reply_data   = UserData},
 
1819
 
 
1820
    ?report_trace(ConnData, "receive pending limit reached", [T]),
 
1821
    return_reply(ConnData2, TransId, UserReply).
 
1822
 
 
1823
 
1265
1824
handle_reply(ConnData, T) ->
1266
1825
    TransId = to_local_trans_id(ConnData),
 
1826
    ?rt2("handle reply", [T, TransId]),
1267
1827
    case megaco_monitor:lookup_request(TransId) of
1268
1828
        [#request{timer_ref = {_Type, Ref}} = Req] -> %% OTP-4843
1269
1829
            %% Don't care about Req and Rep version diff
1307
1867
handle_ack(ConnData, AckStatus, Rep, T) ->
1308
1868
    #reply{trans_id          = TransId,
1309
1869
           timer_ref         = ReplyRef,
1310
 
           pending_timer_ref = PendingRef,  %% BMK BMK BMK Still running?
 
1870
           pending_timer_ref = PendingRef,  %% BMK Still running?
1311
1871
           ack_action        = AckAction} = Rep,
1312
1872
    megaco_monitor:cancel_apply_after(ReplyRef),
1313
1873
    megaco_monitor:cancel_apply_after(PendingRef),
1314
1874
    megaco_monitor:delete_reply(TransId),
1315
 
    megaco_config:del_pending_counter(TransId), %% BMK BMK BMK Still existing?
 
1875
    megaco_config:del_pending_counter(sent, TransId), %% BMK Still existing?
1316
1876
    handle_ack_callback(ConnData, AckStatus, AckAction, T).
1317
1877
 
1318
1878
% handle_ack(ConnData, AckStatus, Rep, T) ->
1322
1882
%     megaco_monitor:delete_reply(TransId),
1323
1883
%     handle_ack_callback(ConnData, AckStatus, Rep#reply.ack_action, T).
1324
1884
 
1325
 
handle_ack_callback(ConnData, AckStatus, discard_ack = AckAction, T) ->
1326
 
    case AckStatus of
1327
 
        ok ->
1328
 
            ok;
1329
 
        {error, Reason} ->
1330
 
            ?report_trace(ConnData, "handle ack",
1331
 
                          [T, AckAction, {error, Reason}])
1332
 
    end;
 
1885
handle_ack_callback(_CD, ok = _AS, discard_ack = _AA, _T) ->
 
1886
    ok;
 
1887
handle_ack_callback(ConnData, {error, Reason}, discard_ack = AckAction, T) ->
 
1888
    ?report_trace(ConnData, "handle ack (no callback)",
 
1889
                  [T, AckAction, {error, Reason}]);
1333
1890
handle_ack_callback(ConnData, AckStatus, {handle_ack, AckData}, T) ->
1334
1891
    ?report_trace(ConnData, "callback: trans ack", [{ack_data, AckData}]),
1335
1892
    ConnHandle = ConnData#conn_data.conn_handle,
1338
1895
    UserArgs   = ConnData#conn_data.user_args,
1339
1896
    Res = (catch apply(UserMod, handle_trans_ack, [ConnHandle, Version, AckStatus, AckData | UserArgs])),
1340
1897
    ?report_debug(ConnData, "return: trans ack", [T, AckData, {return, Res}]),
 
1898
    case Res of
 
1899
        ok ->
 
1900
            ok;
 
1901
        _ ->
 
1902
            warning_msg("transaction ack callback failed: ~w", [Res]),
 
1903
            ok
 
1904
    end,
1341
1905
    Res.
1342
1906
 
 
1907
 
1343
1908
handle_message_error(ConnData, _Error) 
1344
1909
  when ConnData#conn_data.monitor_ref == undefined_monitor_ref ->
1345
1910
    %% May occur if another process already has setup a
1355
1920
    UserArgs   = ConnData#conn_data.user_args,
1356
1921
    Res = (catch apply(UserMod, handle_message_error, [ConnHandle, Version, Error | UserArgs])),
1357
1922
    ?report_debug(ConnData, "return: message error", [Error, {return, Res}]),
 
1923
    case Res of
 
1924
        ok ->
 
1925
            ok;
 
1926
        _ ->
 
1927
            warning_msg("message error callback failed: ~w", [Res]),
 
1928
            ok
 
1929
    end,
1358
1930
    Res.
1359
1931
 
1360
1932
handle_disconnect_callback(ConnData, UserReason)
1361
 
  when record(ConnData, conn_data) ->
 
1933
  when is_record(ConnData, conn_data) ->
1362
1934
    ?report_trace(ConnData, "callback: disconnect", [{reason, UserReason}]),
1363
1935
    ConnHandle = ConnData#conn_data.conn_handle,
1364
1936
    Version    = ConnData#conn_data.protocol_version,
1366
1938
    UserArgs   = ConnData#conn_data.user_args,
1367
1939
    Res = (catch apply(UserMod, handle_disconnect, [ConnHandle, Version, UserReason | UserArgs])),
1368
1940
    ?report_debug(ConnData, "return: disconnect", [{reason, UserReason}, {return, Res}]),
 
1941
    case Res of
 
1942
        ok ->
 
1943
            ok;
 
1944
        _ ->
 
1945
            warning_msg("disconnect callback failed: ~w", [Res]),
 
1946
            ok
 
1947
    end,
1369
1948
    Res.
1370
1949
 
1371
1950
 
1383
1962
%% 
1384
1963
test_request(ConnHandle, Actions, 
1385
1964
             Version, EncodingMod, EncodingConfig)
1386
 
  when record(ConnHandle, megaco_conn_handle),
1387
 
       integer(Version), atom(EncodingMod) ->
 
1965
  when is_record(ConnHandle, megaco_conn_handle) and
 
1966
       is_integer(Version) and is_atom(EncodingMod) ->
1388
1967
    %% Create a fake conn_data structure
1389
1968
    ConnData = #conn_data{serial           = 1, 
1390
1969
                          protocol_version = Version,
1400
1979
    {MegaMsg, EncodeRes}.
1401
1980
 
1402
1981
 
1403
 
test_req_compose_transactions(ConnData, [A|_] = ActionsList) when list(A) ->
 
1982
test_req_compose_transactions(ConnData, [A|_] = ActionsList) when is_list(A) ->
1404
1983
    LastSerial = ConnData#conn_data.serial,
1405
1984
    test_req_compose_transactions(LastSerial, lists:reverse(ActionsList), []);
1406
1985
test_req_compose_transactions(#conn_data{serial = Serial}, Actions) ->
1417
1996
 
1418
1997
 
1419
1998
test_reply(ConnHandle, Version, EncodingMod, EncodingConfig, Error) 
1420
 
  when record(Error, 'ErrorDescriptor') ->
 
1999
  when is_record(Error, 'ErrorDescriptor') ->
1421
2000
    Reply = {transactionError, Error},
1422
2001
    test_reply_encode(ConnHandle, Version, EncodingMod, EncodingConfig, Reply);
1423
2002
test_reply(ConnHandle, Version, EncodingMod, EncodingConfig, Replies) 
1424
 
  when list(Replies) ->
 
2003
  when is_list(Replies) ->
1425
2004
    Reply = {actionReplies, Replies},
1426
2005
    test_reply_encode(ConnHandle, Version, EncodingMod, EncodingConfig, Reply).
1427
2006
 
1464
2043
%% EncodedActionsList -> binary() | [binary()]
1465
2044
%% Reason -> term()
1466
2045
encode_actions(CH, [A|_] = ActionsList, Opts) 
1467
 
  when record(CH, megaco_conn_handle), list(A) ->
 
2046
  when is_record(CH, megaco_conn_handle) and is_list(A) ->
1468
2047
    (catch encode_multi_actions(CH, ActionsList, Opts));
1469
2048
 
1470
2049
encode_actions(CH, [A|_] = Actions, Opts) 
1471
 
  when record(CH, megaco_conn_handle), tuple(A) ->
 
2050
  when is_record(CH, megaco_conn_handle) and is_tuple(A) ->
1472
2051
    do_encode_actions(CH, Actions, Opts).
1473
2052
    
1474
2053
encode_multi_actions(CH, ActionsList, Opts) ->
1475
 
    case prepare_send_options(CH, Opts) of
 
2054
    case prepare_req_send_options(CH, Opts) of
1476
2055
        {ok, CD} ->
1477
2056
            ActsList = [encode_multi_actions(CD, Acts) || Acts <- ActionsList],
1478
2057
            {ok, ActsList};
1489
2068
    end.
1490
2069
 
1491
2070
do_encode_actions(CH, Actions, Opts) 
1492
 
  when record(CH, megaco_conn_handle) ->
1493
 
    case prepare_send_options(CH, Opts) of
 
2071
  when is_record(CH, megaco_conn_handle) ->
 
2072
    case prepare_req_send_options(CH, Opts) of
1494
2073
        {ok, CD} ->
1495
2074
            megaco_messenger_misc:encode_actions(CD, "encode actions", Actions);
1496
2075
        Error ->
1497
2076
            Error
1498
2077
    end.
1499
2078
 
1500
 
prepare_send_options(CH, Opts) ->
 
2079
prepare_req_send_options(CH, Opts) ->
1501
2080
    case megaco_config:lookup_local_conn(CH) of
1502
2081
        [CD] ->
1503
 
            override_send_options(CD, Opts);
 
2082
            override_req_send_options(CD, Opts);
1504
2083
        [] ->
1505
2084
            {error, {not_found, conn_data}}
1506
2085
    end.
1507
2086
    
1508
2087
 
1509
2088
call(ConnHandle, Actions, Options) ->
1510
 
    Options2 = [{reply_data, self()} | Options],
1511
 
    call_or_cast(call, ConnHandle, Actions, Options2).
 
2089
    case lists:keymember(reply_data, 1, Options) of
 
2090
        true ->
 
2091
            {error, {bad_option, reply_data}};
 
2092
        false ->
 
2093
            Options2 = [{reply_data, self()} | Options],
 
2094
            call_or_cast(call, ConnHandle, Actions, Options2)
 
2095
    end.
1512
2096
 
1513
2097
cast(ConnHandle, Actions, Options) ->
1514
2098
    call_or_cast(cast, ConnHandle, Actions, Options).
1521
2105
%% ActionRequest. That is, action requests for several transactions.
1522
2106
%% It could also be a binary or a list of binaries (if 
1523
2107
%% the actions has already been encoded).
1524
 
call_or_cast(CallOrCast, ConnHandle, [A|_] = Actions, Options) when tuple(A) ->
 
2108
call_or_cast(CallOrCast, ConnHandle, [A|_] = Actions, Options) 
 
2109
  when is_tuple(A) ->
1525
2110
    %% Just one transaction
1526
2111
    case call_or_cast(CallOrCast, ConnHandle, [Actions], Options) of
1527
2112
        ok ->
1528
2113
            ok;
1529
2114
        {error, Reason} ->
1530
2115
            {error, Reason};
1531
 
        {Version, [Reply]} when integer(Version) ->
 
2116
        {Version, [Reply]} when is_integer(Version) ->
1532
2117
            {Version, Reply};
1533
 
        {Version, Error} when integer(Version) ->
 
2118
        {Version, Error} when is_integer(Version) ->
1534
2119
            {Version, Error}
1535
2120
    end;
1536
2121
 
1537
 
call_or_cast(CallOrCast, ConnHandle, Actions, Options) when binary(Actions) ->
 
2122
call_or_cast(CallOrCast, ConnHandle, Actions, Options) 
 
2123
  when is_binary(Actions) ->
1538
2124
    %% Just one transaction (although the actions has already been encoded)
1539
2125
    case call_or_cast(CallOrCast, ConnHandle, [Actions], Options) of
1540
2126
        ok ->
1541
2127
            ok;
1542
2128
        {error, Reason} ->
1543
2129
            {error, Reason};
1544
 
        {Version, [Reply]} when integer(Version) ->
 
2130
        {Version, [Reply]} when is_integer(Version) ->
1545
2131
            {Version, Reply};
1546
 
        {Version, Error} when integer(Version) ->
 
2132
        {Version, Error} when is_integer(Version) ->
1547
2133
            {Version, Error}
1548
2134
    end;
1549
2135
 
1550
2136
call_or_cast(CallOrCast, ConnHandle, ActionsList, Options)
1551
 
  when record(ConnHandle, megaco_conn_handle) ->
1552
 
    case prepare_send_options(ConnHandle, Options, ActionsList) of
 
2137
  when is_record(ConnHandle, megaco_conn_handle) ->
 
2138
    case prepare_req_send_options(ConnHandle, Options, ActionsList) of
1553
2139
        {ok, ConnData} ->
1554
2140
            ?report_trace(ConnData, "call_or_cast - options prepared", []),
1555
2141
            case encode_requests(ConnData, ActionsList) of
1612
2198
                        trans_req    = true, 
1613
2199
                        trans_sender = Pid} = CD, 
1614
2200
             CH, [Serial], Action, [Bin])
1615
 
  when pid(Pid), integer(Serial), node(CP) == node() ->
 
2201
  when is_pid(Pid) and is_integer(Serial) and (node(CP) == node()) ->
1616
2202
 
1617
2203
    ?report_trace(CD, "send_request - one transaction via trans-sender", [Serial]),
1618
2204
 
1630
2216
                        trans_req    = true, 
1631
2217
                        trans_sender = Pid} = CD, 
1632
2218
             CH, TransInfo, Action, Bins)
1633
 
  when pid(Pid), list(Bins), node(CP) == node() ->
 
2219
  when is_pid(Pid) and is_list(Bins) and (node(CP) == node()) ->
1634
2220
 
1635
2221
    ?report_trace(CD, "send_request - multi transactions via trans_sender", [TransInfo, Pid]),
1636
2222
 
1646
2232
%% this encoded message.
1647
2233
send_request(#conn_data{control_pid = CP} = CD, 
1648
2234
             CH, TRs, Action, Bin)
1649
 
  when list(TRs), binary(Bin), node(CP) == node() ->
 
2235
  when is_list(TRs) and is_binary(Bin) and (node(CP) == node()) ->
1650
2236
 
1651
2237
%     d("send_request -> entry with"
1652
2238
%       "~n   TRs: ~p", [TRs]),
1686
2272
 
1687
2273
insert_requests(ConnData, ConnHandle, [Serial|Serials], 
1688
2274
                Action, [Bin|Bins], InitTimer, LongTimer) 
1689
 
  when integer(Serial), binary(Bin) ->
 
2275
  when is_integer(Serial) and is_binary(Bin) ->
1690
2276
    TransId = to_local_trans_id(ConnHandle, Serial),
1691
2277
    insert_request(ConnData, ConnHandle, 
1692
2278
                   TransId, Action, Bin, InitTimer, LongTimer),
1697
2283
insert_requests(ConnData, ConnHandle, 
1698
2284
                [{transactionRequest, TR}|TRs], 
1699
2285
                Action, Bin, InitTimer, LongTimer) 
1700
 
  when record(TR, 'TransactionRequest'), binary(Bin) ->
 
2286
  when is_record(TR, 'TransactionRequest') and is_binary(Bin) ->
1701
2287
    #'TransactionRequest'{transactionId = Serial} = TR,
1702
2288
    TransId = to_local_trans_id(ConnHandle, Serial),
1703
2289
    insert_request(ConnData, ConnHandle, 
1742
2328
    ConnData2  = ConnData#conn_data{reply_data = ReplyNode},
1743
2329
    send_request(ConnData2, ConnHandle, TransInfo, Action, Bin).
1744
2330
 
1745
 
prepare_send_options(ConnHandle, Options, Actions) ->
 
2331
prepare_req_send_options(ConnHandle, Options, Actions) ->
1746
2332
    %% Ensures that two processes cannot get same transaction id.
1747
2333
    %% Bad send options may cause spurious transaction id to be consumed.
1748
2334
    Incr = number_of_transactions(Actions),
1749
2335
    case megaco_config:incr_trans_id_counter(ConnHandle, Incr) of
1750
2336
        {ok, ConnData} ->
1751
 
            override_send_options(ConnData, Options);
 
2337
            override_req_send_options(ConnData, Options);
1752
2338
        {error, Reason} ->
1753
2339
            {error, Reason}
1754
2340
    end.
1755
2341
 
1756
 
number_of_transactions([Action|_]) when tuple(Action) ->
 
2342
number_of_transactions([Action|_]) when is_tuple(Action) ->
1757
2343
    1;
1758
2344
number_of_transactions(ActionsList) ->
1759
2345
    length(ActionsList).
1760
2346
 
1761
 
override_send_options(ConnData, [{Key, Val} | Tail]) ->
 
2347
override_req_send_options(ConnData, [{Key, Val} | Tail]) ->
1762
2348
    case Key of
1763
2349
        protocol_version ->
1764
2350
            ConnData2 = ConnData#conn_data{protocol_version = Val},
1765
 
            override_send_options(ConnData2, Tail);         
 
2351
            override_req_send_options(ConnData2, Tail);     
1766
2352
        send_handle ->
1767
2353
            ConnData2 = ConnData#conn_data{send_handle = Val},
1768
 
            override_send_options(ConnData2, Tail);
 
2354
            override_req_send_options(ConnData2, Tail);
1769
2355
        request_timer ->
1770
2356
            case megaco_config:verify_val(Key, Val) of
1771
2357
                true ->
1772
2358
                    ConnData2 = ConnData#conn_data{request_timer = Val},
1773
 
                    override_send_options(ConnData2, Tail);
 
2359
                    override_req_send_options(ConnData2, Tail);
1774
2360
                false ->
1775
2361
                    {error, {bad_send_option, {Key, Val}}}
1776
2362
            end;
1778
2364
            case megaco_config:verify_val(Key, Val) of
1779
2365
                true ->
1780
2366
                    ConnData2 = ConnData#conn_data{long_request_timer = Val},
1781
 
                    override_send_options(ConnData2, Tail);
 
2367
                    override_req_send_options(ConnData2, Tail);
1782
2368
                false ->
1783
2369
                    {error, {bad_send_option, {Key, Val}}}
1784
2370
            end;
1785
2371
        reply_data ->
1786
2372
            ConnData2 = ConnData#conn_data{reply_data = Val},
1787
 
            override_send_options(ConnData2, Tail);
1788
 
        user_mod when atom(Val) ->
 
2373
            override_req_send_options(ConnData2, Tail);
 
2374
        user_mod when is_atom(Val) ->
1789
2375
            ConnData2 = ConnData#conn_data{user_mod = Val},
1790
 
            override_send_options(ConnData2, Tail);
1791
 
        user_args when list(Val) ->
 
2376
            override_req_send_options(ConnData2, Tail);
 
2377
        user_args when is_list(Val) ->
1792
2378
            ConnData2 = ConnData#conn_data{user_args = Val},
1793
 
            override_send_options(ConnData2, Tail);
1794
 
        trans_req when Val == false -> 
1795
 
            %% We only allow turning the transaction-sender off, since
1796
 
            %% the opposite (turning it on) would causing to much headake...
1797
 
            %% This vould allow not using the transaction sender for
1798
 
            %% occasional messages
1799
 
            ConnData2 = ConnData#conn_data{trans_req = Val, 
1800
 
                                           trans_sender = undefined},
1801
 
            override_send_options(ConnData2, Tail);
1802
 
        _Bad ->
1803
 
            {error, {bad_send_option, {Key, Val}}}
1804
 
    end;
1805
 
override_send_options(ConnData, []) ->
 
2379
            override_req_send_options(ConnData2, Tail);
 
2380
        trans_req when Val == false -> 
 
2381
            %% We only allow turning the transaction-sender off, since
 
2382
            %% the opposite (turning it on) would causing to much headake...
 
2383
            %% This vould allow not using the transaction sender for
 
2384
            %% occasional messages
 
2385
            ConnData2 = ConnData#conn_data{trans_req = Val, 
 
2386
                                           trans_sender = undefined},
 
2387
            override_req_send_options(ConnData2, Tail);
 
2388
        _Bad ->
 
2389
            {error, {bad_send_option, {Key, Val}}}
 
2390
    end;
 
2391
override_req_send_options(ConnData, []) ->
 
2392
    {ok, ConnData}.
 
2393
 
 
2394
override_rep_send_options(ConnData, [{Key, Val} | Tail]) ->
 
2395
    case Key of
 
2396
        protocol_version ->
 
2397
            ConnData2 = ConnData#conn_data{protocol_version = Val},
 
2398
            override_rep_send_options(ConnData2, Tail);     
 
2399
        send_handle ->
 
2400
            ConnData2 = ConnData#conn_data{send_handle = Val},
 
2401
            override_rep_send_options(ConnData2, Tail);
 
2402
        reply_timer ->
 
2403
            case megaco_config:verify_val(Key, Val) of
 
2404
                true ->
 
2405
                    ConnData2 = ConnData#conn_data{reply_timer = Val},
 
2406
                    override_rep_send_options(ConnData2, Tail);
 
2407
                false ->
 
2408
                    {error, {bad_send_option, {Key, Val}}}
 
2409
            end;
 
2410
        trans_req when Val == false -> 
 
2411
            %% We only allow turning the transaction-sender off, since
 
2412
            %% the opposite (turning it on) would causing to much headake...
 
2413
            %% This vould allow not using the transaction sender for
 
2414
            %% occasional messages
 
2415
            ConnData2 = ConnData#conn_data{trans_req = Val, 
 
2416
                                           trans_sender = undefined},
 
2417
            override_rep_send_options(ConnData2, Tail);
 
2418
        _Bad ->
 
2419
            {error, {bad_send_option, {Key, Val}}}
 
2420
    end;
 
2421
override_rep_send_options(ConnData, []) ->
1806
2422
    {ok, ConnData}.
1807
2423
 
1808
2424
 
1815
2431
encode_requests(#conn_data{trans_req    = true,
1816
2432
                           trans_sender = Pid,
1817
2433
                           serial       = LastSerial} = CD, ActionsList) 
1818
 
  when pid(Pid) ->
 
2434
  when is_pid(Pid) ->
1819
2435
    (catch encode_requests(CD, LastSerial, 
1820
2436
                           lists:reverse(ActionsList), [], []));
1821
2437
encode_requests(#conn_data{serial    = LastSerial} = CD, ActionsList) ->
1873
2489
    megaco_messenger_misc:encode_trans_request(CD, TR).
1874
2490
    
1875
2491
 
1876
 
 
1877
 
maybe_send_reply(#conn_data{orig_pending_limit = Limit} = ConnData, 
1878
 
                 TransId, Result, ImmAck) ->
 
2492
imm_ack_req(Counter,  when_pending_sent) when (Counter > 0) -> 'NULL';
 
2493
imm_ack_req(_Counter, when_pending_sent)                    -> asn1_NOVALUE;
 
2494
imm_ack_req(_Counter, ImmAck)                               -> ImmAck.
 
2495
 
 
2496
maybe_send_reply(#conn_data{sent_pending_limit = Limit} = ConnData, 
 
2497
                 TransId, Result, SendOpts, ImmAck) ->
 
2498
 
 
2499
%%     d("maybe_send_reply -> entry with"
 
2500
%%       "~n   Limit:    ~p"
 
2501
%%       "~n   TransId:  ~p"
 
2502
%%       "~n   Result:   ~p"
 
2503
%%       "~n   SendOpts: ~p"
 
2504
%%       "~n   ImmAck:   ~p", [Limit, TransId, Result, SendOpts, ImmAck]),
 
2505
 
1879
2506
    %% Pending limit
1880
2507
    %% Before we can send the reply we must check that we have 
1881
2508
    %% not passed the pending limit (and sent an error message).
1882
 
    case check_pending_limit(Limit, TransId) of
1883
 
        ok ->
1884
 
            send_reply(ConnData, Result, ImmAck);
 
2509
    case check_pending_limit(Limit, sent, TransId) of
 
2510
        {ok, Counter} ->
 
2511
            case override_rep_send_options(ConnData, SendOpts) of
 
2512
                {ok, ConnData2} ->
 
2513
                    send_reply(ConnData2, Result, 
 
2514
                               imm_ack_req(Counter, ImmAck));
 
2515
                Error ->
 
2516
                    Error
 
2517
            end;
1885
2518
        aborted ->
1886
2519
            {error, aborted}
1887
2520
    end.
1906
2539
            TR2 =  TR#'TransactionReply'{transactionResult = Reply},
1907
2540
            TraceLabel = "<ERROR> encode trans reply failed",
1908
2541
            ?report_important(CD, TraceLabel, [TR, TR2, ED, Error]),
1909
 
            error_msg("encode trans reply body failed: ~w", [Reason]),
 
2542
            error_msg("failed encoding transaction reply body: ~s", 
 
2543
                      [format_encode_error_reason(Reason)]),
1910
2544
            Body2 = {transactions, [{transactionReply, TR2}]},
1911
 
            megaco_messenger_misc:send_body(CD, TraceLabel, Body2)
 
2545
            megaco_messenger_misc:send_body(CD, TraceLabel, Body2),
 
2546
            Error
1912
2547
    end;
1913
2548
send_reply(#conn_data{serial = Serial} = CD, Result, ImmAck) ->
1914
2549
    %% Encapsule the transaction result into a reply message
 
2550
 
 
2551
%%     d("send_reply -> entry with"
 
2552
%%       "~n   Serial: ~p"
 
2553
%%       "~n   Result: ~p"
 
2554
%%       "~n   ImmAck: ~p", [Serial, Result, ImmAck]),
 
2555
 
1915
2556
    TR = #'TransactionReply'{transactionId     = Serial,
1916
2557
                             immAckRequired    = ImmAck,
1917
2558
                             transactionResult = Result},
1918
2559
    Body = {transactions, [{transactionReply, TR}]},
1919
 
    case megaco_messenger_misc:encode_body(CD, "send trans reply", Body) of
 
2560
    case megaco_messenger_misc:encode_body(CD, "encode trans reply", Body) of
1920
2561
        {ok, Bin} ->
1921
2562
            megaco_messenger_misc:send_message(CD, Bin);
1922
2563
        {error, Reason} = Error ->
1926
2567
            TR2        =  TR#'TransactionReply'{transactionResult = Reply},
1927
2568
            TraceLabel = "<ERROR> encode trans reply body failed",
1928
2569
            ?report_important(CD, TraceLabel, [TR, TR2, ED, Error]),
1929
 
            error_msg("encode trans reply body failed: ~w", [Reason]),
 
2570
            error_msg("failed encoding transaction reply body: ~s", 
 
2571
                      [format_encode_error_reason(Reason)]),
1930
2572
            Body2 = {transactions, [{transactionReply, TR2}]},
1931
 
            megaco_messenger_misc:send_body(CD, TraceLabel, Body2)
 
2573
            megaco_messenger_misc:send_body(CD, TraceLabel, Body2),
 
2574
            Error
1932
2575
    end.
1933
2576
 
1934
 
 
1935
 
maybe_send_pending(#conn_data{orig_pending_limit = Limit} = ConnData, 
 
2577
format_encode_error_reason(Reason) ->
 
2578
    FS = 
 
2579
        case Reason of
 
2580
            {Mod, Func, [EC, Msg], {AE, CS}} when is_atom(Mod)  and 
 
2581
                                                  is_atom(Func) and
 
2582
                                                  is_list(EC)   and
 
2583
                                                  is_tuple(Msg) and
 
2584
                                                  is_list(CS) ->
 
2585
                io_lib:format("~n   Encode module: ~w"
 
2586
                              "~n   Func:          ~w"
 
2587
                              "~n   Encode config: ~w"
 
2588
                              "~n   Message part:  ~p"
 
2589
                              "~n   Actual error:  ~p" 
 
2590
                              "~n   Call stack:    ~w", 
 
2591
                              [Mod, Func, EC, Msg, AE, CS]);
 
2592
 
 
2593
            {Mod, Func, [EC, Msg], AE} when is_atom(Mod)  and 
 
2594
                                            is_atom(Func) and
 
2595
                                            is_list(EC)   and
 
2596
                                            is_tuple(Msg) ->
 
2597
                io_lib:format("~n   Encode module: ~w"
 
2598
                              "~n   Func:          ~w"
 
2599
                              "~n   Encode config: ~w"
 
2600
                              "~n   Message part:  ~p"
 
2601
                              "~n   Actual error:  ~p", 
 
2602
                              [Mod, Func, EC, Msg, AE]);
 
2603
 
 
2604
            {Mod, [EC, Msg], {AE, CS}} when is_atom(Mod)  and 
 
2605
                                            is_list(EC)   and
 
2606
                                            is_tuple(Msg) and
 
2607
                                            is_list(CS) ->
 
2608
                io_lib:format("~n   Encode module: ~w"
 
2609
                              "~n   Encode config: ~w"
 
2610
                              "~n   Message part:  ~p"
 
2611
                              "~n   Actual error:  ~p" 
 
2612
                              "~n   Call stack:    ~w", 
 
2613
                              [Mod, EC, Msg, AE, CS]);
 
2614
 
 
2615
            {Mod, [EC, Msg], AE} when is_atom(Mod)  and 
 
2616
                                      is_list(EC)   and
 
2617
                                      is_tuple(Msg) ->
 
2618
                io_lib:format("~n   Encode module: ~w"
 
2619
                              "~n   Encode config: ~w"
 
2620
                              "~n   Message part:  ~p"
 
2621
                              "~n   Actual error:  ~p", 
 
2622
                              [Mod, EC, Msg, AE]);
 
2623
 
 
2624
            Error ->
 
2625
                io_lib:format("~n   ~w", [Error])
 
2626
        end,
 
2627
    lists:flatten(FS).
 
2628
 
 
2629
                          
 
2630
%% Presumably the user would return immediately (with {pending, Data}) if it 
 
2631
%% knows or suspects a request to take a long time to process. 
 
2632
%% For this reason we assume that handling a resent request 
 
2633
%% could not have caused an update of the pending limit counter.
 
2634
maybe_send_pending(#conn_data{sent_pending_limit = Limit} = ConnData, 
1936
2635
                   TransId) ->      
1937
 
    case check_and_maybe_incr_pending_limit(Limit, TransId) of
 
2636
    case check_and_maybe_incr_pending_limit(Limit, sent, TransId) of
1938
2637
        ok ->
1939
2638
            send_pending(ConnData);
1940
2639
        error ->
1967
2666
maybe_send_ack(_, #conn_data{serial       = Serial,
1968
2667
                             trans_ack    = true,
1969
2668
                             trans_sender = Pid}) 
1970
 
  when pid(Pid) ->
 
2669
  when is_pid(Pid) ->
1971
2670
    %% Send (later) via the transaction sender
1972
2671
    megaco_trans_sender:send_ack(Pid, Serial),
1973
2672
    ok;
1983
2682
    megaco_messenger_misc:send_body(CD, "send trans ack", Body).
1984
2683
 
1985
2684
 
 
2685
send_pending_limit_error(ConnData) ->
 
2686
    ?report_pending_limit_exceeded(ConnData),
 
2687
    Code   = ?megaco_number_of_transactionpending_exceeded,
 
2688
    Reason = "Pending limit exceeded",
 
2689
    send_trans_error(ConnData, Code, Reason).
 
2690
    
1986
2691
send_trans_error(ConnData, Code, Reason) ->
1987
2692
    %% Encapsule the transaction error into a reply message
1988
2693
    ED     = #'ErrorDescriptor'{errorCode = Code, errorText = Reason},
1989
2694
    Serial = ConnData#conn_data.serial,
1990
2695
    TR     = #'TransactionReply'{transactionId     = Serial,
1991
 
                                 transactionResult = {transactionError,ED}},
 
2696
                                 transactionResult = {transactionError, ED}},
1992
2697
    Body   = {transactions, [{transactionReply, TR}]},
1993
2698
    megaco_messenger_misc:send_body(ConnData, "send trans error", Body).
1994
2699
 
1995
2700
 
1996
 
send_pending_limit_error(ConnData) ->
1997
 
    ?report_pending_limit_exceeded(ConnData),
1998
 
    Code = ?megaco_number_of_transactionpending_exceeded,
1999
 
    Reason = "Pending limit exceeded",
2000
 
    send_message_error(ConnData, Code, Reason).
2001
 
    
2002
2701
send_message_error(ConnData, Code, Reason) ->
2003
2702
    ED = #'ErrorDescriptor'{errorCode = Code, errorText = Reason},
2004
2703
    Body = {messageError, ED},
2005
 
    megaco_messenger_misc:send_body(ConnData, "send trans error", Body).
 
2704
    case megaco_messenger_misc:send_body(ConnData, "send trans error", Body) of
 
2705
        {error, Reason} ->
 
2706
            ?report_important(ConnData, 
 
2707
                              "<ERROR> failed sending message error",
 
2708
                              [Body, {error, Reason}]),
 
2709
            error;
 
2710
        _ ->
 
2711
            ok
 
2712
    end.
 
2713
            
2006
2714
 
2007
 
cancel(ConnHandle, Reason) when record(ConnHandle, megaco_conn_handle) ->
 
2715
cancel(ConnHandle, Reason) when is_record(ConnHandle, megaco_conn_handle) ->
2008
2716
    case megaco_config:lookup_local_conn(ConnHandle) of
2009
2717
        [ConnData] ->
2010
2718
            do_cancel(ConnHandle, Reason, ConnData);
2014
2722
    end.
2015
2723
 
2016
2724
do_cancel(ConnHandle, Reason, ConnData) ->
 
2725
    ?report_trace(ConnData, "cancel", [ConnHandle, Reason]),
2017
2726
    LocalMid      = ConnHandle#megaco_conn_handle.local_mid,
2018
2727
    RemoteMid     = ConnHandle#megaco_conn_handle.remote_mid,
2019
 
    ReqTransIdPat = #trans_id{mid = LocalMid, serial = '_'}, 
 
2728
    ReqTransIdPat = #trans_id{mid = LocalMid, _ = '_'}, 
2020
2729
    ReqPat = #request{trans_id          = ReqTransIdPat,
2021
2730
                      remote_mid        = RemoteMid,
2022
 
                      timer_ref         = '_',
2023
 
                      init_timer        = '_',
2024
 
                      init_long_timer   = '_',
2025
 
                      curr_timer        = '_',
2026
 
                      version           = '_',
2027
 
                      bytes             = '_',
2028
 
                      send_handle       = '_',
2029
 
                      user_mod          = '_',
2030
 
                      user_args         = '_',
2031
 
                      reply_action      = '_',
2032
 
                      reply_data        = '_'},
 
2731
                      _                 = '_'},
2033
2732
    CancelReq = fun(Req) ->
2034
2733
                        cancel_request(ConnData, Req, Reason),
2035
2734
                        {_Type, Ref} = Req#request.timer_ref,  %% OTP-4843
2038
2737
    Requests  = megaco_monitor:match_requests(ReqPat),
2039
2738
    lists:foreach(CancelReq, Requests),
2040
2739
    RemoteMid = ConnHandle#megaco_conn_handle.remote_mid,
2041
 
    RepTransIdPat = #trans_id{mid = RemoteMid, serial = '_'}, % BUGBUG List here?
2042
 
    RepPat = #reply{trans_id          = RepTransIdPat,
2043
 
                    local_mid         = LocalMid,
2044
 
                    state             = waiting_for_ack,
2045
 
                    pending_timer_ref = '_',
2046
 
                    timer_ref         = '_',
2047
 
                    version           = '_',
2048
 
                    bytes             = '_',
2049
 
                    ack_action        = '_'},
2050
 
    CancelRep = fun(Rep) -> cancel_reply(ConnData, Rep, Reason) end,
 
2740
    RepTransIdPat = #trans_id{mid = RemoteMid, _ = '_'}, % BUGBUG List here?
 
2741
    RepPat = #reply{trans_id  = RepTransIdPat,
 
2742
                    local_mid = LocalMid,
 
2743
                    _         = '_'},
 
2744
    CancelRep = fun(Rep) -> 
 
2745
                        cancel_reply(ConnData, Rep, Reason) 
 
2746
                end,
2051
2747
    Replies   = megaco_monitor:match_replies(RepPat),
2052
2748
    lists:foreach(CancelRep, Replies),
2053
2749
    ok.
2060
2756
    case megaco_monitor:lookup_request(TransId) of
2061
2757
        [] ->
2062
2758
            ignore;
2063
 
        [Req] when record(Req, request) ->
 
2759
        [Req] when is_record(Req, request) ->
2064
2760
            cancel_request(ConnData, Req, Reason)
2065
2761
    end,
2066
2762
    cancel_requests(ConnData, TRs, Reason).
2067
2763
 
2068
2764
cancel_request(ConnData, Req, Reason)  ->
 
2765
    ?report_trace(ignore, "cancel request", [Req]),
2069
2766
    TransId   = Req#request.trans_id,
2070
2767
    Version   = Req#request.version,
2071
2768
    UserMod   = Req#request.user_mod,
2092
2789
    Version  = ConnData#conn_data.protocol_version,
2093
2790
    UserData = ConnData#conn_data.reply_data,
2094
2791
    case ConnData#conn_data.reply_action of
2095
 
        call when pid(UserData) ->
 
2792
        call when is_pid(UserData) ->
2096
2793
            ?report_trace(ConnData, "callback: (call) trans reply", 
2097
2794
                          [UserReply]),
2098
2795
            Pid = UserData,
2107
2804
                                UserData | UserArgs])),
2108
2805
            ?report_debug(ConnData, "return: (cast) trans reply",
2109
2806
                          [UserReply, {return, Res}]),
 
2807
            case Res of
 
2808
                ok ->
 
2809
                    ok;
 
2810
                _ ->
 
2811
                    warning_msg("transaction reply callback failed: ~w", 
 
2812
                                [Res]),
 
2813
                    ok
 
2814
            end,
2110
2815
            Res;
2111
2816
        remote ->
2112
2817
            ?report_trace(ConnData, "callback: (remote) trans reply", [UserReply]),
2139
2844
            return_unexpected_trans_reply(ConnData, TransId, UserReply)
2140
2845
    end.
2141
2846
 
2142
 
 
2143
 
cancel_reply(ConnData, Rep, Reason) when record(Rep, reply) ->
2144
 
    ?report_trace(ConnData, "cancel reply", [Reason]),
 
2847
cancel_reply(ConnData, #reply{state = waiting_for_ack} = Rep, Reason) ->
 
2848
    ?report_trace(ignore, "cancel reply [waiting_for_ack]", [Rep]),
2145
2849
    megaco_monitor:cancel_apply_after(Rep#reply.pending_timer_ref),
2146
2850
    Serial = (Rep#reply.trans_id)#trans_id.serial,
2147
2851
    ConnData2 = ConnData#conn_data{serial = Serial},
2148
2852
    T = #'TransactionAck'{firstAck = Serial},
2149
 
    handle_ack(ConnData2, {error, Reason}, Rep, T).
 
2853
    handle_ack(ConnData2, {error, Reason}, Rep, T);
 
2854
 
 
2855
cancel_reply(_ConnData, #reply{state = aborted} = Rep, _Reason) ->
 
2856
    ?report_trace(ignore, "cancel reply [aborted]", [Rep]),
 
2857
    #reply{trans_id          = TransId,
 
2858
           timer_ref         = ReplyRef,
 
2859
           pending_timer_ref = PendingRef} = Rep,
 
2860
    megaco_monitor:delete_reply(TransId),
 
2861
    megaco_monitor:cancel_apply_after(ReplyRef),
 
2862
    megaco_monitor:cancel_apply_after(PendingRef), % BMK BMK Still running?
 
2863
    megaco_config:del_pending_counter(TransId),    % BMK BMK Still existing?
 
2864
    ok;
 
2865
 
 
2866
cancel_reply(_ConnData, Rep, ignore) ->
 
2867
    ?report_trace(ignore, "cancel reply [ignore]", [Rep]),
 
2868
    #reply{trans_id          = TransId,
 
2869
           timer_ref         = ReplyRef,
 
2870
           pending_timer_ref = PendingRef} = Rep,
 
2871
    megaco_monitor:delete_reply(TransId),
 
2872
    megaco_monitor:cancel_apply_after(ReplyRef),
 
2873
    megaco_monitor:cancel_apply_after(PendingRef), % BMK BMK Still running?
 
2874
    megaco_config:del_pending_counter(TransId),    % BMK BMK Still existing?
 
2875
    ok;
 
2876
 
 
2877
cancel_reply(_CD, _Rep, _Reason) ->
 
2878
%%     io:format("cancel_reply -> entry with"
 
2879
%%            "~n   CD:     ~p"
 
2880
%%            "~n   Rep:    ~p"
 
2881
%%            "~n   Reason: ~p"
 
2882
%%            "~n", [_CD, _Rep, _Reason]),
 
2883
    ok.
2150
2884
 
2151
2885
 
2152
2886
request_timeout(ConnHandle, TransId) ->
 
2887
    ?rt1(ConnHandle, "request timeout", [TransId]),
2153
2888
    case megaco_monitor:lookup_request(TransId) of
2154
2889
        [] ->
2155
2890
            ignore;
2156
 
        [Req] when record(Req, request) ->
 
2891
        [Req] when is_record(Req, request) ->
2157
2892
            case megaco_config:lookup_local_conn(ConnHandle) of
2158
2893
                [ConnData] ->
2159
2894
                    incNumTimerRecovery(ConnHandle),
2163
2898
                    %% preliminary to a real connection. So this timeout
2164
2899
                    %% is just a glitch. E.g. between the removel of this
2165
2900
                    %% ConnHandle and the timer.
 
2901
                    %% Or this could be because the first message sent
 
2902
                    %% (the service-change) got e messageError reply,
 
2903
                    %% and so there is no transaction-id, and therefor no
 
2904
                    %% way to get hold of the request record.
2166
2905
                    request_timeout_upgraded(TransId);
2167
2906
                [] ->
2168
2907
                    incNumTimerRecovery(ConnHandle),
2183
2922
    ConnData2  = ConnData#conn_data{send_handle      = SendHandle,
2184
2923
                                    protocol_version = Version},
2185
2924
    case CurrTimer of
2186
 
        timeout ->
2187
 
            cancel_request(ConnData2, Req, timeout);
 
2925
        timeout ->  %%%%%%%
 
2926
            cancel_request(ConnData2, Req, timeout);
 
2927
 
 
2928
        %% Restartable timer 
 
2929
        %% (max_retries = infinity_restartable)
 
2930
        {_, timeout} ->  
 
2931
            cancel_request(ConnData2, Req, timeout);
 
2932
 
2188
2933
        Timer ->
2189
2934
            {SendOrNoSend, Data} = Req#request.bytes,
2190
2935
            case SendOrNoSend of
2235
2980
    end.
2236
2981
 
2237
2982
maybe_encode(#conn_data{trans_req = false} = CD, {_Serial, Bin}) 
2238
 
  when binary(Bin) ->
 
2983
  when is_binary(Bin) ->
2239
2984
    Body = {transactions, [{transactionRequest, Bin}]},
2240
2985
    megaco_messenger_misc:encode_body(CD, "encode trans request msg", Body);
2241
 
maybe_encode(_CD, {_Serial, Bin} = D) when binary(Bin) ->
 
2986
maybe_encode(_CD, {_Serial, Bin} = D) when is_binary(Bin) ->
2242
2987
    {ok, D};
2243
2988
maybe_encode(#conn_data{trans_req    = true,
2244
2989
                        trans_sender = Pid} = CD, 
2245
2990
             #'TransactionRequest'{transactionId = Serial} = TR) 
2246
 
  when pid(Pid) ->
 
2991
  when is_pid(Pid) ->
2247
2992
    case megaco_messenger_misc:encode_trans_request(CD, TR) of
2248
2993
        {ok, Bin} ->
2249
2994
            {ok, {Serial, Bin}};
2251
2996
            Error
2252
2997
    end;
2253
2998
maybe_encode(CD, TR) 
2254
 
  when record(TR, 'TransactionRequest') ->
 
2999
  when is_record(TR, 'TransactionRequest') ->
2255
3000
    Body = {transactions, [{transactionRequest, TR}]},
2256
3001
    megaco_messenger_misc:encode_body(CD, "encode trans request msg", Body);
2257
3002
maybe_encode(_CD, Trash) ->
2258
3003
    {error, {invalid_bin, Trash}}.
2259
3004
 
2260
 
maybe_send_message(CD, Bin) when binary(Bin) ->
 
3005
maybe_send_message(CD, Bin) when is_binary(Bin) ->
2261
3006
    megaco_messenger_misc:send_message(CD, Bin);
2262
3007
maybe_send_message(#conn_data{trans_sender = Pid}, {Serial, Bin}) 
2263
 
  when pid(Pid), integer(Serial), binary(Bin) ->
 
3008
  when is_pid(Pid) and is_integer(Serial) and is_binary(Bin) ->
2264
3009
    megaco_trans_sender:send_req(Pid, Serial, Bin).
2265
3010
 
2266
3011
    
2267
3012
reply_timeout(ConnHandle, TransId, timeout) ->
 
3013
    handle_reply_timer_timeout(ConnHandle, TransId);
 
3014
 
 
3015
%% This means that infinity_restartable was used for max_retries.
 
3016
%% There is currently no reason to use this for the reply_timeout,
 
3017
%% since there is no external event to restart the timer!
 
3018
reply_timeout(ConnHandle, TransId, {_, timeout}) ->
 
3019
    handle_reply_timer_timeout(ConnHandle, TransId);
 
3020
 
 
3021
reply_timeout(ConnHandle, TransId, Timer) ->
 
3022
    ?report_trace(ConnHandle, "reply timeout", [Timer, TransId]),
 
3023
 
 
3024
%%     d("reply_timeout -> entry with"
 
3025
%%       "~n   ConnHandle: ~p"
 
3026
%%       "~n   TransId:    ~p"
 
3027
%%       "~n   Timer:      ~p", [ConnHandle, TransId, Timer]),
 
3028
 
 
3029
    case megaco_monitor:lookup_reply(TransId) of
 
3030
        [] ->
 
3031
            ignore; % Trace ??
 
3032
 
 
3033
        [#reply{state      = waiting_for_ack, 
 
3034
                ack_action = {handle_ack, _}} = Rep] ->
 
3035
            case megaco_config:lookup_local_conn(ConnHandle) of
 
3036
                [ConnData] ->
 
3037
                    incNumTimerRecovery(ConnHandle),
 
3038
                    do_reply_timeout(ConnHandle, TransId, ConnData, 
 
3039
                                     Timer, Rep);
 
3040
                [] ->
 
3041
                    incNumTimerRecovery(ConnHandle),
 
3042
                    ConnData = fake_conn_data(ConnHandle),
 
3043
                    do_reply_timeout(ConnHandle, TransId, ConnData, 
 
3044
                                     Timer, Rep)
 
3045
            end;
 
3046
 
 
3047
        [#reply{state = waiting_for_ack} = Rep] ->
 
3048
            do_reply_timeout(ConnHandle, TransId, Timer, Rep);
 
3049
                    
 
3050
        [#reply{state = aborted} = Rep] ->
 
3051
            do_reply_timeout(ConnHandle, TransId, Timer, Rep);
 
3052
                    
 
3053
        _ ->
 
3054
            ignore
 
3055
                
 
3056
    end.
 
3057
 
 
3058
do_reply_timeout(ConnHandle, TransId, ConnData, Timer, 
 
3059
                 #reply{send_handle = SH,
 
3060
                        version     = V,
 
3061
                        bytes       = Bytes} = Rep) ->
 
3062
 
 
3063
    CD = ConnData#conn_data{send_handle      = SH,
 
3064
                            protocol_version = V},
 
3065
    
 
3066
%%     d("do_reply_timeout -> entry with"
 
3067
%%       "~n   ConnHandle: ~p"
 
3068
%%       "~n   TransId:    ~p"
 
3069
%%       "~n   Timer:      ~p"
 
3070
%%       "~n   Rep:        ~p"
 
3071
%%       "~n", [ConnHandle, TransId, Timer, Rep]),
 
3072
 
 
3073
    case megaco_messenger_misc:send_message(CD, Bytes) of
 
3074
        ok ->
 
3075
            ignore;
 
3076
        {ok, _} ->
 
3077
            ignore;
 
3078
        {error, Reason} ->
 
3079
            ?report_important(CD, "<ERROR> re-send trans reply failed",
 
3080
                              [{bytes, Bytes}, {error, Reason}])
 
3081
    end,
 
3082
    do_reply_timeout(ConnHandle, TransId, Timer, Rep).
 
3083
 
 
3084
do_reply_timeout(ConnHandle, TransId, Timer, #reply{bytes = Bytes} = Rep) ->
 
3085
    {WaitFor, Timer2} = recalc_timer(Timer),
 
3086
    OptBin = opt_garb_binary(Timer2, Bytes),
 
3087
    M = ?MODULE,
 
3088
    F = reply_timeout,
 
3089
    A = [ConnHandle, TransId, Timer2],
 
3090
    Ref2 = megaco_monitor:apply_after(M, F, A, WaitFor),
 
3091
    Rep2 = Rep#reply{bytes     = OptBin,
 
3092
                     timer_ref = Ref2},
 
3093
    megaco_monitor:insert_reply(Rep2). % Timing problem?
 
3094
 
 
3095
    
 
3096
handle_reply_timer_timeout(ConnHandle, TransId) ->
2268
3097
    ?report_trace(ConnHandle, "reply timeout", [timeout,TransId]),
2269
3098
    incNumTimerRecovery(ConnHandle),
2270
3099
    %% OTP-4378
2281
3110
            ConnData2 = ConnData#conn_data{serial = Serial},
2282
3111
            T = #'TransactionAck'{firstAck = Serial},
2283
3112
            handle_ack(ConnData2, {error, timeout}, Rep, T);
2284
 
        [#reply{pending_timer_ref = Ref}] ->
 
3113
        [#reply{pending_timer_ref = Ref}] -> % aborted?
2285
3114
            megaco_monitor:cancel_apply_after(Ref),
2286
 
            megaco_monitor:delete_reply(TransId)
2287
 
    end;
2288
 
reply_timeout(ConnHandle, TransId, Timer) ->
2289
 
    ?report_trace(ConnHandle, "reply timeout", [Timer, TransId]),
2290
 
    case megaco_monitor:lookup_reply(TransId) of
2291
 
        [] ->
2292
 
            ignore; % Trace ??
2293
 
        [#reply{state = waiting_for_ack} = Rep] ->
2294
 
            {WaitFor, Timer2} = recalc_timer(Timer),
2295
 
            OptBin = opt_garb_binary(Timer2, Rep#reply.bytes),
2296
 
            M = ?MODULE,
2297
 
            F = reply_timeout,
2298
 
            A = [ConnHandle, TransId, Timer2],
2299
 
            Ref2 = megaco_monitor:apply_after(M, F, A, WaitFor),
2300
 
            Rep2 = Rep#reply{bytes     = OptBin,
2301
 
                             timer_ref = Ref2},
2302
 
            megaco_monitor:insert_reply(Rep2) % Timing problem?
 
3115
            megaco_monitor:delete_reply(TransId),
 
3116
            megaco_config:del_pending_counter(sent, TransId)
2303
3117
    end.
2304
 
 
 
3118
    
2305
3119
pending_timeout(ConnData, TransId, Timer) ->
 
3120
    ?report_trace(ConnData, "pending timeout", [Timer, TransId]),
2306
3121
    case megaco_monitor:lookup_reply(TransId) of
2307
3122
        [#reply{state   = State,
2308
 
                handler = Pid} = Rep] 
2309
 
        when State == prepare; State == eval_request ->
 
3123
                handler = Pid} = Rep] when State == prepare; 
 
3124
                                           State == eval_request ->
2310
3125
 
2311
 
            #conn_data{orig_pending_limit = Limit,
 
3126
            #conn_data{sent_pending_limit = Limit,
2312
3127
                       conn_handle        = ConnHandle} = ConnData,
2313
3128
 
2314
3129
            %% ------------------------------------------
2317
3132
            %% 
2318
3133
            %% ------------------------------------------
2319
3134
 
2320
 
            case check_and_maybe_incr_pending_limit(Limit, TransId) of
 
3135
            case check_and_maybe_incr_pending_limit(Limit, sent, TransId) of
2321
3136
                ok ->
2322
3137
 
2323
3138
                    %% ---------------------------------------------
2333
3148
                            %% We are done
2334
3149
                            incNumTimerRecovery(ConnHandle),
2335
3150
                            ok;
 
3151
                        {_, timeout} ->
 
3152
                            %% We are done
 
3153
                            incNumTimerRecovery(ConnHandle),
 
3154
                            ok;
2336
3155
                        _ ->
2337
3156
                            {WaitFor, Timer2} = recalc_timer(Timer),
2338
3157
                            M = ?MODULE,
2356
3175
                    %% 
2357
3176
                    %% -------------------------------------------
2358
3177
 
2359
 
                    ?report_pending_limit_exceeded(ConnData),
2360
 
 
2361
 
                    Code = ?megaco_number_of_transactionpending_exceeded,
2362
 
                    Reason = "Pending limit exceeded",
2363
 
                    send_message_error(ConnData, Code, Reason),
 
3178
                    send_pending_limit_error(ConnData),
2364
3179
                    handle_request_abort_callback(ConnData, TransId, Pid),
2365
3180
                    %% Timing problem?
2366
 
                    megaco_monitor:insert_reply(Rep#reply{state = aborted});
 
3181
                    Rep2 = Rep#reply{state = aborted},
 
3182
                    %% megaco_monitor:insert_reply(Rep2);
 
3183
                    cancel_reply(ConnData, Rep2, aborted);
2367
3184
 
2368
3185
 
2369
3186
                aborted ->
2373
3190
                    %%   Pending limit already passed 
2374
3191
                    %% 
2375
3192
                    %% -------------------------------------------
2376
 
 
 
3193
                    Rep2 = Rep#reply{state = aborted},
 
3194
                    cancel_reply(ConnData, Rep2, aborted),
2377
3195
                    ignore
2378
3196
 
2379
3197
            end;
2385
3203
            %% No need for any pending trans reply
2386
3204
            ignore;
2387
3205
 
2388
 
        [#reply{state = aborted}] ->
2389
 
            %% glitch
 
3206
        [#reply{state = aborted} = Rep] ->
 
3207
            %% glitch, but cleanup just the same
 
3208
            cancel_reply(ConnData, Rep, aborted),
2390
3209
            ignore
2391
3210
 
2392
3211
    end.
2402
3221
    UserArgs   = ConnData#conn_data.user_args,
2403
3222
    ConnHandle = ConnData#conn_data.conn_handle,
2404
3223
    Version    = ConnData#conn_data.protocol_version,
2405
 
    (catch apply(UserMod, handle_unexpected_trans, 
2406
 
                 [ConnHandle, Version, Trans | UserArgs])).
 
3224
    Res = (catch apply(UserMod, handle_unexpected_trans, 
 
3225
                       [ConnHandle, Version, Trans | UserArgs])),
 
3226
    ?report_debug(ConnData, "return: unexpected trans", 
 
3227
                  [Trans, {return, Res}]),
 
3228
    case Res of
 
3229
        ok ->
 
3230
            ok;
 
3231
        _ ->
 
3232
            warning_msg("unexpected transaction callback failed: ~w", [Res]),
 
3233
            ok
 
3234
    end,
 
3235
    Res.
 
3236
    
2407
3237
 
2408
3238
 
2409
3239
to_remote_trans_id(#conn_data{conn_handle = CH, serial = Serial}) ->
2415
3245
    #trans_id{mid = Mid, serial = Serial}.
2416
3246
 
2417
3247
to_local_trans_id(#conn_data{conn_handle = CH}, [S|_] = Serials) 
2418
 
  when integer(S) ->
 
3248
  when is_integer(S) ->
2419
3249
    Mid = CH#megaco_conn_handle.local_mid, 
2420
3250
    [#trans_id{mid = Mid, serial = Serial} || Serial <- Serials];
2421
3251
to_local_trans_id(#conn_data{conn_handle = CH}, 
2422
3252
                  [{transactionRequest, TR}|_] = TRs) 
2423
 
  when record(TR, 'TransactionRequest') ->
 
3253
  when is_record(TR, 'TransactionRequest') ->
2424
3254
    Mid = CH#megaco_conn_handle.local_mid, 
2425
3255
    [#trans_id{mid = Mid, serial = Serial} || 
2426
3256
        {transactionRequest, 
2427
3257
         #'TransactionRequest'{transactionId = Serial}} <- TRs];
2428
3258
 
2429
3259
to_local_trans_id(#megaco_conn_handle{local_mid = Mid}, Serial) 
2430
 
  when integer(Serial) ->
 
3260
  when is_integer(Serial) ->
2431
3261
    #trans_id{mid = Mid, serial = Serial};
2432
3262
to_local_trans_id(#conn_data{conn_handle = CH}, Serial) 
2433
 
  when integer(Serial) ->
 
3263
  when is_integer(Serial) ->
2434
3264
    Mid = CH#megaco_conn_handle.local_mid, 
2435
3265
    #trans_id{mid = Mid, serial = Serial}.    
2436
3266
    
2438
3268
%% Returns {WaitFor, NewTimer} | {WaitFor, timeout}
2439
3269
init_timer(SingleWaitFor) when SingleWaitFor == infinity ->
2440
3270
    {SingleWaitFor, timeout};
2441
 
init_timer(SingleWaitFor) when integer(SingleWaitFor) ->
 
3271
init_timer(SingleWaitFor) when is_integer(SingleWaitFor) ->
2442
3272
    {SingleWaitFor, timeout};
2443
 
init_timer(Timer) when record(Timer, megaco_incr_timer) ->
 
3273
init_timer(Timer) when is_record(Timer, megaco_incr_timer) ->
2444
3274
    return_incr(Timer).
2445
3275
 
2446
3276
return_incr(Timer) ->
2448
3278
    case Timer#megaco_incr_timer.max_retries of
2449
3279
        infinity ->
2450
3280
            {WaitFor, Timer};
2451
 
        Int when integer(Int), Int > 0 -> 
 
3281
        infinity_restartable ->
 
3282
            {WaitFor, {Timer, timeout}};
 
3283
        Int when is_integer(Int), Int > 0 -> 
2452
3284
            {WaitFor, Timer};
2453
3285
        0  ->
2454
3286
            {WaitFor, timeout}
2455
3287
    end.
2456
3288
 
2457
3289
%% Returns {WaitFor, NewTimer} | {WaitFor, timeout}
2458
 
recalc_timer(Timer) when record(Timer, megaco_incr_timer) ->
 
3290
recalc_timer(Timer) when is_record(Timer, megaco_incr_timer) ->
2459
3291
    Old     = Timer#megaco_incr_timer.wait_for,
2460
3292
    Factor  = Timer#megaco_incr_timer.factor,
2461
3293
    Incr    = Timer#megaco_incr_timer.incr,
2463
3295
    Max     = decr(Timer#megaco_incr_timer.max_retries),
2464
3296
    Timer2  = Timer#megaco_incr_timer{wait_for    = New,
2465
3297
                                      max_retries = Max},
2466
 
    return_incr(Timer2).
2467
 
 
2468
 
decr(infinity) -> infinity;
2469
 
decr(Int)      -> Int - 1.
2470
 
 
 
3298
    return_incr(Timer2);
 
3299
recalc_timer({Timer, timeout}) when is_record(Timer, megaco_incr_timer) ->
 
3300
    recalc_timer(Timer).
 
3301
 
 
3302
decr(infinity = V)             -> V;
 
3303
decr(infinity_restartable = V) -> V;
 
3304
decr(Int) when is_integer(Int) -> Int - 1.
 
3305
 
 
3306
 
 
3307
warning_msg(F, A) ->
 
3308
    ?megaco_warning(F, A).
2471
3309
 
2472
3310
error_msg(F, A) ->
2473
 
    (catch error_logger:error_msg(F ++ "~n", A)).
2474
 
 
2475
 
 
2476
 
% d(F) ->
2477
 
%     d(F,[]).
2478
 
 
2479
 
% d(F,A) ->
2480
 
%     d(true,F,A).
2481
 
%     %% d(get(dbg),F,A).
2482
 
 
2483
 
% d(true,F,A) ->
2484
 
%     io:format("*** [~s] ~p:~p ***"
2485
 
%             "~n   " ++ F ++ "~n", 
2486
 
%             [format_timestamp(now()), self(),?MODULE|A]);
2487
 
% d(_, _, _) ->
2488
 
%     ok.
2489
 
 
2490
 
% format_timestamp(Now) ->
2491
 
%     {N1, N2, N3}   = Now,
2492
 
%     {Date, Time}   = calendar:now_to_datetime(Now),
2493
 
%     {YYYY,MM,DD}   = Date,
2494
 
%     {Hour,Min,Sec} = Time,
2495
 
%     FormatDate = 
2496
 
%         io_lib:format("~.4w:~.2.0w:~.2.0w ~.2.0w:~.2.0w:~.2.0w 4~w",
2497
 
%                       [YYYY,MM,DD,Hour,Min,Sec,round(N3/1000)]),  
2498
 
%     lists:flatten(FormatDate).
 
3311
    ?megaco_error(F, A).
 
3312
 
 
3313
 
 
3314
%% d(F) ->
 
3315
%%     d(F,[]).
 
3316
 
 
3317
%% d(F,A) ->
 
3318
%%     d(true,F,A).
 
3319
%%     %% d(get(dbg),F,A).
 
3320
 
 
3321
%% d(true,F,A) ->
 
3322
%%     io:format("*** [~s] ~p:~p ***"
 
3323
%%            "~n   " ++ F ++ "~n", 
 
3324
%%            [format_timestamp(now()), self(),?MODULE|A]);
 
3325
%% d(_, _, _) ->
 
3326
%%     ok.
 
3327
 
 
3328
%% format_timestamp({_N1, _N2, N3} = Now) ->
 
3329
%%     {Date, Time}   = calendar:now_to_datetime(Now),
 
3330
%%     {YYYY,MM,DD}   = Date,
 
3331
%%     {Hour,Min,Sec} = Time,
 
3332
%%     FormatDate = 
 
3333
%%         io_lib:format("~.4w:~.2.0w:~.2.0w ~.2.0w:~.2.0w:~.2.0w 4~w",
 
3334
%%                       [YYYY,MM,DD,Hour,Min,Sec,round(N3/1000)]),  
 
3335
%%     lists:flatten(FormatDate).
2499
3336
 
2500
3337
              
2501
3338
%%-----------------------------------------------------------------
2505
3342
incNumErrors() ->
2506
3343
    incNum(medGwyGatewayNumErrors).
2507
3344
 
2508
 
% incNumErrors(CH) ->
2509
 
%     incNum({CH, medGwyGatewayNumErrors}).
 
3345
incNumErrors(CH) ->
 
3346
    incNum({CH, medGwyGatewayNumErrors}).
2510
3347
 
2511
3348
incNumTimerRecovery(CH) ->
2512
3349
    incNum({CH, medGwyGatewayNumTimerRecovery}).