File 0544-v3_core-Fix-compiler-crash-when-compiling-failing-bi.patch of Package erlang
From 0f53ac61d9cec00a21ba746962c42bb11417ece7 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Mon, 17 Feb 2020 12:56:03 +0100
Subject: [PATCH 1/4] v3_core: Fix compiler crash when compiling failing binary
construction
The compiler would crash when compiling code such as the following
because the binding of `Var` was not done because the binary
construction would always fail:
case <<face:(Var = 42)>> of
_ -> Var
end
---
lib/compiler/src/v3_core.erl | 19 +++++++++++--------
lib/compiler/test/bs_construct_SUITE.erl | 12 ++++++++++++
2 files changed, 23 insertions(+), 8 deletions(-)
diff --git a/lib/compiler/src/v3_core.erl b/lib/compiler/src/v3_core.erl
index 9e2ca45074..0efc8f7821 100644
--- a/lib/compiler/src/v3_core.erl
+++ b/lib/compiler/src/v3_core.erl
@@ -603,14 +603,14 @@ expr({bin,L,Es0}, St0) ->
try expr_bin(Es0, full_anno(L, St0), St0) of
{_,_,_}=Res -> Res
catch
- throw:bad_binary ->
- St = add_warning(L, bad_binary, St0),
+ throw:{bad_binary,Eps,St1} ->
+ St = add_warning(L, bad_binary, St1),
LineAnno = lineno_anno(L, St),
As = [#c_literal{anno=LineAnno,val=badarg}],
{#icall{anno=#a{anno=LineAnno}, %Must have an #a{}
module=#c_literal{anno=LineAnno,val=erlang},
name=#c_literal{anno=LineAnno,val=error},
- args=As},[],St}
+ args=As},Eps,St}
end;
expr({block,_,Es0}, St0) ->
%% Inline the block directly.
@@ -1147,8 +1147,9 @@ expr_bin_1(Es, St) ->
end, {[],[],St}, Es).
bitstr({bin_element,_,E0,Size0,[Type,{unit,Unit}|Flags]}, St0) ->
- {E1,Eps,St1} = safe(E0, St0),
- {Size1,Eps2,St2} = safe(Size0, St1),
+ {E1,Eps0,St1} = safe(E0, St0),
+ {Size1,Eps1,St2} = safe(Size0, St1),
+ Eps = Eps0 ++ Eps1,
case {Type,E1} of
{_,#c_var{}} -> ok;
{integer,#c_literal{val=I}} when is_integer(I) -> ok;
@@ -1158,20 +1159,22 @@ bitstr({bin_element,_,E0,Size0,[Type,{unit,Unit}|Flags]}, St0) ->
{float,#c_literal{val=V}} when is_number(V) -> ok;
{binary,#c_literal{val=V}} when is_bitstring(V) -> ok;
{_,_} ->
- throw(bad_binary)
+ %% Note that the pre expressions may bind variables that
+ %% are used later or have side effects.
+ throw({bad_binary,Eps,St2})
end,
case Size1 of
#c_var{} -> ok;
#c_literal{val=Sz} when is_integer(Sz), Sz >= 0 -> ok;
#c_literal{val=undefined} -> ok;
#c_literal{val=all} -> ok;
- _ -> throw(bad_binary)
+ _ -> throw({bad_binary,Eps,St2})
end,
{#c_bitstr{val=E1,size=Size1,
unit=#c_literal{val=Unit},
type=#c_literal{val=Type},
flags=#c_literal{val=Flags}},
- Eps ++ Eps2,St2}.
+ Eps,St2}.
%% fun_tq(Id, [Clauses], Line, State, NameInfo) -> {Fun,[PreExp],State}.
diff --git a/lib/compiler/test/bs_construct_SUITE.erl b/lib/compiler/test/bs_construct_SUITE.erl
index f591192af8..aa4f302036 100644
--- a/lib/compiler/test/bs_construct_SUITE.erl
+++ b/lib/compiler/test/bs_construct_SUITE.erl
@@ -304,6 +304,18 @@ fail(Config) when is_list(Config) ->
?line {'EXIT',{badarg,_}} = (catch <<42/binary>>),
?line {'EXIT',{badarg,_}} = (catch <<an_atom/integer>>),
+ %% Make sure that variables are bound even if binary
+ %% construction fails.
+ ?line {'EXIT',{badarg,_}} = (catch case <<face:(V0 = 42)>> of
+ _Any -> V0
+ end),
+ ?line {'EXIT',{badarg,_}} = (catch case <<face:(V1 = 3)>> of
+ a when V1 ->
+ office
+ end),
+ ?line {'EXIT',{badarg,_}} = (catch <<13:(put(?FUNCTION_NAME, 17))>>),
+ 17 = erase(?FUNCTION_NAME),
+
ok.
float_bin(Config) when is_list(Config) ->
--
2.16.4