Skip to content

Commit

Permalink
Merge pull request #8812 from NelsonVides/rfc3339_as_binaries
Browse files Browse the repository at this point in the history
Introduce binary types to RFC3339 functions

OTP-19250
  • Loading branch information
jhogberg authored Sep 25, 2024
2 parents b965715 + 75182b0 commit fc5a5f2
Show file tree
Hide file tree
Showing 4 changed files with 144 additions and 12 deletions.
59 changes: 47 additions & 12 deletions lib/stdlib/src/calendar.erl
Original file line number Diff line number Diff line change
Expand Up @@ -174,7 +174,7 @@ before using it.
-type datetime1970() :: {{year1970(),month(),day()},time()}.
-type yearweeknum() :: {year(),weeknum()}.

-type rfc3339_string() :: [byte(), ...].
-type rfc3339_string() :: [byte(), ...] | binary().
-doc """
The time unit used by the rfc3339 conversion functions.
Expand Down Expand Up @@ -527,6 +527,9 @@ Valid option:
2> calendar:rfc3339_to_system_time("2018-02-01 15:18:02.088Z",
[{unit, nanosecond}]).
1517498282088000000
3> calendar:rfc3339_to_system_time(<<"2018-02-01 15:18:02.088Z">>,
[{unit, nanosecond}]).
1517498282088000000
```
""".
-doc(#{since => <<"OTP 21.0">>}).
Expand All @@ -535,23 +538,43 @@ Valid option:
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:
rfc3339_to_system_time(Bin, Options) when is_binary(Bin) ->
rfc3339_to_system_time_bin(Bin, Options);
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:
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)).

%% _T is the character separating the date and the time:
rfc3339_to_system_time_list(
[Y1, Y2, Y3, Y4, $-, Mon1, Mon2, $-, D1, D2, _T,
H1, H2, $:, Min1, Min2, $:, S1, S2 | TimeStr] = DateTimeString,
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_1(DateTimeIn, Options, Year, Month, Day, Hour, Min, Sec, TimeStr) ->
Unit = proplists:get_value(unit, Options, second),
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_string_adjustment(Time, second, UtcOffset),
check(DateTimeString, Options, Secs),
check(DateTimeIn, Options, Secs),
ScaledEpoch = erlang:convert_time_unit(Secs, second, Unit),
ScaledEpoch + copy_sign(fraction(Unit, FractionStr), ScaledEpoch).

Expand Down Expand Up @@ -651,6 +674,9 @@ Valid options:
For `native` three fractional digits are included. Notice that trailing zeros
are not removed from the fraction.
- **`{return, Return}`** - The desired encoding type for the output,
whether a string or a binary is desired. Defaults to string.
```erlang
1> calendar:system_time_to_rfc3339(erlang:system_time(second)).
"2018-04-23T14:56:28+02:00"
Expand All @@ -663,6 +689,9 @@ Valid options:
4> calendar:system_time_to_rfc3339(erlang:system_time(millisecond),
[{unit, millisecond}, {time_designator, $\s}, {offset, "Z"}]).
"2018-04-23 12:57:20.482Z"
5> calendar:system_time_to_rfc3339(erlang:system_time(millisecond),
[{unit, millisecond}, {time_designator, $\s}, {offset, "Z"}, {return, binary}]).
<<"2018-04-23 12:57:20.482Z">>
```
[RFC 3339]: https://www.ietf.org/rfc/rfc3339.txt
""".
Expand All @@ -672,7 +701,8 @@ Valid options:
Options :: [Option],
Option :: {'offset', offset()}
| {'time_designator', byte()}
| {'unit', rfc3339_time_unit()},
| {'unit', rfc3339_time_unit()}
| {'return', 'string' | 'binary'},
DateTimeString :: rfc3339_string().

system_time_to_rfc3339(Time, Options) ->
Expand All @@ -682,10 +712,10 @@ system_time_to_rfc3339(Time, Options) ->
native ->
TimeMS = erlang:convert_time_unit(Time, native, millisecond),
OffsetOpt1 =
if is_integer(OffsetOpt0) ->
erlang:convert_time_unit(OffsetOpt0, native,
millisecond);
true ->
case is_integer(OffsetOpt0) of
true ->
erlang:convert_time_unit(OffsetOpt0, native, millisecond);
false ->
OffsetOpt0
end,
system_time_to_rfc3339_do(TimeMS, Options, millisecond, OffsetOpt1);
Expand All @@ -707,7 +737,12 @@ system_time_to_rfc3339_do(Time, Options, Unit, OffsetOption) ->
FractionStr = fraction_str(Factor, AdjustedTime),
L = [pad4(Year), "-", pad2(Month), "-", pad2(Day), [T],
pad2(Hour), ":", pad2(Min), ":", pad2(Sec), FractionStr, Offset],
lists:append(L).
case proplists:get_value(return, Options, string) of
string ->
lists:append(L);
binary ->
iolist_to_binary(L)
end.

%% time_difference(T1, T2) = Tdiff
%%
Expand Down
1 change: 1 addition & 0 deletions lib/stdlib/test/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ MODULES= \
binref \
c_SUITE \
calendar_SUITE \
calendar_prop_SUITE \
dets_SUITE \
dict_SUITE \
dict_test_lib \
Expand Down
50 changes: 50 additions & 0 deletions lib/stdlib/test/calendar_prop_SUITE.erl
Original file line number Diff line number Diff line change
@@ -0,0 +1,50 @@
%%
%% %CopyrightBegin%
%%
%% Copyright Ericsson AB 2024. 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
%%
%% http://www.apache.org/licenses/LICENSE-2.0
%%
%% Unless required by applicable law or agreed to in writing, software
%% distributed under the License is distributed on an "AS IS" BASIS,
%% 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_prop_SUITE).

-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]).

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

all() ->
[rfc3339_lists_binaries].

groups() ->
[].

init_per_suite(Config) ->
ct_property_test:init_per_suite(Config).

end_per_suite(_Config) ->
ok.

init_per_group(_GroupName, Config) ->
Config.

end_per_group(_GroupName, Config) ->
Config.

rfc3339_lists_binaries(Config) when is_list(Config) ->
ct_property_test:quickcheck(
calendar_prop:rfc3339_lists_binaries(),
Config).
46 changes: 46 additions & 0 deletions lib/stdlib/test/property_test/calendar_prop.erl
Original file line number Diff line number Diff line change
@@ -0,0 +1,46 @@
%%
%% %CopyrightBegin%
%%
%% Copyright Ericsson AB 2024. 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
%%
%% http://www.apache.org/licenses/LICENSE-2.0
%%
%% Unless required by applicable law or agreed to in writing, software
%% distributed under the License is distributed on an "AS IS" BASIS,
%% 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_prop).
-compile([export_all, nowarn_export_all]).

-include_lib("common_test/include/ct_property_test.hrl").

%%%%%%%%%%%%%%%%%%
%%% 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).

rfc3339_lists_binaries() ->
Ms = [{unit, millisecond}],
?FORALL(
TS,
between_40_years_ago_and_in_40_years(),
begin
DateTimeString = calendar:system_time_to_rfc3339(TS, Ms),
DateTimeBin = calendar:system_time_to_rfc3339(TS, [{return, binary} | Ms]),
ListToBinary = erlang:list_to_binary(DateTimeString),
FromStr = calendar:rfc3339_to_system_time(DateTimeString, Ms),
FromBin = calendar:rfc3339_to_system_time(DateTimeBin, Ms),
DateTimeBin =:= ListToBinary andalso FromStr =:= FromBin
end
).

0 comments on commit fc5a5f2

Please sign in to comment.