File 4383-allow_negative_dates.patch of Package erlang

From ea128074537192dc3b7ff7e134eb69df76f7302a Mon Sep 17 00:00:00 2001
From: Daniel Kukula <daniel.kuku@gmail.com>
Date: Thu, 11 Dec 2025 19:36:10 +0100
Subject: [PATCH 3/4] allow_negative_dates

---
 lib/stdlib/src/calendar.erl                   |  72 ++++++--
 lib/stdlib/test/calendar_SUITE.erl            | 164 +++++++++++++++++-
 lib/stdlib/test/calendar_prop_SUITE.erl       |  18 +-
 .../test/property_test/calendar_prop.erl      |  37 +++-
 4 files changed, 264 insertions(+), 27 deletions(-)

diff --git a/lib/stdlib/doc/src/calendar.xml b/lib/stdlib/doc/src/calendar.xml
index db6c5bed1e..589d457f4a 100644
--- a/lib/stdlib/doc/src/calendar.xml
+++ b/lib/stdlib/doc/src/calendar.xml
@@ -54,9 +54,12 @@
       and the Netherlands adopted it in 1698, England followed in 1752,
       and Russia in 1918 (the October revolution of 1917 took place in
       November according to the Gregorian calendar).</p>
-    <p>The Gregorian calendar in this module is extended back to year 0.
+    <p>The Gregorian calendar in this module is extended back to year 0 and also
+      supports negative years (proleptic Gregorian calendar).
       For a given date, the <em>gregorian days</em> is the number of
-      days up to and including the date specified. Similarly,
+      days up to and including the date specified.
+      Negative years use astronomical year numbering where year 0 = 1 BCE,
+      year -1 = 2 BCE, etc. Similarly,
       the <em>gregorian seconds</em> for a specified date and time is
       the number of seconds up to and including the specified date
       and time.</p>
diff --git a/lib/stdlib/src/calendar.erl b/lib/stdlib/src/calendar.erl
index db6c5bed1e..589d457f4a 100644
--- a/lib/stdlib/src/calendar.erl
+++ b/lib/stdlib/src/calendar.erl
@@ -161,7 +163,7 @@ The year using the Gregorian calendar.
 
 -export_type([date/0, time/0, datetime/0, datetime1970/0]).
 
--type year()     :: non_neg_integer().
+-type year()     :: integer().
 -type year1970() :: 1970..10000.	% should probably be 1970..
 -type month()    :: 1..12.
 -type day()      :: 1..31.
@@ -229,7 +231,7 @@ The time unit used by the rfc3339 conversion functions.
       Year :: year(),
       Month :: month(),
       Day :: day(),
-      Days :: non_neg_integer().
+      Days :: integer().
 date_to_gregorian_days(Year, Month, Day) when is_integer(Day), Day > 0 ->
     %% Neri-Schneider algorithm.
     %% Shift year so March is first month (simplifies leap year handling).
@@ -247,7 +249,7 @@ specified date.
 
 -spec date_to_gregorian_days(Date) -> Days when
       Date :: date(),
-      Days :: non_neg_integer().
+      Days :: integer().
 date_to_gregorian_days({Year, Month, Day}) ->
     date_to_gregorian_days(Year, Month, Day).
 
@@ -263,7 +265,7 @@ specified date and time.
 %%
 -spec datetime_to_gregorian_seconds(DateTime) -> Seconds when
       DateTime :: datetime(),
-      Seconds :: non_neg_integer().
+      Seconds :: integer().
 datetime_to_gregorian_seconds({Date, Time}) ->
     ?SECONDS_PER_DAY*date_to_gregorian_days(Date) +
 	time_to_seconds(Time).
@@ -280,7 +282,7 @@ datetime_to_gregorian_seconds({Date, Time}) ->
       Month :: month(),
       Day :: day().
 day_of_the_week(Year, Month, Day) ->
-    (date_to_gregorian_days(Year, Month, Day) + 5) rem 7 + 1.
+    mod(date_to_gregorian_days(Year, Month, Day) + 5, 7) + 1.
 
 -spec day_of_the_week(Date) -> daynum() when
       Date:: date().
@@ -296,7 +298,7 @@ day_of_the_week({Year, Month, Day}) ->
 %% gregorian_days_to_date(Days) = {Year, Month, Day}
 %%
 -spec gregorian_days_to_date(Days) -> date() when
-      Days :: non_neg_integer().
+      Days :: integer().
 gregorian_days_to_date(Days) ->
     %% Neri-Schneider algorithm.
     %% Shift to March 1, year 0 epoch.
@@ -318,10 +320,14 @@ gregorian_days_to_date(Days) ->
 %% gregorian_seconds_to_datetime(Secs)
 %%
 -spec gregorian_seconds_to_datetime(Seconds) -> datetime() when
-      Seconds :: non_neg_integer().
-gregorian_seconds_to_datetime(Secs) when Secs >= 0 ->
-    Days = Secs div ?SECONDS_PER_DAY,
-    Rest = Secs rem ?SECONDS_PER_DAY,
+      Seconds :: integer().
+gregorian_seconds_to_datetime(Secs) ->
+    Days0 = Secs div ?SECONDS_PER_DAY,
+    Rest0 = Secs rem ?SECONDS_PER_DAY,
+    {Days, Rest} = case Rest0 < 0 of
+        true -> {Days0 - 1, Rest0 + ?SECONDS_PER_DAY};
+        false -> {Days0, Rest0}
+    end,
     {gregorian_days_to_date(Days), seconds_to_time(Rest)}.
 
 
@@ -330,11 +336,11 @@ gregorian_seconds_to_datetime(Secs) when Secs >= 0 ->
 %%
 -spec is_leap_year(Year) -> boolean() when
       Year :: year().
-is_leap_year(Y) when is_integer(Y), Y >= 0 ->
+is_leap_year(Y) when is_integer(Y) ->
     is_leap_year1(Y).
 
 -spec is_leap_year1(year()) -> boolean().
-is_leap_year1(Year) when Year rem 4 =:= 0, Year rem 100 > 0 ->
+is_leap_year1(Year) when Year rem 4 =:= 0, Year rem 100 =/= 0 ->
     true;
 is_leap_year1(Year) when Year rem 400 =:= 0 ->
     true;
@@ -397,7 +403,7 @@ iso_week_number({Year, Month, Day}) ->
       Year :: year(),
       Month :: month(),
       LastDay :: ldom().
-last_day_of_the_month(Y, M) when is_integer(Y), Y >= 0 ->
+last_day_of_the_month(Y, M) when is_integer(Y) ->
     last_day_of_the_month1(Y, M).
 
 -spec last_day_of_the_month1(year(),month()) -> ldom().
@@ -596,6 +602,17 @@ rfc3339_to_system_time(List, Options) when is_list(List) ->
     rfc3339_to_system_time_list(List, Options).
 
 %% _T is the character separating the date and the time:
+%% Handle negative years (ISO 8601 extended format: -YYYY-MM-DD)
+rfc3339_to_system_time_bin(
+    <<$-, Year0:4/binary, $-, Month0:2/binary, $-, Day0:2/binary, _T,
+      Hour0:2/binary, $:, Min0:2/binary, $:, Sec0:2/binary, TimeStr/binary>> = DateTimeBin, Options) ->
+    Hour = binary_to_integer(Hour0),
+    Min = binary_to_integer(Min0),
+    Sec = binary_to_integer(Sec0),
+    Year = -binary_to_integer(Year0),
+    Month = binary_to_integer(Month0),
+    Day = binary_to_integer(Day0),
+    rfc3339_to_system_time_1(DateTimeBin, Options, Year, Month, Day, Hour, Min, Sec, binary_to_list(TimeStr));
 rfc3339_to_system_time_bin(
     <<Year0:4/binary, $-, Month0:2/binary, $-, Day0:2/binary, _T,
       Hour0:2/binary, $:, Min0:2/binary, $:, Sec0:2/binary, TimeStr/binary>> = DateTimeBin, Options) ->
@@ -608,6 +625,17 @@ rfc3339_to_system_time_bin(
     rfc3339_to_system_time_1(DateTimeBin, Options, Year, Month, Day, Hour, Min, Sec, binary_to_list(TimeStr)).
 
 %% _T is the character separating the date and the time:
+%% Handle negative years (ISO 8601 extended format: -YYYY-MM-DD)
+rfc3339_to_system_time_list(
+    [$-, Y1, Y2, Y3, Y4, $-, Mon1, Mon2, $-, D1, D2, _T,
+     H1, H2, $:, Min1, Min2, $:, S1, S2 | TimeStr] = DateTimeString, Options) ->
+    Hour = list_to_integer([H1, H2]),
+    Min = list_to_integer([Min1, Min2]),
+    Sec = list_to_integer([S1, S2]),
+    Year = -list_to_integer([Y1, Y2, Y3, Y4]),
+    Month = list_to_integer([Mon1, Mon2]),
+    Day = list_to_integer([D1, D2]),
+    rfc3339_to_system_time_1(DateTimeString, Options, Year, Month, Day, Hour, Min, Sec, TimeStr);
 rfc3339_to_system_time_list(
     [Y1, Y2, Y3, Y4, $-, Mon1, Mon2, $-, D1, D2, _T,
      H1, H2, $:, Min1, Min2, $:, S1, S2 | TimeStr] = DateTimeString, Options) ->
@@ -892,7 +920,7 @@ valid_date(Y, M, D) when is_integer(Y), is_integer(M), is_integer(D) ->
     valid_date1(Y, M, D).
 
 -spec valid_date1(integer(), integer(), integer()) -> boolean().
-valid_date1(Y, M, D) when Y >= 0, M > 0, M < 13, D > 0 ->
+valid_date1(Y, M, D) when is_integer(Y), M > 0, M < 13, D > 0 ->
     D =< last_day_of_the_month(Y, M);
 valid_date1(_, _, _) ->
     false.
@@ -921,7 +949,10 @@ gregorian_days_of_iso_w01_1(Year) ->
 	D0101 + 7 - DOW + 1
     end.
 
-check(_Arg, _Options, Secs) when Secs >= - ?SECONDS_FROM_0_TO_1970,
+%% Restrict RFC3339 to years -9999..9999 (4-digit format)
+-define(SECONDS_FROM_MINUS_9999_TO_1970, 377705116800).
+
+check(_Arg, _Options, Secs) when Secs >= -?SECONDS_FROM_MINUS_9999_TO_1970,
                                  Secs < ?SECONDS_FROM_0_TO_10000 ->
     ok;
 check(Arg, Options, _Secs) ->
@@ -1020,6 +1051,9 @@ pad2(N) when N < 10 ->
 pad2(N) ->
     integer_to_list(N).
 
+pad4(N) when N < 0 ->
+    %% Negative years: format as -YYYY (ISO 8601 extended format)
+    [$- | pad4(-N)];
 pad4(N) when N < 10 ->
     [$0, $0, $0 | integer_to_list(N)];
 pad4(N) when N < 100 ->
diff --git a/lib/stdlib/test/calendar_SUITE.erl b/lib/stdlib/test/calendar_SUITE.erl
index 82f3590283..d0b128fa0c 100644
--- a/lib/stdlib/test/calendar_SUITE.erl
+++ b/lib/stdlib/test/calendar_SUITE.erl
@@ -28,10 +28,14 @@
 	 gregorian_days/1,
 	 big_gregorian_days/1,
 	 gregorian_days_edge_cases/1,
+	 negative_gregorian_days/1,
 	 gregorian_seconds/1,
+	 negative_gregorian_seconds/1,
 	 day_of_the_week/1,
 	 day_of_the_week_calibrate/1,
+	 negative_day_of_the_week/1,
 	 leap_years/1,
+	 negative_leap_years/1,
 	 last_day_of_the_month/1,
 	 local_time_to_universal_time_dst/1,
 	 iso_week_number/1,
@@ -50,7 +54,9 @@ all() ->
      day_of_the_week_calibrate, leap_years,
      last_day_of_the_month, local_time_to_universal_time_dst,
      iso_week_number, system_time, rfc3339, big_gregorian_days,
-     gregorian_days_edge_cases].
+     gregorian_days_edge_cases, negative_gregorian_days,
+     negative_gregorian_seconds, negative_leap_years,
+     negative_day_of_the_week].
 
 groups() ->
     [].
@@ -156,6 +162,150 @@ check_roundtrip_samples() ->
               Days = calendar:date_to_gregorian_days(Date)
       end, lists:seq(0, 4000000, 10000)).
 
+%% Tests negative dates (dates before year 0).
+%% Uses astronomical year numbering: year 0 = 1 BCE, year -1 = 2 BCE, etc.
+negative_gregorian_days(Config) when is_list(Config) ->
+    %% Test day before epoch (Dec 31, year -1)
+    -1 = calendar:date_to_gregorian_days({-1, 12, 31}),
+    {-1, 12, 31} = calendar:gregorian_days_to_date(-1),
+
+    %% Test year -1 boundaries (year -1 is NOT a leap year: -1 rem 4 = -1)
+    %% Year -1 has 365 days: Jan 1 is day -365, Dec 31 is day -1
+    -365 = calendar:date_to_gregorian_days({-1, 1, 1}),
+    {-1, 1, 1} = calendar:gregorian_days_to_date(-365),
+
+    %% Test year -4 (leap year: -4 rem 4 = 0, -4 rem 100 = -4)
+    true = calendar:is_leap_year(-4),
+    -1461 = calendar:date_to_gregorian_days({-4, 1, 1}),
+    {-4, 1, 1} = calendar:gregorian_days_to_date(-1461),
+    -1096 = calendar:date_to_gregorian_days({-4, 12, 31}),  % 366 days in year -4
+    -1402 = calendar:date_to_gregorian_days({-4, 2, 29}),   % Leap day
+    {-4, 2, 29} = calendar:gregorian_days_to_date(-1402),
+
+    %% Test year -100 (NOT a leap year: divisible by 100)
+    false = calendar:is_leap_year(-100),
+    -36466 = calendar:date_to_gregorian_days({-100, 2, 28}),
+    {-100, 2, 28} = calendar:gregorian_days_to_date(-36466),
+    -36465 = calendar:date_to_gregorian_days({-100, 3, 1}),
+    {-100, 3, 1} = calendar:gregorian_days_to_date(-36465),
+
+    %% Test year -400 (IS a leap year: divisible by 400)
+    true = calendar:is_leap_year(-400),
+    -146038 = calendar:date_to_gregorian_days({-400, 2, 29}),
+    {-400, 2, 29} = calendar:gregorian_days_to_date(-146038),
+
+    %% Test roundtrip for negative days
+    check_negative_roundtrip_samples(),
+
+    %% Test valid_date for negative years
+    true = calendar:valid_date({-1, 12, 31}),
+    true = calendar:valid_date({-4, 2, 29}),
+    false = calendar:valid_date({-1, 2, 29}),  % -1 is not a leap year
+    true = calendar:valid_date({-400, 2, 29}),
+    false = calendar:valid_date({-100, 2, 29}),
+
+    %% Test last_day_of_the_month for negative years
+    29 = calendar:last_day_of_the_month(-4, 2),
+    28 = calendar:last_day_of_the_month(-1, 2),
+    29 = calendar:last_day_of_the_month(-400, 2),
+    28 = calendar:last_day_of_the_month(-100, 2),
+
+    ok.
+
+%% Helper: check roundtrip for negative days
+check_negative_roundtrip_samples() ->
+    %% Sample every 10000 days from -1000000 to 0
+    lists:foreach(
+      fun(Days) ->
+              Date = calendar:gregorian_days_to_date(Days),
+              Days = calendar:date_to_gregorian_days(Date)
+      end, lists:seq(-1000000, 0, 10000)).
+
+%% Tests negative gregorian seconds (times before year 0).
+negative_gregorian_seconds(Config) when is_list(Config) ->
+    %% One second before midnight on Jan 1, year 0
+    -1 = calendar:datetime_to_gregorian_seconds({{-1, 12, 31}, {23, 59, 59}}),
+    {{-1, 12, 31}, {23, 59, 59}} = calendar:gregorian_seconds_to_datetime(-1),
+
+    %% Midnight on Dec 31, year -1
+    -86400 = calendar:datetime_to_gregorian_seconds({{-1, 12, 31}, {0, 0, 0}}),
+    {{-1, 12, 31}, {0, 0, 0}} = calendar:gregorian_seconds_to_datetime(-86400),
+
+    %% Start of year -1
+    -31536000 = calendar:datetime_to_gregorian_seconds({{-1, 1, 1}, {0, 0, 0}}),
+    {{-1, 1, 1}, {0, 0, 0}} = calendar:gregorian_seconds_to_datetime(-31536000),
+
+    %% Test a time in the middle of a negative day
+    {{-1, 12, 31}, {12, 30, 45}} = calendar:gregorian_seconds_to_datetime(-41355),
+
+    %% Test roundtrip for various negative seconds
+    lists:foreach(
+      fun(Secs) ->
+              DateTime = calendar:gregorian_seconds_to_datetime(Secs),
+              Secs = calendar:datetime_to_gregorian_seconds(DateTime)
+      end, lists:seq(-100000000, 0, 1234567)),
+
+    ok.
+
+%% Tests leap year detection for negative years.
+negative_leap_years(Config) when is_list(Config) ->
+    %% Year -1 is NOT a leap year (-1 rem 4 = -1)
+    false = calendar:is_leap_year(-1),
+    %% Year -2 is NOT a leap year
+    false = calendar:is_leap_year(-2),
+    %% Year -3 is NOT a leap year
+    false = calendar:is_leap_year(-3),
+    %% Year -4 IS a leap year (-4 rem 4 = 0, -4 rem 100 = -4)
+    true = calendar:is_leap_year(-4),
+    %% Year -8 IS a leap year
+    true = calendar:is_leap_year(-8),
+    %% Year -100 is NOT a leap year (divisible by 100, not by 400)
+    false = calendar:is_leap_year(-100),
+    %% Year -200 is NOT a leap year
+    false = calendar:is_leap_year(-200),
+    %% Year -300 is NOT a leap year
+    false = calendar:is_leap_year(-300),
+    %% Year -400 IS a leap year (divisible by 400)
+    true = calendar:is_leap_year(-400),
+    %% Year -800 IS a leap year
+    true = calendar:is_leap_year(-800),
+    %% Year -500 is NOT a leap year
+    false = calendar:is_leap_year(-500),
+
+    %% Check leap years from -1000 to 0
+    check_negative_leap_years(-1000, 0),
+
+    ok.
+
+%% Helper: verify leap year logic for negative years
+check_negative_leap_years(Year, EndYear) when Year < EndYear ->
+    Expected = (Year rem 4 =:= 0) andalso
+               ((Year rem 100 =/= 0) orelse (Year rem 400 =:= 0)),
+    Expected = calendar:is_leap_year(Year),
+    check_negative_leap_years(Year + 1, EndYear);
+check_negative_leap_years(_, _) ->
+    ok.
+
+%% Tests day_of_the_week for negative dates
+negative_day_of_the_week(Config) when is_list(Config) ->
+    %% Jan 1, year 0 is a Saturday (day 6)
+    6 = calendar:day_of_the_week({0, 1, 1}),
+    %% Dec 31, year -1 should be Friday (day 5)
+    5 = calendar:day_of_the_week({-1, 12, 31}),
+    %% Dec 30, year -1 should be Thursday (day 4)
+    4 = calendar:day_of_the_week({-1, 12, 30}),
+
+    %% Verify 7-day cycle works for negative dates
+    lists:foreach(
+      fun(Days) ->
+              DOW1 = calendar:day_of_the_week(calendar:gregorian_days_to_date(Days)),
+              DOW2 = calendar:day_of_the_week(calendar:gregorian_days_to_date(Days + 7)),
+              true = (DOW1 =:= DOW2),
+              true = (DOW1 >= 1 andalso DOW1 =< 7)
+      end, lists:seq(-100000, 0, 1000)),
+
+    ok.
+
 %% Tests that datetime_to_gregorian_seconds and
 %% gregorian_seconds_to_date are each others inverses for a sampled
 %% number of seconds from ?START_YEAR-01-01 up to ?END_YEAR-01-01: We check
@@ -305,6 +455,7 @@ rfc3339(Config) when is_list(Config) ->
         roundtrip_fmt_rfc3339_z(253402300799*1_000_000+999_999, Mys),
     "9999-12-31T23:59:59.999999999Z" =
         roundtrip_fmt_rfc3339_z(253402300799*1_000_000_000+999_999_999, Ns),
+    %% Year 10000 is out of range (restricted to -9999..9999)
     {'EXIT', _} = (catch do_format_z(253402300799+1, [])),
     {'EXIT', _} = (catch do_parse("9999-12-31T23:59:60Z", [])),
     {'EXIT', _} = (catch do_format_z(253402300799*1_000_000_000+999_999_999+1, Ns)),
@@ -338,6 +489,17 @@ rfc3339(Config) when is_list(Config) ->
     "1970-01-01T00:00:00.000001Z" =
         test_parse("1970-01-01T00:00:00.000001Z", Mys),
 
+    %% Negative years (ISO 8601 extended format)
+    "-0001-01-01T00:00:00Z" = test_parse("-0001-01-01T00:00:00Z"),
+    "-0001-12-31T23:59:59Z" = test_parse("-0001-12-31T23:59:59Z"),
+    "-0004-02-29T12:30:45Z" = test_parse("-0004-02-29T12:30:45Z"),  % leap year
+    "-0100-06-15T00:00:00Z" = test_parse("-0100-06-15T00:00:00Z"),
+    "-0400-02-29T00:00:00Z" = test_parse("-0400-02-29T00:00:00Z"),  % leap year (div 400)
+    %% Binary input for negative years
+    "-0001-01-01T00:00:00Z" = test_parse(<<"-0001-01-01T00:00:00Z">>),
+    "-0004-02-29T12:30:45Z" = test_parse(<<"-0004-02-29T12:30:45Z">>),
+
+
     test_time(erlang:system_time(second), []),
     test_time(erlang:system_time(second), Z),
     test_time(erlang:system_time(second), Z ++ S),
diff --git a/lib/stdlib/test/calendar_prop_SUITE.erl b/lib/stdlib/test/calendar_prop_SUITE.erl
index 0d91134623..efef81a901 100644
--- a/lib/stdlib/test/calendar_prop_SUITE.erl
+++ b/lib/stdlib/test/calendar_prop_SUITE.erl
@@ -29,7 +29,9 @@
          gregorian_days_roundtrip/1,
          gregorian_days_monotonic/1,
          day_of_week_cycle/1,
-         year_length/1]).
+         year_length/1,
+         negative_leap_year/1,
+         gregorian_seconds_roundtrip/1]).
 
 suite() ->
     [{ct_hooks,[ts_install_cth]}].
@@ -41,7 +43,9 @@ all() ->
      gregorian_days_roundtrip,
      gregorian_days_monotonic,
      day_of_week_cycle,
-     year_length].
+     year_length,
+     negative_leap_year,
+     gregorian_seconds_roundtrip].
 
 groups() ->
     [].
@@ -92,3 +96,13 @@ year_length(Config) when is_list(Config) ->
     ct_property_test:quickcheck(
         calendar_prop:year_length(),
         Config).
+
+negative_leap_year(Config) when is_list(Config) ->
+    ct_property_test:quickcheck(
+        calendar_prop:negative_leap_year(),
+        Config).
+
+gregorian_seconds_roundtrip(Config) when is_list(Config) ->
+    ct_property_test:quickcheck(
+        calendar_prop:gregorian_seconds_roundtrip(),
+        Config).
diff --git a/lib/stdlib/test/property_test/calendar_prop.erl b/lib/stdlib/test/property_test/calendar_prop.erl
index e968bea7b5..2a72f6c94d 100644
--- a/lib/stdlib/test/property_test/calendar_prop.erl
+++ b/lib/stdlib/test/property_test/calendar_prop.erl
@@ -90,10 +90,11 @@ rfc3339_lists_binaries() ->
     ).
 
 %% Property: date_to_gregorian_days and gregorian_days_to_date are inverses
+%% Includes negative days (dates before year 0)
 gregorian_days_roundtrip() ->
     ?FORALL(
         Days,
-        integer(0, 4_000_000),  % Covers year 0 to ~10950
+        integer(-1_000_000, 4_000_000),  % Covers year ~-2738 to ~10950
         begin
             Date = calendar:gregorian_days_to_date(Days),
             Days =:= calendar:date_to_gregorian_days(Date)
@@ -115,10 +116,11 @@ gregorian_days_monotonic() ->
     ).
 
 %% Property: day_of_the_week cycles correctly (1-7, Monday-Sunday)
+%% Includes negative days (dates before year 0)
 day_of_week_cycle() ->
     ?FORALL(
         Days,
-        integer(0, 1_000_000),
+        integer(-500_000, 1_000_000),
         begin
             DOW1 = calendar:day_of_the_week(calendar:gregorian_days_to_date(Days)),
             DOW2 = calendar:day_of_the_week(calendar:gregorian_days_to_date(Days + 7)),
@@ -127,10 +129,11 @@ day_of_week_cycle() ->
     ).
 
 %% Property: leap years have 366 days, non-leap years have 365 days
+%% Includes negative years
 year_length() ->
     ?FORALL(
         Year,
-        integer(0, 10000),
+        integer(-2000, 10000),
         begin
             Jan1 = calendar:date_to_gregorian_days(Year, 1, 1),
             Dec31 = calendar:date_to_gregorian_days(Year, 12, 31),
@@ -143,9 +146,9 @@ year_length() ->
         end
     ).
 
-%% Generator for valid dates
+%% Generator for valid dates (including negative years)
 valid_date() ->
-    ?LET(Year, integer(0, 9999),
+    ?LET(Year, integer(-2000, 9999),
          ?LET(Month, integer(1, 12),
               ?LET(Day, integer(1, calendar:last_day_of_the_month(Year, Month)),
                    {Year, Month, Day}))).
@@ -161,3 +164,27 @@ next_day(Year, Month, Day) ->
         true ->
             {Year + 1, 1, 1}
     end.
+
+%% Property: leap year rules work correctly for negative years
+negative_leap_year() ->
+    ?FORALL(
+        Year,
+        integer(-10000, -1),
+        begin
+            IsLeap = calendar:is_leap_year(Year),
+            Expected = (Year rem 4 =:= 0) andalso
+                       ((Year rem 100 =/= 0) orelse (Year rem 400 =:= 0)),
+            IsLeap =:= Expected
+        end
+    ).
+
+%% Property: gregorian_seconds roundtrip works for negative seconds
+gregorian_seconds_roundtrip() ->
+    ?FORALL(
+        Secs,
+        integer(-100_000_000, 100_000_000),
+        begin
+            DateTime = calendar:gregorian_seconds_to_datetime(Secs),
+            Secs =:= calendar:datetime_to_gregorian_seconds(DateTime)
+        end
+    ).
-- 
2.51.0

openSUSE Build Service is sponsored by