~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
65
65
     garbage_in
66
66
    ].
67
67
 
 
68
 
68
69
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
69
70
 
70
71
plain(suite) ->
73
74
    ["This is to simply test that it is possible to start and stop the "
74
75
     "flex handler."];
75
76
plain(Config) when is_list(Config) ->
76
 
    {ok, Pid, _PortInfo} = megaco_flex_scanner_handler:start_link(),
77
 
    megaco_flex_scanner_handler:stop(Pid),
 
77
    put(tc, plain), 
 
78
    p("begin"),
 
79
    process_flag(trap_exit, true),
 
80
    p("start the flex handler"),
 
81
    {ok, Pid, _PortInfo} = flex_scanner_handler_start(), 
 
82
    p("stop handler"),
 
83
    flex_scanner_handler_stop(Pid),
 
84
    p("end"),
78
85
    ok.
79
86
 
80
87
 
85
92
port_exit(doc) ->
86
93
    ["Test that the handler detects and handles an exiting port."];
87
94
port_exit(Config) when is_list(Config) ->
 
95
    put(tc, port_exit), 
 
96
    p("begin"),
88
97
    process_flag(trap_exit, true),
89
98
 
90
 
    {ok, Pid, {flex, Port}} = megaco_flex_scanner_handler:start_link(),
 
99
    p("start the flex handler"),
 
100
    {ok, Pid, {flex, Port}} = flex_scanner_handler_start(), 
91
101
 
 
102
    p("simulate crash"),
92
103
    exit(Port, simulated_crash), 
93
104
    
 
105
    p("await handler exit"),
94
106
    receive
95
107
        {'EXIT', Pid, _} ->
 
108
            p("end"),
96
109
            ok
97
110
    after 5000 ->
98
 
            megaco_flex_scanner_handler:stop(Pid),
 
111
            p("timeout - stop handler"),
 
112
            flex_scanner_handler_stop(Pid),
 
113
            p("end after timeout"),
99
114
            {error, timeout}
100
115
    end.
101
116
 
108
123
    ["Send in various unexpected messages and requeststo the handler "
109
124
     "to see that it does die on us. "];
110
125
garbage_in(Config) when is_list(Config) ->
 
126
    put(tc, garbage_in), 
 
127
    p("begin"),
111
128
    process_flag(trap_exit, true),
112
129
 
113
 
    {ok, Pid, _PortInfo} = megaco_flex_scanner_handler:start_link(),
 
130
    p("start the flex handler"),
 
131
    {ok, Pid, _PortInfo} = flex_scanner_handler_start(), 
114
132
 
 
133
    p("make an invalid call"),
115
134
    {error, _} = gen_server:call(Pid, garbage_request), 
 
135
    p("make an invalid cast"),
116
136
    gen_server:cast(Pid, garbage_msg),
 
137
    p("send an unknown message"),
117
138
    Pid ! garbage_info,
118
139
 
 
140
    p("wait for any garbage response"),
119
141
    receive
120
142
        Any ->
 
143
            p("end with unexpected message: ~p", [Any]),
121
144
            {error, {unexpected_msg, Any}}
122
145
    after 1000 ->
123
 
            megaco_flex_scanner_handler:stop(Pid),
 
146
            p("end with nothing received - stop handler"),
 
147
            flex_scanner_handler_stop(Pid),
124
148
            ok
125
149
    end.
126
150
 
 
151
 
 
152
 
 
153
%% ------- Misc functions --------
 
154
 
 
155
flex_scanner_handler_start() ->
 
156
    case megaco_flex_scanner_handler:start_link() of
 
157
        {error, {failed_starting_scanner, {error, {load_driver, _}}}} ->
 
158
            p("failed loading driver"),
 
159
            ?SKIP(could_not_load_driver);
 
160
        {error, {failed_starting_scanner, {load_driver, _}}} ->
 
161
            p("failed loading driver"),
 
162
            ?SKIP(could_not_load_driver);
 
163
        Else ->
 
164
            p("driver load result: ~p", [Else]),
 
165
            Else
 
166
    end.
 
167
 
 
168
flex_scanner_handler_stop(Pid) ->
 
169
    megaco_flex_scanner_handler:stop(Pid).
 
170
 
 
171
 
 
172
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
173
 
 
174
p(F) ->
 
175
    p(F, []).
 
176
 
 
177
p(F, A) ->
 
178
    TC = get(tc),
 
179
    io:format("*** [~s] ~p ~w ***"
 
180
              "~n   " ++ F ++ "~n",
 
181
              [formated_timestamp(), self(), TC | A]).
 
182
 
 
183
formated_timestamp() ->
 
184
    format_timestamp(erlang:now()).
 
185
 
 
186
format_timestamp({_N1, _N2, N3} = Now) ->
 
187
    {Date, Time}     = calendar:now_to_datetime(Now),
 
188
    {YYYY, MM, DD}   = Date,
 
189
    {Hour, Min, Sec} = Time,
 
190
    FormatDate =
 
191
        io_lib:format("~.4w:~.2.0w:~.2.0w ~.2.0w:~.2.0w:~.2.0w 4~w",
 
192
                      [YYYY,MM,DD,Hour,Min,Sec,round(N3/1000)]),
 
193
    lists:flatten(FormatDate).
 
194
 
 
195