File 5911-Fix-internal-consistency-error.patch of Package erlang
From c8e684e051af6f8f439db68a21b04b5a03a1cd36 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Mon, 25 Jul 2022 10:42:51 +0200
Subject: [PATCH] Fix internal consistency error
Fixes #6163
---
lib/compiler/src/beam_ssa_opt.erl | 16 ++++++++++++----
lib/compiler/test/float_SUITE.erl | 8 ++++++++
2 files changed, 20 insertions(+), 4 deletions(-)
diff --git a/lib/compiler/src/beam_ssa_opt.erl b/lib/compiler/src/beam_ssa_opt.erl
index eadbb3cc2b..2c6b592595 100644
--- a/lib/compiler/src/beam_ssa_opt.erl
+++ b/lib/compiler/src/beam_ssa_opt.erl
@@ -1077,13 +1077,15 @@ cse_suitable(#b_set{}) -> false.
-record(fs,
{regs=#{} :: #{beam_ssa:b_var():=beam_ssa:b_var()},
non_guards :: gb_sets:set(beam_ssa:label()),
- bs :: beam_ssa:block_map()
+ bs :: beam_ssa:block_map(),
+ preds :: #{beam_ssa:label() => [beam_ssa:label()]}
}).
ssa_opt_float({#opt_st{ssa=Linear0,cnt=Count0}=St, FuncDb}) ->
NonGuards = non_guards(Linear0),
Blocks = maps:from_list(Linear0),
- Fs = #fs{non_guards=NonGuards,bs=Blocks},
+ Preds = beam_ssa:predecessors(Blocks),
+ Fs = #fs{non_guards=NonGuards,bs=Blocks,preds=Preds},
{Linear,Count} = float_opt(Linear0, Count0, Fs),
{St#opt_st{ssa=Linear,cnt=Count}, FuncDb}.
@@ -1207,9 +1209,15 @@ float_maybe_flush(Blk0, Fs0, Count0) ->
{FlushBs,Blk,Fs,Count}
end.
-float_safe_to_skip_flush(L, #fs{bs=Blocks}=Fs) ->
+float_safe_to_skip_flush(L, #fs{bs=Blocks,preds=Preds}=Fs) ->
#b_blk{is=Is} = Blk = map_get(L, Blocks),
- float_can_optimize_blk(Blk, Fs) andalso float_optimizable_is(Is).
+ case Preds of
+ #{L := [_]} ->
+ float_can_optimize_blk(Blk, Fs) andalso float_optimizable_is(Is);
+ #{} ->
+ %% This block can be reached from more than one block; must flush.
+ false
+ end.
float_optimizable_is([#b_set{anno=#{float_op:=_}}|_]) ->
true;
diff --git a/lib/compiler/test/float_SUITE.erl b/lib/compiler/test/float_SUITE.erl
index e530a9f7de..328e8a1a79 100644
--- a/lib/compiler/test/float_SUITE.erl
+++ b/lib/compiler/test/float_SUITE.erl
@@ -181,11 +181,19 @@ math_functions(Config) when is_list(Config) ->
mixed_float_and_int(Config) when is_list(Config) ->
129.0 = pc(77, 23, 5),
+
+ {'EXIT',{badarith,_}} = catch mixed_1(id({a,b,c})),
+ {'EXIT',{{badarg,1/42},_}} = catch mixed_1(id(42)),
+
ok.
pc(Cov, NotCov, X) ->
round(Cov/(Cov+NotCov)*100) + 42 + 2.0*X.
+mixed_1(V) ->
+ {is_tuple(V) orelse 1 / V,
+ 1 / V andalso true}.
+
subtract_number_type(Config) when is_list(Config) ->
120 = fact(5).
--
2.35.3