Skip to content

Commit

Permalink
Merge branch 'bjorn/compiler/fix-bnot-again/GH-7468/OTP-18719' into m…
Browse files Browse the repository at this point in the history
…aint

* bjorn/compiler/fix-bnot-again/GH-7468/OTP-18719:
  Fix unsafe range calculation for the bnot operator
  • Loading branch information
bjorng committed Aug 15, 2023
2 parents 8fd0144 + ad63af9 commit 82ca1ba
Show file tree
Hide file tree
Showing 3 changed files with 43 additions and 48 deletions.
31 changes: 2 additions & 29 deletions lib/compiler/src/beam_bounds.erl
Original file line number Diff line number Diff line change
Expand Up @@ -46,35 +46,8 @@

bounds('bnot', R0) ->
case R0 of
{Exact, Exact} when is_integer(Exact) ->
N = -Exact - 1,
{N, N};
{A, B} when is_integer(A), is_integer(B), A =/= B ->
%% While it's easy to get an exact range, doing so can make certain
%% chains of operations slow to converge, e.g.
%%
%% f(0) -> -1; f(N) -> abs(bnot f(N)).
%%
%% Where the range increases by 1 every time we pass through,
%% making it more or less impossible to reach a fixpoint.
%%
%% We therefore widen the range a bit quicker to ensure that we
%% converge on 'any' within a reasonable time frame, hoping that
%% the range will still be tight enough in the cases where we
%% don't feed the result into itself.
case {abs(A) bsr ?NUM_BITS, abs(B) bsr ?NUM_BITS} of
{0, 0} ->
Min = min(-B - 1, -(B bsl 1) - 1),
Max = max(-A - 1, -(A bsl 1) - 1),
normalize({Min, Max});
{_, _} ->
any
end;
{A, B} ->
%% Widen the range as above to ensure that we get the same result
%% on the finite component(s).
R = {inf_add(inf_neg(inf_add(B, B)), -1),
inf_add(inf_neg(inf_add(A, A)), -1)},
{A,B} ->
R = {inf_add(inf_neg(B), -1), inf_add(inf_neg(A), -1)},
normalize(R);
_ ->
any
Expand Down
32 changes: 18 additions & 14 deletions lib/compiler/src/beam_call_types.erl
Original file line number Diff line number Diff line change
Expand Up @@ -424,9 +424,24 @@ types(erlang, 'bsl', [_,_]=Args) ->
types(erlang, 'bsr', [_,_]=Args) ->
sub_unsafe(beam_bounds_type('bsr', #t_integer{}, Args),
[#t_integer{}, #t_integer{}]);
types(erlang, 'bnot', [_]=Args) ->
sub_unsafe(beam_bounds_type('bnot', #t_integer{}, Args),
[#t_integer{}]);
types(erlang, 'bnot', [_]) ->
%% Calculating the tighest possible range for the result would
%% cause the type analysis pass to loop for a very long time for
%% code such as:
%%
%% f(0) -> -1;
%% f(N) -> abs(bnot f(N)).
%%
%% By calculating looser bounds and widening the range to `any` at
%% some suitable limit, convergence can be ensured (see
%% 8e5b1fbb16d186). However, that can cause a contradiction
%% between the ranges calculated by the type pass and by
%% beam_validator.
%%
%% Therefore, don't attempt to calculate a range now. Save the
%% range calculation for the opt_ranges pass (arith_type/2), which
%% is only run once.
sub_unsafe(#t_integer{}, [#t_integer{}]);

%% Fixed-type arithmetic
types(erlang, 'float', [_]) ->
Expand Down Expand Up @@ -1103,17 +1118,6 @@ beam_bounds_type(Op, Type, [LHS, RHS]) ->
#t_integer{elements=beam_bounds:bounds(Op, R1, R2)};
{number, R1, R2} ->
#t_number{elements=beam_bounds:bounds(Op, R1, R2)}
end;
beam_bounds_type(Op, Type, [Arg]) ->
case beam_types:meet(Arg, Type) of
#t_float{elements=R} ->
#t_float{elements=beam_bounds:bounds(Op, R)};
#t_integer{elements=R} ->
#t_integer{elements=beam_bounds:bounds(Op, R)};
#t_number{elements=R} ->
#t_number{elements=beam_bounds:bounds(Op, R)};
none ->
none
end.

get_range(LHS, RHS, Type) ->
Expand Down
28 changes: 23 additions & 5 deletions lib/compiler/test/beam_bounds_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -192,14 +192,20 @@ bnot_bounds(_Config) ->
A <- Seq,
B <- lists:nthtail(A-Min, Seq)],

{-85,'+inf'} = beam_bounds:bounds('bnot', {'-inf',42}),
{199,'+inf'} = beam_bounds:bounds('bnot', {'-inf',-100}),
{'-inf',-15} = beam_bounds:bounds('bnot', {7,'+inf'}),
{'-inf',19} = beam_bounds:bounds('bnot', {-10,'+inf'}),
{-2228221,'+inf'} = beam_bounds:bounds('bnot', {'-inf', 1114110}),
{-43,'+inf'} = beam_bounds:bounds('bnot', {'-inf',42}),
{99,'+inf'} = beam_bounds:bounds('bnot', {'-inf',-100}),
{'-inf',-8} = beam_bounds:bounds('bnot', {7,'+inf'}),
{'-inf',9} = beam_bounds:bounds('bnot', {-10,'+inf'}),
{-1114111,'+inf'} = beam_bounds:bounds('bnot', {'-inf', 1114110}),

-1 = bnot_bounds_2(0),

{'EXIT',{_,_}} = catch bnot_bounds_3(id(true)),
{'EXIT',{_,_}} = catch bnot_bounds_3(id(false)),
{'EXIT',{_,_}} = catch bnot_bounds_3(id(0)),

{'EXIT',{{bad_generator,-3},_}} = catch bnot_bounds_4(),

ok.

bnot_bounds_1(R) ->
Expand All @@ -218,6 +224,14 @@ bnot_bounds_1(R) ->
bnot_bounds_2(0) -> -1;
bnot_bounds_2(N) -> abs(bnot bnot_bounds_2(N)).

%% GH-7468. Would result in a bad_typed_register failure in beam_validator.
bnot_bounds_3(A) ->
(bnot round(((A xor false) andalso 1) + 2)) bsr ok.

%% GH-7468. Would result in a bad_arg_type failure in beam_validator.
bnot_bounds_4() ->
<< 0 || A <- [1,2], _ <- bnot round(A + trunc(A))>>.

bsr_bounds(_Config) ->
test_noncommutative('bsr', {-12,12}, {0,7}),

Expand Down Expand Up @@ -555,3 +569,7 @@ test_redundant_masking({A,B}=R, M) ->
test_redundant_masking(A, B, M) when A =< B ->
A band M =:= A andalso test_redundant_masking(A + 1, B, M);
test_redundant_masking(_, _, _) -> true.

%%% Common utility functions.

id(I) -> I.

0 comments on commit 82ca1ba

Please sign in to comment.