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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-08-05 20:54:29 UTC
  • mfrom: (6.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090805205429-pm4pnwew8axraosl
Tags: 1:13.b.1-dfsg-5
* Fixed parentheses in Emacs mode (closes: #536891).
* Removed unnecessary conflicts with erlang-manpages package.
* Added workaround for #475459: disabled threads on sparc architecture.
  This breaks wxErlang, so it's only a temporary solution.

Show diffs side-by-side

added added

removed removed

Lines of Context:
51
51
%%%     The purpose is to allow further optimizations at the place from
52
52
%%%     which the code was moved.
53
53
%%%
54
 
%%% (3) Any unreachable code is removed.  Unreachable code is code after
55
 
%%%     jump, call_last and other instructions which never transfer control
56
 
%%%     to the following instruction.  Code is unreachable up to the next
57
 
%%%     *referenced* label.  Note that the optimisations below might
58
 
%%%     generate more possibilities for removing unreachable code.
 
54
%%% (3) Any unreachable code is removed.  Unreachable code is code
 
55
%%%     after jump, call_last and other instructions which never
 
56
%%%     transfer control to the following instruction.  Code is
 
57
%%%     unreachable up to the next *referenced* label.  Note that the
 
58
%%%     optimisations below might generate more possibilities for
 
59
%%%     removing unreachable code.
59
60
%%%
60
61
%%% (4) This code:
61
62
%%%     L1:     jump L2
76
77
%%%      jump L1
77
78
%%%      L1:
78
79
%%%
79
 
%%%      the jump will be removed.
 
80
%%%      the jump (but not the label) will be removed.
80
81
%%%
81
82
%%% (6) If test instructions are used to skip a single jump instruction,
82
83
%%%      the test is inverted and the jump is eliminated (provided that
89
90
%%%      will be changed to
90
91
%%%
91
92
%%%      is_ne L2 {x,1} {x,2}
92
 
%%%
93
 
%%%      (The label L1 will be retained if there were previous references to it.)
 
93
%%%      L1:
 
94
%%%
 
95
%%%      Because there may be backward references to the label L1
 
96
%%%      (for instance from the wait_timeout/1 instruction), we will
 
97
%%%      always keep the label. (beam_clean will remove any unused
 
98
%%%      labels.)
 
99
%%%
 
100
%%% Note: This modules depends on (almost) all branches and jumps only
 
101
%%% going forward, so that we can remove instructions (including defintion
 
102
%%% of labels) after any label that has not been referenced by the code
 
103
%%% preceeding the labels. Regarding the few instructions that have backward
 
104
%%% references to labels, we assume that they only transfer control back
 
105
%%% to an instruction that has already been executed. That is,
 
106
%%% code such as
 
107
%%%
 
108
%%%         jump L_entry
 
109
%%%
 
110
%%%      L_again:
 
111
%%%           .
 
112
%%%           .
 
113
%%%           .
 
114
%%%      L_entry:
 
115
%%%           .
 
116
%%%           .
 
117
%%%           .
 
118
%%%         jump L_again;
 
119
%%%           
 
120
%%% is NOT allowed (and such code is never generated by 
 
121
%%% the code generator).
94
122
%%%
95
123
%%% Terminology note: The optimisation done here is called unreachable-code
96
124
%%% elimination, NOT dead-code elimination.  Dead code elimination
226
254
 
227
255
opt([{test,Test0,{f,Lnum}=Lbl,Ops}=I|Is0], Acc, St) ->
228
256
    case Is0 of
229
 
        [{jump,{f,Lnum}}|Is1] ->
230
 
            case is_label_defined(Is1, Lnum, St) of
231
 
                no ->
 
257
        [{jump,{f,Lnum}}|Is] ->
 
258
            %% We have
 
259
            %%    Test Label Ops
 
260
            %%    jump Label
 
261
            %% The test instruction is definitely not needed.
 
262
            %% The jump instruction is not needed if there is
 
263
            %% a definition of Label following the jump instruction.
 
264
            case is_label_defined(Is, Lnum) of
 
265
                false ->
 
266
                    %% The jump instruction is still needed.
232
267
                    opt(Is0, [I|Acc], label_used(Lbl, St));
233
 
                {yes,Is2} ->
234
 
                    %% The test and jump are redundant.
235
 
                    opt(Is2, Acc, St)
 
268
                true ->
 
269
                    %% Neither the test nor the jump are needed.
 
270
                    opt(Is, Acc, St)
236
271
            end;
237
 
        [{jump,To}|Is1] ->
238
 
            case is_label_defined(Is1, Lnum, St) of
239
 
                no ->
 
272
        [{jump,To}|Is] ->
 
273
            case is_label_defined(Is, Lnum) of
 
274
                false ->
240
275
                    opt(Is0, [I|Acc], label_used(Lbl, St));
241
 
                {yes,Is2} ->
 
276
                true ->
242
277
                    case invert_test(Test0) of
243
278
                        not_possible ->
244
279
                            opt(Is0, [I|Acc], label_used(Lbl, St));
245
280
                        Test ->
246
 
                            opt([{test,Test,To,Ops}|Is2], Acc, St)
 
281
                            opt([{test,Test,To,Ops}|Is], Acc, St)
247
282
                    end
248
283
            end;
249
284
        _Other ->
309
344
    end;
310
345
insert_fc_labels([], _, Acc) -> Acc.
311
346
 
312
 
%% label_defined(Is, Label, St) -> {yes,Is} | no
 
347
%% label_defined(Is, Label) -> true | false.
313
348
%%  Test whether the label Label is defined at the start of the instruction
314
 
%%  sequence, possibly preceeded by other label definitions. Returns 'no'
315
 
%%  if no definition was found, and {yes,Is} if found, where the label
316
 
%%  has been retained in the instruction sequence if there are other
317
 
%%  references to it and removed if not.
 
349
%%  sequence, possibly preceeded by other label definitions.
318
350
%%
319
 
is_label_defined(Is, L, St) ->
320
 
    is_label_defined_1(Is, L, St, []).
321
 
 
322
 
is_label_defined_1([{label,L}|Is]=Is0, L, St, Acc) ->
323
 
    case is_label_used(L, St) of
324
 
        true ->
325
 
            %% Used - keep the label.
326
 
            {yes,reverse(Acc, Is0)};
327
 
        false ->
328
 
            %% Not used - remove the label.
329
 
            {yes,reverse(Acc, Is)}
330
 
    end;
331
 
is_label_defined_1([{label,_}=I|Is], L, St, Acc) ->
332
 
    is_label_defined_1(Is, L, St, [I|Acc]);
333
 
is_label_defined_1(_, _, _, _) -> no.
 
351
is_label_defined([{label,L}|_], L) -> true;
 
352
is_label_defined([{label,_}|Is], L) -> is_label_defined(Is, L);
 
353
is_label_defined(_, _) -> false.
334
354
 
335
355
%% invert_test(Test0) -> not_possible | Test
336
356
 
349
369
insert_labels([], Is, Acc, St) ->
350
370
    opt(Is, Acc, St).
351
371
 
352
 
%% Skip unreachable code up to the next referenced label.
353
 
 
 
372
%% skip_unreachable([Instruction], St).
 
373
%%  Remove all instructions (including definitions of labels
 
374
%%  that have not been referenced yet) up to the next
 
375
%%  referenced label, then call opt/3 to optimize the rest
 
376
%%  of the instruction sequence.
 
377
%%
354
378
skip_unreachable([{label,L}|Is], [{jump,{f,L}}|Acc], St) ->
355
379
    opt([{label,L}|Is], Acc, St);
356
 
skip_unreachable([{label,L}|Is], Acc, St) ->
 
380
skip_unreachable([{label,L}|Is]=Is0, Acc, St) ->
357
381
    case is_label_used(L, St) of
358
 
        true  -> opt([{label,L}|Is], Acc, St);
 
382
        true  -> opt(Is0, Acc, St);
359
383
        false -> skip_unreachable(Is, Acc, St)
360
384
    end;
361
385
skip_unreachable([_|Is], Acc, St) ->