Skip to content

Commit

Permalink
Merge pull request #6582 from jhogberg/john/compiler/infer_relops-sin…
Browse files Browse the repository at this point in the history
…gleton-bug/GH-6568

beam_ssa_type: Don't filter out literals in meet_types/2
  • Loading branch information
jhogberg authored Dec 22, 2022
2 parents 00bf0b2 + b9eb167 commit b099804
Show file tree
Hide file tree
Showing 2 changed files with 56 additions and 23 deletions.
50 changes: 29 additions & 21 deletions lib/compiler/src/beam_ssa_type.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2456,7 +2456,7 @@ infer_types_br_1(V, Ts, Ds) ->
%% Not a relational operator.
{PosTypes, NegTypes} = infer_type(Op0, Args, Ts, Ds),
SuccTs = meet_types(PosTypes, Ts),
FailTs = infer_subtract_types(NegTypes, Ts),
FailTs = subtract_types(NegTypes, Ts),
{SuccTs, FailTs};
InvOp ->
%% This is an relational operator.
Expand All @@ -2482,8 +2482,7 @@ infer_relop('=:=', [LHS,RHS], [LType,RType], Ds) ->
%% can be inferred that L1 is 'cons' (the meet of 'cons' and
%% 'list').
Type = beam_types:meet(LType, RType),
Types = [{LHS,Type},{RHS,Type}],
[{V,T} || {#b_var{}=V,T} <- Types, T =/= any] ++ EqTypes;
[{LHS,Type},{RHS,Type}] ++ EqTypes;
infer_relop(Op, Args, Types, _Ds) ->
infer_relop(Op, Args, Types).

Expand All @@ -2500,18 +2499,15 @@ infer_relop('=/=', [LHS,RHS], [LType,RType]) ->
%% as it may be too specific. See beam_type_SUITE:type_subtraction/1
%% for details.
[{V,beam_types:subtract(ThisType, OtherType)} ||
{#b_var{}=V, ThisType, OtherType} <-
[{RHS, RType, LType}, {LHS, LType, RType}],
{V, ThisType, OtherType} <- [{RHS, RType, LType}, {LHS, LType, RType}],
beam_types:is_singleton_type(OtherType)];
infer_relop(Op, [Arg1,Arg2], Types0) ->
case infer_relop(Op, Types0) of
any ->
%% Both operands lacked ranges.
[];
{NewType1,NewType2} ->
Types = [{Arg1,NewType1},{Arg2,NewType2}],
[{V,T} || {#b_var{}=V,T} <- Types,
T =/= any]
[{Arg1,NewType1},{Arg2,NewType2}]
end.

infer_relop(Op, [#t_integer{elements=R1},
Expand Down Expand Up @@ -2588,16 +2584,6 @@ infer_get_range(#t_integer{elements=R}) -> R;
infer_get_range(#t_number{elements=R}) -> R;
infer_get_range(_) -> unknown.

infer_subtract_types([{V,T0}|Vs], Ts) ->
T1 = concrete_type(V, Ts),
case beam_types:subtract(T1, T0) of
none -> none;
T1 -> infer_subtract_types(Vs, Ts);
T -> infer_subtract_types(Vs, Ts#{V := T})
end;
infer_subtract_types([], Ts) ->
Ts.

infer_br_value(_V, _Bool, none) ->
none;
infer_br_value(V, Bool, NewTs) ->
Expand Down Expand Up @@ -2714,7 +2700,7 @@ infer_success_type({bif,Op}, Args, Ts, _Ds) ->
ArgTypes = concrete_types(Args, Ts),

{_, PosTypes0, CanSubtract} = beam_call_types:types(erlang, Op, ArgTypes),
PosTypes = [T || {#b_var{},_}=T <- zip(Args, PosTypes0)],
PosTypes = zip(Args, PosTypes0),

case CanSubtract of
true -> {PosTypes, PosTypes};
Expand All @@ -2729,7 +2715,7 @@ infer_success_type(call, [#b_remote{mod=#b_literal{val=Mod},
ArgTypes = concrete_types(Args, Ts),

{_, PosTypes0, _CanSubtract} = beam_call_types:types(Mod, Name, ArgTypes),
PosTypes = [T || {#b_var{},_}=T <- zip(Args, PosTypes0)],
PosTypes = zip(Args, PosTypes0),

{PosTypes, []};
infer_success_type(bs_start_match, [_, #b_var{}=Src], _Ts, _Ds) ->
Expand Down Expand Up @@ -2807,7 +2793,13 @@ join_types_1([V | Vs], Bigger, Smaller) ->
join_types_1([], _Bigger, Smaller) ->
Smaller.

meet_types([{V,T0}|Vs], Ts) ->
meet_types([{#b_literal{}=Lit, T0} | Vs], Ts) ->
T1 = concrete_type(Lit, Ts),
case beam_types:meet(T0, T1) of
none -> none;
_ -> meet_types(Vs, Ts)
end;
meet_types([{#b_var{}=V, T0} | Vs], Ts) ->
T1 = concrete_type(V, Ts),
case beam_types:meet(T0, T1) of
none -> none;
Expand All @@ -2817,6 +2809,22 @@ meet_types([{V,T0}|Vs], Ts) ->
meet_types([], Ts) ->
Ts.

subtract_types([{#b_literal{}=Lit, T0} | Vs], Ts) ->
T1 = concrete_type(Lit, Ts),
case beam_types:subtract(T0, T1) of
none -> none;
_ -> subtract_types(Vs, Ts)
end;
subtract_types([{#b_var{}=V, T0}|Vs], Ts) ->
T1 = concrete_type(V, Ts),
case beam_types:subtract(T1, T0) of
none -> none;
T1 -> subtract_types(Vs, Ts);
T -> subtract_types(Vs, Ts#{V := T})
end;
subtract_types([], Ts) ->
Ts.

parallel_join([A | As], [B | Bs]) ->
[beam_types:join(A, B) | parallel_join(As, Bs)];
parallel_join([], []) ->
Expand Down
29 changes: 27 additions & 2 deletions lib/compiler/test/beam_type_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,7 @@
container_subtraction/1,is_list_opt/1,connected_tuple_elements/1,
switch_fail_inference/1,failures/1,
cover_maps_functions/1,min_max_mixed_types/1,
not_equal/1]).
not_equal/1,infer_relops/1]).

%% Force id/1 to return 'any'.
-export([id/1]).
Expand Down Expand Up @@ -68,7 +68,8 @@ groups() ->
failures,
cover_maps_functions,
min_max_mixed_types,
not_equal
not_equal,
infer_relops
]}].

init_per_suite(Config) ->
Expand Down Expand Up @@ -1230,5 +1231,29 @@ not_equal(_Config) ->
do_not_equal(V) when (V / V < (V orelse true)); V; V ->
(V = (a /= V)) orelse 0.


infer_relops(_Config) ->
{'EXIT',{badarith,_}} = catch infer_relops_1(),
{'EXIT',{badarith,_}} = catch infer_relops_2(),
{'EXIT',{badarith,_}} = catch infer_relops_3(id(0)),
ok.

%% GH-6568: Type inference for relational operations returned erroneous results
%% for singletons.
infer_relops_1() ->
<<0 || ((0 rem 0) > [0 || _ <- catch (node())]), _ <- []>>.

infer_relops_2() ->
X = self() + 0,
[0 || [0 || _ <- date()] =< X, _ <- []].

infer_relops_3(X) ->
<<0 || ((+(is_alive())) <
[
infer_relops_3(infer_relops_3(0))
|| X
]) andalso ok
>>.

id(I) ->
I.

0 comments on commit b099804

Please sign in to comment.