aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/calendar.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src/calendar.erl')
-rw-r--r--lib/stdlib/src/calendar.erl246
1 files changed, 229 insertions, 17 deletions
diff --git a/lib/stdlib/src/calendar.erl b/lib/stdlib/src/calendar.erl
index 55a0cfc9a1..3a8fe2211b 100644
--- a/lib/stdlib/src/calendar.erl
+++ b/lib/stdlib/src/calendar.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2016. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2019. 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.
@@ -39,8 +39,14 @@
now_to_datetime/1, % = now_to_universal_time/1
now_to_local_time/1,
now_to_universal_time/1,
+ rfc3339_to_system_time/1,
+ rfc3339_to_system_time/2,
seconds_to_daystime/1,
seconds_to_time/1,
+ system_time_to_local_time/2,
+ system_time_to_universal_time/2,
+ system_time_to_rfc3339/1,
+ system_time_to_rfc3339/2,
time_difference/2,
time_to_seconds/1,
universal_time/0,
@@ -55,10 +61,13 @@
-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_PER_4YEARS, 1461).
+%% -define(DAYS_PER_100YEARS, 36524).
+%% -define(DAYS_PER_400YEARS, 146097).
-define(DAYS_FROM_0_TO_1970, 719528).
+-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)).
%%----------------------------------------------------------------------
%% Types
@@ -83,6 +92,13 @@
-type datetime1970() :: {{year1970(),month(),day()},time()}.
-type yearweeknum() :: {year(),weeknum()}.
+-type rfc3339_string() :: [byte(), ...].
+%% By design 'native' is not supported:
+-type rfc3339_time_unit() :: 'microsecond'
+ | 'millisecond'
+ | 'nanosecond'
+ | 'second'.
+
%%----------------------------------------------------------------------
%% All dates are according the the Gregorian calendar. In this module
@@ -309,8 +325,7 @@ local_time_to_universal_time_dst(DateTime) ->
-spec now_to_datetime(Now) -> datetime1970() when
Now :: erlang:timestamp().
now_to_datetime({MSec, Sec, _uSec}) ->
- Sec0 = MSec*1000000 + Sec + ?DAYS_FROM_0_TO_1970*?SECONDS_PER_DAY,
- gregorian_seconds_to_datetime(Sec0).
+ system_time_to_datetime(MSec*1000000 + Sec).
-spec now_to_universal_time(Now) -> datetime1970() when
Now :: erlang:timestamp().
@@ -328,6 +343,37 @@ now_to_local_time({MSec, Sec, _uSec}) ->
erlang:universaltime_to_localtime(
now_to_universal_time({MSec, Sec, _uSec})).
+-spec rfc3339_to_system_time(DateTimeString) -> integer() when
+ DateTimeString :: rfc3339_string().
+
+rfc3339_to_system_time(DateTimeString) ->
+ rfc3339_to_system_time(DateTimeString, []).
+
+-spec rfc3339_to_system_time(DateTimeString, Options) -> integer() when
+ DateTimeString :: rfc3339_string(),
+ Options :: [Option],
+ Option :: {'unit', rfc3339_time_unit()}.
+
+rfc3339_to_system_time(DateTimeString, Options) ->
+ Unit = proplists:get_value(unit, Options, second),
+ %% _T is the character separating the date and the time:
+ [Y1, Y2, Y3, Y4, $-, Mon1, Mon2, $-, D1, D2, _T,
+ H1, H2, $:, Min1, Min2, $:, S1, S2 | TimeStr] = DateTimeString,
+ 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]),
+ DateTime = {{Year, Month, Day}, {Hour, Min, Sec}},
+ IsFractionChar = fun(C) -> C >= $0 andalso C =< $9 orelse C =:= $. end,
+ {FractionStr, UtcOffset} = lists:splitwith(IsFractionChar, TimeStr),
+ Time = datetime_to_system_time(DateTime),
+ Secs = Time - offset_adjustment(Time, second, UtcOffset),
+ check(DateTimeString, Options, Secs),
+ ScaledEpoch = erlang:convert_time_unit(Secs, second, Unit),
+ ScaledEpoch + copy_sign(fraction(Unit, FractionStr), ScaledEpoch).
+
%% seconds_to_daystime(Secs) = {Days, {Hour, Minute, Second}}
@@ -363,6 +409,56 @@ seconds_to_time(Secs) when Secs >= 0, Secs < ?SECONDS_PER_DAY ->
Second = Secs1 rem ?SECONDS_PER_MINUTE,
{Hour, Minute, Second}.
+-spec system_time_to_local_time(Time, TimeUnit) -> datetime() when
+ Time :: integer(),
+ TimeUnit :: erlang:time_unit().
+
+system_time_to_local_time(Time, TimeUnit) ->
+ UniversalDate = system_time_to_universal_time(Time, TimeUnit),
+ erlang:universaltime_to_localtime(UniversalDate).
+
+-spec system_time_to_universal_time(Time, TimeUnit) -> datetime() when
+ Time :: integer(),
+ TimeUnit :: erlang:time_unit().
+
+system_time_to_universal_time(Time, TimeUnit) ->
+ Secs = erlang:convert_time_unit(Time, TimeUnit, second),
+ system_time_to_datetime(Secs).
+
+-spec system_time_to_rfc3339(Time) -> DateTimeString when
+ Time :: integer(),
+ DateTimeString :: rfc3339_string().
+
+system_time_to_rfc3339(Time) ->
+ system_time_to_rfc3339(Time, []).
+
+-type offset() :: [byte()] | (Time :: integer()).
+-spec system_time_to_rfc3339(Time, Options) -> DateTimeString when
+ Time :: integer(), % Since Epoch
+ Options :: [Option],
+ Option :: {'offset', offset()}
+ | {'time_designator', byte()}
+ | {'unit', rfc3339_time_unit()},
+ DateTimeString :: rfc3339_string().
+
+system_time_to_rfc3339(Time, Options) ->
+ Unit = proplists:get_value(unit, Options, second),
+ OffsetOption = proplists:get_value(offset, Options, ""),
+ T = proplists:get_value(time_designator, Options, $T),
+ AdjustmentSecs = offset_adjustment(Time, Unit, OffsetOption),
+ Offset = offset(OffsetOption, AdjustmentSecs),
+ Adjustment = erlang:convert_time_unit(AdjustmentSecs, second, Unit),
+ AdjustedTime = Time + Adjustment,
+ Factor = factor(Unit),
+ Secs = AdjustedTime div Factor,
+ check(Time, Options, Secs),
+ DateTime = system_time_to_datetime(Secs),
+ {{Year, Month, Day}, {Hour, Min, Sec}} = DateTime,
+ FractionStr = fraction_str(Factor, AdjustedTime),
+ L = [pad4(Year), "-", pad2(Month), "-", pad2(Day), [T],
+ pad2(Hour), ":", pad2(Min), ":", pad2(Sec), FractionStr, Offset],
+ lists:append(L).
+
%% time_difference(T1, T2) = Tdiff
%%
%% Returns the difference between two {Date, Time} structures.
@@ -438,24 +534,41 @@ valid_date({Y, M, D}) ->
%% day_to_year(DayOfEpoch) = {Year, DayOfYear}
%%
-%% The idea here is to first guess a year, and then adjust. Although
-%% the implementation is recursive, at most 1 or 2 recursive steps
+%% 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.
-%% If DayOfEpoch is very large, we need far more than 1 or 2 iterations,
-%% since we just subtract a yearful of days at a time until we're there.
%%
-spec day_to_year(non_neg_integer()) -> {year(), day_of_year()}.
day_to_year(DayOfEpoch) when DayOfEpoch >= 0 ->
- Y0 = DayOfEpoch div ?DAYS_PER_YEAR,
- {Y1, D1} = dty(Y0, DayOfEpoch, dy(Y0)),
+ 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(), non_neg_integer(), non_neg_integer()) ->
+-spec dty(year(), year(), non_neg_integer(), non_neg_integer(),
+ non_neg_integer()) ->
{year(), non_neg_integer()}.
-dty(Y, D1, D2) when D1 < D2 ->
- dty(Y-1, D1, dy(Y-1));
-dty(Y, _D1, D2) ->
- {Y, D2}.
+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.
@@ -550,3 +663,102 @@ df(Year, _) ->
true -> 1;
false -> 0
end.
+
+check(_Arg, _Options, Secs) when Secs >= - ?SECONDS_FROM_0_TO_1970,
+ Secs < ?SECONDS_FROM_0_TO_10000 ->
+ ok;
+check(Arg, Options, _Secs) ->
+ erlang:error({badarg, [Arg, Options]}).
+
+datetime_to_system_time(DateTime) ->
+ datetime_to_gregorian_seconds(DateTime) - ?SECONDS_FROM_0_TO_1970.
+
+system_time_to_datetime(Seconds) ->
+ gregorian_seconds_to_datetime(Seconds + ?SECONDS_FROM_0_TO_1970).
+
+offset(OffsetOption, Secs0) when OffsetOption =:= "";
+ is_integer(OffsetOption) ->
+ Sign = case Secs0 < 0 of
+ true -> $-;
+ false -> $+
+ end,
+ Secs = abs(Secs0),
+ Hour = Secs div 3600,
+ Min = (Secs rem 3600) div 60,
+ [Sign | lists:append([pad2(Hour), ":", pad2(Min)])];
+offset(OffsetOption, _Secs) ->
+ OffsetOption.
+
+offset_adjustment(Time, Unit, OffsetString) when is_list(OffsetString) ->
+ offset_string_adjustment(Time, Unit, OffsetString);
+offset_adjustment(_Time, Unit, Offset) when is_integer(Offset) ->
+ erlang:convert_time_unit(Offset, Unit, second).
+
+offset_string_adjustment(Time, Unit, "") ->
+ local_offset(Time, Unit);
+offset_string_adjustment(_Time, _Unit, "Z") ->
+ 0;
+offset_string_adjustment(_Time, _Unit, "z") ->
+ 0;
+offset_string_adjustment(_Time, _Unit, Tz) ->
+ [Sign, H1, H2, $:, M1, M2] = Tz,
+ Hour = list_to_integer([H1, H2]),
+ Min = list_to_integer([M1, M2]),
+ Adjustment = 3600 * Hour + 60 * Min,
+ case Sign of
+ $- -> -Adjustment;
+ $+ -> Adjustment
+ end.
+
+local_offset(SystemTime, Unit) ->
+ %% Not optimized for special cases.
+ UniversalTime = system_time_to_universal_time(SystemTime, Unit),
+ LocalTime = erlang:universaltime_to_localtime(UniversalTime),
+ LocalSecs = datetime_to_gregorian_seconds(LocalTime),
+ UniversalSecs = datetime_to_gregorian_seconds(UniversalTime),
+ LocalSecs - UniversalSecs.
+
+fraction_str(1, _Time) ->
+ "";
+fraction_str(Factor, Time) ->
+ Fraction = Time rem Factor,
+ S = integer_to_list(abs(Fraction)),
+ [$. | pad(log10(Factor) - length(S), S)].
+
+fraction(second, _) ->
+ 0;
+fraction(_, "") ->
+ 0;
+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;
+factor(nanosecond) -> 1000000000.
+
+log10(1000) -> 3;
+log10(1000000) -> 6;
+log10(1000000000) -> 9.
+
+pad(0, S) ->
+ S;
+pad(I, S) ->
+ [$0 | pad(I - 1, S)].
+
+pad2(N) when N < 10 ->
+ [$0 | integer_to_list(N)];
+pad2(N) ->
+ integer_to_list(N).
+
+pad4(N) when N < 10 ->
+ [$0, $0, $0 | integer_to_list(N)];
+pad4(N) when N < 100 ->
+ [$0, $0 | integer_to_list(N)];
+pad4(N) when N < 1000 ->
+ [$0 | integer_to_list(N)];
+pad4(N) ->
+ integer_to_list(N).