Skip to content

Commit

Permalink
Merge pull request #7157 from jhogberg/john/compiler/fix-bnot-converg…
Browse files Browse the repository at this point in the history
…ence

beam_bounds: Make 'bnot' converge faster
  • Loading branch information
jhogberg authored Apr 26, 2023
2 parents ab803ea + 8e5b1fb commit bab771b
Show file tree
Hide file tree
Showing 3 changed files with 35 additions and 2 deletions.
23 changes: 22 additions & 1 deletion lib/compiler/src/beam_bounds.erl
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,28 @@

bounds('bnot', R0) ->
case R0 of
{A,B} ->
{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} ->
R = {inf_add(inf_neg(B), -1), inf_add(inf_neg(A), -1)},
normalize(R);
_ ->
Expand Down
8 changes: 7 additions & 1 deletion lib/compiler/src/beam_validator.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2830,7 +2830,13 @@ unpack_typed_arg(#tr{r=Reg,t=Type}, Vst) ->
%% The validator is not yet clever enough to do proper range analysis like
%% the main type pass, so our types will be a bit cruder here, but they
%% should at the very least not be in direct conflict.
true = none =/= beam_types:meet(get_movable_term_type(Reg, Vst), Type),
Current = get_movable_term_type(Reg, Vst),
case beam_types:meet(Current, Type) of
none ->
throw({bad_typed_register, Current, Type});
_ ->
ok
end,
Reg;
unpack_typed_arg(Arg, _Vst) ->
Arg.
Expand Down
6 changes: 6 additions & 0 deletions lib/compiler/test/beam_bounds_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -197,6 +197,8 @@ bnot_bounds(_Config) ->
{'-inf',-8} = beam_bounds:bounds('bnot', {7,'+inf'}),
{'-inf',9} = beam_bounds:bounds('bnot', {-10,'+inf'}),

-1 = bnot_bounds_2(0),

ok.

bnot_bounds_1(R) ->
Expand All @@ -211,6 +213,10 @@ bnot_bounds_1(R) ->
ct:fail(bad_min_or_max)
end.

%% GH-7145: 'bnot' converged too slowly, effectively hanging the compiler.
bnot_bounds_2(0) -> -1;
bnot_bounds_2(N) -> abs(bnot bnot_bounds_2(N)).

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

Expand Down

0 comments on commit bab771b

Please sign in to comment.