~statik/ubuntu/maverick/erlang/erlang-merge-testing

« back to all changes in this revision

Viewing changes to lib/compiler/src/compile.erl

  • Committer: Elliot Murphy
  • Date: 2010-06-08 03:55:44 UTC
  • mfrom: (3.5.6 squeeze)
  • Revision ID: elliot@elliotmurphy.com-20100608035544-dd8zh2swk7jr5rz2
* Merge with Debian unstable; remaining Ubuntu changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to. (LP #438365)
  - 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.
* Added missing symlinks to /usr/include for a few new header files.
* Fixed generation of ${erlang-base:Depends} and ${erlang-x11:Depends}
  substitution variables.
* Added a fix for a re:compile/2 crash on a long regular expression.
* Changed urgency to medium as the change fixes a security bug.
* Manpages in section 1 are needed even if only arch-dependent packages are
  built. So, re-enabled them.
* Fixed HiPE architecture recognition for powerpc Debian architecture.
* Moved xsltproc and fop to build-depends-indep and do not build
  documentation if only architecture-specific packages are built.
* Refreshed all patches.
* Made Emacs look in man5 and man7 for Erlang manpages and added code
  skeleton files to erlang-mode package.
* New upstream release.
* Moved manpages from incorrect sections 4 and 6 to correct 5 and 7
  (closes: #498492).
* Made manpages regexp in Emacs mode match only 3erl pages in section 3.
* Removed docb_gen script which is no longer needed to build manpages.
* Added erlang-doc package which contains documentation in HTML and PDF
  formats. This package replaces erlang-doc-html package and it's easier
  to synchronize it with the main Erlang packages as it's built from
  a single source package (closes: #558451).
* Removed RPATH from ssl and crypto application binaries as required by
  Debian policy.
* Added libwxgtk2.4-dev and libwxgtk2.6-dev to build conflicts.
* Added a few dpendencies for erlang-dialyzer, erlang-et, erlang-observer
  and erlang-examples packages which now call functions from more modules
  than in 1:13.b.3.
* Added a workaround which disables vfork() for hppa architecture
  (closes: #562218).
* Strictened check for JDK 1.5 adding a call to String(int[], int, int)
  because GCJ 4.4 doesn't implement it and OpenJDK isn't available for all
  architectures.
* Fixed erlang-manpages package section.
* Made erlang-depends add only substvars which are requested in
  debian/control file. This minimizes number of warnings from dh_gencontrol.
  Also, improved descriptions of the functions in erlang-depends escript.
* Added erlang-erl-docgen package to erlang-nox dependencies.
* Made dummy packages erlang-nox and erlang-x11 architecture all.
* Cleaned up working with custom substitution variables in debian/rules.
* Reorganized debian/rules to ensure that manpages arent built twice, and
  aren't built at all if only architecture-dependent packages are requested.
* Fixed project links in README.Debian.
* Added a new package erlang-jinterface which provides tools for
  communication of Java programs with Erlang processes. This adds build
  depandency on default-jdk and as a result enables Java module for IDL
  compiler.
* Bumped standards version to 3.8.4.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1996-2010. 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
%% Purpose: Run the Erlang compiler.
187
187
format_error({native, E}) ->
188
188
    io_lib:fwrite("native-code compilation failed with reason: ~P.",
189
189
                  [E, 25]);
190
 
format_error({native_crash, E}) ->
191
 
    io_lib:fwrite("native-code compilation crashed with reason: ~P.",
192
 
                  [E, 25]);
 
190
format_error({native_crash,E,Stk}) ->
 
191
    io_lib:fwrite("native-code compilation crashed with reason: ~P.\n~P\n",
 
192
                  [E,25,Stk,25]);
193
193
format_error({open,E}) ->
194
194
    io_lib:format("open error '~s'", [file:format_error(E)]);
195
195
format_error({epp,E}) ->
302
302
            list_to_integer(lib:nonl(Size));
303
303
        _ ->
304
304
            0
305
 
    end.            
 
305
    end.
306
306
 
307
307
run_tc({Name,Fun}, St) ->
308
308
    Before0 = statistics(runtime),
318
318
    Val.
319
319
 
320
320
comp_ret_ok(#compile{code=Code,warnings=Warn0,module=Mod,options=Opts}=St) ->
321
 
    Warn = messages_per_file(Warn0),
322
 
    report_warnings(St#compile{warnings = Warn}),
323
 
    Ret1 = case member(binary, Opts) andalso not member(no_code_generation, Opts) of
324
 
               true -> [Code];
325
 
               false -> []
326
 
           end,
327
 
    Ret2 = case member(return_warnings, Opts) of
328
 
               true -> Ret1 ++ [Warn];
329
 
               false -> Ret1
330
 
           end,
331
 
    list_to_tuple([ok,Mod|Ret2]).
 
321
    case member(warnings_as_errors, Opts) andalso length(Warn0) > 0 of
 
322
        true ->
 
323
            case member(report_warnings, Opts) of
 
324
                true ->
 
325
                    io:format("~p: warnings being treated as errors\n",
 
326
                              [?MODULE]);
 
327
                false ->
 
328
                    ok
 
329
            end,
 
330
            comp_ret_err(St);
 
331
        false ->
 
332
            Warn = messages_per_file(Warn0),
 
333
            report_warnings(St#compile{warnings = Warn}),
 
334
            Ret1 = case member(binary, Opts) andalso
 
335
                       not member(no_code_generation, Opts) of
 
336
                       true -> [Code];
 
337
                       false -> []
 
338
                   end,
 
339
            Ret2 = case member(return_warnings, Opts) of
 
340
                       true -> Ret1 ++ [Warn];
 
341
                       false -> Ret1
 
342
                   end,
 
343
            list_to_tuple([ok,Mod|Ret2])
 
344
    end.
332
345
 
333
346
comp_ret_err(#compile{warnings=Warn0,errors=Err0,options=Opts}=St) ->
334
347
    Warn = messages_per_file(Warn0),
344
357
messages_per_file(Ms) ->
345
358
    T = lists:sort([{File,M} || {File,Messages} <- Ms, M <- Messages]),
346
359
    PrioMs = [erl_scan, epp, erl_parse],
347
 
    {Prio0, Rest} = 
 
360
    {Prio0, Rest} =
348
361
        lists:mapfoldl(fun(M, A) ->
349
362
                               lists:partition(fun({_,{_,Mod,_}}) -> Mod =:= M;
350
363
                                                  (_) -> false
351
364
                                               end, A)
352
365
                       end, T, PrioMs),
353
 
    Prio = lists:sort(fun({_,{L1,_,_}}, {_,{L2,_,_}}) -> L1 =< L2 end, 
 
366
    Prio = lists:sort(fun({_,{L1,_,_}}, {_,{L2,_,_}}) -> L1 =< L2 end,
354
367
                      lists:append(Prio0)),
355
368
    flatmap(fun mpf/1, [Prio, Rest]).
356
369
 
357
370
mpf(Ms) ->
358
 
    [{File,[M || {F,M} <- Ms, F =:= File]} || 
 
371
    [{File,[M || {F,M} <- Ms, F =:= File]} ||
359
372
        File <- lists:usort([F || {F,_} <- Ms])].
360
373
 
361
374
%% passes(form|file, [Option]) -> [{Name,PassFun}]
495
508
 
496
509
select_cond(Flag, ShouldBe, Pass, Ps, Opts) ->
497
510
    ShouldNotBe = not ShouldBe,
498
 
    case member(Flag, Opts) of 
 
511
    case member(Flag, Opts) of
499
512
        ShouldBe    -> select_passes([Pass|Ps], Opts);
500
513
        ShouldNotBe -> select_passes(Ps, Opts)
501
514
    end.
502
515
 
503
516
%% select_list_passes([Pass], Opts) -> {done,[Pass]} | {not_done,[Pass]}
504
517
%%  Evaluate all conditions having to do with listings in the list of
505
 
%%  passes. 
 
518
%%  passes.
506
519
 
507
520
select_list_passes(Ps, Opts) ->
508
521
    select_list_passes_1(Ps, Opts, []).
704
717
    case file:read_file(St#compile.ifile) of
705
718
        {ok,Beam} ->
706
719
            Infile = St#compile.ifile,
707
 
            case is_too_old(Infile) of
 
720
            case no_native_compilation(Infile, St) of
708
721
                true ->
709
722
                    {ok,St#compile{module=none,code=none}};
710
723
                false ->
717
730
            {error,St#compile{errors=St#compile.errors ++ Es}}
718
731
    end.
719
732
 
720
 
is_too_old(BeamFile) ->
 
733
no_native_compilation(BeamFile, #compile{options=Opts0}) ->
721
734
    case beam_lib:chunks(BeamFile, ["CInf"]) of
722
735
        {ok,{_,[{"CInf",Term0}]}} ->
723
736
            Term = binary_to_term(Term0),
724
 
            Opts = proplists:get_value(options, Term, []),
725
 
            lists:member(no_new_funs, Opts);
 
737
 
 
738
            %% Compiler options in the beam file will override
 
739
            %% options passed to the compiler.
 
740
            Opts = proplists:get_value(options, Term, []) ++ Opts0,
 
741
            member(no_new_funs, Opts) orelse not is_native_enabled(Opts);
726
742
        _ -> false
727
743
    end.
728
744
 
782
798
    clean_parse_transforms_1(Fs, [F|Acc]);
783
799
clean_parse_transforms_1([], Acc) -> reverse(Acc).
784
800
 
785
 
transforms(Os) -> [ M || {parse_transform,M} <- Os ]. 
 
801
transforms(Os) -> [ M || {parse_transform,M} <- Os ].
786
802
 
787
803
transform_module(#compile{options=Opt,code=Code0}=St0) ->
788
804
    %% Extract compile options from code into options field.
815
831
    end;
816
832
foldl_transform(St, []) -> {ok,St}.
817
833
 
818
 
get_core_transforms(Opts) -> [M || {core_transform,M} <- Opts]. 
 
834
get_core_transforms(Opts) -> [M || {core_transform,M} <- Opts].
819
835
 
820
836
core_transforms(St) ->
821
837
    %% The options field holds the complete list of options at this
1033
1049
 
1034
1050
test_native(#compile{options=Opts}) ->
1035
1051
    %% This test is done late, in case some other option has turned off native.
1036
 
    member(native, Opts).
 
1052
    %% 'native' given on the command line can be overridden by
 
1053
    %% 'no_native' in the module itself.
 
1054
    is_native_enabled(Opts).
 
1055
 
 
1056
is_native_enabled([native|_]) -> true;
 
1057
is_native_enabled([no_native|_]) -> false;
 
1058
is_native_enabled([_|Opts]) -> is_native_enabled(Opts);
 
1059
is_native_enabled([]) -> false.
1037
1060
 
1038
1061
native_compile(#compile{code=none}=St) -> {ok,St};
1039
1062
native_compile(St) ->
1057
1080
                     St#compile.core_code,
1058
1081
                     St#compile.code,
1059
1082
                     Opts) of
1060
 
        {ok, {_Type,Bin} = T} when is_binary(Bin) ->
1061
 
            {ok, embed_native_code(St, T)};
1062
 
        {error, R} ->
 
1083
        {ok,{_Type,Bin}=T} when is_binary(Bin) ->
 
1084
            {ok,embed_native_code(St, T)};
 
1085
        {error,R} ->
1063
1086
            case IgnoreErrors of
1064
1087
                true ->
1065
 
                    Ws = [{St#compile.ifile,[{none,?MODULE,{native,R}}]}],
1066
 
                    {ok, St#compile{warnings=St#compile.warnings ++ Ws}};
 
1088
                    Ws = [{St#compile.ifile,[{?MODULE,{native,R}}]}],
 
1089
                    {ok,St#compile{warnings=St#compile.warnings ++ Ws}};
1067
1090
                false ->
1068
 
                    Es = [{St#compile.ifile,[{none,?MODULE,{native,R}}]}],
1069
 
                    {error, St#compile{errors=St#compile.errors ++ Es}}
 
1091
                    Es = [{St#compile.ifile,[{?MODULE,{native,R}}]}],
 
1092
                    {error,St#compile{errors=St#compile.errors ++ Es}}
1070
1093
            end
1071
1094
    catch
1072
 
        error:R ->
 
1095
        Class:R ->
 
1096
            Stk = erlang:get_stacktrace(),
1073
1097
            case IgnoreErrors of
1074
1098
                true ->
1075
 
                    Ws = [{St#compile.ifile,[{none,?MODULE,{native_crash,R}}]}],
1076
 
                    {ok, St#compile{warnings=St#compile.warnings ++ Ws}};
 
1099
                    Ws = [{St#compile.ifile,
 
1100
                           [{?MODULE,{native_crash,R,Stk}}]}],
 
1101
                    {ok,St#compile{warnings=St#compile.warnings ++ Ws}};
1077
1102
                false ->
1078
 
                    exit(R)
 
1103
                    erlang:raise(Class, R, Stk)
1079
1104
            end
1080
1105
    end.
1081
1106
 
1264
1289
listing(LFun, Ext, St) ->
1265
1290
    Lfile = outfile(St#compile.base, Ext, St#compile.options),
1266
1291
    case file:open(Lfile, [write,delayed_write]) of
1267
 
        {ok,Lf} -> 
 
1292
        {ok,Lf} ->
1268
1293
            Code = restore_expanded_types(Ext, St#compile.code),
1269
1294
            LFun(Lf, Code),
1270
1295
            ok = file:close(Lf),