File 1179-Fix-calendar-rfc3339-fractional-seconds.patch of Package erlang

From bbfd02f666eeb6aa454de5527fd86f30ba923dc3 Mon Sep 17 00:00:00 2001
From: Maria Scott <maria-12648430@hnc-agency.org>
Date: Sun, 19 Jan 2025 10:39:13 +0100
Subject: [PATCH] Fix calendar rfc3339 fractional seconds

---
 lib/stdlib/src/calendar.erl        | 21 +++++++----
 lib/stdlib/test/calendar_SUITE.erl | 60 +++++++++++++++++++++---------
 2 files changed, 57 insertions(+), 24 deletions(-)

diff --git a/lib/stdlib/src/calendar.erl b/lib/stdlib/src/calendar.erl
index 0257e7b656..e40cbac76b 100644
--- a/lib/stdlib/src/calendar.erl
+++ b/lib/stdlib/src/calendar.erl
@@ -576,7 +576,7 @@ rfc3339_to_system_time_1(DateTimeIn, Options, Year, Month, Day, Hour, Min, Sec,
     Secs = Time - offset_string_adjustment(Time, second, UtcOffset),
     check(DateTimeString, Options, Secs),
     ScaledEpoch = erlang:convert_time_unit(Secs, second, Unit),
-    ScaledEpoch + copy_sign(fraction(Unit, FractionStr), ScaledEpoch).
+    ScaledEpoch + fraction(Unit, FractionStr).
 
 
 
@@ -730,7 +730,11 @@ system_time_to_rfc3339_do(Time, Options, Unit, OffsetOption) ->
     Adjustment = erlang:convert_time_unit(AdjustmentSecs, second, Unit),
     AdjustedTime = Time + Adjustment,
     Factor = factor(Unit),
-    Secs = AdjustedTime div Factor,
+    Secs0 = AdjustedTime div Factor,
+    Secs = if
+	       AdjustedTime rem Factor < 0 -> Secs0 - 1;
+	       true -> Secs0
+	   end,
     check(Time, Options, Secs),
     DateTime = system_time_to_datetime(Secs),
     {{Year, Month, Day}, {Hour, Min, Sec}} = DateTime,
@@ -1028,11 +1032,17 @@ local_offset(SystemTime, Unit) ->
     UniversalSecs = datetime_to_gregorian_seconds(UniversalTime),
     LocalSecs - UniversalSecs.
 
+mod(N, D) ->
+    case N rem D of
+	R when R < 0 -> mod(R + D, D);
+	R -> R
+    end.
+
 fraction_str(1, _Time) ->
     "";
 fraction_str(Factor, Time) ->
-    Fraction = Time rem Factor,
-    S = integer_to_list(abs(Fraction)),
+    Fraction = mod(Time, Factor),
+    S = integer_to_list(Fraction),
     [$. | pad(log10(Factor) - length(S), S)].
 
 fraction(second, _) ->
@@ -1042,9 +1052,6 @@ fraction(_, "") ->
 fraction(Unit, FractionStr) ->
     round(factor(Unit) * list_to_float([$0|FractionStr])).
 
-copy_sign(N1, N2) when N2 < 0 -> -N1;
-copy_sign(N1, _N2) -> N1.
-
 factor(second)      -> 1;
 factor(millisecond) -> 1000;
 factor(microsecond) -> 1000000;
diff --git a/lib/stdlib/test/calendar_SUITE.erl b/lib/stdlib/test/calendar_SUITE.erl
index 1dbbf678fd..08240c4982 100644
--- a/lib/stdlib/test/calendar_SUITE.erl
+++ b/lib/stdlib/test/calendar_SUITE.erl
@@ -214,12 +214,12 @@ rfc3339(Config) when is_list(Config) ->
     %% The leap second is not handled:
     "1991-01-01T00:00:00Z" = test_parse("1990-12-31T23:59:60Z"),
 
-    "9999-12-31T23:59:59Z" = do_format_z(253402300799, []),
-    "9999-12-31T23:59:59.999Z" = do_format_z(253402300799*1000+999, Ms),
+    "9999-12-31T23:59:59Z" = roundtrip_fmt_rfc3339_z(253402300799, []),
+    "9999-12-31T23:59:59.999Z" = roundtrip_fmt_rfc3339_z(253402300799*1000+999, Ms),
     "9999-12-31T23:59:59.999999Z" =
-        do_format_z(253402300799*1000000+999999, Mys),
+        roundtrip_fmt_rfc3339_z(253402300799*1000000+999999, Mys),
     "9999-12-31T23:59:59.999999999Z" =
-        do_format_z(253402300799*1000000000+999999999, Ns),
+        roundtrip_fmt_rfc3339_z(253402300799*1000000000+999999999, Ns),
     {'EXIT', _} = (catch do_format_z(253402300799+1, [])),
     {'EXIT', _} = (catch do_parse("9999-12-31T23:59:60Z", [])),
     {'EXIT', _} = (catch do_format_z(253402300799*1000000000+999999999+1, Ns)),
@@ -268,7 +268,7 @@ rfc3339(Config) when is_list(Config) ->
     test_time(erlang:system_time(millisecond), Ms),
     test_time(erlang:system_time(microsecond), Mys++[{offset, "-02:20"}]),
 
-    946720800 = TO = do_parse("2000-01-01 10:00:00Z", []),
+    946720800 = TO = do_parse("2000-01-01T10:00:00Z", []),
     Str = "2000-01-01T10:02:00+00:02",
     Str = do_format(TO, [{offset, 120}]),
     "2000-01-01T10:02:00.000+00:02" =
@@ -316,24 +316,50 @@ rfc3339(Config) when is_list(Config) ->
     -1613833200000000 = do_parse("1918-11-11T11:00:00+02:00", Mys),
     -1613833200000000 = do_parse("1918-11-11T09:00:00Z", Mys),
 
-    "1970-01-01T00:00:00.000000Z" = do_format_z(0, Mys),
-    "1970-01-01T00:00:01Z" = do_format_z(1, S),
-    "1970-01-01T00:00:00.001Z" = do_format_z(1, Ms),
-    "1970-01-01T00:00:00.000001Z" = do_format_z(1, Mys),
-    "1970-01-01T00:00:00.000000001Z" = do_format_z(1, Ns),
-    "1970-01-01T00:00:01.000000Z" = do_format_z(1000000, Mys),
-    "1970-01-01T00:00:00.543210Z" = do_format_z(543210, Mys),
-    "1970-01-01T00:00:00.543Z" = do_format_z(543, Ms),
-    "1970-01-01T00:00:00.543210000Z" = do_format_z(543210000, Ns),
-    "1970-01-01T00:00:06.543210Z" = do_format_z(6543210, Mys),
-    "1979-06-21T12:12:12.000000Z" = do_format_z(298815132000000, Mys),
-    "1918-11-11T13:00:00.000000Z" = do_format_z(-1613818800000000, Mys),
+    "1970-01-01T00:00:00.000000Z" = roundtrip_fmt_rfc3339_z(0, Mys),
+    "1970-01-01T00:00:01Z" = roundtrip_fmt_rfc3339_z(1, S),
+    "1970-01-01T00:00:00.001Z" = roundtrip_fmt_rfc3339_z(1, Ms),
+    "1970-01-01T00:00:00.000001Z" = roundtrip_fmt_rfc3339_z(1, Mys),
+    "1970-01-01T00:00:00.000000001Z" = roundtrip_fmt_rfc3339_z(1, Ns),
+    "1970-01-01T00:00:01.000000Z" = roundtrip_fmt_rfc3339_z(1000000, Mys),
+    "1970-01-01T00:00:00.543210Z" = roundtrip_fmt_rfc3339_z(543210, Mys),
+    "1970-01-01T00:00:00.543Z" = roundtrip_fmt_rfc3339_z(543, Ms),
+    "1970-01-01T00:00:00.543210000Z" = roundtrip_fmt_rfc3339_z(543210000, Ns),
+    "1970-01-01T00:00:06.543210Z" = roundtrip_fmt_rfc3339_z(6543210, Mys),
+    "1979-06-21T12:12:12.000000Z" = roundtrip_fmt_rfc3339_z(298815132000000, Mys),
+    "1918-11-11T13:00:00.000000Z" = roundtrip_fmt_rfc3339_z(-1613818800000000, Mys),
+
+    %% GH-9279
+    "1969-12-31T23:59:58.750Z" = roundtrip_fmt_rfc3339_z(-1250, Ms),
+    "1969-12-31T23:59:59.000Z" = roundtrip_fmt_rfc3339_z(-1000, Ms),
+    "1969-12-31T23:59:59.007Z" = roundtrip_fmt_rfc3339_z(-993, Ms),
+    "1969-12-31T23:59:59.250Z" = roundtrip_fmt_rfc3339_z(-750, Ms),
+    "1969-12-31T23:59:59.500Z" = roundtrip_fmt_rfc3339_z(-500, Ms),
+    "1969-12-31T23:59:59.750Z" = roundtrip_fmt_rfc3339_z(-250, Ms),
+    "1969-12-31T23:59:59.999Z" = roundtrip_fmt_rfc3339_z(-1, Ms),
+    "1970-01-01T00:00:00.000Z" = roundtrip_fmt_rfc3339_z(0, Ms),
+    "1970-01-01T00:00:00.001Z" = roundtrip_fmt_rfc3339_z(1, Ms),
+    "1970-01-01T00:00:00.017Z" = roundtrip_fmt_rfc3339_z(17, Ms),
+    "1970-01-01T00:00:00.250Z" = roundtrip_fmt_rfc3339_z(250, Ms),
+    "1970-01-01T00:00:00.500Z" = roundtrip_fmt_rfc3339_z(500, Ms),
+    "1970-01-01T00:00:00.750Z" = roundtrip_fmt_rfc3339_z(750, Ms),
+    "1970-01-01T00:00:01.000Z" = roundtrip_fmt_rfc3339_z(1000, Ms),
+    "1970-01-01T00:00:01.250Z" = roundtrip_fmt_rfc3339_z(1250, Ms),
+
     ok.
 
 %%
 %% LOCAL FUNCTIONS
 %%
 
+roundtrip_fmt_rfc3339(Time, Opts) ->
+    Str = calendar:system_time_to_rfc3339(Time, Opts),
+    Time = calendar:rfc3339_to_system_time(Str, Opts),
+    Str.
+
+roundtrip_fmt_rfc3339_z(Time, Opts) ->
+    roundtrip_fmt_rfc3339(Time, [{offset, "Z"} | Opts]).
+
 test_parse(String) ->
     test_parse(String, []).
 
-- 
2.43.0

openSUSE Build Service is sponsored by