~rdoering/ubuntu/intrepid/erlang/fix-535090

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Soren Hansen
  • Date: 2007-05-01 16:57:10 UTC
  • mfrom: (1.1.9 upstream)
  • Revision ID: james.westby@ubuntu.com-20070501165710-2sapk0hp2gf3o0ip
Tags: 1:11.b.4-2ubuntu1
* Merge with Debian Unstable. Remaining changes:
  - Add -fno-stack-protector to fix broken crypto_drv.
* DebianMaintainerField update.

Show diffs side-by-side

added added

removed removed

Lines of Context:
21
21
 
22
22
-export([module/2]).
23
23
 
24
 
-import(lists, [reverse/1,foldl/3,mapfoldl/3,sort/1,member/2]).
 
24
-import(lists, [reverse/1,reverse/2,foldl/3,mapfoldl/3,sort/1,member/2]).
25
25
-define(MAXREG, 1024).
26
26
 
27
27
-record(st,
53
53
       {label,Fail},
54
54
       {block,[{set,[Dst],[{atom,false}],move},{'%live',Live}]},
55
55
       {label,Succ}|Is]=Is0], Acc0, St) ->
56
 
    case split_block(Bl0, Dst, Fail, Acc0) of
 
56
    case split_block(Bl0, Dst, Fail, Acc0, true) of
57
57
        failed ->
58
58
            bopt(Is0, [Block|Acc0], St);
59
59
        {Bl,PreBlock} ->
88
88
%%  Attempt to optimized a block of guard BIFs followed by a test
89
89
%%  instruction.
90
90
bopt_block(Reg, Fail, OldIs, [{block,Bl0}|Acc0], St0) ->
91
 
    case split_block(Bl0, Reg, Fail, Acc0) of
 
91
    case split_block(Bl0, Reg, Fail, Acc0, false) of
92
92
        failed ->
93
93
            %% Reason for failure: The block either contained no
94
94
            %% guard BIFs with the failure label Fail, or the final
120
120
                    %%
121
121
                    %% 3. Other bug or limitation.
122
122
 
123
 
                    %%io:format("~P\n", [_Reason,20]),
 
123
                    %%io:format("~P\n", [_Reason,40]),
124
124
                    failed;
125
125
                {NewCode,St} ->
126
 
                    case is_opt_safe(Bl, NewCode, OldIs, St) of
 
126
                    case is_opt_safe(Bl, NewCode, OldIs, Acc, St) of
127
127
                        false ->
128
128
                            %% The optimization is not safe. (A register
129
129
                            %% used by the instructions following the
130
130
                            %% optimized code is either not assigned a
131
131
                            %% value at all or assigned a different value.)
132
132
 
133
 
                            %%io:format("\nNot safe:\n"),
134
 
                            %%io:format("~p\n", [Bl]),
135
 
                            %%io:format("~p\n", [reverse(NewCode)]),
 
133
%%                          io:format("\nNot safe:\n"),
 
134
%%                          io:format("~p\n", [Bl]),
 
135
%%                          io:format("~p\n", [reverse(NewCode)]),
 
136
%%                          io:format("~p\n", [reverse(Acc0)]),
136
137
                            failed;
137
138
                        true -> {NewCode++Acc,St}
138
139
                    end
144
145
    Pre = update_fail_label(Pre0, Fail, []),
145
146
    bopt_cg(Tree, Fail, make_block(Pre, []), St).
146
147
 
147
 
%% is_opt_safe(OriginalCode, OptCode, FollowingCode, State) -> true|false
 
148
%% is_opt_safe(OriginalCode, OptCode, FollowingCode,
 
149
%%             ReversedPreceedingCode, State) -> true|false
148
150
%%  Comparing the original code to the optimized code, determine
149
151
%%  whether the optimized code is guaranteed to work in the same
150
152
%%  way as the original code.
151
153
 
152
 
is_opt_safe(Bl, NewCode, OldIs, St) ->
 
154
is_opt_safe(Bl, NewCode, OldIs, PreceedingCode, St) ->
153
155
    %% Here are the conditions that must be true for the
154
156
    %% optimization to be safe.
155
157
    %%
156
 
    %% 1. Any register that was assigned a value in the original
157
 
    %%    code, but is not in the optimized code, must be guaranteed
158
 
    %%    to be KILLED in the following code. (NotSet below.)
159
 
    %% 
160
 
    %% 2. Any register that is assigned a value in the optimized
161
 
    %%    code must be UNUSED in the following code. (NewDst, Set.)
 
158
    %% 1. If a register is INITIALIZED by PreceedingCode,
 
159
    %%    then if that register assigned a value in the original
 
160
    %%    code, but not in the optimized code, it must be UNUSED or KILLED
 
161
    %%    in the code that follows.
 
162
    %%
 
163
    %% 2. If a register is not known to be INITIALIZED by PreccedingCode,
 
164
    %%    then if that register assigned a value in the original
 
165
    %%    code, but not in the optimized code, it must be KILLED
 
166
    %%    by the code that follows.
 
167
    %%
 
168
    %% 3. Any register that is assigned a value in the optimized
 
169
    %%    code must be UNUSED or KILLED in the following code.
162
170
    %%    (Possible future improvement: Registers that are known
163
171
    %%    to be assigned the SAME value in the original and optimized
164
172
    %%    code don't need to be unused in the following code.)
165
173
 
 
174
    InitInPreceeding = initialized_regs(PreceedingCode),
 
175
 
166
176
    PrevDst = dst_regs(Bl),
167
177
    NewDst = dst_regs(NewCode),
168
178
    NotSet = ordsets:subtract(PrevDst, NewDst),
169
 
 
170
 
    %% Note: The following line is an optimization. We don't need
171
 
    %% to test whether variables in NotSet for being unused, because
172
 
    %% they will all be tested for being killed (a stronger condition
173
 
    %% than being unused).
174
 
    
175
 
    Set = ordsets:subtract(NewDst, NotSet),
176
 
 
177
 
    all_killed(NotSet, OldIs, St) andalso
178
 
        none_used(Set, OldIs, St).
179
 
 
180
 
% update_fail_label([{set,_,_,{bif,_,{f,0}}}=I|Is], Fail, Acc) ->
181
 
%     update_fail_label(Is, Fail, [I|Acc]);
 
179
    MustBeKilled = ordsets:subtract(NotSet, InitInPreceeding),
 
180
    MustBeUnused = ordsets:subtract(ordsets:union(NotSet, NewDst), MustBeKilled),
 
181
 
 
182
    all_killed(MustBeKilled, OldIs, St) andalso
 
183
        none_used(MustBeUnused, OldIs, St).
 
184
 
182
185
update_fail_label([{set,Ds,As,{bif,N,{f,_}}}|Is], Fail, Acc) ->
183
186
    update_fail_label(Is, Fail, [{set,Ds,As,{bif,N,{f,Fail}}}|Acc]);
184
187
update_fail_label([], _, Acc) -> Acc.
188
191
 
189
192
extend_block(BlAcc, Fail, [{protected,_,_,_}=Prot|OldAcc]) ->
190
193
    extend_block([Prot|BlAcc], Fail, OldAcc);
191
 
extend_block(BlAcc0, Fail, [{block,Is0}|OldAcc]=OldAcc0) ->
 
194
extend_block(BlAcc0, Fail, [{block,Is0}|OldAcc]) ->
192
195
    case extend_block_1(reverse(Is0), Fail, BlAcc0) of
193
 
        {[],_} -> {BlAcc0,OldAcc0};
194
196
        {BlAcc,[]} -> extend_block(BlAcc, Fail, OldAcc);
195
197
        {BlAcc,Is} -> {BlAcc,[{block,Is}|OldAcc]}
196
198
    end;
206
208
extend_block_1([_|_]=Is, _, Acc) -> {Acc,reverse(Is)};
207
209
extend_block_1([], _, Acc) -> {Acc,[]}.
208
210
 
209
 
split_block(Is0, Dst, Fail, PreIs) ->
210
 
    case beam_jump:is_label_used_in(Fail, PreIs) of
 
211
%% split_block([Instruction], Destination, FailLabel, [PreInstruction],
 
212
%%             ProhibitFailLabelInPreBlock) -> failed | {Block,PreBlock}
 
213
%% Split a sequence of instructions into two blocks - one containing
 
214
%% all guard bif instructions and a pre-block all instructions before
 
215
%% the guard BIFs.
 
216
 
 
217
split_block(Is0, Dst, Fail, PreIs, ProhibitFailLabel) ->
 
218
    case ProhibitFailLabel andalso beam_jump:is_label_used_in(Fail, PreIs) of
211
219
        true ->
212
220
            %% The failure label was used in one of the instructions (most
213
 
            %% probably bit syntax construction) preceeding the block.
214
 
            %% We cannot allow that because the failure label will be
215
 
            %% eliminated.
 
221
            %% probably bit syntax construction) preceeding the block,
 
222
            %% the caller might eliminate the label.
216
223
            failed;
217
224
        false ->
218
225
            case reverse(Is0) of
219
226
                [{'%live',_}|[{set,[Dst],_,_}|_]=Is] ->
220
 
                    split_block_1(Is, Fail);
 
227
                    split_block_1(Is, Fail, ProhibitFailLabel);
221
228
                [{set,[Dst],_,_}|_]=Is ->
222
 
                    split_block_1(Is, Fail);
 
229
                    split_block_1(Is, Fail, ProhibitFailLabel);
223
230
                _ -> failed
224
231
            end
225
232
    end.
226
233
 
227
 
split_block_1(Is, Fail) ->
228
 
    case split_block_2(Is, Fail, []) of
 
234
split_block_1(Is, Fail, ProhibitFailLabel) ->
 
235
    case split_block_2(Is, Fail, ProhibitFailLabel, []) of
229
236
        failed -> failed;
230
237
        {[],_} -> failed;
231
238
        {_,_}=Res -> Res
232
239
    end.
233
240
 
234
 
split_block_2([{set,[_],_,{bif,_,{f,Fail}}}=I|Is], Fail, Acc) ->
235
 
    split_block_2(Is, Fail, [I|Acc]);
236
 
split_block_2([{'%live',_}|Is], Fail, Acc) ->
237
 
    split_block_2(Is, Fail, Acc);
238
 
split_block_2(Is, Fail, Acc) ->
239
 
    %% We are done, but we must make sure that the failure label
240
 
    %% is not used in the pre-block (because the failure label
241
 
    %% might be removed).
242
 
    split_block_3(Is, Fail, {Acc,reverse(Is)}).
 
241
split_block_2([{set,[_],_,{bif,_,{f,Fail}}}=I|Is], Fail, Flag, Acc) ->
 
242
    split_block_2(Is, Fail, Flag, [I|Acc]);
 
243
split_block_2([{'%live',_}|Is], Fail, Flag, Acc) ->
 
244
    split_block_2(Is, Fail, Flag, Acc);
 
245
split_block_2(Is0, Fail, ProhibitFailLabel, Acc) ->
 
246
    Is = reverse(Is0),
 
247
    Res = {Acc,Is},
 
248
    case ProhibitFailLabel of
 
249
        true ->
 
250
            %% We are done, but we must make sure that the failure label
 
251
            %% is not used in the pre-block (because it might be removed).
 
252
            split_block_3(Is, Fail, Res);
 
253
        false ->
 
254
            %% Done. The caller will not remove the failure label.
 
255
            Res
 
256
    end.
243
257
 
244
258
split_block_3([{set,[_],_,{bif,_,{f,Fail}}}|_], Fail, _) ->
245
259
    failed;
354
368
bif_to_test('>=', As) -> {test,is_ge,fail,As};
355
369
bif_to_test('>', [L,R]) -> {test,is_lt,fail,[R,L]};
356
370
bif_to_test('<', As) -> {test,is_lt,fail,As};
 
371
bif_to_test(is_function, [_,_]=As) -> {test,is_function2,fail,As};
 
372
bif_to_test(is_record, [_,_,_]=As) -> {test,is_record,fail,As};
357
373
bif_to_test(Name, [_]=As) ->
358
374
    case erl_internal:new_type_test(Name, 1) of
359
375
        false -> exit({bif_to_test,Name,As,failed});
631
647
is_used_at_none(R, [_|T], St) ->
632
648
    is_used_at_none(R, T, St);
633
649
is_used_at_none(_, [], _) -> true.
 
650
 
 
651
%% initialized_regs([Instruction]) -> [Register])
 
652
%%  Given a REVERSED instruction sequence, return a list of the registers
 
653
%%  that are guaranteed to be initialized (not contain garbage).
 
654
 
 
655
initialized_regs(Is) ->
 
656
    initialized_regs(Is, ordsets:new()).
 
657
 
 
658
initialized_regs([{set,Dst,Src,_}|Is], Regs) ->
 
659
    initialized_regs(Is, add_init_regs(Dst, add_init_regs(Src, Regs)));
 
660
initialized_regs([{test,_,_,Src}|Is], Regs) ->
 
661
    initialized_regs(Is, add_init_regs(Src, Regs));
 
662
initialized_regs([{block,Bl}|Is], Regs) ->
 
663
    initialized_regs(reverse(Bl, Is), Regs);
 
664
initialized_regs([_|_], Regs) -> Regs;
 
665
initialized_regs([], Regs) -> Regs.
 
666
 
 
667
add_init_regs([{x,_}=X|T], Regs) ->
 
668
    add_init_regs(T, ordsets:add_element(X, Regs));
 
669
add_init_regs([_|T], Regs) ->
 
670
    add_init_regs(T, Regs);
 
671
add_init_regs([], Regs) -> Regs.
 
672