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

« back to all changes in this revision

Viewing changes to lib/debugger/test/exception_SUITE.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 1999-2011. 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
%%
 
21
-module(exception_SUITE).
 
22
 
 
23
-export([all/0, suite/0,groups/0,init_per_group/2,end_per_group/2,
 
24
         init_per_testcase/2,end_per_testcase/2,
 
25
         init_per_suite/1,end_per_suite/1,
 
26
         badmatch/1,pending_errors/1,nil_arith/1]).
 
27
 
 
28
-export([bad_guy/2]).
 
29
 
 
30
-include_lib("test_server/include/test_server.hrl").
 
31
 
 
32
suite() -> [{ct_hooks,[ts_install_cth]}].
 
33
 
 
34
all() -> 
 
35
    cases().
 
36
 
 
37
groups() -> 
 
38
    [].
 
39
 
 
40
init_per_group(_GroupName, Config) ->
 
41
    Config.
 
42
 
 
43
end_per_group(_GroupName, Config) ->
 
44
    Config.
 
45
 
 
46
 
 
47
cases() -> 
 
48
    [badmatch, pending_errors, nil_arith].
 
49
 
 
50
-define(try_match(E),
 
51
        catch ?MODULE:bar(),
 
52
        {'EXIT', {{badmatch, nomatch}, _}} = (catch E = nomatch)).
 
53
 
 
54
init_per_testcase(_Case, Config) ->
 
55
    test_lib:interpret(?MODULE),
 
56
    Dog = test_server:timetrap(?t:minutes(1)),
 
57
    [{watchdog,Dog}|Config].
 
58
 
 
59
end_per_testcase(_Case, Config) ->
 
60
    Dog = ?config(watchdog, Config),
 
61
    ?t:timetrap_cancel(Dog),
 
62
    ok.
 
63
 
 
64
init_per_suite(Config) when is_list(Config) ->
 
65
    ?line test_lib:interpret(?MODULE),
 
66
    ?line true = lists:member(?MODULE, int:interpreted()),
 
67
    Config.
 
68
 
 
69
end_per_suite(Config) when is_list(Config) ->
 
70
    ok.
 
71
 
 
72
badmatch(doc) -> "Test that deliberately bad matches are reported correctly.";
 
73
badmatch(suite) -> [];
 
74
badmatch(Config) when list(Config) ->
 
75
    ?line ?try_match(a),
 
76
    ?line ?try_match(42),
 
77
    ?line ?try_match({a, b, c}),
 
78
    ?line ?try_match([]),
 
79
    ?line ?try_match(1.0),
 
80
    ok.
 
81
 
 
82
pending_errors(doc) ->
 
83
    ["Test various exceptions, in the presence of a previous error suppressed ",
 
84
     "in a guard."];
 
85
pending_errors(suite) -> [];
 
86
pending_errors(Config) when list(Config) ->
 
87
    ?line pending(e_badmatch, {badmatch, b}),
 
88
    ?line pending(x, function_clause),
 
89
    ?line pending(e_case, {case_clause, xxx}),
 
90
    ?line pending(e_if, if_clause),
 
91
    ?line pending(e_badarith, badarith),
 
92
    ?line pending(e_undef, undef),
 
93
    ?line pending(e_timeoutval, timeout_value),
 
94
    ?line pending(e_badarg, badarg),
 
95
    ?line pending(e_badarg_spawn, badarg),
 
96
    ok.
 
97
 
 
98
bad_guy(pe_badarith, Other) when Other+1 == 0 -> % badarith (suppressed)
 
99
    ok;
 
100
bad_guy(pe_badarg, Other) when length(Other) > 0 -> % badarg (suppressed)
 
101
    ok;
 
102
bad_guy(_, e_case) ->
 
103
    case xxx of
 
104
        ok -> ok
 
105
    end;                                        % case_clause
 
106
bad_guy(_, e_if) ->
 
107
    if
 
108
        a == b -> ok
 
109
    end;                                        % if_clause
 
110
bad_guy(_, e_badarith) ->
 
111
    1+b;                                        % badarith
 
112
bad_guy(_, e_undef) ->
 
113
    non_existing_module:foo();                  % undef
 
114
bad_guy(_, e_timeoutval) ->
 
115
    receive
 
116
        after arne ->                           % timeout_value
 
117
                ok
 
118
        end;
 
119
bad_guy(_, e_badarg) ->
 
120
    node(xxx);                                  % badarg
 
121
bad_guy(_, e_badarg_spawn) ->
 
122
    spawn({}, {}, {});                          % badarg
 
123
bad_guy(_, e_badmatch) ->
 
124
    a = b.                                      % badmatch
 
125
 
 
126
pending(Arg, Expected) ->
 
127
    pending(pe_badarith, Arg, Expected),
 
128
    pending(pe_badarg, Arg, Expected).
 
129
 
 
130
pending(First, Second, Expected) ->
 
131
    pending_catched(First, Second, Expected),
 
132
    pending_exit_message([First, Second], Expected).
 
133
 
 
134
pending_catched(First, Second, Expected) ->
 
135
    ok = io:format("Catching bad_guy(~p, ~p)", [First, Second]),
 
136
    case catch bad_guy(First, Second) of
 
137
        {'EXIT', Reason} ->
 
138
            pending(Reason, bad_guy, [First, Second], Expected);
 
139
        Other ->
 
140
            test_server:fail({not_exit, Other})
 
141
    end.
 
142
 
 
143
pending_exit_message(Args, Expected) ->
 
144
    ok = io:format("Trapping EXITs from spawn_link(~p, ~p, ~p)",
 
145
                   [?MODULE, bad_guy, Args]),
 
146
    process_flag(trap_exit, true),
 
147
    Pid = spawn_link(?MODULE, bad_guy, Args),
 
148
    receive
 
149
        {'EXIT', Pid, Reason} ->
 
150
            pending(Reason, bad_guy, Args, Expected);
 
151
        Other ->
 
152
            test_server:fail({unexpected_message, Other})
 
153
    after 10000 ->
 
154
            test_server:fail(timeout)
 
155
    end,
 
156
    process_flag(trap_exit, false).
 
157
 
 
158
pending({badarg,[{erlang,Bif,BifArgs},{?MODULE,Func,Arity}|_]}, Func, Args, _Code)
 
159
  when atom(Bif), list(BifArgs), length(Args) == Arity -> %Threaded code.
 
160
    ok;
 
161
pending({badarg,[{erlang,Bif,BifArgs},{?MODULE,Func,Args}|_]}, Func, Args, _Code)
 
162
  when atom(Bif), list(BifArgs) -> %From interpreted code.
 
163
    ok;
 
164
pending({undef,[{non_existing_module,foo,[]}|_]}, _, _, _) ->
 
165
    ok;
 
166
pending({function_clause,[{?MODULE,Func,Args}|_]}, Func, Args, _Code) ->
 
167
    ok;
 
168
pending({Code,[{?MODULE,Func,Arity}|_]}, Func, Args, Code) when length(Args) == Arity -> %Threaded code
 
169
    ok;
 
170
pending({Code,[{?MODULE,Func,Args}|_]}, Func, Args, Code) -> %From interpreted code.
 
171
    ok;
 
172
pending(Reason, Func, Args, Code) ->
 
173
    test_server:fail({bad_exit_reason,Reason,{Func,Args,Code}}).
 
174
 
 
175
nil_arith(doc) ->
 
176
    "Test that doing arithmetics on [] gives a badarith EXIT and not a crash.";
 
177
nil_arith(suite) ->
 
178
    [];
 
179
nil_arith(Config) when list(Config) ->
 
180
    ?line ba_plus_minus_times([], []),
 
181
 
 
182
    ?line ba_plus_minus_times([], 0),
 
183
    ?line ba_plus_minus_times([], 42),
 
184
    ?line ba_plus_minus_times([], 38724978123478923784),
 
185
    ?line ba_plus_minus_times([], 38.72),
 
186
 
 
187
    ?line ba_plus_minus_times(0, []),
 
188
    ?line ba_plus_minus_times(334, []),
 
189
    ?line ba_plus_minus_times(387249797813478923784, []),
 
190
    ?line ba_plus_minus_times(344.22, []),
 
191
 
 
192
    ?line ba_div_rem([], []),
 
193
 
 
194
    ?line ba_div_rem([], 0),
 
195
    ?line ba_div_rem([], 1),
 
196
    ?line ba_div_rem([], 42),
 
197
    ?line ba_div_rem([], 38724978123478923784),
 
198
    ?line ba_div_rem(344.22, []),
 
199
 
 
200
    ?line ba_div_rem(0, []),
 
201
    ?line ba_div_rem(1, []),
 
202
    ?line ba_div_rem(334, []),
 
203
    ?line ba_div_rem(387249797813478923784, []),
 
204
    ?line ba_div_rem(344.22, []),
 
205
 
 
206
    ?line ba_div_rem(344.22, 0.0),
 
207
    ?line ba_div_rem(1, 0.0),
 
208
    ?line ba_div_rem(392873498733971, 0.0),
 
209
 
 
210
    ?line ba_bop([], []),
 
211
    ?line ba_bop(0, []),
 
212
    ?line ba_bop(42, []),
 
213
    ?line ba_bop(-42342742987343, []),
 
214
    ?line ba_bop(238.342, []),
 
215
    ?line ba_bop([], 0),
 
216
    ?line ba_bop([], -243),
 
217
    ?line ba_bop([], 243),
 
218
    ?line ba_bop([], 2438724982478933),
 
219
    ?line ba_bop([], 3987.37),
 
220
 
 
221
    ?line ba_bnot([]),
 
222
    ?line ba_bnot(23.33),
 
223
 
 
224
    ?line ba_shift([], []),
 
225
    ?line ba_shift([], 0),
 
226
    ?line ba_shift([], 4),
 
227
    ?line ba_shift([], -4),
 
228
    ?line ba_shift([], 2343333333333),
 
229
    ?line ba_shift([], -333333333),
 
230
    ?line ba_shift([], 234.00),
 
231
    ?line ba_shift(23, []),
 
232
    ?line ba_shift(0, []),
 
233
    ?line ba_shift(-3433443433433323, []),
 
234
    ?line ba_shift(433443433433323, []),
 
235
    ?line ba_shift(343.93, []),
 
236
    ok.
 
237
 
 
238
ba_plus_minus_times(A, B) ->
 
239
    io:format("~p + ~p", [A, B]),
 
240
    {'EXIT', {badarith, _}} = (catch A + B),
 
241
    io:format("~p - ~p", [A, B]),
 
242
    {'EXIT', {badarith, _}} = (catch A - B),
 
243
    io:format("~p * ~p", [A, B]),
 
244
    {'EXIT', {badarith, _}} = (catch A * B).
 
245
 
 
246
ba_div_rem(A, B) ->
 
247
    io:format("~p / ~p", [A, B]),
 
248
    {'EXIT', {badarith, _}} = (catch A / B),
 
249
    io:format("~p div ~p", [A, B]),
 
250
    {'EXIT', {badarith, _}} = (catch A div B),
 
251
    io:format("~p rem ~p", [A, B]),
 
252
    {'EXIT', {badarith, _}} = (catch A rem B).
 
253
 
 
254
ba_bop(A, B) ->
 
255
    io:format("~p band ~p", [A, B]),
 
256
    {'EXIT', {badarith, _}} = (catch A band B),
 
257
    io:format("~p bor ~p", [A, B]),
 
258
    {'EXIT', {badarith, _}} = (catch A bor B),
 
259
    io:format("~p bxor ~p", [A, B]),
 
260
    {'EXIT', {badarith, _}} = (catch A bxor B).
 
261
 
 
262
ba_shift(A, B) ->
 
263
    io:format("~p bsl ~p", [A, B]),
 
264
    {'EXIT', {badarith, _}} = (catch A bsl B),
 
265
    io:format("~p bsr ~p", [A, B]),
 
266
    {'EXIT', {badarith, _}} = (catch A bsr B).
 
267
 
 
268
ba_bnot(A) ->
 
269
    io:format("bnot ~p", [A]),
 
270
    {'EXIT', {badarith, _}} = (catch bnot A).