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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%% ``The contents of this file are subject to the Erlang Public License,
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2000-2009. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
2
7
%% Version 1.1, (the "License"); you may not use this file except in
3
8
%% compliance with the License. You should have received a copy of the
4
9
%% Erlang Public License along with this software. If not, it can be
5
 
%% retrieved via the world wide web at http://www.erlang.org/.
 
10
%% retrieved online at http://www.erlang.org/.
6
11
%% 
7
12
%% Software distributed under the License is distributed on an "AS IS"
8
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
9
14
%% the License for the specific language governing rights and limitations
10
15
%% under the License.
11
16
%% 
12
 
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
13
 
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
14
 
%% AB. All Rights Reserved.''
15
 
%% 
16
 
%%     $Id$
 
17
%% %CopyrightEnd%
17
18
%%
18
19
%% Purpose : Function inlining optimisation for Core.
19
20
 
97
98
 
98
99
inline(Fs0, St0) ->
99
100
    %% Generate list of augmented functions.
100
 
    Fs1 = map(fun ({#c_fname{id=F,arity=A},#c_fun{body=B}}=Def) ->
101
 
                      Weight = core_lib:fold(fun weight_func/2, 0, B),
 
101
    Fs1 = map(fun ({#c_var{name={F,A}},#c_fun{body=B}}=Def) ->
 
102
                      Weight = cerl_trees:fold(fun weight_func/2, 0, B),
102
103
                      #fstat{func=F,arity=A,def=Def,weight=Weight}
103
104
              end, Fs0),
104
105
    %% Get inlineable functions, and inline them with themselves.
117
118
                              end
118
119
                      end, [], Fs1),
119
120
    Is1 = map(fun (#ifun{body=B}=If) ->
120
 
                      If#ifun{body=core_lib:map(match_fail_fun(), B)}
 
121
                      If#ifun{body=cerl_trees:map(match_fail_fun(), B)}
121
122
              end, Is0),
122
123
    Is2 = [inline_inline(If, Is1) || If <- Is1],
123
124
    %% We would like to remove inlined, non-exported functions here,
139
140
%%  ourselves.
140
141
 
141
142
inline_inline(#ifun{body=B,weight=Iw}=If, Is) ->
142
 
    Inline = fun (#c_apply{op=#c_fname{id=F,arity=A},args=As}=Call) ->
 
143
    Inline = fun (#c_apply{op=#c_var{name={F,A}},args=As}=Call) ->
143
144
                     case find_inl(F, A, Is) of
144
145
                         #ifun{vars=Vs,body=B2,weight=W} when W < Iw ->
145
146
                             #c_let{vars=Vs,
149
150
                     end;
150
151
                 (Core) -> Core
151
152
             end,
152
 
    If#ifun{body=core_lib:map(Inline, B)}.
 
153
    If#ifun{body=cerl_trees:map(Inline, B)}.
153
154
 
154
155
%% inline_func(Fstat, [Inline]) -> Fstat.
155
156
%%  Try to inline calls in a normal function.  Here we inline anything
156
157
%%  in the inline list.
157
158
 
158
159
inline_func(#fstat{def={Name,F0}}=Fstat, Is) ->
159
 
    Inline = fun (#c_apply{op=#c_fname{id=F,arity=A},args=As}=Call, Mod) ->
 
160
    Inline = fun (#c_apply{op=#c_var{name={F,A}},args=As}=Call, Mod) ->
160
161
                     case find_inl(F, A, Is) of
161
162
                         #ifun{vars=Vs,body=B} ->
162
163
                             {#c_let{vars=Vs,
167
168
                     end;
168
169
                 (Core, Mod) -> {Core,Mod}
169
170
             end,
170
 
    {F1,Mod} = core_lib:mapfold(Inline, false, F0),
 
171
    {F1,Mod} = cerl_trees:mapfold(Inline, false, F0),
171
172
    Fstat#fstat{def={Name,F1},modified=Mod}.
172
173
 
173
174
weight_func(_Core, Acc) -> Acc + 1.
194
195
%% kill_id_anns(Body) -> Body'
195
196
 
196
197
kill_id_anns(Body) ->
197
 
    core_lib:map(fun(#c_fun{anno=A0}=CFun) ->
198
 
                         A = kill_id_anns_1(A0),
199
 
                         CFun#c_fun{anno=A};
200
 
                    (Expr) when is_list(Expr) ->
201
 
                         Expr;
202
 
                    (Expr) ->
203
 
                         %% Mark everything as compiler generated to suppress
204
 
                         %% bogus warnings.
205
 
                         A = [compiler_generated|core_lib:get_anno(Expr)],
206
 
                         core_lib:set_anno(Expr, A)
207
 
                         end, Body).
 
198
    cerl_trees:map(fun(#c_fun{anno=A0}=CFun) ->
 
199
                           A = kill_id_anns_1(A0),
 
200
                           CFun#c_fun{anno=A};
 
201
                      (Expr) ->
 
202
                           %% Mark everything as compiler generated to suppress
 
203
                           %% bogus warnings.
 
204
                           A = [compiler_generated|core_lib:get_anno(Expr)],
 
205
                           core_lib:set_anno(Expr, A)
 
206
                   end, Body).
208
207
 
209
208
kill_id_anns_1([{'id',_}|As]) ->
210
209
    kill_id_anns_1(As);