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

« back to all changes in this revision

Viewing changes to erts/emulator/test/beam_literals_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
3
%% 
4
 
%% Copyright Ericsson AB 1999-2009. All Rights Reserved.
 
4
%% Copyright Ericsson AB 1999-2011. All Rights Reserved.
5
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
18
18
%%
19
19
 
20
20
-module(beam_literals_SUITE).
21
 
-export([all/1]).
 
21
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 
22
         init_per_group/2,end_per_group/2]).
22
23
-export([putting/1, matching_smalls/1, matching_smalls_jt/1,
23
24
         matching_bigs/1, matching_more_bigs/1,
24
25
         matching_bigs_and_smalls/1, badmatch/1, case_clause/1,
25
26
         receiving/1, literal_type_tests/1,
26
 
         put_list/1, fconv/1, literal_case_expression/1]).
27
 
 
28
 
-include("test_server.hrl").
29
 
 
30
 
all(suite) ->
 
27
         put_list/1, fconv/1, literal_case_expression/1,
 
28
         increment/1]).
 
29
 
 
30
-include_lib("test_server/include/test_server.hrl").
 
31
 
 
32
suite() -> [{ct_hooks,[ts_install_cth]}].
 
33
 
 
34
all() -> 
31
35
    [putting, matching_smalls, matching_smalls_jt,
32
36
     matching_bigs, matching_more_bigs,
33
37
     matching_bigs_and_smalls, badmatch, case_clause,
34
 
     receiving, literal_type_tests,
35
 
     put_list, fconv, literal_case_expression].
 
38
     receiving, literal_type_tests, put_list, fconv,
 
39
     literal_case_expression, increment].
 
40
 
 
41
groups() -> 
 
42
    [].
 
43
 
 
44
init_per_suite(Config) ->
 
45
    Config.
 
46
 
 
47
end_per_suite(_Config) ->
 
48
    ok.
 
49
 
 
50
init_per_group(_GroupName, Config) ->
 
51
    Config.
 
52
 
 
53
end_per_group(_GroupName, Config) ->
 
54
    Config.
 
55
 
36
56
 
37
57
putting(doc) -> "Test creating lists and tuples containing big number literals.";
38
58
putting(Config) when is_list(Config) ->
48
68
matching_bigs(Config) when is_list(Config) ->
49
69
    a = matching1(3972907842873739),
50
70
    b = matching1(-389789298378939783333333333333333333784),
 
71
    other = matching1(3141699999999999999999999999999999999),
51
72
    other = matching1(42).
52
73
 
53
74
matching_smalls(doc) -> "Test matching small numbers (both positive and negative).";
236
257
make_test([]) -> [].
237
258
 
238
259
test(T, L) ->
239
 
    S = lists:flatten(io_lib:format("begin io:format(\"~~p~~n\", [{~p,~p}]), if ~w(~w) -> true; true -> false end end. ", [T, L, T, L])),
 
260
    S = lists:flatten(io_lib:format("begin io:format(\"~~p~n\", [{~p,~p}]), if ~w(~w) -> true; true -> false end end. ", [T, L, T, L])),
240
261
    {ok,Toks,_Line} = erl_scan:string(S),
241
262
    {ok,E} = erl_parse:parse_exprs(Toks),
242
263
    {value,Val,_Bs} = erl_eval:exprs(E, []),
243
264
    {match,0,{atom,0,Val},hd(E)}.
244
265
 
245
266
test(T, A, L) ->
246
 
    S = lists:flatten(io_lib:format("begin io:format(\"~~p~~n\", [{~p,~p,~p}]), if ~w(~w, ~w) -> true; true -> false end end. ",
 
267
    S = lists:flatten(io_lib:format("begin io:format(\"~~p~n\", [{~p,~p,~p}]), if ~w(~w, ~w) -> true; true -> false end end. ",
247
268
                                    [T,L,A,T,L,A])),
248
269
    {ok,Toks,_Line} = erl_scan:string(S),
249
270
    {ok,E} = erl_parse:parse_exprs(Toks),
405
426
literal_case_expression(Config) when is_list(Config) ->
406
427
    ?line DataDir = ?config(data_dir, Config),
407
428
    ?line Src = filename:join(DataDir, "literal_case_expression"),
408
 
    ?line {ok,literal_case_expression=Mod,Code} = compile:file(Src, [from_asm,binary]),
 
429
    ?line {ok,literal_case_expression=Mod,Code} =
 
430
        compile:file(Src, [from_asm,binary]),
409
431
    ?line {module,Mod} = code:load_binary(Mod, Src, Code),
410
432
    ?line ok = Mod:x(),
411
433
    ?line ok = Mod:y(),
 
434
    ?line ok = Mod:zi1(),
 
435
    ?line ok = Mod:zi2(),
 
436
    ?line ok = Mod:za1(),
 
437
    ?line ok = Mod:za2(),
412
438
    ?line true = code:delete(Mod),
413
439
    ?line code:purge(Mod),
414
440
    ok.
415
441
 
 
442
%% Test the i_increment instruction.
 
443
increment(Config) when is_list(Config) ->
 
444
    %% In the 32-bit emulator, Neg32 can be represented as a small,
 
445
    %% but -Neg32 cannot. Therefore the i_increment instruction must
 
446
    %% not be used in the subtraction that follows (since i_increment
 
447
    %% cannot handle a bignum literal).
 
448
    Neg32 = -(1 bsl 27),
 
449
    Big32 = id(1 bsl 32),
 
450
    Result32 = (1 bsl 32) + (1 bsl 27),
 
451
    ?line Result32 = Big32 + (1 bsl 27),
 
452
    ?line Result32 = Big32 - Neg32,
 
453
 
 
454
    %% Same thing, but for the 64-bit emulator.
 
455
    Neg64 = -(1 bsl 59),
 
456
    Big64 = id(1 bsl 64),
 
457
    Result64 = (1 bsl 64) + (1 bsl 59),
 
458
    ?line Result64 = Big64 + (1 bsl 59),
 
459
    ?line Result64 = Big64 - Neg64,
 
460
 
 
461
    %% Test error handling for the i_increment instruction.
 
462
    Bad = id(bad),
 
463
    ?line {'EXIT',{badarith,_}} = (catch Bad + 42),
 
464
 
 
465
    %% Small operands, but a big result.
 
466
    Res32 = 1 bsl 27,
 
467
    Small32 = id(Res32-1),
 
468
    ?line Res32 = Small32 + 1,
 
469
    Res64 = 1 bsl 59,
 
470
    Small64 = id(Res64-1),
 
471
    ?line Res64 = Small64 + 1,
 
472
    ok.
 
473
 
416
474
%% Help functions.
417
475
 
418
476
chksum(Term) ->