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

« back to all changes in this revision

Viewing changes to lib/compiler/test/compile_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
-module(compile_SUITE).
20
20
 
21
21
%% Tests compile:file/1 and compile:file/2 with various options.
22
22
 
23
 
-include("test_server.hrl").
 
23
-include_lib("test_server/include/test_server.hrl").
24
24
 
25
 
-export([all/1,
 
25
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 
26
         init_per_group/2,end_per_group/2,
26
27
         app_test/1,
27
28
         file_1/1, module_mismatch/1, big_file/1, outdir/1, 
28
 
         binary/1, cond_and_ifdef/1, listings/1, listings_big/1,
 
29
         binary/1, makedep/1, cond_and_ifdef/1, listings/1, listings_big/1,
29
30
         other_output/1, package_forms/1, encrypted_abstr/1,
30
 
         bad_record_use/1, bad_record_use1/1, bad_record_use2/1, strict_record/1,
 
31
         bad_record_use1/1, bad_record_use2/1, strict_record/1,
31
32
         missing_testheap/1, cover/1, env/1, core/1, asm/1]).
32
33
 
33
34
-export([init/3]).
34
35
 
 
36
suite() -> [{ct_hooks,[ts_install_cth]}].
35
37
 
36
38
%% To cover the stripping of 'type' and 'spec' in beam_asm.
37
39
-type all_return_type() :: [atom()].
38
 
-spec all('suite' | [_]) -> all_return_type().
 
40
-spec all() -> all_return_type().
39
41
 
40
 
all(suite) ->
41
 
    test_lib:recompile(?MODULE),
42
 
    [app_test,
43
 
     file_1, module_mismatch, big_file, outdir, binary,
44
 
     cond_and_ifdef, listings, listings_big,
45
 
     other_output, package_forms,
46
 
     encrypted_abstr,
47
 
     bad_record_use, strict_record,
 
42
all() -> 
 
43
    test_lib:recompile(compile_SUITE),
 
44
    [app_test, file_1, module_mismatch, big_file, outdir,
 
45
     binary, makedep, cond_and_ifdef, listings, listings_big,
 
46
     other_output, package_forms, encrypted_abstr,
 
47
     {group, bad_record_use}, strict_record,
48
48
     missing_testheap, cover, env, core, asm].
49
49
 
 
50
groups() -> 
 
51
    [{bad_record_use, [],
 
52
      [bad_record_use1, bad_record_use2]}].
 
53
 
 
54
init_per_suite(Config) ->
 
55
    Config.
 
56
 
 
57
end_per_suite(_Config) ->
 
58
    ok.
 
59
 
 
60
init_per_group(_GroupName, Config) ->
 
61
        Config.
 
62
 
 
63
end_per_group(_GroupName, Config) ->
 
64
        Config.
 
65
 
 
66
 
50
67
 
51
68
%% Test that the Application file has no `basic' errors.";
52
69
app_test(Config) when is_list(Config) ->
132
149
    ?line test_server:timetrap_cancel(Dog),
133
150
    ok.
134
151
 
 
152
%% Tests that the dependencies-Makefile-related options work.
 
153
 
 
154
makedep(Config) when is_list(Config) ->
 
155
    ?line Dog = test_server:timetrap(test_server:seconds(60)),
 
156
    ?line {Simple,Target} = files(Config, "makedep"),
 
157
    ?line DataDir = ?config(data_dir, Config),
 
158
    ?line SimpleRootname = filename:rootname(Simple),
 
159
    ?line IncludeDir = filename:join(filename:dirname(Simple), "include"),
 
160
    ?line IncludeOptions = [
 
161
      {d,need_foo},
 
162
      {d,foo_value,42},
 
163
      {d,include_generated},
 
164
      {i,IncludeDir}
 
165
    ],
 
166
    %% Basic rule.
 
167
    ?line BasicMf1Name = SimpleRootname ++ "-basic1.mk",
 
168
    ?line {ok,BasicMf1} = file:read_file(BasicMf1Name),
 
169
    ?line {ok,_,Mf1} = compile:file(Simple, [binary,makedep]),
 
170
    ?line BasicMf1 = makedep_canonicalize_result(Mf1, DataDir),
 
171
    %% Basic rule with one existing header.
 
172
    ?line BasicMf2Name = SimpleRootname ++ "-basic2.mk",
 
173
    ?line {ok,BasicMf2} = file:read_file(BasicMf2Name),
 
174
    ?line {ok,_,Mf2} = compile:file(Simple, [binary,makedep|IncludeOptions]),
 
175
    ?line BasicMf2 = makedep_canonicalize_result(Mf2, DataDir),
 
176
    %% Rule with one existing header and one missing header.
 
177
    ?line MissingMfName = SimpleRootname ++ "-missing.mk",
 
178
    ?line {ok,MissingMf} = file:read_file(MissingMfName),
 
179
    ?line {ok,_,Mf3} = compile:file(Simple,
 
180
      [binary,makedep,makedep_add_missing|IncludeOptions]),
 
181
    ?line MissingMf = makedep_canonicalize_result(Mf3, DataDir),
 
182
    %% Rule with modified target.
 
183
    ?line TargetMf1Name = SimpleRootname ++ "-target1.mk",
 
184
    ?line {ok,TargetMf1} = file:read_file(TargetMf1Name),
 
185
    ?line {ok,_,Mf4} = compile:file(Simple,
 
186
      [binary,makedep,{makedep_target,"$target"}|IncludeOptions]),
 
187
    ?line TargetMf1 = makedep_modify_target(
 
188
      makedep_canonicalize_result(Mf4, DataDir), "$$target"),
 
189
    %% Rule with quoted modified target.
 
190
    ?line TargetMf2Name = SimpleRootname ++ "-target2.mk",
 
191
    ?line {ok,TargetMf2} = file:read_file(TargetMf2Name),
 
192
    ?line {ok,_,Mf5} = compile:file(Simple,
 
193
      [binary,makedep,{makedep_target,"$target"},makedep_quote_target|
 
194
        IncludeOptions]),
 
195
    ?line TargetMf2 = makedep_modify_target(
 
196
      makedep_canonicalize_result(Mf5, DataDir), "$$target"),
 
197
    %% Basic rule written to some file.
 
198
    ?line {ok,_} = compile:file(Simple,
 
199
      [makedep,{makedep_output,Target}|IncludeOptions]),
 
200
    ?line {ok,Mf6} = file:read_file(Target),
 
201
    ?line BasicMf2 = makedep_canonicalize_result(Mf6, DataDir),
 
202
 
 
203
    ?line ok = file:delete(Target),
 
204
    ?line ok = file:del_dir(filename:dirname(Target)),
 
205
    ?line test_server:timetrap_cancel(Dog),
 
206
    ok.
 
207
 
 
208
makedep_canonicalize_result(Mf, DataDir) ->
 
209
    Mf0 = binary_to_list(Mf),
 
210
    %% Replace the Datadir by "$(srcdir)".
 
211
    Mf1 = re:replace(Mf0, DataDir, "$(srcdir)/",
 
212
      [global,multiline,{return,list}]),
 
213
    %% Long lines are splitted, put back everything on one line.
 
214
    Mf2 = re:replace(Mf1, "\\\\\n  ", "", [global,multiline,{return,list}]),
 
215
    list_to_binary(Mf2).
 
216
 
 
217
makedep_modify_target(Mf, Target) ->
 
218
    Mf0 = binary_to_list(Mf),
 
219
    Mf1 = re:replace(Mf0, Target, "$target", [{return,list}]),
 
220
    list_to_binary(Mf1).
 
221
 
135
222
%% Tests that conditional compilation, defining values, including files work.
136
223
 
137
224
cond_and_ifdef(Config) when is_list(Config) ->
465
552
        {error, _} -> false
466
553
    end.
467
554
 
468
 
bad_record_use(suite) ->  [bad_record_use1, bad_record_use2].
469
555
 
470
556
%% Tests that the compiler does not accept
471
557
%% bad use of records.
625
711
                                    {raw_abstract_v1,Abstr}}]}} = 
626
712
                             beam_lib:chunks(Beam, [abstract_code]),
627
713
                         {Mod,Abstr} end || Beam <- TestBeams],
628
 
    ?line Res = p_run(fun(F) -> do_core(F, Outdir) end, Abstr),
 
714
    ?line Res = test_lib:p_run(fun(F) -> do_core(F, Outdir) end, Abstr),
629
715
    ?line test_server:timetrap_cancel(Dog),
630
716
    Res.
631
717
 
661
747
 
662
748
    ?line Wc = filename:join(filename:dirname(code:which(?MODULE)), "*.beam"),
663
749
    ?line TestBeams = filelib:wildcard(Wc),
664
 
    ?line Res = p_run(fun(F) -> do_asm(F, Outdir) end, TestBeams),
 
750
    ?line Res = test_lib:p_run(fun(F) -> do_asm(F, Outdir) end, TestBeams),
665
751
    ?line test_server:timetrap_cancel(Dog),
666
752
    Res.
667
753
 
688
774
                      [M,Class,Error,erlang:get_stacktrace()]),
689
775
            error
690
776
    end.
691
 
    
692
 
%% p_run(fun() -> ok|error, List) -> ok
693
 
%%  Will fail the test case if there were any errors.
694
 
 
695
 
p_run(Test, List) ->
696
 
    N = erlang:system_info(schedulers) + 1,
697
 
    p_run_loop(Test, List, N, [], 0, 0).
698
 
 
699
 
p_run_loop(_, [], _, [], Errors, Ws) ->
700
 
    case Errors of
701
 
        0 ->
702
 
            case Ws of
703
 
                0 -> ok;
704
 
                1 -> {comment,"1 core_lint failure"};
705
 
                N -> {comment,integer_to_list(N)++" core_lint failures"}
706
 
            end;
707
 
        N -> ?t:fail({N,errors})
708
 
    end;
709
 
p_run_loop(Test, [H|T], N, Refs, Errors, Ws) when length(Refs) < N ->
710
 
    {_,Ref} = erlang:spawn_monitor(fun() -> exit(Test(H)) end),
711
 
    p_run_loop(Test, T, N, [Ref|Refs], Errors, Ws);
712
 
p_run_loop(Test, List, N, Refs0, Errors0, Ws0) ->
713
 
    receive
714
 
        {'DOWN',Ref,process,_,Res} ->
715
 
            {Errors,Ws} = case Res of
716
 
                              ok -> {Errors0,Ws0};
717
 
                              error -> {Errors0+1,Ws0};
718
 
                              warning -> {Errors0,Ws0+1}
719
 
                          end,
720
 
            Refs = Refs0 -- [Ref],
721
 
            p_run_loop(Test, List, N, Refs, Errors, Ws)
722
 
    end.