File 0293-Fix-incorrect-bs_match-without-any-ensure-instructio.patch of Package erlang
From 0d454bd7191d7f48402f496f9731bd4000ec4ea3 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Tue, 21 Jan 2025 15:57:50 +0100
Subject: [PATCH 3/3] Fix incorrect bs_match without any ensure instruction
The compiler could sometimes generate unsafe code when
matching literal data in a binary. For example:
t(Data) ->
<<Rest/bits>> = Data,
{_, Bits} = ext:ernal(Rest),
case Rest of
<<0, _:Bits>> -> not_empty;
<<>> -> empty
end.
The generated code for the first clause of the `case` would
look like this:
{bs_match,{f,20},{y,2},{commands,[{'=:=',nil,8,0}]}}.
That is unsafe because the first command in a `bs_match` instruction
must always be an `ensure*` instruction to ensure that the bitstring
is of sufficient size.
This unsafe code generation was introduced in 60f8f9eaa7966258126d0c.
This commit ensures that a `bs_match_string` instruction will be
emitted instead of a `bs_match` instruction:
{test,bs_match_string,{f,20},[{y,2},8,{string,<<0>>}]}.
Fixes #9304
---
lib/compiler/src/beam_ssa.erl | 4 +++-
lib/compiler/src/beam_ssa_codegen.erl | 19 +++++++++++--------
lib/compiler/src/beam_ssa_pre_codegen.erl | 12 +++++++++---
lib/compiler/test/bs_match_SUITE.erl | 21 +++++++++++++++++++++
4 files changed, 44 insertions(+), 12 deletions(-)
diff --git a/lib/compiler/src/beam_ssa.erl b/lib/compiler/src/beam_ssa.erl
index 2169481e2a..a7b0dd3289 100644
--- a/lib/compiler/src/beam_ssa.erl
+++ b/lib/compiler/src/beam_ssa.erl
@@ -133,7 +133,9 @@
'+' | '-' | '*' | '/'.
%% Primops only used internally during code generation.
--type cg_prim_op() :: 'bs_ensured_get' | 'bs_ensured_skip' |
+-type cg_prim_op() :: 'bs_ensured_get' |
+ 'bs_ensured_match_string' |
+ 'bs_ensured_skip' |
'bs_get' | 'bs_get_position' | 'bs_match_string' |
'bs_restore' | 'bs_save' | 'bs_set_position' | 'bs_skip' |
'copy' | 'match_fail' | 'put_tuple_arity' |
diff --git a/lib/compiler/src/beam_ssa_codegen.erl b/lib/compiler/src/beam_ssa_codegen.erl
index 9b444d34b1..f4b98d3a0b 100644
--- a/lib/compiler/src/beam_ssa_codegen.erl
+++ b/lib/compiler/src/beam_ssa_codegen.erl
@@ -376,6 +376,7 @@ classify_heap_need(Name, _Args) ->
classify_heap_need(bs_ensure) -> gc;
classify_heap_need(bs_ensured_get) -> gc;
classify_heap_need(bs_ensured_skip) -> gc;
+classify_heap_need(bs_ensured_match_string) -> gc;
classify_heap_need(bs_get) -> gc;
classify_heap_need(bs_get_tail) -> gc;
classify_heap_need(bs_init_writable) -> gc;
@@ -485,6 +486,7 @@ prefer_xregs_is([#cg_set{op=Op}=I|Is], St, Copies0, Acc)
when Op =:= bs_ensured_get;
Op =:= bs_ensured_skip;
Op =:= bs_ensure;
+ Op =:= bs_ensured_match_string;
Op =:= bs_match_string ->
Copies = prefer_xregs_prune(I, Copies0, St),
prefer_xregs_is(Is, St, Copies, [I|Acc]);
@@ -1195,8 +1197,9 @@ cg_block([#cg_set{op=bs_ensure,args=Ss0},
cg_block([#cg_set{op=bs_get}=Set,
#cg_set{op=succeeded,dst=Bool}], {Bool,Fail}, St) ->
{cg_bs_get(Fail, Set, St),St};
-cg_block([#cg_set{op=bs_match_string,args=[CtxVar,#b_literal{val=String0}]},
- #cg_set{op=succeeded,dst=Bool}], {Bool,Fail}, St) ->
+cg_block([#cg_set{op=Op,args=[CtxVar,#b_literal{val=String0}]},
+ #cg_set{op=succeeded,dst=Bool}], {Bool,Fail}, St)
+ when Op =:= bs_match_string; Op =:= bs_ensured_match_string ->
CtxReg = beam_arg(CtxVar, St),
Bits = bit_size(String0),
@@ -1205,7 +1208,7 @@ cg_block([#cg_set{op=bs_match_string,args=[CtxVar,#b_literal{val=String0}]},
Rem -> <<String0/bitstring,0:(8-Rem)>>
end,
- Is = [{test,bs_match_string,Fail,[CtxReg,Bits,{string,String}]}],
+ Is = [{test,Op,Fail,[CtxReg,Bits,{string,String}]}],
{Is,St};
cg_block([#cg_set{dst=Dst0,op=landingpad,args=Args0}|T], Context, St0) ->
[Dst,{atom,Kind},Tag] = beam_args([Dst0|Args0], St0),
@@ -2347,6 +2350,11 @@ bs_translate_instr({bs_ensured_get,Live,{atom,Type},Ctx,{field_flags,Flags0},
{anno,_} -> false
end],
{Ctx,{f,0},{Type,Live,{literal,Flags},Size,Unit,Dst}};
+bs_translate_instr({test,bs_ensured_match_string,Fail,
+ [Ctx,Bits,{string,String}]}) ->
+ <<Value:Bits,_/bitstring>> = String,
+ Live = nil,
+ {Ctx,Fail,{'=:=',Live,Bits,Value}};
bs_translate_instr({bs_ensured_skip,Ctx,Stride}) ->
{Ctx,{f,0},{skip,Stride}};
bs_translate_instr({bs_ensured_get_tail,Live,Ctx,Unit,Dst}) ->
@@ -2355,11 +2363,6 @@ bs_translate_instr({bs_get_tail,Ctx,Dst,Live}) ->
{Ctx,{f,0},{get_tail,Live,1,Dst}};
bs_translate_instr({test,bs_test_tail2,Fail,[Ctx,Bits]}) ->
{Ctx,Fail,{test_tail,Bits}};
-bs_translate_instr({test,bs_match_string,Fail,[Ctx,Bits,{string,String}]})
- when bit_size(String) =< 64 ->
- <<Value:Bits,_/bitstring>> = String,
- Live = nil,
- {Ctx,Fail,{'=:=',Live,Bits,Value}};
bs_translate_instr(_) -> none.
diff --git a/lib/compiler/src/beam_ssa_pre_codegen.erl b/lib/compiler/src/beam_ssa_pre_codegen.erl
index c9da0233a9..a86068d0a8 100644
--- a/lib/compiler/src/beam_ssa_pre_codegen.erl
+++ b/lib/compiler/src/beam_ssa_pre_codegen.erl
@@ -572,7 +572,7 @@ bs_insert_is([], _, _, Acc) ->
%%
%% * bs_get / bs_ensured_get
%% * bs_skip / bs_ensured_skip
-%% * bs_match_string
+%% * bs_match_string / bs_ensured_match_string
%%
%% The bs_ensured_* instructions don't check that the bitstring being
%% matched is long enough, because that has already been done by a
@@ -634,8 +634,13 @@ bs_instrs_is([#b_set{anno=Anno0,op=Op,args=Args0}=I0|Is], CtxChain, Acc) ->
Anno0
end,
I1#b_set{anno=Anno,op=bs_skip,args=[Type,Ctx|As]};
- {bs_match,[#b_literal{val=string},Ctx|As]} ->
- I1#b_set{op=bs_match_string,args=[Ctx|As]};
+ {bs_match,[#b_literal{val=string},Ctx,#b_literal{val=S}=S0]} ->
+ case Anno0 of
+ #{ensured := true} when bit_size(S) =< 64 ->
+ I1#b_set{op=bs_ensured_match_string,args=[Ctx,S0]};
+ #{} ->
+ I1#b_set{op=bs_match_string,args=[Ctx,S0]}
+ end;
{_,_} ->
I1
end,
@@ -2621,6 +2626,7 @@ reserve_zreg([#b_set{op=Op,dst=Dst} | Is], Last, ShortLived, A) ->
end;
reserve_zreg([], _, _, A) -> A.
+use_zreg(bs_ensured_match_string) -> yes;
use_zreg(bs_ensured_skip) -> yes;
use_zreg(bs_ensure) -> yes;
use_zreg(bs_match_string) -> yes;
diff --git a/lib/compiler/test/bs_match_SUITE.erl b/lib/compiler/test/bs_match_SUITE.erl
index 2b06ec0a8d..7c90b4f2f7 100644
--- a/lib/compiler/test/bs_match_SUITE.erl
+++ b/lib/compiler/test/bs_match_SUITE.erl
@@ -61,6 +61,7 @@
-export([coverage_id/1,coverage_external_ignore/2]).
-include_lib("common_test/include/ct.hrl").
+-include_lib("stdlib/include/assert.hrl").
-include_lib("syntax_tools/include/merl.hrl").
@@ -2751,6 +2752,13 @@ bs_match(_Config) ->
{0,<<1,2,3>>} = do_bs_match_gh_8280(),
+ not_empty = do_bs_match_gh_9304(id(<<0,0:32>>)),
+ empty = do_bs_match_gh_9304(id(<<>>)),
+ ?assertError({case_clause,_}, do_bs_match_gh_9304(id(<<0:1>>))),
+ ?assertError({case_clause,_}, do_bs_match_gh_9304(id(<<0>>))),
+ ?assertError({case_clause,_}, do_bs_match_gh_9304(id(<<0,0:64>>))),
+ ?assertError({case_clause,_}, do_bs_match_gh_9304(id(<<1,0:32>>))),
+
ok.
do_bs_match_1(_, X) ->
@@ -2831,6 +2839,19 @@ do_bs_match_gh_8280() ->
<<A, B:(byte_size(B))/binary>> = id(<<0, 1, 2, 3>>),
{A, B}.
+do_bs_match_gh_9304(Data) ->
+ <<Rest/bits>> = Data,
+ {_, Bits} = do_bs_match_gh_9304_1(Rest),
+ case Rest of
+ %% The compiler emitted a bs_match instruction without any
+ %% ensure command.
+ <<0, _:Bits>> -> not_empty;
+ <<>> -> empty
+ end.
+
+do_bs_match_gh_9304_1(Data) ->
+ id({dummy, 32}).
+
%% GH-6348/OTP-18297: Allow aliases for binaries.
-record(ba_foo, {a,b,c}).
--
2.43.0