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

« back to all changes in this revision

Viewing changes to erts/emulator/test/bif_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 2005-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2005-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(bif_SUITE).
21
21
 
22
 
-include("test_server.hrl").
 
22
-include_lib("test_server/include/test_server.hrl").
23
23
 
24
 
-export([all/1,init_per_testcase/2,fin_per_testcase/2,
 
24
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 
25
         init_per_group/2,end_per_group/2,
 
26
         init_per_testcase/2,end_per_testcase/2,
 
27
         types/1,
25
28
         t_list_to_existing_atom/1,os_env/1,otp_7526/1,
26
29
         binary_to_atom/1,binary_to_existing_atom/1,
27
30
         atom_to_binary/1,min_max/1]).
28
31
 
29
 
all(suite) ->
30
 
    [t_list_to_existing_atom,os_env,otp_7526,
31
 
     atom_to_binary,binary_to_atom,binary_to_existing_atom,
 
32
suite() -> [{ct_hooks,[ts_install_cth]}].
 
33
 
 
34
all() -> 
 
35
    [types, t_list_to_existing_atom, os_env, otp_7526,
 
36
     atom_to_binary, binary_to_atom, binary_to_existing_atom,
32
37
     min_max].
33
38
 
 
39
groups() -> 
 
40
    [].
 
41
 
 
42
init_per_suite(Config) ->
 
43
    Config.
 
44
 
 
45
end_per_suite(_Config) ->
 
46
    ok.
 
47
 
 
48
init_per_group(_GroupName, Config) ->
 
49
    Config.
 
50
 
 
51
end_per_group(_GroupName, Config) ->
 
52
    Config.
 
53
 
 
54
 
34
55
init_per_testcase(Func, Config) when is_atom(Func), is_list(Config) ->
35
56
    Dog=?t:timetrap(?t:minutes(1)),
36
57
    [{watchdog, Dog}|Config].
37
58
 
38
 
fin_per_testcase(_Func, Config) ->
 
59
end_per_testcase(_Func, Config) ->
39
60
    Dog=?config(watchdog, Config),
40
61
    ?t:timetrap_cancel(Dog).
41
62
 
 
63
types(Config) when is_list(Config) ->
 
64
    c:l(erl_bif_types),
 
65
    case erlang:function_exported(erl_bif_types, module_info, 0) of
 
66
        false ->
 
67
            %% Fail cleanly.
 
68
            ?line ?t:fail("erl_bif_types not compiled");
 
69
        true ->
 
70
            types_1()
 
71
    end.
 
72
 
 
73
types_1() ->
 
74
    ?line List0 = erlang:system_info(snifs),
 
75
 
 
76
    %% Ignore missing type information for hipe BIFs.
 
77
    ?line List = [MFA || {M,_,_}=MFA <- List0, M =/= hipe_bifs],
 
78
 
 
79
    case [MFA || MFA <- List, not known_types(MFA)] of
 
80
        [] ->
 
81
            types_2(List);
 
82
        BadTypes ->
 
83
            io:put_chars("No type information:\n"),
 
84
            io:format("~p\n", [lists:sort(BadTypes)]),
 
85
            ?line ?t:fail({length(BadTypes),bifs_without_types})
 
86
    end.
 
87
 
 
88
types_2(List) ->
 
89
    BadArity = [MFA || {M,F,A}=MFA <- List,
 
90
                       begin
 
91
                           Types = erl_bif_types:arg_types(M, F, A),
 
92
                           length(Types) =/= A
 
93
                       end],
 
94
    case BadArity of
 
95
        [] ->
 
96
            types_3(List);
 
97
        [_|_] ->
 
98
            io:put_chars("Bifs with bad arity\n"),
 
99
            io:format("~p\n", [BadArity]),
 
100
            ?line ?t:fail({length(BadArity),bad_arity})
 
101
    end.
 
102
 
 
103
types_3(List) ->
 
104
    BadSmokeTest = [MFA || {M,F,A}=MFA <- List,
 
105
                           begin
 
106
                               try erl_bif_types:type(M, F, A) of
 
107
                                   Type ->
 
108
                                       %% Test that type is returned.
 
109
                                       not erl_types:is_erl_type(Type)
 
110
                               catch
 
111
                                   Class:Error ->
 
112
                                       io:format("~p: ~p ~p\n",
 
113
                                                 [MFA,Class,Error]),
 
114
                                       true
 
115
                               end
 
116
                           end],
 
117
    case BadSmokeTest of
 
118
        [] ->
 
119
            ok;
 
120
        [_|_] ->
 
121
            io:put_chars("Bifs with failing calls to erlang_bif_types:type/3 "
 
122
                         "(or with bogus return values):\n"),
 
123
            io:format("~p\n", [BadSmokeTest]),
 
124
            ?line ?t:fail({length(BadSmokeTest),bad_smoke_test})
 
125
    end.
 
126
 
 
127
known_types({M,F,A}) ->
 
128
    erl_bif_types:is_known(M, F, A).
 
129
 
42
130
t_list_to_existing_atom(Config) when is_list(Config) ->
43
131
    ?line all = list_to_existing_atom("all"),
44
132
    ?line ?MODULE = list_to_existing_atom(?MODULE_STRING),
308
396
 
309
397
    ?line 42.0 = erlang:min(42.0, 42),
310
398
    ?line 42.0 = erlang:max(42.0, 42),
 
399
    %% And now (R14) they are also autoimported!
 
400
    ?line a = min(id(a), a),
 
401
    ?line a = min(id(a), b),
 
402
    ?line a = min(id(b), a),
 
403
    ?line b = min(id(b), b),
 
404
    ?line a = max(id(a), a),
 
405
    ?line b = max(id(a), b),
 
406
    ?line b = max(id(b), a),
 
407
    ?line b = max(id(b), b),
 
408
 
 
409
    ?line 42.0 = min(42.0, 42),
 
410
    ?line 42.0 = max(42.0, 42),
311
411
 
312
412
    ok.
313
413