File 0323-Eliminate-a-crash-in-beam_ssa_codegen.patch of Package erlang
From b3571cd3b5e58132a7824141a96d17cb73cd98ef Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Mon, 30 Aug 2021 09:09:58 +0200
Subject: [PATCH] Eliminate a crash in beam_ssa_codegen
The following example:
valid(Type) -> is_list(mime_to_ext(Type)).
mime_to_ext(<<"application/a2l">>) -> [<<"a2l">>];
mime_to_ext(_Type) -> nil.
would crash `beam_ssa_codegen`:
$ erlc a.erl
Function: valid/1
a.erl: internal error in pass beam_ssa_codegen:
exception error: no function clause matching beam_ssa_codegen:cg_instr(is_nonempty_list,[{x,0}],{x,0})
in function beam_ssa_codegen:cg_block/3 (beam_ssa_codegen.erl, line 1326)
in call from beam_ssa_codegen:cg_linear/2 (beam_ssa_codegen.erl, line 956)
in call from beam_ssa_codegen:cg_linear/2 (beam_ssa_codegen.erl, line 957)
in call from beam_ssa_codegen:function/3 (beam_ssa_codegen.erl, line 130)
in call from lists:mapfoldl/3 (lists.erl, line 1376)
in call from beam_ssa_codegen:module/2 (beam_ssa_codegen.erl, line 49)
in call from compile:'-select_passes/2-anonymous-0-'/3 (compile.erl, line 691)
Closes #5158.
---
lib/compiler/src/beam_ssa_codegen.erl | 8 ++++++++
lib/compiler/src/beam_ssa_type.erl | 14 +++++++++-----
lib/compiler/test/beam_type_SUITE.erl | 19 +++++++++++++++++--
3 files changed, 34 insertions(+), 7 deletions(-)
diff --git a/lib/compiler/src/beam_ssa_codegen.erl b/lib/compiler/src/beam_ssa_codegen.erl
index f80d7b5bb1..c74b696711 100644
--- a/lib/compiler/src/beam_ssa_codegen.erl
+++ b/lib/compiler/src/beam_ssa_codegen.erl
@@ -1679,6 +1679,14 @@ cg_instr(bs_get_position, [Ctx], Dst, Set) ->
cg_instr(put_map, [{atom,assoc},SrcMap|Ss], Dst, Set) ->
Live = get_live(Set),
[{put_map_assoc,{f,0},SrcMap,Dst,Live,{list,Ss}}];
+cg_instr(is_nonempty_list, Ss, Dst, Set) ->
+ #cg_set{anno=#{was_bif_is_list := true}} = Set, %Assertion.
+
+ %% This instruction was a call to is_list/1, which was rewritten
+ %% to an is_nonempty_list test by beam_ssa_type. BEAM has no
+ %% is_nonempty_list instruction that will return a boolean, so
+ %% we must revert it to an is_list/1 call.
+ [{bif,is_list,{f,0},Ss,Dst}];
cg_instr(Op, Args, Dst, _Set) ->
cg_instr(Op, Args, Dst).
diff --git a/lib/compiler/src/beam_ssa_type.erl b/lib/compiler/src/beam_ssa_type.erl
index 8ab7473139..6a04d11b37 100644
--- a/lib/compiler/src/beam_ssa_type.erl
+++ b/lib/compiler/src/beam_ssa_type.erl
@@ -885,15 +885,19 @@ simplify(#b_set{op={bif,'=:='},args=[LHS,RHS]}=I, Ts) ->
{_,_} ->
eval_bif(I, Ts)
end
- end;
-simplify(#b_set{op={bif,is_list},args=[Src]}=I, Ts) ->
+ end;
+simplify(#b_set{op={bif,is_list},args=[Src]}=I0, Ts) ->
case raw_type(Src, Ts) of
#t_union{list=#t_cons{}} ->
- I#b_set{op=is_nonempty_list,args=[Src]};
+ I = I0#b_set{op=is_nonempty_list,args=[Src]},
+ %% We might need to convert back to is_list/1 if it turns
+ %% out that this instruction is followed by a #b_ret{}
+ %% terminator.
+ beam_ssa:add_anno(was_bif_is_list, true, I);
#t_union{list=nil} ->
- I#b_set{op={bif,'=:='},args=[Src,#b_literal{val=[]}]};
+ I0#b_set{op={bif,'=:='},args=[Src,#b_literal{val=[]}]};
_ ->
- eval_bif(I, Ts)
+ eval_bif(I0, Ts)
end;
simplify(#b_set{op={bif,Op},args=Args}=I, Ts) ->
Types = normalized_types(Args, Ts),
diff --git a/lib/compiler/test/beam_type_SUITE.erl b/lib/compiler/test/beam_type_SUITE.erl
index 1f4fa6599f..7cc18cdda0 100644
--- a/lib/compiler/test/beam_type_SUITE.erl
+++ b/lib/compiler/test/beam_type_SUITE.erl
@@ -26,7 +26,7 @@
arity_checks/1,elixir_binaries/1,find_best/1,
test_size/1,cover_lists_functions/1,list_append/1,bad_binary_unit/1,
none_argument/1,success_type_oscillation/1,type_subtraction/1,
- container_subtraction/1]).
+ container_subtraction/1,is_list_opt/1]).
%% Force id/1 to return 'any'.
-export([id/1]).
@@ -58,7 +58,8 @@ groups() ->
none_argument,
success_type_oscillation,
type_subtraction,
- container_subtraction
+ container_subtraction,
+ is_list_opt
]}].
init_per_suite(Config) ->
@@ -661,5 +662,19 @@ cs_1({_,_}=Other) ->
cs_2({bar,baz}) ->
ok.
+is_list_opt(_Config) ->
+ true = is_list_opt_1(id(<<"application/a2l">>)),
+ false = is_list_opt_1(id(<<"">>)),
+ ok.
+
+is_list_opt_1(Type) ->
+ %% The call to is_list/1 would be optimized to an is_nonempty_list
+ %% instruction, which is illegal in a return context. That would
+ %% crash beam_ssa_codegen.
+ is_list(is_list_opt_2(Type)).
+
+is_list_opt_2(<<"application/a2l">>) -> [<<"a2l">>];
+is_list_opt_2(_Type) -> nil.
+
id(I) ->
I.
--
2.31.1