Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:23
erlang
0346-Fix-negative-zero-to-string.patch
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 0346-Fix-negative-zero-to-string.patch of Package erlang
From e78af03b493413214816a58dbf4845a01120a4ea Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= <jose.valim@dashbit.co> Date: Wed, 2 Dec 2020 16:04:59 +0100 Subject: [PATCH] Fix negative zero to string Both float_to_binary and float_to_list will correctly print negative zeros when using the scientific mode but not when using the decimal representation. This patch makes it consistent to always show negative floats. io:format/2 has also been fixed to consider negative zeros. This is important because some operations, such as math:atan2, will return drastically different results if negative zeros are given compared to positive zeros. Negative zeros also are encoded differently in bitstrings. --- .../emulator/sys/common/erl_sys_common_misc.c | 2 +- erts/emulator/test/num_bif_SUITE.erl | 11 ++++++ lib/stdlib/src/io_lib_format.erl | 38 +++++++++++++------ lib/stdlib/test/io_SUITE.erl | 25 +++++++++--- 4 files changed, 58 insertions(+), 18 deletions(-) diff --git a/erts/emulator/sys/common/erl_sys_common_misc.c b/erts/emulator/sys/common/erl_sys_common_misc.c index fd7c3b2cda..c840971e6d 100644 --- a/erts/emulator/sys/common/erl_sys_common_misc.c +++ b/erts/emulator/sys/common/erl_sys_common_misc.c @@ -182,7 +182,7 @@ sys_double_to_chars_fast(double f, char *buffer, int buffer_size, int decimals, if (decimals < 0) return -1; - if (f < 0) { + if (signbit(f)) { neg = 1; af = -f; } diff --git a/erts/emulator/test/num_bif_SUITE.erl b/erts/emulator/test/num_bif_SUITE.erl index 6b834705cf..f055a4d7f8 100644 --- a/erts/emulator/test/num_bif_SUITE.erl +++ b/erts/emulator/test/num_bif_SUITE.erl @@ -187,6 +187,17 @@ t_float_to_string(Config) when is_list(Config) -> test_fts("1.2300000000e+20",1.23e20, [{scientific, 10}, compact]), test_fts("1.23000000000000000000e+20",1.23e20, []), + %% Negative zero + <<NegZero/float>> = <<16#8000000000000000:64>>, + "-0.0" = float_to_list(NegZero, [{decimals, 1}, compact]), + "-0.0" = float_to_list(NegZero, [{decimals, 1}]), + "-0.0e+00" = float_to_list(NegZero, [{scientific, 1}]), + "-0.0e+00" = float_to_list(NegZero, [{scientific, 1}, compact]), + <<"-0.0">> = float_to_binary(NegZero, [{decimals, 1}, compact]), + <<"-0.0">> = float_to_binary(NegZero, [{decimals, 1}]), + <<"-0.0e+00">> = float_to_binary(NegZero, [{scientific, 1}]), + <<"-0.0e+00">> = float_to_binary(NegZero, [{scientific, 1}, compact]), + fts_rand_float_decimals(1000), ok. diff --git a/lib/stdlib/src/io_lib_format.erl b/lib/stdlib/src/io_lib_format.erl index 435b31750e..bf6869a492 100644 --- a/lib/stdlib/src/io_lib_format.erl +++ b/lib/stdlib/src/io_lib_format.erl @@ -449,9 +449,10 @@ fwrite_e(Fl, F, Adj, none, Pad) -> fwrite_e(Fl, F, Adj, P, Pad) when P >= 2 -> term(float_e(Fl, float_data(Fl), P), F, Adj, F, Pad). -float_e(Fl, Fd, P) when Fl < 0.0 -> %Negative numbers - [$-|float_e(-Fl, Fd, P)]; -float_e(_Fl, {Ds,E}, P) -> +float_e(Fl, Fd, P) -> + signbit(Fl) ++ abs_float_e(abs(Fl), Fd, P). + +abs_float_e(_Fl, {Ds,E}, P) -> case float_man(Ds, 1, P-1) of {[$0|Fs],true} -> [[$1|Fs]|float_exp(E)]; {Fs,false} -> [Fs|float_exp(E-1)] @@ -503,16 +504,27 @@ fwrite_f(Fl, F, Adj, none, Pad) -> fwrite_f(Fl, F, Adj, P, Pad) when P >= 1 -> term(float_f(Fl, float_data(Fl), P), F, Adj, F, Pad). -float_f(Fl, Fd, P) when Fl < 0.0 -> - [$-|float_f(-Fl, Fd, P)]; -float_f(Fl, {Ds,E}, P) when E =< 0 -> - float_f(Fl, {lists:duplicate(-E+1, $0)++Ds,1}, P); %Prepend enough 0's -float_f(_Fl, {Ds,E}, P) -> +float_f(Fl, Fd, P) -> + signbit(Fl) ++ abs_float_f(abs(Fl), Fd, P). + +abs_float_f(Fl, {Ds,E}, P) when E =< 0 -> + abs_float_f(Fl, {lists:duplicate(-E+1, $0)++Ds,1}, P); %Prepend enough 0's +abs_float_f(_Fl, {Ds,E}, P) -> case float_man(Ds, E, P) of {Fs,true} -> "1" ++ Fs; %Handle carry {Fs,false} -> Fs end. +%% signbit(Float) -> [$-] | [] + +signbit(Fl) when Fl < 0.0 -> [$-]; +signbit(Fl) when Fl > 0.0 -> []; +signbit(Fl) -> + case <<Fl/float>> of + <<1:1,_:63>> -> [$-]; + _ -> [] + end. + %% float_data([FloatChar]) -> {[Digit],Exponent} float_data(Fl) -> @@ -545,13 +557,15 @@ float_data([_|Cs], Ds) -> -spec fwrite_g(float()) -> string(). -fwrite_g(0.0) -> +fwrite_g(Fl) -> + signbit(Fl) ++ abs_fwrite_g(abs(Fl)). + +abs_fwrite_g(0.0) -> "0.0"; -fwrite_g(Float) when is_float(Float) -> +abs_fwrite_g(Float) when is_float(Float) -> {Frac, Exp} = mantissa_exponent(Float), {Place, Digits} = fwrite_g_1(Float, Exp, Frac), - R = insert_decimal(Place, [$0 + D || D <- Digits], Float), - [$- || true <- [Float < 0.0]] ++ R. + insert_decimal(Place, [$0 + D || D <- Digits], Float). -define(BIG_POW, (1 bsl 52)). -define(MIN_EXP, (-1074)). diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl index 5b8e42db1c..bb59a5e53f 100644 --- a/lib/stdlib/test/io_SUITE.erl +++ b/lib/stdlib/test/io_SUITE.erl @@ -29,7 +29,7 @@ printable_range/1, bad_printable_range/1, io_lib_print_binary_depth_one/1, otp_10302/1, otp_10755/1, otp_10836/1, io_lib_width_too_small/1, - io_with_huge_message_queue/1, format_string/1, + io_with_huge_message_queue/1, format_string/1, format_neg_zero/1, maps/1, coverage/1, otp_14178_unicode_atoms/1, otp_14175/1, otp_14285/1, limit_term/1, otp_14983/1, otp_15103/1, otp_15076/1, otp_15159/1, otp_15639/1, otp_15705/1, otp_15847/1, otp_15875/1, @@ -60,7 +60,7 @@ all() -> manpage, otp_6708, otp_7084, otp_7421, io_lib_collect_line_3_wb, cr_whitespace_in_string, io_fread_newlines, otp_8989, io_lib_fread_literal, - printable_range, bad_printable_range, + printable_range, bad_printable_range, format_neg_zero, io_lib_print_binary_depth_one, otp_10302, otp_10755, otp_10836, io_lib_width_too_small, io_with_huge_message_queue, format_string, maps, coverage, otp_14178_unicode_atoms, otp_14175, @@ -88,6 +88,14 @@ error_1(Config) when is_list(Config) -> {'EXIT', _} = (catch io:format(F1, "~p", ["hej"])), ok. +format_neg_zero(Config) when is_list(Config) -> + <<NegZero/float>> = <<16#8000000000000000:64>>, + "-0.000000" = io_lib:format("~f", [NegZero]), + "-0.00000e+0" = io_lib:format("~g", [NegZero]), + "-0.00000e+0" = io_lib:format("~e", [NegZero]), + "-0.0" = io_lib_format:fwrite_g(NegZero), + ok. + float_g(Config) when is_list(Config) -> ["5.00000e-2", "0.500000", @@ -1094,13 +1102,20 @@ g_t(V) when is_float(V) -> %% Note: in a few cases the least significant digit has been %% incremented by one, namely when the correctly rounded string %% converts to another floating point number. -g_t(0.0, "0.0") -> - ok; -g_t(V, Sv) -> +g_t(V, Sv) when V > 0.0; V < 0.0 -> try g_t_1(V, Sv) catch throw:Reason -> throw({Reason, V, Sv}) + end; +g_t(Zero, Format) -> + case <<Zero/float>> of + <<1:1,_:63>> -> + "-0.0" = Format, + ok; + <<0:1,_:63>> -> + "0.0" = Format, + ok end. g_t_1(V, Sv) -> -- 2.26.2
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor