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

« back to all changes in this revision

Viewing changes to erts/emulator/test/guard_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
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 1997-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1997-2011. 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
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
 
20
20
-module(guard_SUITE).
21
21
 
22
 
-export([all/1, bad_arith/1, bad_tuple/1, test_heap_guards/1, guard_bifs/1,
23
 
         type_tests/1]).
 
22
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 
23
         init_per_group/2,end_per_group/2, bad_arith/1, bad_tuple/1, 
 
24
         test_heap_guards/1, guard_bifs/1,
 
25
         type_tests/1,guard_bif_binary_part/1]).
24
26
 
25
 
-include("test_server.hrl").
 
27
-include_lib("test_server/include/test_server.hrl").
26
28
 
27
29
-export([init/3]).
28
30
-import(lists, [member/2]).
29
31
 
30
 
all(suite) -> [bad_arith, bad_tuple, test_heap_guards, guard_bifs, type_tests].
 
32
suite() -> [{ct_hooks,[ts_install_cth]}].
 
33
 
 
34
all() -> 
 
35
    [bad_arith, bad_tuple, test_heap_guards, guard_bifs,
 
36
     type_tests, guard_bif_binary_part].
 
37
 
 
38
groups() -> 
 
39
    [].
 
40
 
 
41
init_per_suite(Config) ->
 
42
    Config.
 
43
 
 
44
end_per_suite(_Config) ->
 
45
    ok.
 
46
 
 
47
init_per_group(_GroupName, Config) ->
 
48
    Config.
 
49
 
 
50
end_per_group(_GroupName, Config) ->
 
51
    Config.
 
52
 
31
53
 
32
54
bad_arith(doc) -> "Test that a bad arithmetic operation in a guard works correctly.";
33
55
bad_arith(Config) when is_list(Config) ->
136
158
dummy(_) ->
137
159
    ok.
138
160
 
 
161
-define(MASK_ERROR(EXPR),mask_error((catch (EXPR)))).
 
162
mask_error({'EXIT',{Err,_}}) ->
 
163
    Err;
 
164
mask_error(Else) ->
 
165
    Else.
 
166
 
 
167
guard_bif_binary_part(doc) ->
 
168
    ["Test the binary_part/2,3 guard BIF's extensively"];
 
169
guard_bif_binary_part(Config) when is_list(Config) ->
 
170
    %% Overflow tests that need to be unoptimized
 
171
    ?line badarg =
 
172
        ?MASK_ERROR(
 
173
           binary_part(<<1,2,3>>,{16#FFFFFFFFFFFFFFFF,
 
174
                                 -16#7FFFFFFFFFFFFFFF-1})),
 
175
    ?line badarg =
 
176
        ?MASK_ERROR(
 
177
           binary_part(<<1,2,3>>,{16#FFFFFFFFFFFFFFFF,
 
178
                                 16#7FFFFFFFFFFFFFFF})),
 
179
    F = fun(X) ->
 
180
                Master = self(),
 
181
                {Pid,Ref} = spawn_monitor( fun() ->
 
182
                                             A = lists:duplicate(X,a),
 
183
                                             B = [do_binary_part_guard() | A],
 
184
                                             Master ! {self(),hd(B)},
 
185
                                             ok
 
186
                                     end),
 
187
                receive
 
188
                    {Pid,ok} ->
 
189
                        erlang:demonitor(Ref,[flush]),
 
190
                        ok;
 
191
                    Error ->
 
192
                        Error
 
193
                end
 
194
        end,
 
195
    [ ok = F(N) || N <- lists:seq(1,10000) ],
 
196
    ok.
 
197
 
 
198
 
 
199
do_binary_part_guard() ->
 
200
    ?line 1 = bptest(<<1,2,3>>),
 
201
    ?line 2 = bptest(<<2,1,3>>),
 
202
    ?line error = bptest(<<1>>),
 
203
    ?line error = bptest(<<>>),
 
204
    ?line error = bptest(apa),
 
205
    ?line 3 = bptest(<<2,3,3>>),
 
206
    % With one variable (pos)
 
207
    ?line 1 = bptest(<<1,2,3>>,1),
 
208
    ?line 2 = bptest(<<2,1,3>>,1),
 
209
    ?line error = bptest(<<1>>,1),
 
210
    ?line error = bptest(<<>>,1),
 
211
    ?line error = bptest(apa,1),
 
212
    ?line 3 = bptest(<<2,3,3>>,1),
 
213
    % With one variable (length)
 
214
    ?line 1 = bptesty(<<1,2,3>>,1),
 
215
    ?line 2 = bptesty(<<2,1,3>>,1),
 
216
    ?line error = bptesty(<<1>>,1),
 
217
    ?line error = bptesty(<<>>,1),
 
218
    ?line error = bptesty(apa,1),
 
219
    ?line 3 = bptesty(<<2,3,3>>,2),
 
220
    % With one variable (whole tuple)
 
221
    ?line 1 = bptestx(<<1,2,3>>,{1,1}),
 
222
    ?line 2 = bptestx(<<2,1,3>>,{1,1}),
 
223
    ?line error = bptestx(<<1>>,{1,1}),
 
224
    ?line error = bptestx(<<>>,{1,1}),
 
225
    ?line error = bptestx(apa,{1,1}),
 
226
    ?line 3 = bptestx(<<2,3,3>>,{1,2}),
 
227
    % With two variables
 
228
    ?line 1 = bptest(<<1,2,3>>,1,1),
 
229
    ?line 2 = bptest(<<2,1,3>>,1,1),
 
230
    ?line error = bptest(<<1>>,1,1),
 
231
    ?line error = bptest(<<>>,1,1),
 
232
    ?line error = bptest(apa,1,1),
 
233
    ?line 3 = bptest(<<2,3,3>>,1,2),
 
234
    % Direct (autoimported) call, these will be evaluated by the compiler...
 
235
    ?line <<2>> = binary_part(<<1,2,3>>,1,1),
 
236
    ?line <<1>> = binary_part(<<2,1,3>>,1,1),
 
237
    % Compiler warnings due to constant evaluation expected (3)
 
238
    ?line badarg = ?MASK_ERROR(binary_part(<<1>>,1,1)),
 
239
    ?line badarg = ?MASK_ERROR(binary_part(<<>>,1,1)),
 
240
    ?line badarg = ?MASK_ERROR(binary_part(apa,1,1)),
 
241
    ?line <<3,3>> = binary_part(<<2,3,3>>,1,2),
 
242
    % Direct call through apply
 
243
    ?line <<2>> = apply(erlang,binary_part,[<<1,2,3>>,1,1]),
 
244
    ?line <<1>> = apply(erlang,binary_part,[<<2,1,3>>,1,1]),
 
245
    % Compiler warnings due to constant evaluation expected (3)
 
246
    ?line badarg = ?MASK_ERROR(apply(erlang,binary_part,[<<1>>,1,1])),
 
247
    ?line badarg = ?MASK_ERROR(apply(erlang,binary_part,[<<>>,1,1])),
 
248
    ?line badarg = ?MASK_ERROR(apply(erlang,binary_part,[apa,1,1])),
 
249
    ?line <<3,3>> = apply(erlang,binary_part,[<<2,3,3>>,1,2]),
 
250
    % Constant propagation
 
251
    ?line  Bin = <<1,2,3>>,
 
252
    ?line  ok = if
 
253
                    binary_part(Bin,1,1) =:= <<2>> ->
 
254
                        ok;
 
255
                    %% Compiler warning, clause cannot match (expected)
 
256
                    true ->
 
257
                        error
 
258
                end,
 
259
    ?line  ok = if
 
260
                    binary_part(Bin,{1,1}) =:= <<2>> ->
 
261
                        ok;
 
262
                    %% Compiler warning, clause cannot match (expected)
 
263
                    true ->
 
264
                        error
 
265
                end,
 
266
    ok.
 
267
 
 
268
 
 
269
bptest(B) when length(B) =:= 1337 ->
 
270
    1;
 
271
bptest(B) when binary_part(B,{1,1}) =:= <<2>> ->
 
272
    1;
 
273
bptest(B) when erlang:binary_part(B,1,1) =:= <<1>> ->
 
274
    2;
 
275
bptest(B)  when erlang:binary_part(B,{1,2}) =:= <<3,3>> ->
 
276
    3;
 
277
bptest(_) ->
 
278
    error.
 
279
 
 
280
bptest(B,A) when length(B) =:= A ->
 
281
    1;
 
282
bptest(B,A) when binary_part(B,{A,1}) =:= <<2>> ->
 
283
    1;
 
284
bptest(B,A) when erlang:binary_part(B,A,1) =:= <<1>> ->
 
285
    2;
 
286
bptest(B,A)  when erlang:binary_part(B,{A,2}) =:= <<3,3>> ->
 
287
    3;
 
288
bptest(_,_) ->
 
289
    error.
 
290
 
 
291
bptestx(B,A) when length(B) =:= A ->
 
292
    1;
 
293
bptestx(B,A) when binary_part(B,A) =:= <<2>> ->
 
294
    1;
 
295
bptestx(B,A) when erlang:binary_part(B,A) =:= <<1>> ->
 
296
    2;
 
297
bptestx(B,A)  when erlang:binary_part(B,A) =:= <<3,3>> ->
 
298
    3;
 
299
bptestx(_,_) ->
 
300
    error.
 
301
 
 
302
bptesty(B,A) when length(B) =:= A ->
 
303
    1;
 
304
bptesty(B,A) when binary_part(B,{1,A}) =:= <<2>> ->
 
305
    1;
 
306
bptesty(B,A) when erlang:binary_part(B,1,A) =:= <<1>> ->
 
307
    2;
 
308
bptesty(B,A)  when erlang:binary_part(B,{1,A}) =:= <<3,3>> ->
 
309
    3;
 
310
bptesty(_,_) ->
 
311
    error.
 
312
 
 
313
bptest(B,A,_C) when length(B) =:= A ->
 
314
    1;
 
315
bptest(B,A,C) when binary_part(B,{A,C}) =:= <<2>> ->
 
316
    1;
 
317
bptest(B,A,C) when erlang:binary_part(B,A,C) =:= <<1>> ->
 
318
    2;
 
319
bptest(B,A,C)  when erlang:binary_part(B,{A,C}) =:= <<3,3>> ->
 
320
    3;
 
321
bptest(_,_,_) ->
 
322
    error.
 
323
 
 
324
 
139
325
guard_bifs(doc) -> "Test all guard bifs with nasty (but legal arguments).";
140
326
guard_bifs(Config) when is_list(Config) ->
141
327
    ?line Big = -237849247829874297658726487367328971246284736473821617265433,