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

« back to all changes in this revision

Viewing changes to lib/compiler/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 2001-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2001-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
-module(guard_SUITE).
20
20
 
21
 
-include("test_server.hrl").
 
21
-include_lib("test_server/include/test_server.hrl").
22
22
 
23
 
-export([all/1,
 
23
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 
24
         init_per_group/2,end_per_group/2,
24
25
         misc/1,const_cond/1,basic_not/1,complex_not/1,nested_nots/1,
25
26
         semicolon/1,complex_semicolon/1,comma/1,
26
27
         or_guard/1,more_or_guards/1,
31
32
         t_is_boolean/1,is_function_2/1,
32
33
         tricky/1,rel_ops/1,literal_type_tests/1,
33
34
         basic_andalso_orelse/1,traverse_dcd/1,
34
 
         check_qlc_hrl/1,andalso_semi/1,tuple_size/1]).
35
 
 
36
 
all(suite) ->
37
 
    test_lib:recompile(?MODULE),
38
 
    [misc,const_cond,basic_not,complex_not,nested_nots,
39
 
     semicolon,complex_semicolon,
40
 
     comma,or_guard,more_or_guards,
41
 
     complex_or_guards,and_guard,
42
 
     xor_guard,more_xor_guards,
43
 
     build_in_guard,old_guard_tests,gbif,
44
 
     t_is_boolean,is_function_2,tricky,rel_ops,literal_type_tests,
45
 
     basic_andalso_orelse,traverse_dcd,check_qlc_hrl,andalso_semi,
46
 
     tuple_size].
 
35
         check_qlc_hrl/1,andalso_semi/1,t_tuple_size/1,binary_part/1]).
 
36
 
 
37
suite() -> [{ct_hooks,[ts_install_cth]}].
 
38
 
 
39
all() -> 
 
40
    test_lib:recompile(guard_SUITE),
 
41
    [misc, const_cond, basic_not, complex_not, nested_nots,
 
42
     semicolon, complex_semicolon, comma, or_guard,
 
43
     more_or_guards, complex_or_guards, and_guard, xor_guard,
 
44
     more_xor_guards, build_in_guard, old_guard_tests, gbif,
 
45
     t_is_boolean, is_function_2, tricky, rel_ops,
 
46
     literal_type_tests, basic_andalso_orelse, traverse_dcd,
 
47
     check_qlc_hrl, andalso_semi, t_tuple_size, binary_part].
 
48
 
 
49
groups() -> 
 
50
    [].
 
51
 
 
52
init_per_suite(Config) ->
 
53
    Config.
 
54
 
 
55
end_per_suite(_Config) ->
 
56
    ok.
 
57
 
 
58
init_per_group(_GroupName, Config) ->
 
59
    Config.
 
60
 
 
61
end_per_group(_GroupName, Config) ->
 
62
    Config.
 
63
 
47
64
 
48
65
misc(Config) when is_list(Config) ->
49
66
    ?line 42 = case id(42) of
94
111
const_cond(T, Sz) ->
95
112
    case T of
96
113
        _X when false -> never;
97
 
        _X when tuple(T), eq == eq, tuple_size(T) == Sz -> ok;
98
 
        _X when tuple(T), eq == leq, tuple_size(T) =< Sz -> ok;
 
114
        _X when is_tuple(T), eq == eq, tuple_size(T) == Sz -> ok;
 
115
        _X when is_tuple(T), eq == leq, tuple_size(T) =< Sz -> ok;
99
116
        _X -> error
100
117
    end.
101
118
 
1137
1154
make_test([]) -> [].
1138
1155
 
1139
1156
test(T, L) ->
1140
 
    S0 = io_lib:format("begin io:format(\"~~p~~n\", [{~p,~p}]), if ~w(~w) -> true; true -> false end end. ", [T,L,T,L]),
 
1157
    S0 = io_lib:format("begin io:format(\"~~p~n\", [{~p,~p}]), if ~w(~w) -> true; true -> false end end. ", [T,L,T,L]),
1141
1158
    S = lists:flatten(S0),
1142
1159
    {ok,Toks,_Line} = erl_scan:string(S),
1143
1160
    {ok,E} = erl_parse:parse_exprs(Toks),
1145
1162
    {match,0,{atom,0,Val},hd(E)}.
1146
1163
 
1147
1164
test(T, L1, L2) ->
1148
 
    S0 = io_lib:format("begin io:format(\"~~p~~n\", [{~p,~p,~p}]), if ~w(~w, ~w) -> true; true -> false end end. ", [T,L1,L2,T,L1,L2]),
 
1165
    S0 = io_lib:format("begin io:format(\"~~p~n\", [{~p,~p,~p}]), if ~w(~w, ~w) -> true; true -> false end end. ", [T,L1,L2,T,L1,L2]),
1149
1166
    S = lists:flatten(S0),
1150
1167
    {ok,Toks,_Line} = erl_scan:string(S),
1151
1168
    {ok,E} = erl_parse:parse_exprs(Toks),
1316
1333
andalso_semi(Config) when is_list(Config) ->
1317
1334
    ?line ok = andalso_semi_foo(0),
1318
1335
    ?line ok = andalso_semi_foo(1),
1319
 
    ?line {'EXIT',{function_clause,_}} = (catch andalso_semi_foo(2)),
 
1336
    ?line fc(catch andalso_semi_foo(2)),
1320
1337
 
1321
1338
    ?line ok = andalso_semi_bar([a,b,c]),
1322
1339
    ?line ok = andalso_semi_bar(1),
1323
 
    ?line {'EXIT',{function_clause,_}} = (catch andalso_semi_bar([a,b])),
 
1340
    ?line fc(catch andalso_semi_bar([a,b])),
1324
1341
    ok.
1325
1342
 
1326
1343
andalso_semi_foo(Bar) when is_integer(Bar) andalso Bar =:= 0; Bar =:= 1 ->
1330
1347
   ok.
1331
1348
 
1332
1349
 
1333
 
tuple_size(Config) when is_list(Config) ->
 
1350
t_tuple_size(Config) when is_list(Config) ->
1334
1351
    ?line 10 = do_tuple_size({1,2,3,4}),
1335
 
    ?line {'EXIT',{function_clause,_}} = (catch do_tuple_size({1,2,3})),
1336
 
    ?line {'EXIT',{function_clause,_}} = (catch do_tuple_size(42)),
 
1352
    ?line fc(catch do_tuple_size({1,2,3})),
 
1353
    ?line fc(catch do_tuple_size(42)),
1337
1354
 
1338
1355
    ?line error = ludicrous_tuple_size({a,b,c}),
1339
1356
    ?line error = ludicrous_tuple_size([a,b,c]),
1362
1379
  when tuple_size(T) =:= 16#FFFFFFFFFFFFFFFF -> ok;
1363
1380
ludicrous_tuple_size(_) -> error.
1364
1381
 
 
1382
%%
 
1383
%% The binary_part/2,3 guard BIFs
 
1384
%%
 
1385
-define(MASK_ERROR(EXPR),mask_error((catch (EXPR)))).
 
1386
mask_error({'EXIT',{Err,_}}) ->
 
1387
    Err;
 
1388
mask_error(Else) ->
 
1389
    Else.
 
1390
 
 
1391
binary_part(doc) ->
 
1392
    ["Tests the binary_part/2,3 guard (GC) bif's"];
 
1393
binary_part(Config) when is_list(Config) ->
 
1394
    %% This is more or less a copy of what the guard_SUITE in emulator
 
1395
    %% does to cover the guard bif's
 
1396
    ?line 1 = bptest(<<1,2,3>>),
 
1397
    ?line 2 = bptest(<<2,1,3>>),
 
1398
    ?line error = bptest(<<1>>),
 
1399
    ?line error = bptest(<<>>),
 
1400
    ?line error = bptest(apa),
 
1401
    ?line 3 = bptest(<<2,3,3>>),
 
1402
    % With one variable (pos)
 
1403
    ?line 1 = bptest(<<1,2,3>>,1),
 
1404
    ?line 2 = bptest(<<2,1,3>>,1),
 
1405
    ?line error = bptest(<<1>>,1),
 
1406
    ?line error = bptest(<<>>,1),
 
1407
    ?line error = bptest(apa,1),
 
1408
    ?line 3 = bptest(<<2,3,3>>,1),
 
1409
    % With one variable (length)
 
1410
    ?line 1 = bptesty(<<1,2,3>>,1),
 
1411
    ?line 2 = bptesty(<<2,1,3>>,1),
 
1412
    ?line error = bptesty(<<1>>,1),
 
1413
    ?line error = bptesty(<<>>,1),
 
1414
    ?line error = bptesty(apa,1),
 
1415
    ?line 3 = bptesty(<<2,3,3>>,2),
 
1416
    % With one variable (whole tuple)
 
1417
    ?line 1 = bptestx(<<1,2,3>>,{1,1}),
 
1418
    ?line 2 = bptestx(<<2,1,3>>,{1,1}),
 
1419
    ?line error = bptestx(<<1>>,{1,1}),
 
1420
    ?line error = bptestx(<<>>,{1,1}),
 
1421
    ?line error = bptestx(apa,{1,1}),
 
1422
    ?line 3 = bptestx(<<2,3,3>>,{1,2}),
 
1423
    % With two variables
 
1424
    ?line 1 = bptest(<<1,2,3>>,1,1),
 
1425
    ?line 2 = bptest(<<2,1,3>>,1,1),
 
1426
    ?line error = bptest(<<1>>,1,1),
 
1427
    ?line error = bptest(<<>>,1,1),
 
1428
    ?line error = bptest(apa,1,1),
 
1429
    ?line 3 = bptest(<<2,3,3>>,1,2),
 
1430
    % Direct (autoimported) call, these will be evaluated by the compiler...
 
1431
    ?line <<2>> = binary_part(<<1,2,3>>,1,1),
 
1432
    ?line <<1>> = binary_part(<<2,1,3>>,1,1),
 
1433
    % Compiler warnings due to constant evaluation expected (3)
 
1434
    ?line badarg = ?MASK_ERROR(binary_part(<<1>>,1,1)),
 
1435
    ?line badarg = ?MASK_ERROR(binary_part(<<>>,1,1)),
 
1436
    ?line badarg = ?MASK_ERROR(binary_part(apa,1,1)),
 
1437
    ?line <<3,3>> = binary_part(<<2,3,3>>,1,2),
 
1438
    % Direct call through apply
 
1439
    ?line <<2>> = apply(erlang,binary_part,[<<1,2,3>>,1,1]),
 
1440
    ?line <<1>> = apply(erlang,binary_part,[<<2,1,3>>,1,1]),
 
1441
    % Compiler warnings due to constant evaluation expected (3)
 
1442
    ?line badarg = ?MASK_ERROR(apply(erlang,binary_part,[<<1>>,1,1])),
 
1443
    ?line badarg = ?MASK_ERROR(apply(erlang,binary_part,[<<>>,1,1])),
 
1444
    ?line badarg = ?MASK_ERROR(apply(erlang,binary_part,[apa,1,1])),
 
1445
    ?line <<3,3>> = apply(erlang,binary_part,[<<2,3,3>>,1,2]),
 
1446
    % Constant propagation
 
1447
    ?line  Bin = <<1,2,3>>,
 
1448
    ?line  ok = if
 
1449
                    binary_part(Bin,1,1) =:= <<2>> ->
 
1450
                        ok;
 
1451
                    %% Compiler warning, clause cannot match (expected)
 
1452
                    true ->
 
1453
                        error
 
1454
                end,
 
1455
    ?line  ok = if
 
1456
                    binary_part(Bin,{1,1}) =:= <<2>> ->
 
1457
                        ok;
 
1458
                    %% Compiler warning, clause cannot match (expected)
 
1459
                    true ->
 
1460
                        error
 
1461
                end,
 
1462
    ok.
 
1463
 
 
1464
 
 
1465
bptest(B) when length(B) =:= 1337 ->
 
1466
    1;
 
1467
bptest(B) when binary_part(B,{1,1}) =:= <<2>> ->
 
1468
    1;
 
1469
bptest(B) when erlang:binary_part(B,1,1) =:= <<1>> ->
 
1470
    2;
 
1471
bptest(B)  when erlang:binary_part(B,{1,2}) =:= <<3,3>> ->
 
1472
    3;
 
1473
bptest(_) ->
 
1474
    error.
 
1475
 
 
1476
bptest(B,A) when length(B) =:= A ->
 
1477
    1;
 
1478
bptest(B,A) when binary_part(B,{A,1}) =:= <<2>> ->
 
1479
    1;
 
1480
bptest(B,A) when erlang:binary_part(B,A,1) =:= <<1>> ->
 
1481
    2;
 
1482
bptest(B,A)  when erlang:binary_part(B,{A,2}) =:= <<3,3>> ->
 
1483
    3;
 
1484
bptest(_,_) ->
 
1485
    error.
 
1486
 
 
1487
bptestx(B,A) when length(B) =:= A ->
 
1488
    1;
 
1489
bptestx(B,A) when binary_part(B,A) =:= <<2>> ->
 
1490
    1;
 
1491
bptestx(B,A) when erlang:binary_part(B,A) =:= <<1>> ->
 
1492
    2;
 
1493
bptestx(B,A)  when erlang:binary_part(B,A) =:= <<3,3>> ->
 
1494
    3;
 
1495
bptestx(_,_) ->
 
1496
    error.
 
1497
 
 
1498
bptesty(B,A) when length(B) =:= A ->
 
1499
    1;
 
1500
bptesty(B,A) when binary_part(B,{1,A}) =:= <<2>> ->
 
1501
    1;
 
1502
bptesty(B,A) when erlang:binary_part(B,1,A) =:= <<1>> ->
 
1503
    2;
 
1504
bptesty(B,A)  when erlang:binary_part(B,{1,A}) =:= <<3,3>> ->
 
1505
    3;
 
1506
bptesty(_,_) ->
 
1507
    error.
 
1508
 
 
1509
bptest(B,A,_C) when length(B) =:= A ->
 
1510
    1;
 
1511
bptest(B,A,C) when binary_part(B,{A,C}) =:= <<2>> ->
 
1512
    1;
 
1513
bptest(B,A,C) when erlang:binary_part(B,A,C) =:= <<1>> ->
 
1514
    2;
 
1515
bptest(B,A,C)  when erlang:binary_part(B,{A,C}) =:= <<3,3>> ->
 
1516
    3;
 
1517
bptest(_,_,_) ->
 
1518
    error.
 
1519
 
 
1520
 
 
1521
 
1365
1522
 
1366
1523
%% Call this function to turn off constant propagation.
1367
1524
id(I) -> I.
1374
1531
            io:format("     Got: ~p\n", [Other]),
1375
1532
            test_server:fail()
1376
1533
    end.
 
1534
 
 
1535
fc({'EXIT',{function_clause,_}}) -> ok;
 
1536
fc({'EXIT',{{case_clause,_},_}}) when ?MODULE =:= guard_inline_SUITE -> ok.