~ubuntu-branches/ubuntu/karmic/erlang/karmic-security

« back to all changes in this revision

Viewing changes to lib/megaco/test/megaco_test_mgc.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%%<copyright>
2
 
%% <year>2003-2007</year>
3
 
%% <holder>Ericsson AB, All Rights Reserved</holder>
4
 
%%</copyright>
5
 
%%<legalnotice>
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2003-2009. All Rights Reserved.
 
5
%% 
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%%
 
11
%% 
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
 
16
%% 
 
17
%% %CopyrightEnd%
16
18
%%
17
 
%% The Initial Developer of the Original Code is Ericsson AB.
18
 
%%</legalnotice>
 
19
 
19
20
%%
20
21
%%----------------------------------------------------------------------
21
22
%% Purpose: Implements an "MGC" used by the test suite
72
73
              ack_info    = undefined,
73
74
              abort_info  = undefined,
74
75
              req_info    = undefined,
75
 
              mg          = []}).
 
76
              mg          = [],
 
77
              dsi_timer}).
76
78
 
77
79
 
78
80
%%% ------------------------------------------------------------------
95
97
 
96
98
mk_recv_info([], Acc) ->
97
99
    Acc;
98
 
mk_recv_info([{Encoding, Transport}|ET], Acc) ->
 
100
mk_recv_info([{Encoding, Transport}|ET], Acc) 
 
101
  when is_atom(Encoding) andalso is_atom(Transport) ->
99
102
    {EMod, Port} = select_encoding(Encoding),
100
103
    TMod         = select_transport(Transport),
101
104
    RI = [{encoding_module,  EMod},
103
106
          {transport_module, TMod},
104
107
          {port,             Port}],
105
108
    mk_recv_info(ET, [RI|Acc]);
106
 
mk_recv_info([{Encoding, EC, Transport}|ET], Acc) ->
 
109
mk_recv_info([{Encoding, Transport, TO}|ET], Acc) 
 
110
  when is_atom(Encoding) andalso is_atom(Transport) andalso is_list(TO) ->
 
111
    {EMod, Port} = select_encoding(Encoding),
 
112
    TMod         = select_transport(Transport),
 
113
    RI = [{encoding_module,  EMod},
 
114
          {encoding_config,  []},
 
115
          {transport_module, TMod},
 
116
          {port,             Port},
 
117
          {transport_opts,   TO}],
 
118
    mk_recv_info(ET, [RI|Acc]);
 
119
mk_recv_info([{Encoding, EC, Transport}|ET], Acc) 
 
120
  when is_atom(Encoding) andalso is_list(EC) andalso is_atom(Transport) ->
107
121
    {EMod, Port} = select_encoding(Encoding),
108
122
    TMod         = select_transport(Transport),
109
123
    RI = [{encoding_module,  EMod},
266
280
    put(verbosity, Verbosity),
267
281
    put(sname,   "MGC"),
268
282
    i("mgc -> starting"),
269
 
    {Mid, TcpSup, UdpSup} = init(Config),
 
283
    {Mid, TcpSup, UdpSup, DSITimer} = init(Config),
270
284
    notify_started(Parent),
271
 
    S = #mgc{parent = Parent, 
272
 
             tcp_sup = TcpSup, udp_sup = UdpSup, mid = Mid},
 
285
    S = #mgc{parent    = Parent, 
 
286
             tcp_sup   = TcpSup, 
 
287
             udp_sup   = UdpSup, 
 
288
             mid       = Mid,
 
289
             dsi_timer = DSITimer},
273
290
    i("mgc -> started"),
 
291
    display_system_info("at start "),
274
292
    loop(S).
275
293
 
276
294
init(Config) ->
279
297
    Mid = get_conf(local_mid, Config),
280
298
    RI  = get_conf(receive_info, Config),
281
299
 
 
300
    d("init -> maybe start the display system info timer"),
 
301
    DSITimer = 
 
302
        case get_conf(display_system_info, Config, undefined) of
 
303
            Time when is_integer(Time) ->
 
304
                d("init -> creating display system info timer"),
 
305
                create_timer(Time, display_system_info);
 
306
            _ ->
 
307
                undefined
 
308
        end,
 
309
    Conf0 = lists:keydelete(display_system_info, 1, Config),
 
310
 
282
311
    d("init -> start megaco"),
283
312
    application:start(megaco),
284
313
 
293
322
        _ ->
294
323
            ok
295
324
    end,
296
 
    Conf0 = lists:keydelete(megaco_trace,    1, Config),
 
325
    Conf1 = lists:keydelete(megaco_trace,    1, Conf0),
297
326
 
298
327
    d("init -> start megaco user"),
299
 
    Conf1 = lists:keydelete(local_mid,    1, Conf0),
300
 
    Conf2 = lists:keydelete(receive_info, 1, Conf1),
301
 
    ok = megaco:start_user(Mid, Conf2),
 
328
    Conf2 = lists:keydelete(local_mid,    1, Conf1),
 
329
    Conf3 = lists:keydelete(receive_info, 1, Conf2),
 
330
    ok = megaco:start_user(Mid, Conf3),
302
331
 
303
332
    d("init -> update user info (user_mod)"),
304
333
    ok = megaco:update_user_info(Mid, user_mod,  ?MODULE),
313
342
 
314
343
    d("init -> start transports"),
315
344
    {Tcp, Udp} = start_transports(Transports),
316
 
    {Mid, Tcp, Udp}.
 
345
    {Mid, Tcp, Udp, DSITimer}.
317
346
    
318
 
 
319
347
loop(S) ->
320
348
    d("loop -> await request"),
321
349
    receive
322
 
        {stop, Parent} when S#mgc.parent == Parent ->
 
350
        {display_system_info, Time} ->
 
351
            display_system_info(S#mgc.mid),
 
352
            NewTimer = create_timer(Time, display_system_info),
 
353
            loop(S#mgc{dsi_timer = NewTimer});
 
354
 
 
355
        {stop, Parent} when S#mgc.parent =:= Parent ->
323
356
            i("loop -> stopping", []),
 
357
            display_system_info(S#mgc.mid, "at finish "),
 
358
            cancel_timer(S#mgc.dsi_timer),
324
359
            Mid = S#mgc.mid,
325
360
            (catch close_conns(Mid)),
326
361
            megaco:stop_user(Mid),
467
502
            loop(S);
468
503
 
469
504
 
470
 
        {'EXIT', Pid, Reason} ->
471
 
            error_msg("MGC received unexpected exit signal from ~p:~n~p", 
472
 
                      [Pid, Reason]),
473
 
            loop(S);
 
505
        {'EXIT', Pid, Reason} when S#mgc.tcp_sup =:= Pid ->
 
506
            error_msg("MGC received unexpected exit "
 
507
                      "from TCP transport supervisor (~p):~n~p", 
 
508
                      [Pid, Reason]),
 
509
            i("loop -> [tcp] exiting", []),
 
510
            display_system_info(S#mgc.mid, "at bad finish (tcp) "),
 
511
            cancel_timer(S#mgc.dsi_timer),
 
512
            Mid = S#mgc.mid,
 
513
            (catch close_conns(Mid)),
 
514
            megaco:stop_user(Mid),
 
515
            application:stop(megaco),
 
516
            i("loop -> stopped", []),
 
517
            StopReason = {error, {tcp_terminated, Pid, Reason}}, 
 
518
            server_reply(S#mgc.parent, stopped, StopReason),
 
519
            exit(StopReason);
 
520
 
 
521
 
 
522
        {'EXIT', Pid, Reason} when S#mgc.udp_sup =:= Pid ->
 
523
            error_msg("MGC received unexpected exit "
 
524
                      "from UDP transport supervisor (~p):~n~p", 
 
525
                      [Pid, Reason]),
 
526
            i("loop -> [udp] exiting", []),
 
527
            display_system_info(S#mgc.mid, "at bad finish (udp) "),
 
528
            cancel_timer(S#mgc.dsi_timer),
 
529
            Mid = S#mgc.mid,
 
530
            (catch close_conns(Mid)),
 
531
            megaco:stop_user(Mid),
 
532
            application:stop(megaco),
 
533
            i("loop -> stopped", []),
 
534
            StopReason = {error, {udp_terminated, Pid, Reason}}, 
 
535
            server_reply(S#mgc.parent, stopped, StopReason),
 
536
            exit(StopReason);
474
537
 
475
538
 
476
539
        Invalid ->
553
616
    TM = get_transport_module(RI),
554
617
    d("parse_receive_info1 -> get transport port"),
555
618
    TP = get_transport_port(RI),
 
619
    d("parse_receive_info1 -> get transport opts"),
 
620
    TO = get_transport_opts(RI),
556
621
    RH1 = RH#megaco_receive_handle{send_mod        = TM,
557
622
                                   encoding_mod    = EM,
558
623
                                   encoding_config = EC},
559
624
    d("parse_receive_info1 -> "
 
625
      "~n   Transport Opts: ~p"
560
626
      "~n   Port:           ~p"
561
 
      "~n   Receive handle: ~p", [TP, RH1]),
562
 
    {TP, RH1}.
 
627
      "~n   Receive handle: ~p", [TO, TP, RH1]),
 
628
    {TO, TP, RH1}.
563
629
 
564
630
 
565
631
 
582
648
    
583
649
start_transports1([], Tcp, Udp) ->
584
650
    {Tcp, Udp};
585
 
start_transports1([{_Port, RH}|Transports], Tcp, Udp) 
 
651
start_transports1([{_TO, _Port, RH}|Transports], Tcp, Udp) 
586
652
  when ((RH#megaco_receive_handle.send_mod =:= megaco_tcp) andalso 
587
653
        (not is_pid(Tcp)))  ->
588
654
    case megaco_tcp:start_transport() of
591
657
        Else ->
592
658
            throw({error, {failed_starting_tcp_transport, Else}})
593
659
    end;
594
 
start_transports1([{_Port, RH}|Transports], Tcp, Udp) 
 
660
start_transports1([{_TO, _Port, RH}|Transports], Tcp, Udp) 
595
661
  when ((RH#megaco_receive_handle.send_mod =:= megaco_udp) andalso 
596
662
        (not is_pid(Udp))) ->
597
663
    case megaco_udp:start_transport() of
605
671
 
606
672
start_transports2([], _, _) ->
607
673
    ok;
608
 
start_transports2([{Port, RH}|Transports], Tcp, Udp) 
 
674
start_transports2([{TO, Port, RH}|Transports], Tcp, Udp) 
609
675
  when RH#megaco_receive_handle.send_mod =:= megaco_tcp ->
610
 
    start_tcp(RH, Port, Tcp),
 
676
    start_tcp(TO, RH, Port, Tcp),
611
677
    start_transports2(Transports, Tcp, Udp);
612
 
start_transports2([{Port, RH}|Transports], Tcp, Udp) 
 
678
start_transports2([{TO, Port, RH}|Transports], Tcp, Udp) 
613
679
  when RH#megaco_receive_handle.send_mod =:= megaco_udp ->
614
 
    start_udp(RH, Port, Udp),
 
680
    start_udp(TO, RH, Port, Udp),
615
681
    start_transports2(Transports, Tcp, Udp).
616
682
 
617
 
start_tcp(RH, Port, Sup) ->
 
683
start_tcp(TO, RH, Port, Sup) ->
618
684
    d("start tcp transport"),
619
 
    start_tcp(RH, Port, Sup, 250).
 
685
    start_tcp(TO, RH, Port, Sup, 250).
620
686
 
621
 
start_tcp(RH, Port, Sup, Timeout) 
 
687
start_tcp(TO, RH, Port, Sup, Timeout) 
622
688
  when is_pid(Sup) andalso is_integer(Timeout) andalso (Timeout > 0) ->
623
689
    d("tcp listen on ~p", [Port]),
624
690
    Opts = [{port,           Port}, 
625
691
            {receive_handle, RH}, 
626
 
            {tcp_options,    [{nodelay, true}]}],
 
692
            {tcp_options,    [{nodelay, true}]}] ++ TO,
627
693
    try_start_tcp(Sup, Opts, Timeout, noError).
628
694
 
629
695
try_start_tcp(Sup, Opts, Timeout, Error0) when (Timeout < 5000) ->
647
713
    throw({error, {failed_starting_tcp_listen, Error}}).
648
714
 
649
715
 
650
 
start_udp(RH, Port, Sup) ->
 
716
start_udp(TO, RH, Port, Sup) ->
651
717
    d("start udp transport"),
652
 
    start_udp(RH, Port, Sup, 250).
 
718
    start_udp(TO, RH, Port, Sup, 250).
653
719
 
654
 
start_udp(RH, Port, Sup, Timeout) ->
 
720
start_udp(TO, RH, Port, Sup, Timeout) ->
655
721
    d("udp open ~p", [Port]),
656
 
    Opts = [{port, Port}, {receive_handle, RH}],
 
722
    Opts = [{port, Port}, {receive_handle, RH}] ++ TO,
657
723
    try_start_udp(Sup, Opts, Timeout, noError).
658
724
 
659
725
try_start_udp(Sup, Opts, Timeout, Error0) when (Timeout < 5000) ->
1049
1115
get_transport_port(RI) ->
1050
1116
    get_conf(port, RI).
1051
1117
 
 
1118
get_transport_opts(RI) ->
 
1119
    get_conf(transport_opts, RI, []).
 
1120
 
1052
1121
 
1053
1122
get_conf(Key, Config) ->
1054
1123
    case lists:keysearch(Key, 1, Config) of
1058
1127
            exit({error, {not_found, Key, Config}})
1059
1128
    end.
1060
1129
 
 
1130
get_conf(Key, Config, Default) ->
 
1131
    case lists:keysearch(Key, 1, Config) of
 
1132
        {value, {Key, Val}} ->
 
1133
            Val;
 
1134
        _ ->
 
1135
            Default
 
1136
    end.
 
1137
 
1061
1138
 
1062
1139
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1063
1140
 
1069
1146
    random:uniform(N).
1070
1147
 
1071
1148
 
 
1149
display_system_info(Mid) ->
 
1150
    display_system_info(Mid, "").
 
1151
 
 
1152
display_system_info(Mid, Pre) ->
 
1153
    TimeStr = format_timestamp(now()),
 
1154
    MibStr  = lists:flatten(io_lib:format("~p ", [Mid])), 
 
1155
    megaco_test_lib:display_system_info(MibStr ++ Pre ++ TimeStr).
 
1156
 
 
1157
 
 
1158
create_timer(Time, Event) ->
 
1159
    erlang:send_after(Time, self(), {Event, Time}).
 
1160
 
 
1161
cancel_timer(undefined) ->
 
1162
    ok;
 
1163
cancel_timer(Ref) ->
 
1164
    erlang:cancel_timer(Ref).
 
1165
 
 
1166
 
1072
1167
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1073
1168
 
1074
1169
i(F) ->