File 0174-Fix-broken-bs_match-instructions-when-optimizations-.patch of Package erlang
From 27fcc5b93a9e7c7f2870112b54f3935655783ee9 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Thu, 7 Mar 2024 16:11:09 +0100
Subject: [PATCH 1/2] Fix broken bs_match instructions when optimizations are
disabled
Disabling the `ssa_opt_bs_ensure` optimization could cause the
`beam_ssa_codegen` pass to emit incorrect unsafe `bs_match`
instructions lacking an `ensure_exact` command. (This bug was found
when the `bs_test_partial_tail/1` in the next commit was added.)
Use a function annotation to record that the `ssa_opt_bs_ensure` optimization
has been run, and only generate `bs_match` instruction if it has been run
based on the annotation.
---
lib/compiler/src/beam_ssa_codegen.erl | 12 ++++++------
lib/compiler/src/beam_ssa_opt.erl | 6 ++++--
2 files changed, 10 insertions(+), 8 deletions(-)
diff --git a/lib/compiler/src/beam_ssa_codegen.erl b/lib/compiler/src/beam_ssa_codegen.erl
index e618bcf761..711e776846 100644
--- a/lib/compiler/src/beam_ssa_codegen.erl
+++ b/lib/compiler/src/beam_ssa_codegen.erl
@@ -47,9 +47,8 @@
-spec module(beam_ssa:b_module(), [compile:option()]) ->
{'ok',beam_asm:module_code()}.
-module(#b_module{name=Mod,exports=Es,attributes=Attrs,body=Fs}, Opts) ->
- NoBsMatch = member(no_bs_match, Opts),
- {Asm,St} = functions(Fs, NoBsMatch, {atom,Mod}),
+module(#b_module{name=Mod,exports=Es,attributes=Attrs,body=Fs}, _Opts) ->
+ {Asm,St} = functions(Fs, {atom,Mod}),
{ok,{Mod,Es,Attrs,Asm,St#cg.lcount}}.
-record(need, {h=0 :: non_neg_integer(), % heap words
@@ -110,12 +109,13 @@ module(#b_module{name=Mod,exports=Es,attributes=Attrs,body=Fs}, Opts) ->
-type ssa_register() :: xreg() | yreg() | freg() | zreg().
-functions(Forms, NoBsMatch, AtomMod) ->
- mapfoldl(fun (F, St) -> function(F, NoBsMatch, AtomMod, St) end,
+functions(Forms, AtomMod) ->
+ mapfoldl(fun (F, St) -> function(F, AtomMod, St) end,
#cg{lcount=1}, Forms).
-function(#b_function{anno=Anno,bs=Blocks}, NoBsMatch, AtomMod, St0) ->
+function(#b_function{anno=Anno,bs=Blocks}, AtomMod, St0) ->
#{func_info:={_,Name,Arity}} = Anno,
+ NoBsMatch = not maps:get(bs_ensure_opt, Anno, false),
try
assert_exception_block(Blocks), %Assertion.
Regs = maps:get(registers, Anno),
diff --git a/lib/compiler/src/beam_ssa_opt.erl b/lib/compiler/src/beam_ssa_opt.erl
index b3b458b185..d3530bf723 100644
--- a/lib/compiler/src/beam_ssa_opt.erl
+++ b/lib/compiler/src/beam_ssa_opt.erl
@@ -3453,11 +3453,13 @@ redundant_br_safe_bool(Is, Bool) ->
%%% <<A, B:(byte_size(B))/binary>> = <<0, 1, 2, 3>>
%%%
-ssa_opt_bs_ensure({#opt_st{ssa=Blocks0,cnt=Count0}=St, FuncDb}) when is_map(Blocks0) ->
+ssa_opt_bs_ensure({#opt_st{ssa=Blocks0,cnt=Count0,anno=Anno0}=St, FuncDb})
+ when is_map(Blocks0) ->
RPO = beam_ssa:rpo(Blocks0),
Seen = sets:new([{version,2}]),
{Blocks,Count} = ssa_opt_bs_ensure(RPO, Seen, Count0, Blocks0),
- {St#opt_st{ssa=Blocks,cnt=Count}, FuncDb}.
+ Anno = Anno0#{bs_ensure_opt => true},
+ {St#opt_st{ssa=Blocks,cnt=Count,anno=Anno}, FuncDb}.
ssa_opt_bs_ensure([L|Ls], Seen0, Count0, Blocks0) ->
case sets:is_element(L, Seen0) of
--
2.35.3