Skip to content

Commit

Permalink
feat: (universal/local)_time_to_system_time/1,2
Browse files Browse the repository at this point in the history
  • Loading branch information
MarkoMin committed Feb 17, 2025
1 parent 29e2d7e commit eadf47e
Show file tree
Hide file tree
Showing 3 changed files with 110 additions and 9 deletions.
49 changes: 47 additions & 2 deletions lib/stdlib/src/calendar.erl
Original file line number Diff line number Diff line change
Expand Up @@ -99,7 +99,9 @@ The following apply:
iso_week_number/0,
iso_week_number/1,
last_day_of_the_month/2,
local_time/0,
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,
Expand All @@ -118,6 +120,8 @@ The following apply:
time_to_seconds/1,
universal_time/0,
universal_time_to_local_time/1,
universal_time_to_system_time/1,
universal_time_to_system_time/2,
valid_date/1,
valid_date/3]).

Expand Down Expand Up @@ -395,6 +399,31 @@ last_day_of_the_month1(_, M) when is_integer(M), M > 0, M < 13 ->
local_time() ->
erlang:localtime().

-doc(#{equiv => local_time_to_system_time(LocalTime, [])}).
-doc(#{since => <<"OTP 28.0">>}).
-spec local_time_to_system_time(datetime1970()) -> pos_integer().
local_time_to_system_time(LocalTime) ->
local_time_to_system_time(LocalTime, []).

-doc(#{since => <<"OTP 28.0">>}).
-doc """
Converts local time into system time.
Error will occur if the local time is non existing or ambiguous due to DST,
see [`calendar:local_time_to_universal_time_dst/1`](`local_time_to_universal_time_dst/1`).
""".
-spec local_time_to_system_time(datetime1970(), Options) -> pos_integer() when
Options :: [Option],
Option :: {unit, erlang:time_unit()}.
local_time_to_system_time(LocalTime, Options) ->
case local_time_to_universal_time_dst(LocalTime) of
[UniversalTime] ->
universal_time_to_system_time(UniversalTime, Options);
[] ->
error({non_existing_local_time, LocalTime});
[_, _] ->
error({ambiguous_local_time, LocalTime})
end.


%% local_time_to_universal_time(DateTime)
%%
Expand Down Expand Up @@ -798,7 +827,23 @@ operating system. Returns local time if universal time is unavailable.
-spec universal_time() -> datetime().
universal_time() ->
erlang:universaltime().


-doc(#{equiv => universal_time_to_system_time(LocalTime, [])}).
-doc(#{since => <<"OTP 28.0">>}).
-spec universal_time_to_system_time(datetime()) -> integer().
universal_time_to_system_time(UniversalTime) ->
universal_time_to_system_time(UniversalTime, []).

-doc(#{since => <<"OTP 28.0">>}).
-doc "Converts universal time into system time.".
-spec universal_time_to_system_time(datetime(), Options) -> integer() when
Options :: [Option],
Option :: {unit, erlang:time_unit()}.
universal_time_to_system_time(DateTime, Options) ->
Unit = proplists:get_value(unit, Options, second),
Factor = factor(Unit),
Time = datetime_to_system_time(DateTime),
Time * Factor.

%% universal_time_to_local_time(DateTime)
%%
Expand Down
18 changes: 16 additions & 2 deletions lib/stdlib/test/calendar_prop_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -21,13 +21,17 @@

-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
init_per_group/2, end_per_group/2,
rfc3339_lists_binaries/1]).
rfc3339_lists_binaries/1,
universal_time_system_time_symmetry/1,
local_time_system_time_symmetry/1]).

suite() ->
[{ct_hooks,[ts_install_cth]}].

all() ->
[rfc3339_lists_binaries].
[rfc3339_lists_binaries,
universal_time_system_time_symmetry,
local_time_system_time_symmetry].

groups() ->
[].
Expand All @@ -48,3 +52,13 @@ rfc3339_lists_binaries(Config) when is_list(Config) ->
ct_property_test:quickcheck(
calendar_prop:rfc3339_lists_binaries(),
Config).

universal_time_system_time_symmetry(Config) when is_list(Config) ->
ct_property_test:quickcheck(
calendar_prop:universal_time_system_time_symmetry(),
Config).

local_time_system_time_symmetry(Config) when is_list(Config) ->
ct_property_test:quickcheck(
calendar_prop:local_time_system_time_symmetry(),
Config).
52 changes: 47 additions & 5 deletions lib/stdlib/test/property_test/calendar_prop.erl
Original file line number Diff line number Diff line change
Expand Up @@ -26,15 +26,23 @@
%%% Properties %%%
%%%%%%%%%%%%%%%%%%

between_40_years_ago_and_in_40_years() ->
integer(erlang:system_time(millisecond) - 40*1000*60*60*24*365,
erlang:system_time(millisecond) + 40*1000*60*60*24*365).
between_40_years_ago_and_in_40_years(Unit) ->
integer(erlang:system_time(Unit) - erlang:convert_time_unit(40*60*60*24*365, second, Unit),
erlang:system_time(Unit) + erlang:convert_time_unit(40*60*60*24*365, second, Unit)).

unit() ->
proper_types:oneof([second,
millisecond,
microsecond,
nanosecond,
native]).

rfc3339_lists_binaries() ->
Ms = [{unit, millisecond}],
Unit = millisecond,
Ms = [{unit, Unit}],
?FORALL(
TS,
between_40_years_ago_and_in_40_years(),
between_40_years_ago_and_in_40_years(Unit),
begin
DateTimeString = calendar:system_time_to_rfc3339(TS, Ms),
DateTimeBin = calendar:system_time_to_rfc3339(TS, [{return, binary} | Ms]),
Expand All @@ -44,3 +52,37 @@ rfc3339_lists_binaries() ->
DateTimeBin =:= ListToBinary andalso FromStr =:= FromBin
end
).

universal_time_system_time_symmetry() ->
?FORALL(
{SystemTime0, Unit},
?LET(Unit,
unit(),
{between_40_years_ago_and_in_40_years(Unit), Unit}),
begin
Options = [{unit, Unit}],
UTime = calendar:system_time_to_universal_time(SystemTime0, Unit),
SystemTime = calendar:universal_time_to_system_time(UTime, Options),
loss(SystemTime0, Unit) =:= (SystemTime0 - SystemTime)
end
).

local_time_system_time_symmetry() ->
?FORALL(
{SystemTime0, Unit},
?LET(Unit,
unit(),
{between_40_years_ago_and_in_40_years(Unit), Unit}),
begin
Options = [{unit, Unit}],
UTime = calendar:system_time_to_local_time(SystemTime0, Unit),
SystemTime = calendar:local_time_to_system_time(UTime, Options),
loss(SystemTime0, Unit) =:= (SystemTime0 - SystemTime)
end
).

loss(_SystemTime, second) -> 0;
loss(SystemTime, millisecond) -> SystemTime rem 1_000;
loss(SystemTime, microsecond) -> SystemTime rem 1_000_000;
loss(SystemTime, nanosecond) -> SystemTime rem 1_000_000_000;
loss(SystemTime, native) -> loss(erlang:convert_time_unit(SystemTime, native, nanosecond), nanosecond).

0 comments on commit eadf47e

Please sign in to comment.