File 0345-Do-not-consider-zero-floats-as-singleton.patch of Package erlang
From 9d397879dad1fa829515f19abb07e2a3658fe2d3 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Jos=C3=A9=20Valim?= <jose.valim@dashbit.co>
Date: Thu, 3 Dec 2020 07:41:40 +0100
Subject: [PATCH] Do not consider zero floats as singleton
There is currently a bug in the compiler where 0.0
is considered a singleton. However, 0.0 can match both
-0.0 and 0.0 which makes this assumption invalid. Here
is a failing test:
float_zero(Config) when is_list(Config) ->
<<16#0000000000000000:64>> = to_fbin(1*0.0),
<<16#8000000000000000:64>> = to_fbin(-1*0.0),
ok.
to_fbin(X = 0.0) -> <<X/float>>.
This commit changes beam_types:get_single_value/1 to not
consider float singletons and therefore not perform constant
propagation.
Furthermore, we also need to instruct beam_asm to encode
0.0 and -0.0 as two distinct literals.
---
lib/compiler/src/beam_dict.erl | 29 ++++++++++++++++++++++++-----
lib/compiler/src/beam_types.erl | 3 ++-
lib/compiler/test/float_SUITE.erl | 10 ++++++++--
3 files changed, 34 insertions(+), 8 deletions(-)
diff --git a/lib/compiler/src/beam_dict.erl b/lib/compiler/src/beam_dict.erl
index 76d4e62f6b..8619056cbf 100644
--- a/lib/compiler/src/beam_dict.erl
+++ b/lib/compiler/src/beam_dict.erl
@@ -169,12 +169,28 @@ lambda(Lbl, NumFree, #asm{wrappers=Wrappers0,
%% literal(Literal, Dict) -> {Index,Dict'}
-spec literal(term(), bdict()) -> {non_neg_integer(), bdict()}.
-literal(Lit, #asm{literals=Tab0,next_literal=NextIndex}=Dict) ->
+-dialyzer({no_improper_lists, literal/2}).
+
+literal(Lit, Dict) when is_float(Lit) ->
+ %% A literal 0.0 actually has two representations: 0.0 and -0.0.
+ %% While they are equal, they must be encoded differently (the bit sign).
+ if
+ %% We do not explicitly match on 0.0 because a buggy compiler
+ %% could replace Lit by 0.0, which would discard its sign.
+ Lit > 0.0; Lit < 0.0 ->
+ literal1([term|Lit], Dict);
+ true ->
+ literal1([binary|my_term_to_binary(Lit)], Dict)
+ end;
+literal(Lit, Dict) ->
+ literal1([term|Lit], Dict).
+
+literal1(Key, #asm{literals=Tab0,next_literal=NextIndex}=Dict) ->
case Tab0 of
- #{Lit:=Index} ->
+ #{Key:=Index} ->
{Index,Dict};
#{} ->
- Tab = Tab0#{Lit=>NextIndex},
+ Tab = Tab0#{Key=>NextIndex},
{NextIndex,Dict#asm{literals=Tab,next_literal=NextIndex+1}}
end.
@@ -267,8 +283,11 @@ lambda_table(#asm{locals=Loc0,lambdas={NumLambdas,Lambdas0}}) ->
-spec literal_table(bdict()) -> {non_neg_integer(), [[binary(),...]]}.
literal_table(#asm{literals=Tab,next_literal=NumLiterals}) ->
- L0 = maps:fold(fun(Lit, Num, Acc) ->
- [{Num,my_term_to_binary(Lit)}|Acc]
+ L0 = maps:fold(fun
+ ([term|Lit], Num, Acc) ->
+ [{Num,my_term_to_binary(Lit)}|Acc];
+ ([binary|Lit], Num, Acc) ->
+ [{Num,Lit}|Acc]
end, [], Tab),
L1 = lists:sort(L0),
L = [[<<(byte_size(Term)):32>>,Term] || {_,Term} <- L1],
diff --git a/lib/compiler/src/beam_types.erl b/lib/compiler/src/beam_types.erl
index 48e720edd7..7559673a94 100644
--- a/lib/compiler/src/beam_types.erl
+++ b/lib/compiler/src/beam_types.erl
@@ -423,7 +423,8 @@ is_bs_matchable_type(Type) ->
Result :: {ok, term()} | error.
get_singleton_value(#t_atom{elements=[Atom]}) ->
{ok, Atom};
-get_singleton_value(#t_float{elements={Float,Float}}) ->
+get_singleton_value(#t_float{elements={Float,Float}}) when Float =/= 0.0 ->
+ %% 0.0 is not actually a singleton as it has two encodings: 0.0 and -0.0
{ok, Float};
get_singleton_value(#t_integer{elements={Int,Int}}) ->
{ok, Int};
diff --git a/lib/compiler/test/float_SUITE.erl b/lib/compiler/test/float_SUITE.erl
index 586dfe8102..c9c0beb70f 100644
--- a/lib/compiler/test/float_SUITE.erl
+++ b/lib/compiler/test/float_SUITE.erl
@@ -22,14 +22,14 @@
init_per_group/2,end_per_group/2,
pending/1,bif_calls/1,math_functions/1,mixed_float_and_int/1,
subtract_number_type/1,float_followed_by_guard/1,
- fconv_line_numbers/1,exception_signals/1]).
+ fconv_line_numbers/1,float_zero/1,exception_signals/1]).
-include_lib("common_test/include/ct.hrl").
suite() -> [{ct_hooks,[ts_install_cth]}].
all() ->
- [pending, bif_calls, math_functions,
+ [pending, bif_calls, math_functions, float_zero,
mixed_float_and_int, subtract_number_type,
float_followed_by_guard,fconv_line_numbers,
exception_signals].
@@ -50,6 +50,12 @@ init_per_group(_GroupName, Config) ->
end_per_group(_GroupName, Config) ->
Config.
+float_zero(Config) when is_list(Config) ->
+ <<16#0000000000000000:64>> = match_on_zero_and_to_binary(1*0.0),
+ <<16#8000000000000000:64>> = match_on_zero_and_to_binary(-1*0.0),
+ ok.
+
+match_on_zero_and_to_binary(0.0 = X) -> <<X/float>>.
%% Thanks to Tobias Lindahl <tobias.lindahl@it.uu.se>
%% Shows the effect of pending exceptions on the x86.
--
2.26.2