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

« back to all changes in this revision

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

  • 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
 
%% ``The contents of this file are subject to the Erlang Public License,
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2002-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 2002, Ericsson AB.
14
 
%% All Rights Reserved.''
15
 
%% 
16
 
%%     $Id$
 
17
%% %CopyrightEnd%
17
18
%%
18
19
 
19
20
-module(beam_dead).
126
127
%%%
127
128
%%%  provided that {x,0} is killed at both L2 and L3.
128
129
%%%
129
 
%%% (6) Remove redundant is_boolean such as the one in
130
 
%%%
131
 
%%%             test is_eq_exact Fail Reg true
132
 
%%%             test is_boolean Fail Reg
133
 
%%%
134
 
%%%     The following sequence
135
 
%%%
136
 
%%%             test is_ne_eq_exact Fail Reg true
137
 
%%%             test is_boolean Fail Reg
138
 
%%%
139
 
%%%     can be rewritten to
140
 
%%%
141
 
%%%             test is_eq_exact Fail Reg false
142
 
%%%
143
 
%%%     (The idea is that both tests end up in the same place if they fail,
144
 
%%%     and that the is_boolean test never can fail if the first test succeeds;
145
 
%%%     therefore the is_boolean test is redundant.)
146
 
%%%
147
130
 
148
131
-import(lists, [mapfoldl/3,reverse/1]).
149
132
 
155
138
    {ok,{Mod,Exp,Attr,Fs,Lc}}.
156
139
 
157
140
function({function,Name,Arity,CLabel,Is0}, Lc0) ->
158
 
    Is1 = beam_jump:remove_unused_labels(Is0),
159
 
    Is2 = bopt(Is1),
160
 
 
161
 
    %% Optimize away dead code.
162
 
    {Is3,Lc} = forward(Is2, Lc0),
163
 
    Is4 = backward(Is3),
164
 
    Is = move_move_into_block(Is4, []),
165
 
    {{function,Name,Arity,CLabel,Is},Lc}.
166
 
 
167
 
%%%
168
 
%%% Remove redundant is_boolean tests.
169
 
%%%
170
 
 
171
 
bopt(Is) ->
172
 
    bopt_1(Is, []).
173
 
 
174
 
bopt_1([{test,is_boolean,_,_}=I|Is], Acc0) ->
175
 
    case opt_is_bool(I, Acc0) of
176
 
        no -> bopt_1(Is, [I|Acc0]);
177
 
        yes -> bopt_1(Is, Acc0);
178
 
        {yes,Acc} -> bopt_1(Is, Acc)
179
 
    end;
180
 
bopt_1([I|Is], Acc) -> bopt_1(Is, [I|Acc]);
181
 
bopt_1([], Acc) -> reverse(Acc).
182
 
 
183
 
opt_is_bool({test,is_boolean,{f,Lbl},[Reg]}, Acc) ->
184
 
    opt_is_bool_1(Acc, Reg, Lbl).
185
 
 
186
 
opt_is_bool_1([{test,is_eq_exact,{f,Lbl},[Reg,{atom,true}]}|_], Reg, Lbl) ->
187
 
    %% Instruction not needed in this context.
188
 
    yes;
189
 
opt_is_bool_1([{test,is_ne_exact,{f,Lbl},[Reg,{atom,true}]}|Acc], Reg, Lbl) ->
190
 
    %% Rewrite to shorter test.
191
 
    {yes,[{test,is_eq_exact,{f,Lbl},[Reg,{atom,false}]}|Acc]};
192
 
opt_is_bool_1([{test,_,{f,Lbl},_}=Test|Acc0], Reg, Lbl) ->
193
 
    case opt_is_bool_1(Acc0, Reg, Lbl) of
194
 
        {yes,Acc} -> {yes,[Test|Acc]};
195
 
        Other -> Other
196
 
    end;
197
 
opt_is_bool_1(_, _, _) -> no.
 
141
    try
 
142
        Is1 = beam_jump:remove_unused_labels(Is0),
 
143
 
 
144
        %% Initialize label information with the code
 
145
        %% for the func_info label. Without it, a register
 
146
        %% may seem to be live when it is not.
 
147
        [{label,L},{func_info,_,_,_}=FI|_] = Is1,
 
148
        D0 = beam_utils:empty_label_index(),
 
149
        D = beam_utils:index_label(L, [FI], D0),
 
150
 
 
151
        %% Optimize away dead code.
 
152
        {Is2,Lc} = forward(Is1, Lc0),
 
153
        Is3 = backward(Is2, D),
 
154
        Is = move_move_into_block(Is3, []),
 
155
        {{function,Name,Arity,CLabel,Is},Lc}
 
156
    catch
 
157
        Class:Error ->
 
158
            Stack = erlang:get_stacktrace(),
 
159
            io:fwrite("Function: ~w/~w\n", [Name,Arity]),
 
160
            erlang:raise(Class, Error, Stack)
 
161
    end.
198
162
 
199
163
%% We must split the basic block when we encounter instructions with labels,
200
164
%% such as catches and BIFs. All labels must be visible outside the blocks.
204
168
    Is = split_blocks(Is0, []),
205
169
    {function,Name,Arity,CLabel,Is}.
206
170
 
207
 
split_blocks([{block,[{'%live',_}=Live]}|Is], Acc) ->
208
 
    split_blocks(Is, [Live|Acc]);
209
171
split_blocks([{block,[]}|Is], Acc) ->
210
172
    split_blocks(Is, Acc);
211
173
split_blocks([{block,Bl}|Is], Acc0) ->
231
193
split_block([], Bl, Acc) -> make_block(Bl, Acc).
232
194
 
233
195
make_block([], Acc) -> Acc;
234
 
make_block([{'%live',_},{set,[D],Ss,{bif,Op,Fail}}|Bl]=Bl0, Acc) ->
 
196
make_block([{set,[D],Ss,{bif,Op,Fail}}|Bl]=Bl0, Acc) ->
235
197
    %% If the last instruction in the block is a comparison or boolean operator
236
 
    %% (such as '=:='), move it out of the block to faciliate further
 
198
    %% (such as '=:='), move it out of the block to facilitate further
237
199
    %% optimizations.
238
200
    Arity = length(Ss),
239
201
    case erl_internal:comp_op(Op, Arity) orelse
248
210
                false -> [I,{block,reverse(Bl)}|Acc]
249
211
            end
250
212
    end;
251
 
make_block([{'%live',_},{set,[Dst],[Src],move}|Bl], Acc) ->
 
213
make_block([{set,[Dst],[Src],move}|Bl], Acc) ->
252
214
    %% Make optimization of {move,Src,Dst}, {jump,...} possible.
253
215
    I = {move,Src,Dst},
254
216
    case Bl =:= [] of
277
239
forward(Is, Lc) ->
278
240
    forward(Is, gb_trees:empty(), Lc, []).
279
241
 
280
 
forward([{'%live',_}|Is], D, Lc, Acc) ->
281
 
    %% Remove - prevents optimizations.
282
 
    forward(Is, D, Lc, Acc);
283
 
forward([{block,[{'%live',_}]}|Is], D, Lc, Acc) ->
 
242
forward([{block,[]}|Is], D, Lc, Acc) ->
284
243
    %% Empty blocks can prevent optimizations.
285
244
    forward(Is, D, Lc, Acc);
286
245
forward([{select_val,Reg,_,{list,List}}=I|Is], D0, Lc, Acc) ->
299
258
                _ -> Blk                       %Keep move instruction.
300
259
            end,
301
260
    forward([Block|Is], D, Lc, [LblI|Acc]);
 
261
forward([{label,Lbl}=LblI|[{move,Lit,Dst}|Is1]=Is0], D, Lc, Acc) ->
 
262
    Is = case gb_trees:lookup({Lbl,Dst}, D) of
 
263
             {value,Lit} ->
 
264
                 %% The move instruction seems to be redundant, but also make
 
265
                 %% sure that the instruction preceeding the label
 
266
                 %% cannot fall through to the move instruction.
 
267
                 case is_unreachable_after(Acc) of
 
268
                     false -> Is0;        %Must keep move instruction.
 
269
                     true -> Is1     %Safe to remove move instruction.
 
270
                  end;
 
271
             _ -> Is0                  %Keep move instruction.
 
272
          end,
 
273
    forward(Is, D, Lc, [LblI|Acc]);
302
274
forward([{test,is_eq_exact,_,[Dst,Src]}=I,
303
275
         {block,[{set,[Dst],[Src],move}|Bl]}|Is], D, Lc, Acc) ->
304
276
    forward([I,{block,Bl}|Is], D, Lc, Acc);
341
313
%%% Scan instructions in reverse execution order and remove dead code.
342
314
%%%
343
315
 
344
 
backward(Is) ->
345
 
    backward(Is, beam_utils:empty_label_index(), []).
 
316
backward(Is, D) ->
 
317
    backward(Is, D, []).
346
318
 
 
319
backward([{test,is_eq_exact,Fail,[Dst,{integer,Arity}]}=I|
 
320
          [{bif,tuple_size,Fail,[Reg],Dst}|Is]=Is0], D, Acc) ->
 
321
    %% Provided that Dst is killed following this sequence,
 
322
    %% we can rewrite the instructions like this:
 
323
    %%
 
324
    %% bif tuple_size Fail Reg Dst  ==>  is_tuple Fail Reg
 
325
    %% is_eq_exact Fail Dst Integer      test_arity Fail Reg Integer
 
326
    %%
 
327
    %% (still two instructions, but they they will be combined to
 
328
    %% one by the loader).
 
329
    case beam_utils:is_killed(Dst, Acc, D) andalso (Arity bsr 32) =:= 0 of
 
330
        false ->
 
331
            %% Not safe because the register Dst is not killed
 
332
            %% (probably cannot not happen in practice) or the arity
 
333
            %% does not fit in 32 bits (the loader will fail to load
 
334
            %% the module). We must move the first instruction to the
 
335
            %% accumulator to avoid an infinite loop.
 
336
            backward(Is0, D, [I|Acc]);
 
337
        true ->
 
338
            %% Safe.
 
339
            backward([{test,test_arity,Fail,[Reg,Arity]},
 
340
                      {test,is_tuple,Fail,[Reg]}|Is], D, Acc)
 
341
    end;
347
342
backward([{label,Lbl}=L|Is], D, Acc) ->
348
343
    backward(Is, beam_utils:index_label(Lbl, Acc, D), [L|Acc]);
349
344
backward([{select_val,Reg,{f,Fail0},{list,List0}}|Is], D, Acc) ->
372
367
    catch
373
368
        throw:not_possible -> backward(Is0, D, [J|Acc])
374
369
    end;
375
 
backward([{test,bs_start_match2,{f,To0},[Src|_]=Info}|Is], D, Acc) ->
 
370
backward([{test,bs_start_match2,{f,To0},Live,[Src|_]=Info,Dst}|Is], D, Acc) ->
376
371
    To = shortcut_bs_start_match(To0, Src, D),
377
 
    I = {test,bs_start_match2,{f,To},Info},
 
372
    I = {test,bs_start_match2,{f,To},Live,Info,Dst},
378
373
    backward(Is, D, [I|Acc]);
379
 
backward([{test,Op,{f,To0},Ops}|Is], D, Acc) ->
380
 
    To = shortcut_bs_test(To0, Is, D),
 
374
backward([{test,is_eq_exact=Op,{f,To0},[Reg,{atom,Val}]=Ops}|Is], D, Acc) ->
 
375
    To1 = shortcut_bs_test(To0, Is, D),
 
376
    To = shortcut_fail_label(To1, Reg, Val, D),
381
377
    I = {test,Op,{f,To},Ops},
382
378
    backward(Is, D, [I|Acc]);
383
 
backward([{block,[{'%live',_}]}|Is], D, Acc) ->
384
 
    %% A redundant block could prevent some jump optimizations in beam_jump.
385
 
    %% Ge rid of it.
386
 
    backward(Is, D, Acc);
 
379
backward([{test,Op,{f,To0},Ops0}|Is], D, Acc) ->
 
380
    To1 = shortcut_bs_test(To0, Is, D),
 
381
    To2 = shortcut_label(To1, D),
 
382
    %% Try to shortcut a repeated test:
 
383
    %%
 
384
    %%        test Op {f,Fail1} Operands        test Op {f,Fail2} Operands
 
385
    %%        . . .                       ==>   ...
 
386
    %% Fail1: test Op {f,Fail2} Operands        Fail1: test Op {f,Fail2} Operands
 
387
    %%
 
388
    To = case beam_utils:code_at(To2, D) of
 
389
             [{test,Op,{f,To3},Ops}|_] ->
 
390
                 case equal_ops(Ops0, Ops) of
 
391
                     true -> To3;
 
392
                     false -> To2
 
393
                 end;
 
394
             _Code ->
 
395
                 To2
 
396
         end,
 
397
    I = {test,Op,{f,To},Ops0},
 
398
    backward(Is, D, [I|Acc]);
 
399
backward([{test,Op,{f,To0},Live,Ops0,Dst}|Is], D, Acc) ->
 
400
    To1 = shortcut_bs_test(To0, Is, D),
 
401
    To2 = shortcut_label(To1, D),
 
402
    %% Try to shortcut a repeated test:
 
403
    %%
 
404
    %%        test Op {f,Fail1} _ Ops _         test Op {f,Fail2} _ Ops _
 
405
    %%        . . .                       ==>   ...
 
406
    %% Fail1: test Op {f,Fail2} _ Ops _   Fail1: test Op {f,Fail2} _ Ops _
 
407
    %%
 
408
    To = case beam_utils:code_at(To2, D) of
 
409
             [{test,Op,{f,To3},_,Ops,_}|_] ->
 
410
                 case equal_ops(Ops0, Ops) of
 
411
                     true -> To3;
 
412
                     false -> To2
 
413
                 end;
 
414
             _Code ->
 
415
                 To2
 
416
         end,
 
417
    I = {test,Op,{f,To},Live,Ops0,Dst},
 
418
    backward(Is, D, [I|Acc]);
387
419
backward([{kill,_}=I|Is], D, [Exit|_]=Acc) ->
388
420
    case beam_jump:is_exit_instruction(Exit) of
389
421
        false -> backward(Is, D, [I|Acc]);
390
422
        true -> backward(Is, D, Acc)
391
423
    end;
392
 
backward([{'%live',_}|Is], D, Acc) ->
393
 
    backward(Is, D, Acc);
394
424
backward([I|Is], D, Acc) ->
395
425
    backward(Is, D, [I|Acc]);
396
426
backward([], _D, Acc) -> Acc.
397
427
 
 
428
equal_ops([{field_flags,FlA0}|T0], [{field_flags,FlB0}|T1]) ->
 
429
    FlA = lists:keydelete(anno, 1, FlA0),
 
430
    FlB = lists:keydelete(anno, 1, FlB0),
 
431
    FlA =:= FlB andalso equal_ops(T0, T1);
 
432
equal_ops([Op|T0], [Op|T1]) ->
 
433
    equal_ops(T0, T1);
 
434
equal_ops([], []) -> true;
 
435
equal_ops(_, _) -> false.
 
436
    
398
437
shortcut_select_list([{_,Val}=Lit,{f,To0}|T], Reg, D, Acc) ->
399
438
    To = shortcut_select_label(To0, Reg, Val, D),
400
439
    shortcut_select_list(T, Reg, D, [{f,To},Lit|Acc]);
415
454
            shortcut_select_label(To, Reg, Val, D);
416
455
        [{test,is_eq_exact,{f,_},[Reg,{atom,Val}]},{label,To}|_] when is_atom(Val) ->
417
456
            shortcut_select_label(To, Reg, Val, D);
418
 
        [{test,is_eq_exact,{f,To},[Reg,{atom,_}]}|_] when is_atom(Val) ->
 
457
        [{test,is_eq_exact,{f,_},[Reg,{atom,Val}]},{jump,{f,To}}|_] when is_atom(Val) ->
 
458
            shortcut_select_label(To, Reg, Val, D);
 
459
        [{test,is_eq_exact,{f,To},[Reg,{atom,AnotherVal}]}|_]
 
460
        when is_atom(Val), Val =/= AnotherVal ->
419
461
            shortcut_select_label(To, Reg, Val, D);
420
462
        [{test,is_ne_exact,{f,To},[Reg,{atom,Val}]}|_] when is_atom(Val) ->
421
463
            shortcut_select_label(To, Reg, Val, D);
427
469
            To0
428
470
    end.
429
471
 
 
472
shortcut_fail_label(To0, Reg, Val, D) ->
 
473
    case beam_utils:code_at(To0, D) of
 
474
        [{jump,{f,To}}|_] ->
 
475
            shortcut_fail_label(To, Reg, Val, D);
 
476
        [{test,is_eq_exact,{f,To},[Reg,{atom,Val}]}|_] when is_atom(Val) ->
 
477
            shortcut_fail_label(To, Reg, Val, D);
 
478
        _ ->
 
479
            To0
 
480
    end.
 
481
 
430
482
shortcut_boolean_label(To0, Reg, Bool0, D) when is_boolean(Bool0) ->
431
483
    case beam_utils:code_at(To0, D) of
432
484
        [{bif,'not',_,[Reg],Reg},{jump,{f,To}}|_] ->
476
528
shortcut_bs_test(To, Is, D) ->
477
529
    shortcut_bs_test_1(beam_utils:code_at(To, D), Is, To, D).
478
530
 
479
 
shortcut_bs_test_1(none, _, To, _) ->
480
 
    %% Probably the func_info label.
481
 
    To;
482
531
shortcut_bs_test_1([{bs_restore2,Reg,SavePoint}|Is], PrevIs, To, D) ->
483
532
    shortcut_bs_test_2(Is, {Reg,SavePoint}, PrevIs, To, D);
484
533
shortcut_bs_test_1([_|_], _, To, _) -> To.
505
554
    end;
506
555
shortcut_bs_test_2([_|_], _, _, To, _) -> To.
507
556
 
508
 
count_bits_matched([{test,_,_,[_,_,Sz,U,{field_flags,_},_]}|Is], SavePoint, Bits) ->
 
557
count_bits_matched([{test,_,_,_,[_,Sz,U,{field_flags,_}],_}|Is], SavePoint, Bits) ->
509
558
    case Sz of
510
559
        {integer,N} -> count_bits_matched(Is, SavePoint, Bits+N*U);
511
560
        _ -> count_bits_matched(Is, SavePoint, Bits)
544
593
 
545
594
shortcut_bs_start_match_2([{jump,{f,To}}|_], _, _) ->
546
595
    To;
547
 
shortcut_bs_start_match_2([{test,bs_start_match2,{f,To},[Reg|_]}|_], Reg, _) ->
 
596
shortcut_bs_start_match_2([{test,bs_start_match2,{f,To},_,[Reg|_],_}|_], Reg, _) ->
548
597
    To;
549
598
shortcut_bs_start_match_2(_Is, _Reg, To) ->
550
599
    To.