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

« back to all changes in this revision

Viewing changes to lib/megaco/test/megaco_test_mgc.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:
28
28
         request_discard/1, request_discard/2, 
29
29
         request_pending/1, request_pending/2, request_pending_ignore/1, 
30
30
         request_handle/1, request_handle/2, 
31
 
         request_handle_sloppy/1, 
32
 
         ack_info/2, req_info/2, 
 
31
         request_handle_pending/1, request_handle_pending/2, 
 
32
         request_handle_sloppy/1, request_handle_sloppy/2, 
 
33
         ack_info/2, abort_info/2, req_info/2, 
 
34
         disconnect/2, 
33
35
         verbosity/2]).
34
36
-export([mgc/3]).
35
37
 
42
44
         handle_trans_request/4,
43
45
         handle_trans_long_request/4,
44
46
         handle_trans_reply/5,
45
 
         handle_trans_ack/5
 
47
         handle_trans_ack/5,
 
48
         handle_unexpected_trans/4,
 
49
         handle_trans_request_abort/5
46
50
        ]).
47
51
 
48
52
-include("megaco_test_lib.hrl").
55
59
-define(A5556, ["11111111", "11111111", "11111111"]).
56
60
 
57
61
-define(valid_actions, 
58
 
        [ignore, pending, pending_ignore, discard_ack, handle_ack, handle_sloppy_ack]).
 
62
        [ignore, pending, pending_ignore, discard_ack, handle_ack, handle_pending_ack, handle_sloppy_ack]).
59
63
 
60
64
-record(mgc, {parent      = undefined,
61
65
              tcp_sup     = undefined,
64
68
              req_timeout = 0,
65
69
              mid         = undefined,
66
70
              ack_info    = undefined,
 
71
              abort_info  = undefined,
67
72
              req_info    = undefined,
68
73
              mg          = []}).
69
74
 
71
76
%%% ------------------------------------------------------------------
72
77
 
73
78
start(Node, Mid, ET, Verbosity) ->
 
79
    %% Conf = [{megaco_trace, io}],
 
80
    %% Conf = [{megaco_trace, "megaco-mgc.trace"}],
74
81
    Conf = [{megaco_trace, false}],
75
82
    start(Node, Mid, ET, Conf, Verbosity).
76
83
 
167
174
update_conn_info(Pid, Tag, Val) ->
168
175
    server_request(Pid, {update_conn_info, Tag, Val}, update_conn_info_ack).
169
176
 
 
177
disconnect(Pid, Reason) ->
 
178
    server_request(Pid, {disconnect, Reason}, disconnected).
 
179
 
170
180
ack_info(Pid, InfoPid) ->
171
181
    Pid ! {ack_info, InfoPid, self()}.
172
182
 
 
183
abort_info(Pid, InfoPid) ->
 
184
    Pid ! {abort_info, InfoPid, self()}.
 
185
 
173
186
req_info(Pid, InfoPid) ->
174
187
    Pid ! {req_info, InfoPid, self()}.
175
188
 
200
213
request_handle(Pid, To) ->
201
214
    request_action(Pid, {handle_ack, To}).
202
215
 
 
216
request_handle_pending(Pid) ->
 
217
    request_handle_pending(Pid, 0).
 
218
 
 
219
request_handle_pending(Pid, To) ->
 
220
    request_action(Pid, {handle_pending_ack, To}).
 
221
 
203
222
request_handle_sloppy(Pid) ->
204
 
    request_action(Pid, {handle_sloppy_ack, 0}).
 
223
    request_handle_sloppy(Pid, 0).
 
224
 
 
225
request_handle_sloppy(Pid, To) ->
 
226
    request_action(Pid, {handle_sloppy_ack, To}).
205
227
 
206
228
request_action(Pid, Action) ->
207
229
    server_request(Pid, request_action, Action, request_action_ack).
261
283
    case lists:keysearch(megaco_trace, 1, Config) of
262
284
        {value, {megaco_trace, true}} ->
263
285
            megaco:enable_trace(max, io);
 
286
        {value, {megaco_trace, io}} ->
 
287
            megaco:enable_trace(max, io);
 
288
        {value, {megaco_trace, File}} when list(File) ->
 
289
            megaco:enable_trace(max, File);
264
290
        _ ->
265
291
            ok
266
292
    end,
300
326
            server_reply(Parent, stopped, ok),
301
327
            exit(normal);
302
328
 
 
329
        {{disconnect, Reason}, Parent} when S#mgc.parent == Parent ->
 
330
            i("loop -> disconnecting", []),
 
331
            Mid = S#mgc.mid,
 
332
            [Conn|_] = megaco:user_info(Mid, connections),
 
333
            Res = megaco:disconnect(Conn, {self(), Reason}),
 
334
            server_reply(Parent, disconnected, Res),
 
335
            loop(S);
303
336
 
304
337
        {{update_user_info, Tag, Val}, Parent} when S#mgc.parent == Parent ->
305
338
            i("loop -> got update_user_info: ~w -> ~p", [Tag, Val]),
330
363
            i("loop -> got conn_info request for ~w", [Tag]),
331
364
            Conns = megaco:user_info(S#mgc.mid, connections), 
332
365
            Fun = fun(CH) ->
333
 
                          (catch megaco:conn_info(CH, Tag))
 
366
                          {CH, (catch megaco:conn_info(CH, Tag))}
334
367
                  end,
335
368
            Res = lists:map(Fun, Conns),
336
369
            d("loop -> Res: ~p", [Res]),
343
376
            i("loop -> got new request_action: ~p:~w", [Action,To]),
344
377
            {Reply, S1} = 
345
378
                case lists:member(Action, ?valid_actions) of
346
 
                    true when To >= 0 ->
 
379
                    true when To >= 0; To == infinity ->
347
380
                        {{ok, S#mgc.req_action}, 
348
381
                         S#mgc{req_action = Action, req_timeout = To}};
349
382
                    true ->
415
448
            loop(S#mgc{ack_info = To});
416
449
 
417
450
 
 
451
        {abort_info, To, Parent} when S#mgc.parent == Parent ->
 
452
            i("loop -> received request to inform about received aborts ", []),
 
453
            loop(S#mgc{abort_info = To});
 
454
 
 
455
 
418
456
        {req_info, To, Parent} when S#mgc.parent == Parent ->
419
 
            i("loop -> received request to inform about received ack's ", []),
 
457
            i("loop -> received request to inform about received req's ", []),
420
458
            loop(S#mgc{req_info = To});
421
459
 
422
460
 
442
480
    megaco:reset_stats(),
443
481
    do_reset_trans_stats(megaco:user_info(Mid, connections), []).
444
482
 
445
 
do_reset_trans_stats([], Reset) ->
 
483
do_reset_trans_stats([], _Reset) ->
446
484
    ok;
447
485
do_reset_trans_stats([CH|CHs], Reset) ->
448
486
    SendMod = megaco:conn_info(CH, send_mod),
481
519
        Else ->
482
520
            {SendMod, Else}
483
521
    end;
484
 
get_trans_stats(P, SendMod) ->
 
522
get_trans_stats(_P, SendMod) ->
485
523
    {SendMod, undefined}.
486
524
 
487
 
parse_receive_info([], RH) ->
 
525
parse_receive_info([], _RH) ->
488
526
    throw({error, no_receive_info});
489
527
parse_receive_info(RI, RH) ->
490
528
    parse_receive_info(RI, RH, []).
491
529
 
492
 
parse_receive_info([], RH, ListenTo) ->
 
530
parse_receive_info([], _RH, ListenTo) ->
493
531
    ListenTo;
494
532
parse_receive_info([RI|RIs], RH, ListenTo) ->
495
533
    d("parse_receive_info -> parse receive info"),
532
570
  when RH#megaco_receive_handle.send_mod == megaco_udp ->
533
571
    UdpSup1 = start_udp(RH, Port, UdpSup),
534
572
    start_transports(ListenTo, TcpSup, UdpSup1);
535
 
start_transports([{Port, RH}|ListenTo], _TcpSup, _UdpSup) ->
 
573
start_transports([{_Port, RH}|_ListenTo], _TcpSup, _UdpSup) ->
536
574
    throw({error, {bad_send_mod, RH#megaco_receive_handle.send_mod}}).
537
575
 
538
576
 
646
684
      "~n   PV: ~p"
647
685
      "~n   AS: ~p"
648
686
      "~n   AD: ~p", [CH, PV, AS, AD]),
649
 
    {ok, S}.
 
687
    {ok, S};
 
688
 
 
689
handle_megaco_request({handle_unexpected_trans, CH, PV, TR}, S) ->
 
690
    d("handle_megaco_request(handle_unexpected_trans) -> entry with"
 
691
      "~n   CH: ~p"
 
692
      "~n   PV: ~p"
 
693
      "~n   TR: ~p", [CH, PV, TR]),
 
694
    {ok, S};
 
695
 
 
696
handle_megaco_request({handle_trans_request_abort, CH, PV, TI, Handler}, S) ->
 
697
    d("handle_megaco_request(handle_trans_request_abort) -> entry with"
 
698
      "~n   CH:      ~p"
 
699
      "~n   PV:      ~p"
 
700
      "~n   TI:      ~p"
 
701
      "~n   Handler: ~p", [CH, PV, TI, Handler]),
 
702
    Reply = 
 
703
        case S#mgc.abort_info of
 
704
            P when pid(P) ->
 
705
                P ! {abort_received, self(), TI},
 
706
                ok;
 
707
            _ ->
 
708
                ok
 
709
        end,
 
710
    {Reply, S}.
650
711
 
651
712
 
652
713
do_handle_trans_request(CH, PV, ARs, 
664
725
 
665
726
handle_act_requests(_CH, _PV, _ActReqs, ignore) ->
666
727
    ignore;
667
 
handle_act_requests(CH, PV, ActReqs, pending) ->
 
728
handle_act_requests(_CH, _PV, ActReqs, pending) ->
668
729
    {pending, ActReqs};
669
 
handle_act_requests(CH, PV, ActReqs, pending_ignore) ->
 
730
handle_act_requests(_CH, _PV, ActReqs, pending_ignore) ->
670
731
    {pending_ignore, ActReqs};
671
732
handle_act_requests(CH, PV, ActReqs, handle_ack) ->
672
733
    Reply = (catch do_handle_act_requests(CH, PV, ActReqs, [])),
678
739
    Reply = (catch do_handle_act_requests(CH, PV, ActReqs, [])),
679
740
    {discard_ack, Reply}.
680
741
 
681
 
do_handle_act_requests(CH, PV, [], ActReplies) ->
 
742
do_handle_act_requests(_CH, _PV, [], ActReplies) ->
682
743
    lists:reverse(ActReplies);
683
744
do_handle_act_requests(CH, PV, [ActReq|ActReqs], ActReplies) ->
684
745
    ActReply = handle_act_request(CH, PV, ActReq),
697
758
handle_cmd_requests(CH, PV, CtxId, Cmds) ->
698
759
    do_handle_cmd_requests(CH, PV, CtxId, Cmds, []).
699
760
 
700
 
do_handle_cmd_requests(CH, PV, CtxId, [], CmdReplies) ->
 
761
do_handle_cmd_requests(_CH, _PV, _CtxId, [], CmdReplies) ->
701
762
    lists:reverse(CmdReplies);
702
763
do_handle_cmd_requests(CH, PV, CtxId, [Cmd|Cmds], CmdReplies) ->
703
764
    CmdReply = handle_cmd_request(CH, PV, CtxId, Cmd),
727
788
                                       observedEventsDescriptor = EvDesc}) ->
728
789
    handle_event(CH, PV, CtxId, Tid, EvDesc).
729
790
 
730
 
handle_event(CH, PV, Cid, Tid, EvDesc) ->
 
791
handle_event(_CH, _PV, _Cid, Tid, EvDesc) ->
731
792
    d("handle_event -> received"
732
793
      "~n   EvDesc: ~p"
733
794
      "~n   Tid:    ~p", [EvDesc, Tid]),
734
795
    {notifyReply, cre_notifyRep(Tid)}.
735
796
    
736
797
 
737
 
service_change(CH, PV, SCR) ->
 
798
service_change(CH, _PV, SCR) ->
738
799
    SCP = SCR#'ServiceChangeRequest'.serviceChangeParms,
739
 
    #'ServiceChangeParm'{serviceChangeMethod  = Method,
740
 
                         serviceChangeAddress = Address,
 
800
    #'ServiceChangeParm'{serviceChangeAddress = Address,
741
801
                         serviceChangeProfile = Profile,
742
 
                         serviceChangeReason  = [Reason],
743
 
                         serviceChangeDelay   = Delay,
744
 
                         serviceChangeMgcId   = MgcId} = SCP,
 
802
                         serviceChangeReason  = [_Reason]} = SCP,
745
803
    TermId = SCR#'ServiceChangeRequest'.terminationID,
746
804
    if
747
805
        TermId == [?megaco_root_termination_id] ->
804
862
            Reply
805
863
    end.
806
864
 
807
 
handle_disconnect(CH, PV, 
 
865
handle_disconnect(_CH, _PV, 
808
866
                  {user_disconnect, {Pid, ignore}}, 
809
867
                  Pid) ->
810
868
    ok;
 
869
handle_disconnect(CH, _PV, 
 
870
                  {user_disconnect, {Pid, cancel}}, 
 
871
                  Pid) ->
 
872
    megaco:cancel(CH, disconnected),
 
873
    ok;
811
874
handle_disconnect(CH, PV, R, Pid) ->
812
875
    request(Pid, {handle_disconnect, CH, PV, R}).
813
876
 
837
900
    Req = {handle_trans_ack, ConnHandle, ProtocolVersion, AckStatus, AckData},
838
901
    request(Pid, Req).
839
902
 
 
903
handle_unexpected_trans(ConnHandle, ProtocolVersion, Trans, Pid) ->
 
904
    Req = {handle_unexpected_trans, ConnHandle, ProtocolVersion, Trans},
 
905
    request(Pid, Req).
 
906
 
 
907
handle_trans_request_abort(ConnHandle, ProtocolVersion, TransId, 
 
908
                           Handler, Pid) ->
 
909
    Req = {handle_trans_request_abort, 
 
910
           ConnHandle, ProtocolVersion, TransId, Handler},
 
911
    request(Pid, Req).
 
912
 
840
913
 
841
914
request(Pid, Request) ->
842
915
    Pid ! {request, Request, self()},
843
916
    receive
844
917
        {reply, {delay_reply, To, Reply}, Pid} ->
 
918
            megaco:report_event(ignore, self(), Pid, 
 
919
                                "reply: delay_reply", [To, Reply]),
845
920
            sleep(To),
 
921
            megaco:report_event(ignore, self(), Pid, 
 
922
                                "reply: delay done now return", []),
846
923
            Reply;
847
924
        {reply, {exit, To, Reason}, Pid} ->
 
925
            megaco:report_event(ignore, self(), Pid, 
 
926
                                "reply: exit", [To, Reason]),
848
927
            sleep(To),
 
928
            megaco:report_event(ignore, self(), Pid, 
 
929
                                "reply: sleep done now exit", []),
849
930
            exit(Reason);
850
931
        {reply, Reply, Pid} ->
 
932
            megaco:report_event(ignore, self(), Pid, "reply", [Reply]),
851
933
            Reply
852
934
    end.
853
935
 
936
1018
    print(printable(Severity,Verbosity), P, F, A).
937
1019
 
938
1020
print(true, P, F, A) ->
 
1021
    print(P, F, A);
 
1022
print(_, _, _, _) ->
 
1023
    ok.
 
1024
 
 
1025
print(P, F, A) ->
939
1026
    io:format("*** [~s] ~s ~p ~s ***"
940
1027
              "~n   " ++ F ++ "~n~n", 
941
 
              [format_timestamp(now()), P, self(), get(sname) | A]);
942
 
print(_, _, _, _) ->
943
 
    ok.
944
 
 
945
 
 
946
 
format_timestamp(Now) ->
947
 
    {N1, N2, N3} = Now,
 
1028
              [format_timestamp(now()), P, self(), get(sname) | A]).
 
1029
 
 
1030
format_timestamp({_N1, _N2, N3} = Now) ->
948
1031
    {Date, Time}   = calendar:now_to_datetime(Now),
949
1032
    {YYYY,MM,DD}   = Date,
950
1033
    {Hour,Min,Sec} = Time,