Skip to content

Commit

Permalink
Merge pull request #7271 from frej/frej/fix-binary-construction-crash
Browse files Browse the repository at this point in the history
compiler: Fix type inference bug for bit strings
  • Loading branch information
bjorng authored May 24, 2023
2 parents 5047860 + fd735d6 commit 830c717
Show file tree
Hide file tree
Showing 2 changed files with 28 additions and 1 deletion.
18 changes: 18 additions & 0 deletions lib/compiler/src/beam_ssa_type.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2512,6 +2512,24 @@ infer_types_br_1(V, Ts, Ds) ->
{TrueTypes, FalseTypes}
end.

infer_relop('=:=', [LHS,RHS],
[#t_bitstring{appendable=LHSApp}=LType0,
#t_bitstring{appendable=RHSApp}=RType0], Ds)
when LHSApp ; RHSApp ->
%% Bit strings are special in that nothing about their
%% appendable-status can be deduced from a comparison. The only
%% information gained is the size_unit. The appendable status is
%% unchanged by the comparison.
%%
%% In order to avoid narrowing the types with regard to
%% appendable-status, deduce the types for the case when neither
%% LHS or RHS are appendable, then restore the appendable-status.
[{LHS,LType},{RHS,RType}|EqTypes] =
infer_relop('=:=', [LHS,RHS],
[LType0#t_bitstring{appendable=false},
RType0#t_bitstring{appendable=false}], Ds),
[{LHS,LType#t_bitstring{appendable=LHSApp}},
{RHS,RType#t_bitstring{appendable=RHSApp}}|EqTypes];
infer_relop('=:=', [LHS,RHS], [LType,RType], Ds) ->
EqTypes = infer_eq_type(map_get(LHS, Ds), RType),

Expand Down
11 changes: 10 additions & 1 deletion lib/compiler/test/beam_ssa_check_SUITE_data/appendable.erl
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@
%% %CopyrightEnd%
-module(appendable).
-export([make_empty/0, t0/0, t1/0, t2/0, t3/0, t4/0,
t5/0, t6/0, t7/0, t8/1, t9/1, t10/1, t11/1, t12/0]).
t5/0, t6/0, t7/0, t8/1, t9/1, t10/1, t11/1, t12/0, t13/0]).

%% Check that just returning an empty bitstring is considered
%% appendable.
Expand Down Expand Up @@ -160,3 +160,12 @@ t12() ->

t12_inner([x|B]) ->
[x|<<B/binary,1:8>>].

%% Check that the compiler doesn't infer anything about the appendable
%% status of a bitstring from a comparison.
t13() ->
%ssa% () when post_ssa_opt ->
%ssa% B = bif:binary_part(A, 0, 0),
%ssa% C = bif:'=:='(B, A) { arg_types => #{ 0 => {t_bitstring,8,false}, 1 => {t_bitstring,256,true}} },
%ssa% _ = bs_create_bin(append, _, B, ...) { arg_types => #{ 2 => {t_bitstring,256,false} } }.
<<(_V4 = binary_part(_V4 = <<0 || _ <- []>>, 0, 0))/bitstring>>.

0 comments on commit 830c717

Please sign in to comment.