~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/hipe/flow/cfg.inc

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-07 15:07:37 UTC
  • mfrom: (1.2.1 upstream) (5.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090507150737-i4yb5elwinm7r0hc
Tags: 1:13.b-dfsg1-1
* Removed another bunch of non-free RFCs from original tarball
  (closes: #527053).
* Fixed build-dependencies list by adding missing comma. This requires
  libsctp-dev again. Also, added libsctp1 dependency to erlang-base and
  erlang-base-hipe packages because the shared library is loaded via
  dlopen now and cannot be added using dh_slibdeps (closes: #526682).
* Weakened dependency of erlang-webtool on erlang-observer to recommends
  to avoid circular dependencies (closes: #526627).
* Added solaris-i386 to HiPE enabled architectures.
* Made script sources in /usr/lib/erlang/erts-*/bin directory executable,
  which is more convenient if a user wants to create a target Erlang system.
* Shortened extended description line for erlang-dev package to make it
  fit 80x25 terminals.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%% -*- Erlang -*-
2
2
%% -*- erlang-indent-level: 2 -*-
3
3
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
4
 
%% $Id$
 
4
%%
 
5
%% %CopyrightBegin%
 
6
%% 
 
7
%% Copyright Ericsson AB 2001-2009. All Rights Reserved.
 
8
%% 
 
9
%% The contents of this file are subject to the Erlang Public License,
 
10
%% Version 1.1, (the "License"); you may not use this file except in
 
11
%% compliance with the License. You should have received a copy of the
 
12
%% Erlang Public License along with this software. If not, it can be
 
13
%% retrieved online at http://www.erlang.org/.
 
14
%% 
 
15
%% Software distributed under the License is distributed on an "AS IS"
 
16
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
17
%% the License for the specific language governing rights and limitations
 
18
%% under the License.
 
19
%% 
 
20
%% %CopyrightEnd%
 
21
%%
5
22
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
6
23
%%
7
24
%%                       CONTROL FLOW GRAPHS
83
100
-export([breadthorder/1]).
84
101
-endif.
85
102
 
86
 
-compile(inline). 
 
103
-compile(inline).
87
104
 
88
105
%%=====================================================================
89
106
%%
121
138
%% Primitives (not all of these are exported)
122
139
%%
123
140
 
124
 
-spec start_label(#cfg{}) -> non_neg_integer().
 
141
-spec start_label(cfg()) -> cfg_lbl().
125
142
start_label(CFG) -> (CFG#cfg.info)#cfg_info.start_label.
126
143
 
127
144
-ifndef(GEN_CFG).
128
 
-spec start_label_update(#cfg{}, non_neg_integer()) -> #cfg{}.
 
145
-spec start_label_update(cfg(), cfg_lbl()) -> cfg().
129
146
start_label_update(CFG, NewStartLabel) ->
130
147
  Info = CFG#cfg.info,
131
 
  CFG#cfg{info=Info#cfg_info{start_label=NewStartLabel}}.
 
148
  CFG#cfg{info = Info#cfg_info{start_label = NewStartLabel}}.
132
149
 
133
 
-spec function(#cfg{}) -> mfa().
 
150
-spec function(cfg()) -> mfa().
134
151
function(CFG) -> (CFG#cfg.info)#cfg_info.'fun'.
135
152
 
136
 
-spec is_closure(#cfg{}) -> bool().
 
153
-spec is_closure(cfg()) -> bool().
137
154
is_closure(CFG) -> (CFG#cfg.info)#cfg_info.is_closure.
138
155
 
139
 
-spec is_leaf(#cfg{}) -> bool().
 
156
-spec is_leaf(cfg()) -> bool().
140
157
is_leaf(CFG) -> (CFG#cfg.info)#cfg_info.is_leaf.
141
158
 
142
159
mk_empty_cfg(Fun, StartLbl, Data, Closure, Leaf, Params) ->
143
160
  Info = #cfg_info{'fun' = Fun,
144
 
                   start_label=StartLbl,
145
 
                   is_closure=Closure,
146
 
                   is_leaf=Leaf,
147
 
                   params=Params},
148
 
  #cfg{table=gb_trees:empty(), data=Data, info=Info}.
 
161
                   start_label = StartLbl,
 
162
                   is_closure = Closure,
 
163
                   is_leaf = Leaf,
 
164
                   params = Params},
 
165
  #cfg{table = gb_trees:empty(), data = Data, info = Info}.
149
166
 
150
167
data(CFG) -> CFG#cfg.data.
151
168
-endif. % GEN_CFG
152
169
 
153
170
-ifdef(REMOVE_TRIVIAL_BBS_NEEDED).
154
 
-spec update_data(#cfg{}, cfg_data()) -> #cfg{}.
 
171
-spec update_data(cfg(), cfg_data()) -> cfg().
155
172
update_data(CFG, D) ->
156
 
  CFG#cfg{data=D}.
 
173
  CFG#cfg{data = D}.
157
174
-endif.
158
175
 
159
176
-ifdef(PARAMS_NEEDED).
163
180
-ifdef(PARAMS_UPDATE_NEEDED).
164
181
params_update(CFG, NewParams) ->
165
182
  Info = CFG#cfg.info,
166
 
  CFG#cfg{info=Info#cfg_info{params=NewParams}}.
 
183
  CFG#cfg{info = Info#cfg_info{params = NewParams}}.
167
184
-endif.
168
185
 
169
186
-ifdef(CLOSURE_ARITY_NEEDED).
170
 
-spec closure_arity(#cfg{}) -> byte().
 
187
-spec closure_arity(cfg()) -> arity().
171
188
closure_arity(CFG) ->
172
189
  Info = CFG#cfg.info,
173
190
  Info#cfg_info.closure_arity.
174
191
 
175
 
-spec closure_arity_update(#cfg{}, byte()) -> #cfg{}.
 
192
-spec closure_arity_update(cfg(), arity()) -> cfg().
176
193
closure_arity_update(CFG, Arity) ->
177
194
  Info = CFG#cfg.info,
178
 
  CFG#cfg{info=Info#cfg_info{closure_arity=Arity}}.
 
195
  CFG#cfg{info = Info#cfg_info{closure_arity = Arity}}.
179
196
-endif.
180
197
 
181
 
%% %% Don't forget to do a start_label_update if neccessary.
 
198
%% %% Don't forget to do a start_label_update if necessary.
182
199
%% update_code(CFG, NewCode) ->
183
200
%%   take_bbs(NewCode, CFG).
184
201
 
187
204
%% info_add(CFG, A) ->
188
205
%%    As = info(CFG),
189
206
%%    Info = CFG#cfg.info,
190
 
%%    CFG#cfg{info=Info#cfg_info{info=[A|As]}}.
 
207
%%    CFG#cfg{info = Info#cfg_info{info = [A|As]}}.
191
208
info_update(CFG, I) ->
192
209
  Info = CFG#cfg.info,
193
 
  CFG#cfg{info=Info#cfg_info{info=I}}.
 
210
  CFG#cfg{info = Info#cfg_info{info = I}}.
194
211
-endif.
195
212
 
196
213
%%=====================================================================
197
214
-ifndef(GEN_CFG).
198
215
 
199
 
%% @spec other_entrypoints(CFG::cfg()) -> [label()]
200
 
%% @doc  Returns a list of labels that are refered to from the data section.
 
216
-spec other_entrypoints(cfg()) -> [cfg_lbl()].
 
217
%% @doc Returns a list of labels that are refered to from the data section.
201
218
 
202
219
other_entrypoints(CFG) ->
203
220
  hipe_consttab:referred_labels(data(CFG)).
206
223
%%   Lbl =:= start_label(CFG) orelse
207
224
%%      lists:member(Lbl, other_entrypoints(CFG)).
208
225
 
209
 
%% @spec bb(CFG::cfg(), Label::label()) -> basic_block()
 
226
%% @spec bb(CFG::cfg(), Label::cfg_lbl()) -> basic_block()
210
227
%% @doc  Returns the basic block of the CFG which begins at the Label.
211
228
bb(CFG, Label) ->
212
229
  HT = CFG#cfg.table,
217
234
      not_found
218
235
  end.
219
236
 
220
 
%% Remove duplicates from a list. The first instance
221
 
%% (in left-to-right order) of an element is kept,
222
 
%% remaining instances are removed.
223
 
-spec remove_duplicates([Elem]) -> [Elem].
 
237
%% Remove duplicates from a list. The first instance (in left-to-right
 
238
%% order) of an element is kept, remaining instances are removed.
 
239
-spec remove_duplicates([cfg_lbl()]) -> [cfg_lbl()].
224
240
remove_duplicates(List) ->
225
241
  remove_duplicates(List, []).
226
242
 
227
 
-spec remove_duplicates([Elem], [Elem]) -> [Elem].
 
243
-spec remove_duplicates([cfg_lbl()], [cfg_lbl()]) -> [cfg_lbl()].
228
244
remove_duplicates([H|T], Acc) ->
229
245
  NewAcc =
230
246
    case lists:member(H, Acc) of
240
256
                        %% if Icode also starts using this function
241
257
 
242
258
%% @spec bb_insert_between(CFG::cfg(),
243
 
%%                         Label::label(), NewBB::basic_block(),
244
 
%%                         Pred::label(), Succ::label()) -> cfg() 
 
259
%%                         Label::cfg_lbl(), NewBB::basic_block(),
 
260
%%                         Pred::cfg_lbl(), Succ::cfg_lbl()) -> cfg() 
245
261
%%
246
262
%% @doc Insert the new basic block with label Label in the edge from
247
263
%%      Pred to Succ
248
264
 
249
265
bb_insert_between(CFG, Label, NewBB, Pred, Succ) ->
250
266
  Last = hipe_bb:last(NewBB),
251
 
  
252
267
  %% Asserts that NewBB ends in a label
253
268
  true = is_branch(Last),
254
 
 
255
269
  %% Asserts that the only Successor of NewBB is Succ
256
270
  [Succ] = remove_duplicates(branch_successors(Last)),
257
 
 
258
271
  HT = CFG#cfg.table,
259
 
 
260
272
  %% Asserts that Label does not exist in the CFG
261
273
  none = gb_trees:lookup(Label, HT),
262
 
 
263
274
  %% Updates the predecessor of NewBB
264
275
  {value, {PBB, PSucc, PPred}} = gb_trees:lookup(Pred, HT),
265
276
  NewPSucc = [Label|lists:delete(Succ, PSucc)],
267
278
  PButLast = hipe_bb:butlast(PBB),
268
279
  NewPBB = hipe_bb:code_update(PBB, PButLast++[redirect_jmp(PLast, Succ, Label)]),
269
280
  HT1 = gb_trees:update(Pred, {NewPBB,NewPSucc,PPred}, HT),
270
 
 
271
281
  %% Updates the successor of NewBB
272
282
  {value, {SBB, SSucc, SPred}} = gb_trees:lookup(Succ, HT1),
273
283
  NewSPred = [Label|lists:delete(Pred, SPred)],
275
285
  NewSCode = redirect_phis(SCode, Pred, Label, []),
276
286
  NewSBB = hipe_bb:code_update(SBB, NewSCode),
277
287
  HT2 = gb_trees:update(Succ, {NewSBB,SSucc,NewSPred}, HT1),
278
 
  
279
288
  %% Enters NewBB into the CFG
280
289
  HT3 = gb_trees:insert(Label, {NewBB,[Succ],[Pred]}, HT2), 
281
290
  CFG#cfg{table = HT3}.
293
302
 
294
303
-endif.
295
304
 
296
 
%% @spec bb_add(CFG::cfg(), Label::label(), NewBB::basic_block()) -> cfg()
 
305
%% @spec bb_add(CFG::cfg(), Label::cfg_lbl(), NewBB::basic_block()) -> cfg()
297
306
%% @doc  Adds a new basic block to a CFG (or updates an existing block).
298
307
bb_add(CFG, Label, NewBB) ->
299
308
  %% Asserting that the NewBB is a legal basic block
300
309
  Last = hipe_bb:last(NewBB),
301
310
  case is_branch(Last) of
302
311
    true  -> ok;
303
 
    false -> throw({?MODULE,{"Basic block ends without branch",Last}})
 
312
    false -> throw({?MODULE, {"Basic block ends without branch", Last}})
304
313
  end,
305
314
  %% The order of the elements from branch_successors/1 is
306
 
  %% significant. It determines the basic block order when
307
 
  %% the CFG is converted to linear form, and the order may
308
 
  %% have been tuned for branch prediction purposes.
 
315
  %% significant. It determines the basic block order when the CFG is
 
316
  %% converted to linear form. That order may have been tuned for
 
317
  %% branch prediction purposes.
309
318
  Succ = remove_duplicates(branch_successors(Last)),
310
319
  HT = CFG#cfg.table,
311
320
  {OldSucc, OldPred} = case gb_trees:lookup(Label, HT) of
314
323
                         none ->
315
324
                           {[], []}
316
325
                       end,
317
 
  %% Change this block to contain new BB and new successors, but keep the
318
 
  %% old predecessors which will be updated in the following steps
 
326
  %% Change this block to contain new BB and new successors, but keep
 
327
  %% the old predecessors which will be updated in the following steps
319
328
  HT1 = gb_trees:enter(Label, {NewBB, Succ, OldPred}, HT),
320
329
  %% Add this block as predecessor to its new successors
321
 
  HT2 = lists:foldl(fun (P,HTAcc) ->
 
330
  HT2 = lists:foldl(fun (P, HTAcc) ->
322
331
                      add_pred(HTAcc, P, Label)
323
332
                    end,
324
333
                    HT1, Succ -- OldSucc),
325
334
  %% Remove this block as predecessor of its former successors
326
 
  HT3 = lists:foldl(fun (S,HTAcc) ->
 
335
  HT3 = lists:foldl(fun (S, HTAcc) ->
327
336
                      remove_pred(HTAcc, S, Label)
328
337
                    end,
329
338
                    HT2, OldSucc -- Succ),
330
339
  CFG#cfg{table = HT3}.
331
340
 
332
 
 
333
341
remove_pred(HT, FromL, PredL) ->
334
342
  case gb_trees:lookup(FromL, HT) of
335
343
    {value, {Block, Succ, Preds}} ->
351
359
 
352
360
%% find_highest_label(CFG) ->
353
361
%%   Labels = labels(CFG),
354
 
%%   lists:foldl(fun(X, Acc) -> max(X, Acc) end, 0, Labels).
 
362
%%   lists:foldl(fun(X, Acc) -> erlang:max(X, Acc) end, 0, Labels).
355
363
%% 
356
364
%% find_highest_var(CFG) ->
357
365
%%   Labels = labels(CFG),
358
366
%%   Fun = fun(X, Max) ->
359
367
%%          Code = hipe_bb:code(bb(CFG, X)),
360
368
%%          NewMax = highest_var(Code),
361
 
%%          max(Max, NewMax)
 
369
%%          erlang:max(Max, NewMax)
362
370
%%      end,
363
371
%%   lists:foldl(Fun, 0, Labels).
364
 
%% 
365
 
%% max(X, Y) ->
366
 
%%   case X > Y of
367
 
%%     true -> X;
368
 
%%     false -> Y
369
 
%%   end.
370
372
 
371
373
-ifdef(CFG_CAN_HAVE_PHI_NODES).
372
374
%% phi-instructions in a removed block's successors must be aware of
656
658
 
657
659
-ifdef(REMOVE_TRIVIAL_BBS_NEEDED).
658
660
 
659
 
-spec remove_trivial_bbs(#cfg{}) -> #cfg{}.
 
661
-spec remove_trivial_bbs(cfg()) -> cfg().
660
662
remove_trivial_bbs(CFG) ->
661
663
  ?opt_start_timer("Merge BBs"),
662
664
  CFG0 = merge_bbs(rewrite_trivial_branches(CFG)),
731
733
                            remove_pred(HTAcc, S, Label)
732
734
                        end,
733
735
                        HT, Succ),
734
 
      CFG#cfg{table=gb_trees:delete(Label, HT1)};
 
736
      CFG#cfg{table = gb_trees:delete(Label, HT1)};
735
737
    none -> 
736
738
      CFG
737
739
  end.
813
815
 
814
816
%% Rewrite all pure branches with one successor to goto:s
815
817
 
816
 
-spec rewrite_trivial_branches(#cfg{}) -> #cfg{}.
 
818
-spec rewrite_trivial_branches(cfg()) -> cfg().
817
819
rewrite_trivial_branches(CFG) ->
818
820
  rewrite_trivial_branches(postorder(CFG), CFG).
819
821
 
920
922
 
921
923
-ifdef(REMOVE_UNREACHABLE_CODE).
922
924
 
923
 
-spec remove_unreachable_code(#cfg{}) -> #cfg{}.
 
925
-spec remove_unreachable_code(cfg()) -> cfg().
924
926
 
925
927
remove_unreachable_code(CFG) ->
926
928
  Start = start_label(CFG),