~ubuntu-branches/ubuntu/lucid/erlang/lucid

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-06-11 12:18:07 UTC
  • mfrom: (1.2.2 upstream)
  • Revision ID: james.westby@ubuntu.com-20090611121807-ks7eb4xrt7dsysgx
Tags: 1:13.b.1-dfsg-1
* New upstream release.
* Removed unnecessary dependency of erlang-os-mon on erlang-observer and
  erlang-tools and added missing dependency of erlang-nox on erlang-os-mon
  (closes: #529512).
* Removed a patch to eunit application because the bug was fixed upstream.

Show diffs side-by-side

added added

removed removed

Lines of Context:
48
48
 
49
49
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
50
50
 
51
 
init(Config) when list(Config) ->
 
51
init(Config) when is_list(Config) ->
52
52
    Flag = process_flag(trap_exit, true),    
53
53
    Res = (catch start()),
54
54
    process_flag(trap_exit, Flag),
60
60
    end.
61
61
    
62
62
 
63
 
finish(Config) when list(Config) ->
 
63
finish(Config) when is_list(Config) ->
64
64
    case lists:keysearch(flex_scanner, 1, Config) of
65
65
        {value, {flex_scanner, {Pid, _Conf}}} ->
66
66
            stop(Pid),
89
89
    end.
90
90
 
91
91
 
92
 
scanner_conf(Config) when list(Config) ->
 
92
scanner_conf(Config) when is_list(Config) ->
93
93
    case lists:keysearch(flex_scanner, 1, Config) of
94
94
        {value, {flex_scanner, {Pid, Conf}}} ->
95
95
            case ping_flex_scanner(Pid) of
118
118
 
119
119
 
120
120
handler(Pid) ->
121
 
    case (catch megaco_flex_scanner:start()) of
122
 
        {ok, Port} when port(Port) ->
123
 
            Pid ! {flex_scanner_started, self(), {flex, Port}},
124
 
            handler(Pid, Port);
 
121
    SMP = erlang:system_info(smp_support), 
 
122
    case (catch megaco_flex_scanner:start(SMP)) of
 
123
        {ok, PortOrPorts} ->
 
124
            Pid ! {flex_scanner_started, self(), {flex, PortOrPorts}},
 
125
            handler(Pid, PortOrPorts);
125
126
        {error, {load_driver, {open_error, Reason}}} ->
126
127
            Error = {failed_loading_flex_scanner_driver, Reason},
127
128
            Pid ! {flex_scanner_error, Error},
136
137
            exit(Error)
137
138
    end.
138
139
 
139
 
handler(Pid, Port) ->
 
140
handler(Pid, PortOrPorts) ->
140
141
    receive
141
142
        {ping, Pinger} ->
142
143
            Pinger ! {pong, self()},
143
 
            handler(Pid, Port);
144
 
        {'EXIT', Port, Reason} ->
 
144
            handler(Pid, PortOrPorts);
 
145
        {'EXIT', Port, Reason} when (PortOrPorts =:= Port) ->
145
146
            Pid ! {flex_scanner_exit, Reason},
146
147
            exit({flex_scanner_exit, Reason});
 
148
        {'EXIT', Port, Reason} when is_port(Port) ->
 
149
            case megaco_flex_scanner:is_scanner_port(Port, PortOrPorts) of
 
150
                true ->
 
151
                    Pid ! {flex_scanner_exit, Reason},
 
152
                    exit({flex_scanner_exit, Reason});
 
153
                false ->
 
154
                    io:format("flex scanner handler got port exit "
 
155
                              "from unknown:"
 
156
                              "~n   ~p: ~p", [Port, Reason]),
 
157
                    ok
 
158
            end,
 
159
            handler(Pid, PortOrPorts);
147
160
        stop ->
148
 
            megaco_flex_scanner:stop(Port),
 
161
            megaco_flex_scanner:stop(PortOrPorts),
149
162
            exit(normal);
150
163
        Other ->
151
164
            io:format("flex scanner handler got something:~n"
152
165
                      "~p", [Other]),
153
 
            handler(Pid, Port)
 
166
            handler(Pid, PortOrPorts)
154
167
    end.
155
168
            
156
169