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

« back to all changes in this revision

Viewing changes to lib/compiler/src/beam_block.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 1999-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 : Partitions assembly instructions into basic blocks and
19
20
%% optimizes them.
21
22
-module(beam_block).
22
23
 
23
24
-export([module/2]).
24
 
-export([live_at_entry/1]).                     %Used by beam_type, beam_bool.
25
 
-export([merge_blocks/2]).                      %Used by beam_jump.
26
25
-import(lists, [mapfoldl/3,reverse/1,reverse/2,foldl/3,member/2]).
27
26
-define(MAXREG, 1024).
28
27
 
31
30
    {ok,{Mod,Exp,Attr,Fs,Lc}}.
32
31
 
33
32
function({function,Name,Arity,CLabel,Is0}, Lc0) ->
34
 
    %% Collect basic blocks and optimize them.
35
 
    Is1 = beam_jump:remove_unused_labels(Is0),  %Extra labels may thwart optimizations.
36
 
    Is2 = blockify(Is1),
37
 
    {Is,Lc} = bsm_opt(Is2, Lc0),
38
 
 
39
 
    %% Done.
40
 
    {{function,Name,Arity,CLabel,Is},Lc}.
 
33
    try
 
34
        %% Extra labels may thwart optimizations.
 
35
        Is1 = beam_jump:remove_unused_labels(Is0),
 
36
 
 
37
        %% Collect basic blocks and optimize them.
 
38
        Is2 = blockify(Is1),
 
39
        Is3 = beam_utils:live_opt(Is2),
 
40
        Is4 = opt_blocks(Is3),
 
41
        Is5 = beam_utils:delete_live_annos(Is4),
 
42
 
 
43
        %% Optimize bit syntax.
 
44
        {Is,Lc} = bsm_opt(Is5, Lc0),
 
45
 
 
46
        %% Done.
 
47
        {{function,Name,Arity,CLabel,Is},Lc}
 
48
    catch
 
49
        Class:Error ->
 
50
            Stack = erlang:get_stacktrace(),
 
51
            io:fwrite("Function: ~w/~w\n", [Name,Arity]),
 
52
            erlang:raise(Class, Error, Stack)
 
53
    end.
41
54
 
42
55
%% blockify(Instructions0) -> Instructions
43
 
%%  Collect sequences of instructions to basic blocks and
44
 
%%  optimize the contents of the blocks. Also do some simple
45
 
%%  optimations on instructions outside the blocks.
 
56
%%  Collect sequences of instructions to basic blocks.
 
57
%%  Also do some simple optimations on instructions outside the blocks.
46
58
 
47
59
blockify(Is) ->
48
60
    blockify(Is, []).
86
98
            blockify(Is, [{jump,BrTrue},
87
99
                          {test,is_eq_exact,BrFalse,[Reg,AtomTrue]}|Acc])
88
100
    end;
89
 
blockify([{test,is_eq,F,[_,_]=Ss}=I|Is], Acc) ->
90
 
    case is_exact_eq_ok(Ss) of
91
 
        false -> blockify(Is, [I|Acc]);
92
 
        true -> blockify(Is, [{test,is_eq_exact,F,Ss}|Acc])
93
 
    end;
94
 
blockify([{test,is_ne,F,[_,_]=Ss}=I|Is], Acc) ->
95
 
    case is_exact_eq_ok(Ss) of
96
 
        false -> blockify(Is, [I|Acc]);
97
 
        true -> blockify(Is, [{test,is_ne_exact,F,Ss}|Acc])
98
 
    end;
99
101
blockify([I|Is0]=IsAll, Acc) ->
100
102
    case is_bs_put(I) of
101
103
        true ->
106
108
            case collect(I) of
107
109
                error -> blockify(Is0, [I|Acc]);
108
110
                Instr when is_tuple(Instr) ->
109
 
                    {Block0,Is} = collect_block(IsAll),
110
 
                    Block = opt_block(Block0),
 
111
                    {Block,Is} = collect_block(IsAll),
111
112
                    blockify(Is, [{block,Block}|Acc])
112
113
            end
113
114
    end;
114
115
blockify([], Acc) -> reverse(Acc).
115
116
 
116
 
is_last_bool([I,{'%live',_}], Reg) ->
117
 
    is_last_bool([I], Reg);
118
117
is_last_bool([{set,[Reg],As,{bif,N,_}}], Reg) ->
119
118
    Ar = length(As),
120
119
    erl_internal:new_type_test(N, Ar) orelse erl_internal:comp_op(N, Ar)
122
121
is_last_bool([_|Is], Reg) -> is_last_bool(Is, Reg);
123
122
is_last_bool([], _) -> false.
124
123
 
125
 
is_exact_eq_ok([{atom,_},_]) -> true;
126
 
is_exact_eq_ok([nil,_]) -> true;
127
 
is_exact_eq_ok([_,{atom,_}]) -> true;
128
 
is_exact_eq_ok([_,nil]) -> true;
129
 
is_exact_eq_ok([_,_]) -> false.
130
 
 
131
124
collect_block(Is) ->
132
125
    collect_block(Is, []).
133
126
 
141
134
 
142
135
collect({allocate_zero,N,R}) -> {set,[],[],{alloc,R,{zero,N,0,[]}}};
143
136
collect({test_heap,N,R})     -> {set,[],[],{alloc,R,{nozero,nostack,N,[]}}};
144
 
collect({bif,N,nofail,As,D}) -> {set,[D],As,{bif,N}};
145
 
collect({bif,N0,F,As,D})      ->
146
 
    N = case N0 of
147
 
            '==' ->
148
 
                case is_exact_eq_ok(As) of
149
 
                    false -> N0;
150
 
                    true -> '=:='
151
 
 
152
 
                end;
153
 
            '/=' ->
154
 
                case is_exact_eq_ok(As) of
155
 
                    false -> N0;
156
 
                    true -> '=/='
157
 
                end;
158
 
            _ -> N0
159
 
        end,
160
 
    {set,[D],As,{bif,N,F}};
 
137
collect({bif,N,F,As,D})      -> {set,[D],As,{bif,N,F}};
161
138
collect({gc_bif,N,F,R,As,D}) -> {set,[D],As,{alloc,R,{gc_bif,N,F}}};
162
139
collect({move,S,D})          -> {set,[D],[S],move};
163
140
collect({put_list,S1,S2,D})  -> {set,[D],[S1,S2],put_list};
169
146
collect({get_list,S,D1,D2})  -> {set,[D1,D2],[S],get_list};
170
147
collect(remove_message)      -> {set,[],[],remove_message};
171
148
collect({'catch',R,L})       -> {set,[R],[],{'catch',L}};
172
 
collect({'%live',_}=Live)    -> Live;
173
149
collect(_)                   -> error.
174
150
 
 
151
opt_blocks([{block,Bl0}|Is]) ->
 
152
    %% The live annotation at the beginning is not useful.
 
153
    [{'%live',_}|Bl] = Bl0,
 
154
    [{block,opt_block(Bl)}|opt_blocks(Is)];
 
155
opt_blocks([I|Is]) ->
 
156
    [I|opt_blocks(Is)];
 
157
opt_blocks([]) -> [].
 
158
 
175
159
opt_block(Is0) ->
176
160
    %% We explicitly move any allocate instruction upwards before optimising
177
161
    %% moves, to avoid any potential problems with the calculation of live
224
208
alloc_may_pass({set,_,_,_}) -> true.
225
209
    
226
210
combine_alloc({_,Ns,Nh1,Init}, {_,nostack,Nh2,[]})  ->
227
 
    {zero,Ns,beam_flatten:combine_heap_needs(Nh1, Nh2),Init}.
228
 
 
229
 
merge_blocks([{set,[],[],{alloc,R,{Attr,Ns,Nh1,Init}}}=Alloc1|B1],
230
 
             [{set,[],[],{alloc,_,{_,nostack,Nh2,[]}}}|B2]=B2Orig) ->
231
 
    case any_allocation(B1) of
232
 
        true ->
233
 
            %% It is not safe to combine the allocations, because
234
 
            %% there is another allocation instruction (probably a
235
 
            %% gc_bif) that may "eat" the allocated space.
236
 
            [Alloc1|merge_blocks(B1, B2Orig)];
237
 
        false ->
238
 
            %% It is safe to combine the allocations.
239
 
            Alloc = {set,[],[],
240
 
                     {alloc,R,
241
 
                      {Attr,Ns,beam_flatten:combine_heap_needs(Nh1, Nh2),Init}}},
242
 
            [Alloc|merge_blocks(B1, B2)]
243
 
    end;
244
 
merge_blocks(B1, B2) -> merge_blocks_1(B1++[{set,[],[],stop_here}|B2]).
245
 
 
246
 
merge_blocks_1([{set,[],_,stop_here}|Is]) -> Is;
247
 
merge_blocks_1([{set,[D],_,move}=I|Is]) ->
248
 
    case beam_utils:is_killed_block(D, Is) of
249
 
        true -> merge_blocks_1(Is);
250
 
        false -> [I|merge_blocks_1(Is)]
251
 
    end;
252
 
merge_blocks_1([I|Is]) -> [I|merge_blocks_1(Is)].
253
 
 
254
 
any_allocation([{set,_,_,{alloc,_,_}}|_]) -> true;
255
 
any_allocation([_|Is]) -> any_allocation(Is);
256
 
any_allocation([]) -> false.
257
 
    
 
211
    {zero,Ns,beam_utils:combine_heap_needs(Nh1, Nh2),Init}.
258
212
 
259
213
%% opt([Instruction]) -> [Instruction]
260
214
%%  Optimize the instruction stream inside a basic block.
274
228
opt([{set,Ds0,Ss,Op}|Is0]) ->   
275
229
    {Ds,Is} = opt_moves(Ds0, Is0),
276
230
    [{set,Ds,Ss,Op}|opt(Is)];
277
 
opt([I|Is]) -> [I|opt(Is)];
 
231
opt([{'%live',_}=I|Is]) ->
 
232
    [I|opt(Is)];
278
233
opt([]) -> [].
279
234
 
280
235
%% opt_moves([Dest], [Instruction]) -> {[Dest],[Instruction]}
287
242
        {D1,Is} -> {[D1],Is}
288
243
    end;
289
244
opt_moves([X0,Y0], Is0) ->
290
 
%%    {[X0,Y0],Is0}.
291
245
    {X,Is2} = case opt_move(X0, Is0) of
292
246
                  not_possible -> {X0,Is0};
293
247
                  {Y0,_} -> {X0,Is0};
331
285
    case is_transparent(R, I) of
332
286
        false -> not_possible;
333
287
        true -> opt_move_1(R, Is, SafeRegs, [I|Acc])
334
 
    end;
335
 
opt_move_1(_, [], _, _) -> not_possible.
 
288
    end.
336
289
 
337
290
%% Reverse the instructions, while checking that there are no instructions that
338
291
%% would interfere with using the new destination register chosen.
408
361
count_ones(Bits, Acc) ->
409
362
    count_ones(Bits bsr 1, Acc + (Bits band 1)).
410
363
 
411
 
%% live_at_entry(Is) -> NumberOfRegisters
412
 
%%  Calculate the number of register live at the entry to the code
413
 
%%  sequence.
414
 
 
415
 
live_at_entry([{set,_,_,{alloc,R,_}}|_]) -> R;
416
 
live_at_entry(Is0) ->
417
 
    case reverse(Is0) of
418
 
        [{'%live',Regs}|Is] -> live_at_entry_1(Is, (1 bsl Regs)-1);
419
 
        _ -> unknown
420
 
    end.
421
 
 
422
 
live_at_entry_1([{set,[],[],{alloc,_,_}}|Is], Rset) ->
423
 
    live_at_entry_1(Is, Rset);
424
 
live_at_entry_1([{set,Ds,Ss,_}|Is], Rset0) ->
425
 
    Rset = x_live(Ss, x_dead(Ds, Rset0)),
426
 
    live_at_entry_1(Is, Rset);
427
 
live_at_entry_1([], Rset) -> live_regs_1(0, Rset).
428
 
 
429
364
%% Calculate the new number of live registers when we move an allocate
430
365
%% instruction upwards, passing a 'set' instruction.
431
366
 
432
367
alloc_live_regs({set,Ds,Ss,_}, Regs0) ->
433
368
    Rset = x_live(Ss, x_dead(Ds, (1 bsl Regs0)-1)),
434
 
    live_regs_1(0, Rset).
 
369
    live_regs(Rset).
 
370
 
 
371
live_regs(Regs) ->
 
372
    live_regs_1(0, Regs).
435
373
 
436
374
live_regs_1(N, 0) -> N;
437
375
live_regs_1(N, Regs) -> live_regs_1(N+1, Regs bsr 1).
501
439
        little when Sz < 128 ->
502
440
            %% We only try to optimize relatively small fields, to avoid
503
441
            %% an explosion in code size.
504
 
            try <<N:Sz/little>> of
505
 
                <<Int:Sz>> ->
506
 
                    Flags = force_big(F),
507
 
                    Is = [{bs_put_integer,Fail,{integer,Sz},1,
508
 
                           Flags,{integer,Int}}|Is0],
509
 
                    opt_bs_1(Is, Acc)
510
 
            catch
511
 
                error:_ ->
512
 
                    opt_bs_1(Is0, [I|Acc])
513
 
            end;
 
442
            <<Int:Sz>> = <<N:Sz/little>>,
 
443
            Flags = force_big(F),
 
444
            Is = [{bs_put_integer,Fail,{integer,Sz},1,
 
445
                   Flags,{integer,Int}}|Is0],
 
446
            opt_bs_1(Is, Acc);
514
447
        _ ->                                    %native or too wide little field
515
448
            opt_bs_1(Is0, [I|Acc])
516
449
    end;
623
556
    [F|Lbls] = bsm_subst_labels([F0|Lbls0], Save, D),
624
557
    Acc = [{select_val,Reg,F,{list,Lbls}}|Acc0],
625
558
    bsm_reroute(Is, D, S, Acc);
626
 
bsm_reroute([{test,TestOp,F0,TestArgs}|Is], D, {_,Save}=S, Acc0) ->
 
559
bsm_reroute([{test,TestOp,F0,TestArgs}=I|Is], D, {_,Save}=S, Acc0) ->
627
560
    F = bsm_subst_label(F0, Save, D),
628
561
    Acc = [{test,TestOp,F,TestArgs}|Acc0],
629
 
    case bsm_not_bs_test(TestOp, length(TestArgs)) of
 
562
    case bsm_not_bs_test(I) of
630
563
        true ->
631
564
            %% The test instruction will not update the bit offset for the
632
565
            %% binary being matched. Therefore the save position can be kept.
636
569
            %% remembered Save position.
637
570
            bsm_reroute(Is, D, none, Acc)
638
571
    end;
 
572
bsm_reroute([{test,TestOp,F0,Live,TestArgs,Dst}|Is], D, {_,Save}, Acc0) ->
 
573
    F = bsm_subst_label(F0, Save, D),
 
574
    Acc = [{test,TestOp,F,Live,TestArgs,Dst}|Acc0],
 
575
    %% The test instruction will update the bit offset. Kill our
 
576
    %% remembered Save position.
 
577
    bsm_reroute(Is, D, none, Acc);
639
578
bsm_reroute([{block,[{set,[],[],{alloc,_,_}}]}=Bl,
640
579
             {bs_context_to_binary,_}=I|Is], D, S, Acc) ->
641
580
    %% To help further bit syntax optimizations.
659
598
    bsm_opt_2(Is, [I|Acc]);
660
599
bsm_opt_2([], Acc) -> reverse(Acc).
661
600
 
662
 
%% bsm_not_bs_test(Name, Arity) -> true|false.
 
601
%% bsm_not_bs_test({test,Name,_,Operands}) -> true|false.
663
602
%%  Test whether is the test is a "safe", i.e. does not move the
664
603
%%  bit offset for a binary.
665
604
%%
666
 
%%  true means that the test is safe, false that we don't know or
 
605
%%  'true' means that the test is safe, 'false' that we don't know or
667
606
%%  that the test moves the offset (e.g. bs_get_integer2).
668
607
 
669
 
bsm_not_bs_test(is_eq_exact, 2)  -> true;
670
 
bsm_not_bs_test(is_ne_exact, 2) -> true;
671
 
bsm_not_bs_test(is_ge, 2) -> true;
672
 
bsm_not_bs_test(is_lt, 2)  -> true;
673
 
bsm_not_bs_test(is_eq, 2) -> true;
674
 
bsm_not_bs_test(is_ne, 2) -> true;
675
 
bsm_not_bs_test(bs_test_tail2, 2) -> true;
676
 
bsm_not_bs_test(F, A) -> erl_internal:new_type_test(F, A).
 
608
bsm_not_bs_test({test,bs_test_tail2,_,[_,_]}) -> true;
 
609
bsm_not_bs_test(Test) -> beam_utils:is_pure_test(Test).
677
610
 
678
611
bsm_subst_labels(Fs, Save, D) ->
679
612
    bsm_subst_labels_1(Fs, Save, D, []).
689
622
        none -> F
690
623
    end;
691
624
bsm_subst_label(Other, _, _) -> Other.
692