~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

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

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
3
%%
4
 
%% Copyright Ericsson AB 1996-2010. All Rights Reserved.
 
4
%% Copyright Ericsson AB 1996-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
31
31
-import(ordsets, [from_list/1,add_element/2,union/2]).
32
32
-import(lists,   [member/2,foldl/3,foldr/3]).
33
33
 
34
 
-compile({nowarn_deprecated_function, {erlang,hash,2}}).
35
 
 
36
34
-include("../include/erl_bits.hrl").
37
35
 
38
36
-record(expand, {module=[],                     %Module name
43
41
                 mod_imports,                   %Module Imports
44
42
                 compile=[],                    %Compile flags
45
43
                 attributes=[],                 %Attributes
 
44
                 callbacks=[],                  %Callbacks
46
45
                 defined=[],                    %Defined functions
47
46
                 vcount=0,                      %Variable counter
48
47
                 func=[],                       %Current function
49
48
                 arity=[],                      %Arity for current function
50
49
                 fcount=0,                      %Local fun count
51
 
                 fun_index=0,                   %Global index for funs
52
50
                 bitdefault,
53
51
                 bittypes
54
52
                }).
172
170
               end, Predef, Forms),
173
171
    St#expand{defined=ordsets:from_list(Fs)}.
174
172
 
175
 
module_attrs(St) ->
176
 
    {[{attribute,Line,Name,Val} || {Name,Line,Val} <- St#expand.attributes],St}.
 
173
module_attrs(#expand{attributes=Attributes}=St) ->
 
174
    Attrs = [{attribute,Line,Name,Val} || {Name,Line,Val} <- Attributes],
 
175
    Callbacks = [Callback || {_,_,callback,_}=Callback <- Attrs],
 
176
    {Attrs,St#expand{callbacks=Callbacks}}.
177
177
 
178
178
module_predef_funcs(St) ->
 
179
    {Mpf1,St1}=module_predef_func_beh_info(St),
 
180
    {Mpf2,St2}=module_predef_funcs_mod_info(St1),
 
181
    {Mpf1++Mpf2,St2}.
 
182
 
 
183
module_predef_func_beh_info(#expand{callbacks=[]}=St) ->
 
184
    {[], St};
 
185
module_predef_func_beh_info(#expand{callbacks=Callbacks,defined=Defined,
 
186
                                    exports=Exports}=St) ->
 
187
    PreDef=[{behaviour_info,1}],
 
188
    PreExp=PreDef,
 
189
    {[gen_beh_info(Callbacks)],
 
190
     St#expand{defined=union(from_list(PreDef), Defined),
 
191
               exports=union(from_list(PreExp), Exports)}}.
 
192
 
 
193
gen_beh_info(Callbacks) ->
 
194
    List = make_list(Callbacks),
 
195
    {function,0,behaviour_info,1,
 
196
     [{clause,0,[{atom,0,callbacks}],[],
 
197
       [List]}]}.
 
198
 
 
199
make_list([]) -> {nil,0};
 
200
make_list([{_,_,_,[{{Name,Arity},_}]}|Rest]) ->
 
201
    {cons,0,
 
202
     {tuple,0,
 
203
      [{atom,0,Name},
 
204
       {integer,0,Arity}]},
 
205
     make_list(Rest)}.
 
206
 
 
207
module_predef_funcs_mod_info(St) ->
179
208
    PreDef = [{module_info,0},{module_info,1}],
180
209
    PreExp = PreDef,
181
210
    {[{function,0,module_info,0,
223
252
    St#expand{exports=union(from_list(Es), St#expand.exports)};
224
253
attribute(import, Is, _L, St) ->
225
254
    import(Is, St);
226
 
attribute(compile, C, _L, St) when is_list(C) ->
227
 
    St#expand{compile=St#expand.compile ++ C};
228
 
attribute(compile, C, _L, St) ->
229
 
    St#expand{compile=St#expand.compile ++ [C]};
 
255
attribute(compile, _C, _L, St) ->
 
256
    St;
230
257
attribute(Name, Val, Line, St) when is_list(Val) ->
231
258
    St#expand{attributes=St#expand.attributes ++ [{Name,Line,Val}]};
232
259
attribute(Name, Val, Line, St) ->
508
535
%% Transform an "explicit" fun {'fun', Line, {clauses, Cs}} into an
509
536
%% extended form {'fun', Line, {clauses, Cs}, Info}, unless it is the
510
537
%% name of a BIF (erl_lint has checked that it is not an import).
511
 
%% Process the body sequence directly to get the new and used variables.
512
538
%% "Implicit" funs {'fun', Line, {function, F, A}} are not changed.
513
539
 
514
540
fun_tq(Lf, {function,F,A}=Function, St0) ->
515
 
    {As,St1} = new_vars(A, Lf, St0),
516
 
    Cs = [{clause,Lf,As,[],[{call,Lf,{atom,Lf,F},As}]}],
517
541
    case erl_internal:bif(F, A) of
518
542
        true ->
 
543
            {As,St1} = new_vars(A, Lf, St0),
 
544
            Cs = [{clause,Lf,As,[],[{call,Lf,{atom,Lf,F},As}]}],
519
545
            fun_tq(Lf, {clauses,Cs}, St1);
520
546
        false ->
521
 
            Index = St0#expand.fun_index,
522
 
            Uniq = erlang:hash(Cs, (1 bsl 27)-1),
523
 
            {Fname,St2} = new_fun_name(St1),
524
 
            {{'fun',Lf,Function,{Index,Uniq,Fname}},
525
 
             St2#expand{fun_index=Index+1}}
 
547
            {Fname,St1} = new_fun_name(St0),
 
548
            Index = Uniq = 0,
 
549
            {{'fun',Lf,Function,{Index,Uniq,Fname}},St1}
526
550
    end;
527
 
fun_tq(L, {function,M,F,A}, St) ->
528
 
    {{call,L,{remote,L,{atom,L,erlang},{atom,L,make_fun}},
529
 
      [{atom,L,M},{atom,L,F},{integer,L,A}]},St};
 
551
fun_tq(L, {function,M,F,A}, St) when is_atom(M), is_atom(F), is_integer(A) ->
 
552
    %% This is the old format for external funs, generated by a pre-R15
 
553
    %% compiler. That means that a tool, such as the debugger or xref,
 
554
    %% directly invoked this module with the abstract code from a
 
555
    %% pre-R15 BEAM file. Be helpful, and translate it to the new format.
 
556
    fun_tq(L, {function,{atom,L,M},{atom,L,F},{integer,L,A}}, St);
 
557
fun_tq(Lf, {function,_,_,_}=ExtFun, St) ->
 
558
    {{'fun',Lf,ExtFun},St};
530
559
fun_tq(Lf, {clauses,Cs0}, St0) ->
531
 
    Uniq = erlang:hash(Cs0, (1 bsl 27)-1),
532
560
    {Cs1,St1} = fun_clauses(Cs0, St0),
533
 
    Index = St1#expand.fun_index,
534
561
    {Fname,St2} = new_fun_name(St1),
535
 
    {{'fun',Lf,{clauses,Cs1},{Index,Uniq,Fname}},
536
 
     St2#expand{fun_index=Index+1}}.
 
562
    %% Set dummy values for Index and Uniq -- the real values will
 
563
    %% be assigned by beam_asm.
 
564
    Index = Uniq = 0,
 
565
    {{'fun',Lf,{clauses,Cs1},{Index,Uniq,Fname}},St2}.
537
566
 
538
567
fun_clauses([{clause,L,H0,G0,B0}|Cs0], St0) ->
539
568
    {H,St1} = head(H0, St0),