File 0292-Rename-internal-bit-syntax-matching-instructions.patch of Package erlang
From d3e160ce0f7a057eba35a969e689109a4591177e Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Tue, 21 Jan 2025 16:33:32 +0100
Subject: [PATCH 2/3] Rename internal bit syntax matching instructions
The internal instructions `bs_checked_get` and `bs_checked_skip` have
confusing names. One might think that they do some extra checking,
while the opposite is true.
Rename them to `bs_ensured_get` and `bs_ensured_skip` to make the
connection to the `bs_ensure` instruction clearer.
---
lib/compiler/src/beam_ssa.erl | 2 +-
lib/compiler/src/beam_ssa_codegen.erl | 31 +++++++++++------------
lib/compiler/src/beam_ssa_pre_codegen.erl | 24 +++++++++++++-----
3 files changed, 34 insertions(+), 23 deletions(-)
diff --git a/lib/compiler/src/beam_ssa.erl b/lib/compiler/src/beam_ssa.erl
index 9c84d96363..2169481e2a 100644
--- a/lib/compiler/src/beam_ssa.erl
+++ b/lib/compiler/src/beam_ssa.erl
@@ -133,7 +133,7 @@
'+' | '-' | '*' | '/'.
%% Primops only used internally during code generation.
--type cg_prim_op() :: 'bs_checked_get' | 'bs_checked_skip' |
+-type cg_prim_op() :: 'bs_ensured_get' | '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 e5ff7da4c2..9b444d34b1 100644
--- a/lib/compiler/src/beam_ssa_codegen.erl
+++ b/lib/compiler/src/beam_ssa_codegen.erl
@@ -374,8 +374,8 @@ classify_heap_need(Name, _Args) ->
%% by classify_heap_need/2.
classify_heap_need(bs_ensure) -> gc;
-classify_heap_need(bs_checked_get) -> gc;
-classify_heap_need(bs_checked_skip) -> gc;
+classify_heap_need(bs_ensured_get) -> gc;
+classify_heap_need(bs_ensured_skip) -> gc;
classify_heap_need(bs_get) -> gc;
classify_heap_need(bs_get_tail) -> gc;
classify_heap_need(bs_init_writable) -> gc;
@@ -482,9 +482,8 @@ prefer_xregs_is([#cg_set{op=call,dst=Dst}=I0|Is], St, Copies, Acc) ->
I = prefer_xregs_call(I0, Copies, St),
prefer_xregs_is(Is, St, #{Dst=>{x,0}}, [I|Acc]);
prefer_xregs_is([#cg_set{op=Op}=I|Is], St, Copies0, Acc)
- when Op =:= bs_checked_get;
- Op =:= bs_checked_skip;
- Op =:= bs_checked_get_tail;
+ when Op =:= bs_ensured_get;
+ Op =:= bs_ensured_skip;
Op =:= bs_ensure;
Op =:= bs_match_string ->
Copies = prefer_xregs_prune(I, Copies0, St),
@@ -682,7 +681,7 @@ need_live_anno(Op) ->
case Op of
{bif,_} -> true;
bs_create_bin -> true;
- bs_checked_get -> true;
+ bs_ensured_get -> true;
bs_get -> true;
bs_get_position -> true;
bs_get_tail -> true;
@@ -1802,17 +1801,17 @@ cg_instr(bs_start_match, [{atom,new}, Src0], Dst, Set) ->
{Src, Pre} = force_reg(Src0, Dst),
Live = get_live(Set),
Pre ++ [{bs_start_match4,{atom,no_fail},Live,Src,Dst}];
-cg_instr(bs_checked_get, [Kind,Ctx,{literal,Flags},{integer,Size},{integer,Unit}], Dst, Set) ->
+cg_instr(bs_ensured_get, [Kind,Ctx,{literal,Flags},{integer,Size},{integer,Unit}], Dst, Set) ->
%% Temporary instruction that will be incorporated into a bs_match
%% instruction by the bs_translate sub pass.
Live = get_live(Set),
- [{bs_checked_get,Live,Kind,Ctx,field_flags(Flags, Set),Size,Unit,Dst}];
-cg_instr(bs_checked_get, [{atom,binary},Ctx,{literal,_Flags},
+ [{bs_ensured_get,Live,Kind,Ctx,field_flags(Flags, Set),Size,Unit,Dst}];
+cg_instr(bs_ensured_get, [{atom,binary},Ctx,{literal,_Flags},
{atom,all},{integer,Unit}], Dst, Set) ->
%% Temporary instruction that will be incorporated into a bs_match
%% instruction by the bs_translate sub pass.
Live = get_live(Set),
- [{bs_checked_get_tail,Live,Ctx,Unit,Dst}];
+ [{bs_ensured_get_tail,Live,Ctx,Unit,Dst}];
cg_instr(bs_get_tail, [Src], Dst, Set) ->
Live = get_live(Set),
[{bs_get_tail,Src,Dst,Live}];
@@ -1848,12 +1847,12 @@ cg_instr(is_nonempty_list, Ss, Dst, Set) ->
cg_instr(Op, Args, Dst, _Set) ->
cg_instr(Op, Args, Dst).
-cg_instr(bs_checked_skip, [_Type,Ctx,_Flags,{integer,Sz},{integer,U}], {z,_})
+cg_instr(bs_ensured_skip, [_Type,Ctx,_Flags,{integer,Sz},{integer,U}], {z,_})
when is_integer(Sz) ->
%% Temporary instruction that will be incorporated into a bs_match
%% instruction by the bs_translate sub pass.
- [{bs_checked_skip,Ctx,Sz*U}];
-cg_instr(bs_checked_skip, [_Type,_Ctx,_Flags,{atom,all},{integer,_U}], {z,_}) ->
+ [{bs_ensured_skip,Ctx,Sz*U}];
+cg_instr(bs_ensured_skip, [_Type,_Ctx,_Flags,{atom,all},{integer,_U}], {z,_}) ->
[];
cg_instr(bs_init_writable, Args, Dst) ->
setup_args(Args) ++ [bs_init_writable|copy({x,0}, Dst)];
@@ -2334,7 +2333,7 @@ bs_translate_fixup_tail([], Bits) ->
bs_translate_instr({test,bs_ensure,Fail,[Ctx,Size,Unit]}) ->
{Ctx,Fail,{ensure_at_least,Size,Unit}};
-bs_translate_instr({bs_checked_get,Live,{atom,Type},Ctx,{field_flags,Flags0},
+bs_translate_instr({bs_ensured_get,Live,{atom,Type},Ctx,{field_flags,Flags0},
Size,Unit,Dst}) ->
%% Only keep flags that have a meaning for binary matching and are
%% distinct from the default value.
@@ -2348,9 +2347,9 @@ bs_translate_instr({bs_checked_get,Live,{atom,Type},Ctx,{field_flags,Flags0},
{anno,_} -> false
end],
{Ctx,{f,0},{Type,Live,{literal,Flags},Size,Unit,Dst}};
-bs_translate_instr({bs_checked_skip,Ctx,Stride}) ->
+bs_translate_instr({bs_ensured_skip,Ctx,Stride}) ->
{Ctx,{f,0},{skip,Stride}};
-bs_translate_instr({bs_checked_get_tail,Live,Ctx,Unit,Dst}) ->
+bs_translate_instr({bs_ensured_get_tail,Live,Ctx,Unit,Dst}) ->
{Ctx,{f,0},{get_tail,Live,Unit,Dst}};
bs_translate_instr({bs_get_tail,Ctx,Dst,Live}) ->
{Ctx,{f,0},{get_tail,Live,1,Dst}};
diff --git a/lib/compiler/src/beam_ssa_pre_codegen.erl b/lib/compiler/src/beam_ssa_pre_codegen.erl
index a985b7c8c3..c9da0233a9 100644
--- a/lib/compiler/src/beam_ssa_pre_codegen.erl
+++ b/lib/compiler/src/beam_ssa_pre_codegen.erl
@@ -568,9 +568,18 @@ bs_insert_is([#b_set{dst=Dst}=I|Is], Saves, Restores, Acc0) ->
bs_insert_is([], _, _, Acc) ->
{reverse(Acc), []}.
-%% Translate bs_match instructions to bs_get, bs_match_string,
-%% or bs_skip. Also rename match context variables to use the
-%% variable assigned to by the start_match instruction.
+%% Translate bs_match instructions to one of:
+%%
+%% * bs_get / bs_ensured_get
+%% * bs_skip / bs_ensured_skip
+%% * bs_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
+%% bs_ensure instruction.
+%%
+%% Also rename match context variables to use the variable assigned to
+%% by the start_match instruction.
bs_instrs([{L,#b_blk{is=Is0}=Blk}|Bs], CtxChain, Acc0) ->
case bs_instrs_is(Is0, CtxChain, []) of
@@ -591,6 +600,8 @@ bs_rewrite_skip([{L,#b_blk{is=Is0,last=Last0}=Blk}|Bs]) ->
no ->
[{L,Blk}|bs_rewrite_skip(Bs)];
{yes,Is} ->
+ %% bs_skip was rewritten to bs_ensured_skip, which
+ %% can't fail.
#b_br{succ=Succ} = Last0,
Last = beam_ssa:normalize(Last0#b_br{fail=Succ}),
[{L,Blk#b_blk{is=Is,last=Last}}|bs_rewrite_skip(Bs)]
@@ -600,7 +611,7 @@ bs_rewrite_skip([]) ->
bs_rewrite_skip_is([#b_set{anno=#{ensured := true},op=bs_skip}=I0,
#b_set{op={succeeded,guard}}], Acc) ->
- I = I0#b_set{op=bs_checked_skip},
+ I = I0#b_set{op=bs_ensured_skip},
{yes,reverse(Acc, [I])};
bs_rewrite_skip_is([I|Is], Acc) ->
bs_rewrite_skip_is(Is, [I|Acc]);
@@ -640,7 +651,8 @@ bs_combine(Dst, Ctx, [{L,#b_blk{is=Is0}=Blk}|Acc]) ->
#b_set{anno=Anno,op=bs_match,args=[Type,_|As]}=BsMatch|Is1] = reverse(Is0),
if
is_map_key(ensured, Anno) ->
- Is = reverse(Is1, [BsMatch#b_set{op=bs_checked_get,dst=Dst,
+ %% This instruction can't fail.
+ Is = reverse(Is1, [BsMatch#b_set{op=bs_ensured_get,dst=Dst,
args=[Type,Ctx|As]}]),
#b_blk{last=#b_br{succ=Succ}=Br0} = Blk,
Br = beam_ssa:normalize(Br0#b_br{fail=Succ}),
@@ -2609,7 +2621,7 @@ reserve_zreg([#b_set{op=Op,dst=Dst} | Is], Last, ShortLived, A) ->
end;
reserve_zreg([], _, _, A) -> A.
-use_zreg(bs_checked_skip) -> yes;
+use_zreg(bs_ensured_skip) -> yes;
use_zreg(bs_ensure) -> yes;
use_zreg(bs_match_string) -> yes;
use_zreg(bs_set_position) -> yes;
--
2.43.0