Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
191 changes: 46 additions & 145 deletions lib/stdlib/src/calendar.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2,9 +2,9 @@
%% %CopyrightBegin%
%%
%% SPDX-License-Identifier: Apache-2.0
%%
%%
%% Copyright Ericsson AB 1996-2025. All Rights Reserved.
%%
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
%% You may obtain a copy of the License at
Expand All @@ -16,7 +16,7 @@
%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
%% See the License for the specific language governing permissions and
%% limitations under the License.
%%
%%
%% %CopyrightEnd%
%%
-module(calendar).
Expand Down Expand Up @@ -90,7 +90,7 @@ The following apply:

%% local and universal time, time conversions

-export([date_to_gregorian_days/1,
-export([date_to_gregorian_days/1,
date_to_gregorian_days/3,
datetime_to_gregorian_seconds/1,
day_of_the_week/1,
Expand All @@ -104,9 +104,9 @@ The following apply:
local_time/0,
local_time_to_system_time/1,
local_time_to_system_time/2,
local_time_to_universal_time/1,
local_time_to_universal_time/2,
local_time_to_universal_time_dst/1,
local_time_to_universal_time/1,
local_time_to_universal_time/2,
local_time_to_universal_time_dst/1,
now_to_datetime/1, % = now_to_universal_time/1
now_to_local_time/1,
now_to_universal_time/1,
Expand Down Expand Up @@ -135,10 +135,16 @@ The following apply:
-define(SECONDS_PER_DAY, 86400).
-define(DAYS_PER_YEAR, 365).
-define(DAYS_PER_LEAP_YEAR, 366).
%% -define(DAYS_PER_4YEARS, 1461).
%% -define(DAYS_PER_100YEARS, 36524).
%% -define(DAYS_PER_400YEARS, 146097).
-define(DAYS_FROM_0_TO_1970, 719528).

%% Neri-Schneider algorithm constants.
-define(MARCH_1_YEAR_0, 60). % Gregorian days from Jan 1 year 0 to Mar 1 year 0
-define(DAYS_PER_ERA, 146097). % Days in 400 years
-define(DAYS_PER_4_YEARS, 1460). % 365 * 4 (without leap adjustment)
-define(DAYS_PER_100_YEARS, 36524). % Days in 100 years
-define(YEARS_PER_ERA, 400).
-define(DAYS_PER_5_MONTHS, 153). % Days in Mar-Apr-May-Jun-Jul
-define(MONTHS_PER_CYCLE, 5).
-define(DAYS_FROM_0_TO_10000, 2932897).
-define(SECONDS_FROM_0_TO_1970, (?DAYS_FROM_0_TO_1970*?SECONDS_PER_DAY)).
-define(SECONDS_FROM_0_TO_10000, (?DAYS_FROM_0_TO_10000*?SECONDS_PER_DAY)).
Expand Down Expand Up @@ -225,11 +231,15 @@ The time unit used by the rfc3339 conversion functions.
Day :: day(),
Days :: non_neg_integer().
date_to_gregorian_days(Year, Month, Day) when is_integer(Day), Day > 0 ->
Last = last_day_of_the_month(Year, Month),
if
Day =< Last ->
dy(Year) + dm(Month) + df(Year, Month) + Day - 1
end.
%% Neri-Schneider algorithm.
%% Shift year so March is first month (simplifies leap year handling).
Y = if Month =< 2 -> Year - 1; true -> Year end,
Era = if Y >= 0 -> Y div ?YEARS_PER_ERA; true -> (Y - 399) div ?YEARS_PER_ERA end,
YearOfEra = Y - Era * ?YEARS_PER_ERA,
MonthPrime = if Month > 2 -> Month - 3; true -> Month + 9 end,
DayOfYear = (?DAYS_PER_5_MONTHS * MonthPrime + 2) div ?MONTHS_PER_CYCLE + Day - 1,
DayOfEra = ?DAYS_PER_YEAR * YearOfEra + YearOfEra div 4 - YearOfEra div 100 + DayOfYear,
Era * ?DAYS_PER_ERA + DayOfEra + ?MARCH_1_YEAR_0.

-doc """
Computes the number of gregorian days starting with year 0 and ending at the
Expand Down Expand Up @@ -288,9 +298,20 @@ day_of_the_week({Year, Month, Day}) ->
-spec gregorian_days_to_date(Days) -> date() when
Days :: non_neg_integer().
gregorian_days_to_date(Days) ->
{Year, DayOfYear} = day_to_year(Days),
{Month, DayOfMonth} = year_day_to_date(Year, DayOfYear),
{Year, Month, DayOfMonth}.
%% Neri-Schneider algorithm.
%% Shift to March 1, year 0 epoch.
Z = Days - ?MARCH_1_YEAR_0,
Era = if Z >= 0 -> Z div ?DAYS_PER_ERA; true -> (Z - ?DAYS_PER_ERA + 1) div ?DAYS_PER_ERA end,
DayOfEra = Z - Era * ?DAYS_PER_ERA,
YearOfEra = (DayOfEra - DayOfEra div ?DAYS_PER_4_YEARS + DayOfEra div ?DAYS_PER_100_YEARS
- DayOfEra div (?DAYS_PER_ERA - 1)) div ?DAYS_PER_YEAR,
DayOfYear = DayOfEra - (?DAYS_PER_YEAR * YearOfEra + YearOfEra div 4 - YearOfEra div 100),
MonthPrime = (?MONTHS_PER_CYCLE * DayOfYear + 2) div ?DAYS_PER_5_MONTHS,
Day = DayOfYear - (?DAYS_PER_5_MONTHS * MonthPrime + 2) div ?MONTHS_PER_CYCLE + 1,
Month = if MonthPrime < 10 -> MonthPrime + 3; true -> MonthPrime - 9 end,
Y = YearOfEra + Era * ?YEARS_PER_ERA,
Year = if Month =< 2 -> Y + 1; true -> Y end,
{Year, Month, Day}.


%% gregorian_seconds_to_datetime(Secs)
Expand Down Expand Up @@ -425,7 +446,7 @@ local_time_to_system_time(LocalTime, Options) ->
[_, _] ->
error({ambiguous_local_time, LocalTime})
end.


%% local_time_to_universal_time(DateTime)
%%
Expand Down Expand Up @@ -498,9 +519,9 @@ local_time_to_universal_time_dst(DateTime) ->
%% Convert from erlang:timestamp() to UTC.
%%
%% Args: Now = now(); now() = {MegaSec, Sec, MilliSec}, MegaSec = Sec
%% = MilliSec = integer()
%% = MilliSec = integer()
%% Returns: {date(), time()}, date() = {Y, M, D}, time() = {H, M, S}.
%%
%%
-doc """
Returns Universal Coordinated Time (UTC) converted from the return value from
`erlang:timestamp/0`.
Expand Down Expand Up @@ -624,7 +645,7 @@ Converts a specified number of seconds into days, hours, minutes, and seconds.
seconds_to_daystime(Secs) ->
Days0 = Secs div ?SECONDS_PER_DAY,
Secs0 = Secs rem ?SECONDS_PER_DAY,
if
if
Secs0 < 0 ->
{Days0 - 1, seconds_to_time(Secs0 + ?SECONDS_PER_DAY)};
true ->
Expand Down Expand Up @@ -783,7 +804,7 @@ system_time_to_rfc3339_do(Time, Options, Unit, OffsetOption) ->
%%
%% Returns the difference between two {Date, Time} structures.
%%
%% T1 = T2 = {Date, Time}, Tdiff = {Day, {Hour, Min, Sec}},
%% T1 = T2 = {Date, Time}, Tdiff = {Day, {Hour, Min, Sec}},
%% Date = {Year, Month, Day}, Time = {Hour, Minute, Sec},
%% Year = Month = Day = Hour = Minute = Sec = integer()
%%
Expand All @@ -801,7 +822,7 @@ epoch later than `T1`.
T2 :: datetime(),
Days :: integer(),
Time :: time().
time_difference({{Y1, Mo1, D1}, {H1, Mi1, S1}},
time_difference({{Y1, Mo1, D1}, {H1, Mi1, S1}},
{{Y2, Mo2, D2}, {H2, Mi2, S2}}) ->
Secs = datetime_to_gregorian_seconds({{Y2, Mo2, D2}, {H2, Mi2, S2}}) -
datetime_to_gregorian_seconds({{Y1, Mo1, D1}, {H1, Mi1, S1}}),
Expand All @@ -817,7 +838,7 @@ time_difference({{Y1, Mo1, D1}, {H1, Mi1, S1}},
time_to_seconds({H, M, S}) when is_integer(H), is_integer(M), is_integer(S) ->
H * ?SECONDS_PER_HOUR +
M * ?SECONDS_PER_MINUTE + S.


%% universal_time()
%%
Expand Down Expand Up @@ -886,45 +907,6 @@ valid_date({Y, M, D}) ->
%%
%% LOCAL FUNCTIONS
%%
-type day_of_year() :: 0..365.

%% day_to_year(DayOfEpoch) = {Year, DayOfYear}
%%
%% The idea here is to first set the upper and lower bounds for a year,
%% and then adjust a range by interpolation search. Although complexity
%% of the algorithm is log(log(n)), at most 1 or 2 recursive steps
%% are taken.
%%
-spec day_to_year(non_neg_integer()) -> {year(), day_of_year()}.
day_to_year(DayOfEpoch) when DayOfEpoch >= 0 ->
YMax = DayOfEpoch div ?DAYS_PER_YEAR,
YMin = DayOfEpoch div ?DAYS_PER_LEAP_YEAR,
{Y1, D1} = dty(YMin, YMax, DayOfEpoch, dy(YMin), dy(YMax)),
{Y1, DayOfEpoch - D1}.

-spec dty(year(), year(), non_neg_integer(), non_neg_integer(),
non_neg_integer()) ->
{year(), non_neg_integer()}.
dty(Min, Max, _D1, DMin, _DMax) when Min == Max ->
{Min, DMin};
dty(Min, Max, D1, DMin, DMax) ->
Diff = Max - Min,
Mid = Min + (Diff * (D1 - DMin)) div (DMax - DMin),
MidLength =
case is_leap_year(Mid) of
true -> ?DAYS_PER_LEAP_YEAR;
false -> ?DAYS_PER_YEAR
end,
case dy(Mid) of
D2 when D1 < D2 ->
NewMax = Mid - 1,
dty(Min, NewMax, D1, DMin, dy(NewMax));
D2 when D1 - D2 >= MidLength ->
NewMin = Mid + 1,
dty(NewMin, Max, D1, dy(NewMin), DMax);
D2 ->
{Mid, D2}
end.

%%
%% The Gregorian days of the iso week 01 day 1 for a given year.
Expand All @@ -939,87 +921,6 @@ gregorian_days_of_iso_w01_1(Year) ->
D0101 + 7 - DOW + 1
end.

%% year_day_to_date(Year, DayOfYear) = {Month, DayOfMonth}
%%
%% Note: 1 is the first day of the month.
%%
-spec year_day_to_date(year(), day_of_year()) -> {month(), day()}.
year_day_to_date(Year, DayOfYear) ->
ExtraDay = case is_leap_year(Year) of
true ->
1;
false ->
0
end,
{Month, Day} = year_day_to_date2(ExtraDay, DayOfYear),
{Month, Day + 1}.


%% Note: 0 is the first day of the month
%%
-spec year_day_to_date2(0 | 1, day_of_year()) -> {month(), 0..30}.
year_day_to_date2(_, Day) when Day < 31 ->
{1, Day};
year_day_to_date2(E, Day) when 31 =< Day, Day < 59 + E ->
{2, Day - 31};
year_day_to_date2(E, Day) when 59 + E =< Day, Day < 90 + E ->
{3, Day - (59 + E)};
year_day_to_date2(E, Day) when 90 + E =< Day, Day < 120 + E ->
{4, Day - (90 + E)};
year_day_to_date2(E, Day) when 120 + E =< Day, Day < 151 + E ->
{5, Day - (120 + E)};
year_day_to_date2(E, Day) when 151 + E =< Day, Day < 181 + E ->
{6, Day - (151 + E)};
year_day_to_date2(E, Day) when 181 + E =< Day, Day < 212 + E ->
{7, Day - (181 + E)};
year_day_to_date2(E, Day) when 212 + E =< Day, Day < 243 + E ->
{8, Day - (212 + E)};
year_day_to_date2(E, Day) when 243 + E =< Day, Day < 273 + E ->
{9, Day - (243 + E)};
year_day_to_date2(E, Day) when 273 + E =< Day, Day < 304 + E ->
{10, Day - (273 + E)};
year_day_to_date2(E, Day) when 304 + E =< Day, Day < 334 + E ->
{11, Day - (304 + E)};
year_day_to_date2(E, Day) when 334 + E =< Day ->
{12, Day - (334 + E)}.

%% dy(Year)
%%
%% Days in previous years.
%%
-spec dy(integer()) -> non_neg_integer().
dy(Y) when Y =< 0 ->
0;
dy(Y) ->
X = Y - 1,
(X div 4) - (X div 100) + (X div 400) +
X*?DAYS_PER_YEAR + ?DAYS_PER_LEAP_YEAR.

%% dm(Month)
%%
%% Returns the total number of days in all months
%% preceeding Month, for an ordinary year.
%%
-spec dm(month()) ->
0 | 31 | 59 | 90 | 120 | 151 | 181 | 212 | 243 | 273 | 304 | 334.
dm(1) -> 0; dm(2) -> 31; dm(3) -> 59; dm(4) -> 90;
dm(5) -> 120; dm(6) -> 151; dm(7) -> 181; dm(8) -> 212;
dm(9) -> 243; dm(10) -> 273; dm(11) -> 304; dm(12) -> 334.

%% df(Year, Month)
%%
%% Accounts for an extra day in February if Year is
%% a leap year, and if Month > 2.
%%
-spec df(year(), month()) -> 0 | 1.
df(_, Month) when Month < 3 ->
0;
df(Year, _) ->
case is_leap_year(Year) of
true -> 1;
false -> 0
end.

check(_Arg, _Options, Secs) when Secs >= - ?SECONDS_FROM_0_TO_1970,
Secs < ?SECONDS_FROM_0_TO_10000 ->
ok;
Expand Down
Loading