~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/inets/test/tftp_test_lib.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2007-2010. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%% 
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%% 
 
17
%% %CopyrightEnd%
 
18
%%
 
19
 
 
20
-module(tftp_test_lib).
 
21
 
 
22
-compile(export_all).
 
23
 
 
24
-include("tftp_test_lib.hrl").
 
25
 
 
26
%%
 
27
%% -----
 
28
%%
 
29
 
 
30
init_per_testcase(_Case, Config) when is_list(Config) ->
 
31
    io:format("\n ", []),
 
32
    ?IGNORE(application:stop(inets)),   
 
33
    Config.
 
34
 
 
35
end_per_testcase(_Case, Config) when is_list(Config) ->
 
36
    ?IGNORE(application:stop(inets)),   
 
37
    Config.
 
38
 
 
39
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
40
%% Infrastructure for test suite
 
41
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
42
 
 
43
error(Actual, Mod, Line) ->
 
44
    (catch global:send(tftp_global_logger, {failed, Mod, Line})),
 
45
    log("<ERROR> Bad result: ~p\n", [Actual], Mod, Line),
 
46
    Label = lists:concat([Mod, "(", Line, ") unexpected result"]),
 
47
    et:report_event(60, Mod, Mod, Label,
 
48
                        [{line, Mod, Line}, {error, Actual}]),
 
49
    case global:whereis_name(tftp_test_case_sup) of
 
50
        undefined -> 
 
51
            ignore;
 
52
        Pid -> 
 
53
            Fail = #'REASON'{mod = Mod, line = Line, desc = Actual},
 
54
            Pid ! {fail, self(), Fail}
 
55
    end,
 
56
    Actual.
 
57
 
 
58
log(Format, Args, Mod, Line) ->
 
59
    case global:whereis_name(tftp_global_logger) of
 
60
        undefined ->
 
61
            io:format(user, "~p(~p): " ++ Format, 
 
62
                      [Mod, Line] ++ Args);
 
63
        Pid ->
 
64
            io:format(Pid, "~p(~p): " ++ Format, 
 
65
                      [Mod, Line] ++ Args)
 
66
    end.
 
67
 
 
68
default_config() ->
 
69
    [].
 
70
 
 
71
t() -> 
 
72
    t([{?MODULE, all}]).
 
73
 
 
74
t(Cases) ->
 
75
    t(Cases, default_config()).
 
76
 
 
77
t(Cases, Config) ->
 
78
    process_flag(trap_exit, true),
 
79
    Res = lists:flatten(do_test(Cases, Config)),
 
80
    io:format("Res: ~p\n", [Res]),
 
81
    display_result(Res),
 
82
    Res.
 
83
 
 
84
do_test({Mod, Fun}, Config) when is_atom(Mod), is_atom(Fun) ->
 
85
    case catch apply(Mod, Fun, [suite]) of
 
86
        [] ->
 
87
            io:format("Eval:   ~p:", [{Mod, Fun}]),
 
88
            Res = eval(Mod, Fun, Config),
 
89
            {R, _, _} = Res,
 
90
            io:format(" ~p\n", [R]),
 
91
            Res;
 
92
 
 
93
        Cases when is_list(Cases) ->
 
94
            io:format("Expand: ~p ...\n", [{Mod, Fun}]),
 
95
            Map = fun(Case) when is_atom(Case)-> {Mod, Case};
 
96
                     (Case) -> Case
 
97
                  end,
 
98
            do_test(lists:map(Map, Cases), Config);
 
99
 
 
100
        {req, _, {conf, Init, Cases, Finish}} ->
 
101
            case (catch apply(Mod, Init, [Config])) of
 
102
                Conf when is_list(Conf) ->
 
103
                    io:format("Expand: ~p ...\n", [{Mod, Fun}]),
 
104
                    Map = fun(Case) when is_atom(Case)-> {Mod, Case};
 
105
                             (Case) -> Case
 
106
                          end,
 
107
                    Res = do_test(lists:map(Map, Cases), Conf),
 
108
                    (catch apply(Mod, Finish, [Conf])),
 
109
                    Res;
 
110
                    
 
111
                {'EXIT', {skipped, Reason}} ->
 
112
                    io:format(" => skipping: ~p\n", [Reason]),
 
113
                    [{skipped, {Mod, Fun}, Reason}];
 
114
                    
 
115
                Error ->
 
116
                    io:format(" => failed: ~p\n", [Error]),
 
117
                    [{failed, {Mod, Fun}, Error}]
 
118
            end;
 
119
                    
 
120
        {'EXIT', {undef, _}} ->
 
121
            io:format("Undefined:   ~p\n", [{Mod, Fun}]),
 
122
            [{nyi, {Mod, Fun}, ok}];
 
123
                    
 
124
        Error ->
 
125
            io:format("Ignoring:   ~p: ~p\n", [{Mod, Fun}, Error]),
 
126
            [{failed, {Mod, Fun}, Error}]
 
127
    end;
 
128
do_test(Mod, Config) when is_atom(Mod) ->
 
129
    Res = do_test({Mod, all}, Config),
 
130
    Res;
 
131
do_test(Cases, Config) when is_list(Cases) ->
 
132
    [do_test(Case, Config) || Case <- Cases];
 
133
do_test(Bad, _Config) ->
 
134
    [{badarg, Bad, ok}].
 
135
 
 
136
eval(Mod, Fun, Config) ->
 
137
    TestCase = {?MODULE, Mod, Fun},
 
138
    Label = lists:concat(["TEST CASE: ", Fun]),
 
139
    et:report_event(40, ?MODULE, Mod, Label ++ " started",
 
140
                        [TestCase, Config]),
 
141
    global:register_name(tftp_test_case_sup, self()),
 
142
    Flag = process_flag(trap_exit, true),
 
143
    Config2 = Mod:init_per_testcase(Fun, Config),
 
144
    Pid = spawn_link(?MODULE, do_eval, [self(), Mod, Fun, Config2]),
 
145
    R = wait_for_evaluator(Pid, Mod, Fun, Config2, []),
 
146
    Mod:end_per_testcase(Fun, Config2),
 
147
    global:unregister_name(tftp_test_case_sup),
 
148
    process_flag(trap_exit, Flag),
 
149
    R.
 
150
 
 
151
wait_for_evaluator(Pid, Mod, Fun, Config, Errors) ->
 
152
    TestCase = {?MODULE, Mod, Fun},
 
153
    Label = lists:concat(["TEST CASE: ", Fun]),
 
154
    receive
 
155
        {done, Pid, ok} when Errors == [] ->
 
156
            et:report_event(40, Mod, ?MODULE, Label ++ " ok",
 
157
                                [TestCase, Config]),
 
158
            {ok, {Mod, Fun}, Errors};
 
159
        {done, Pid, {ok, _}} when Errors == [] ->
 
160
            et:report_event(40, Mod, ?MODULE, Label ++ " ok",
 
161
                                [TestCase, Config]),
 
162
            {ok, {Mod, Fun}, Errors};
 
163
        {done, Pid, Fail} ->
 
164
            et:report_event(20, Mod, ?MODULE, Label ++ " failed",
 
165
                                [TestCase, Config, {return, Fail}, Errors]),
 
166
            {failed, {Mod,Fun}, Fail};
 
167
        {'EXIT', Pid, {skipped, Reason}} -> 
 
168
            et:report_event(20, Mod, ?MODULE, Label ++ " skipped",
 
169
                                [TestCase, Config, {skipped, Reason}]),
 
170
            {skipped, {Mod, Fun}, Errors};
 
171
        {'EXIT', Pid, Reason} -> 
 
172
            et:report_event(20, Mod, ?MODULE, Label ++ " crashed",
 
173
                                [TestCase, Config, {'EXIT', Reason}]),
 
174
            {crashed, {Mod, Fun}, [{'EXIT', Reason} | Errors]};
 
175
        {fail, Pid, Reason} ->
 
176
            wait_for_evaluator(Pid, Mod, Fun, Config, Errors ++ [Reason])
 
177
    end.
 
178
 
 
179
do_eval(ReplyTo, Mod, Fun, Config) ->
 
180
    case (catch apply(Mod, Fun, [Config])) of
 
181
        {'EXIT', {skipped, Reason}} ->
 
182
            ReplyTo ! {'EXIT', self(), {skipped, Reason}};
 
183
        Other ->
 
184
            ReplyTo ! {done, self(), Other}
 
185
    end,
 
186
    unlink(ReplyTo),
 
187
    exit(shutdown).
 
188
 
 
189
display_result([]) ->    
 
190
    io:format("OK\n", []);
 
191
display_result(Res) when is_list(Res) ->
 
192
    Ok      = [MF || {ok, MF, _}  <- Res],
 
193
    Nyi     = [MF || {nyi, MF, _} <- Res],
 
194
    Skipped = [{MF, Reason} || {skipped, MF, Reason} <- Res],
 
195
    Failed  = [{MF, Reason} || {failed, MF, Reason} <- Res],
 
196
    Crashed = [{MF, Reason} || {crashed, MF, Reason} <- Res],
 
197
    display_summary(Ok, Nyi, Skipped, Failed, Crashed),
 
198
    display_skipped(Skipped),
 
199
    display_failed(Failed),
 
200
    display_crashed(Crashed).
 
201
 
 
202
display_summary(Ok, Nyi, Skipped, Failed, Crashed) ->
 
203
    io:format("\nTest case summary:\n", []),
 
204
    display_summary(Ok,      "successful"),
 
205
    display_summary(Nyi,     "not yet implemented"),
 
206
    display_summary(Skipped, "skipped"),
 
207
    display_summary(Failed,  "failed"),
 
208
    display_summary(Crashed, "crashed"),
 
209
    io:format("\n", []).
 
210
   
 
211
display_summary(Res, Info) ->
 
212
    io:format("  ~w test cases ~s\n", [length(Res), Info]).
 
213
    
 
214
display_skipped([]) ->
 
215
    ok;
 
216
display_skipped(Skipped) ->
 
217
    io:format("Skipped test cases:\n", []),
 
218
    F = fun({MF, Reason}) -> io:format("  ~p => ~p\n", [MF, Reason]) end,
 
219
    lists:foreach(F, Skipped),
 
220
    io:format("\n", []).
 
221
    
 
222
 
 
223
display_failed([]) ->
 
224
    ok;
 
225
display_failed(Failed) ->
 
226
    io:format("Failed test cases:\n", []),
 
227
    F = fun({MF, Reason}) -> io:format("  ~p => ~p\n", [MF, Reason]) end,
 
228
    lists:foreach(F, Failed),
 
229
    io:format("\n", []).
 
230
 
 
231
display_crashed([]) ->
 
232
    ok;
 
233
display_crashed(Crashed) ->
 
234
    io:format("Crashed test cases:\n", []),
 
235
    F = fun({MF, Reason}) -> io:format("  ~p => ~p\n", [MF, Reason]) end,
 
236
    lists:foreach(F, Crashed),
 
237
    io:format("\n", []).
 
238
 
 
239
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
240
%% generic callback
 
241
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
242
 
 
243
-record(generic_state, {state, prepare, open, read, write, abort}).
 
244
 
 
245
prepare(Peer, Access, LocalFilename, Mode, SuggestedOptions, Initial) when is_list(Initial) ->
 
246
    State   = lookup_option(state,   mandatory, Initial),
 
247
    Prepare = lookup_option(prepare, mandatory, Initial),
 
248
    Open    = lookup_option(open,    mandatory, Initial),
 
249
    Read    = lookup_option(read,    mandatory, Initial),
 
250
    Write   = lookup_option(write,   mandatory, Initial),
 
251
    Abort   = lookup_option(abort,   mandatory, Initial),
 
252
    case Prepare(Peer, Access, LocalFilename, Mode, SuggestedOptions, State) of
 
253
        {ok, AcceptedOptions, NewState} ->
 
254
            {ok,
 
255
             AcceptedOptions,
 
256
             #generic_state{state   = NewState,
 
257
                            prepare = Prepare,
 
258
                            open    = Open,
 
259
                            read    = Read,
 
260
                            write   = Write,
 
261
                            abort   = Abort}};
 
262
        Other ->
 
263
            Other
 
264
    end.
 
265
 
 
266
open(Peer, Access, LocalFilename, Mode, SuggestedOptions, Initial) when is_list(Initial) ->
 
267
    case prepare(Peer, Access, LocalFilename, Mode, SuggestedOptions, Initial) of
 
268
        {ok, SuggestedOptions2, GenericState} ->
 
269
            open(Peer, Access, LocalFilename, Mode, SuggestedOptions2, GenericState);
 
270
        Other ->
 
271
            Other
 
272
    end;
 
273
open(Peer, Access, LocalFilename, Mode, SuggestedOptions, #generic_state{state = State, open = Open} = GenericState) ->
 
274
    case Open(Peer, Access, LocalFilename, Mode, SuggestedOptions, State) of
 
275
        {ok, SuggestedOptions2, NewState} ->
 
276
            {ok, SuggestedOptions2, GenericState#generic_state{state = NewState}};
 
277
        Other ->
 
278
            Other
 
279
    end.
 
280
 
 
281
read(#generic_state{state = State, read = Read} = GenericState) ->
 
282
    case Read(State) of
 
283
        {more, DataBlock, NewState} ->
 
284
            {more, DataBlock, GenericState#generic_state{state = NewState}};
 
285
        Other ->
 
286
            Other
 
287
    end.
 
288
 
 
289
write(DataBlock, #generic_state{state = State, write = Write} = GenericState) ->
 
290
    case Write(DataBlock, State) of
 
291
        {more, NewState} ->
 
292
            {more, GenericState#generic_state{state = NewState}};
 
293
        Other ->
 
294
            Other
 
295
    end.
 
296
 
 
297
abort(Code, Text, #generic_state{state = State, abort = Abort}) ->
 
298
    Abort(Code, Text, State).
 
299
 
 
300
lookup_option(Key, Default, Options) ->
 
301
    case lists:keysearch(Key, 1, Options) of
 
302
        {value, {_, Val}} ->
 
303
            Val;
 
304
        false ->
 
305
            Default
 
306
    end.
 
307