File 2173-beam_ssa_throw-Remove-pointless-assertion-that-cause.patch of Package erlang
From 3a285636bcceff0cdd06e56a293bac952a4bc618 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org>
Date: Thu, 10 Jun 2021 13:05:04 +0200
Subject: [PATCH] beam_ssa_throw: Remove pointless assertion that caused
crashes
We don't have to care about this when simulating a throw, since we
will assume all paths are possible if we get the types wrong. We
only need to be careful not to assert something we cannot prove.
---
lib/compiler/src/beam_ssa_throw.erl | 10 +++++-----
lib/compiler/test/trycatch_SUITE.erl | 26 ++++++++++++++++++++++++++
2 files changed, 31 insertions(+), 5 deletions(-)
diff --git a/lib/compiler/src/beam_ssa_throw.erl b/lib/compiler/src/beam_ssa_throw.erl
index cf742ec6ce..ae70872730 100644
--- a/lib/compiler/src/beam_ssa_throw.erl
+++ b/lib/compiler/src/beam_ssa_throw.erl
@@ -418,12 +418,12 @@ ois_is([#b_set{op=get_tl,dst=Dst,args=[Src]} | Is], Ts0) ->
{Type, _, _} = beam_call_types:types(erlang, tl, [SrcType]),
Ts = Ts0#{ Dst => Type },
ois_is(Is, Ts);
-ois_is([#b_set{op=get_tuple_element,dst=Dst,args=[Src, Offset]} | Is], Ts0) ->
+ois_is([#b_set{op=get_tuple_element,
+ dst=Dst,
+ args=[Src, #b_literal{val=Offset}]} | Is], Ts0) ->
Type = case Ts0 of
- #{ Src := #t_tuple{size=Size,elements=Es} } ->
- #b_literal{val=N} = Offset,
- true = Size > N, %Assertion.
- beam_types:get_tuple_element(N + 1, Es);
+ #{ Src := #t_tuple{size=Size,elements=Es} } when Offset < Size ->
+ beam_types:get_tuple_element(Offset + 1, Es);
#{} ->
any
end,
diff --git a/lib/compiler/test/trycatch_SUITE.erl b/lib/compiler/test/trycatch_SUITE.erl
index 0c82f908b5..6221e64bcd 100644
--- a/lib/compiler/test/trycatch_SUITE.erl
+++ b/lib/compiler/test/trycatch_SUITE.erl
@@ -30,6 +30,7 @@
stacktrace/1,nested_stacktrace/1,raise/1,
no_return_in_try_block/1,
expression_export/1,
+ throw_opt_crash/1,
coverage/1]).
-include_lib("common_test/include/ct.hrl").
@@ -48,6 +49,7 @@ groups() ->
hockey,handle_info,catch_in_catch,grab_bag,
stacktrace,nested_stacktrace,raise,
no_return_in_try_block,expression_export,
+ throw_opt_crash,
coverage]}].
@@ -1552,6 +1554,30 @@ expr_export_5() ->
ok
end.
+%% GH-4953: Type inference in throw optimization could crash in rare
+%% circumstances when a thrown type conflicted with one that was matched in
+%% a catch clause.
+throw_opt_crash(_Config) ->
+ try
+ throw_opt_crash_1(id(false), {pass, id(b), id(c)}),
+ throw_opt_crash_1(id(false), {crash, id(b)}),
+ ok
+ catch
+ throw:{pass, B, C} ->
+ {error, gurka, {B, C}};
+ throw:{beta, B, C} ->
+ {error, gaffel, {B, C}};
+ throw:{gamma, B, C} ->
+ {error, grammofon, {B, C}}
+ end.
+
+throw_opt_crash_1(true, {_, _ ,_}=Term) ->
+ throw(Term);
+throw_opt_crash_1(true, {_, _}=Term) ->
+ throw(Term);
+throw_opt_crash_1(false, _Term) ->
+ ok.
+
coverage(_Config) ->
{'EXIT',{{badfun,true},[_|_]}} = (catch coverage_1()),
ok = coverage_ssa_throw(),
--
2.26.2