1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 1997-2020. All Rights Reserved.
5%%
6%% Licensed under the Apache License, Version 2.0 (the "License");
7%% you may not use this file except in compliance with the License.
8%% You may obtain a copy of the License at
9%%
10%%     http://www.apache.org/licenses/LICENSE-2.0
11%%
12%% Unless required by applicable law or agreed to in writing, software
13%% distributed under the License is distributed on an "AS IS" BASIS,
14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15%% See the License for the specific language governing permissions and
16%% limitations under the License.
17%%
18%% %CopyrightEnd%
19%%
20-module(calendar_SUITE).
21
22-include_lib("common_test/include/ct.hrl").
23
24-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
25	 init_per_group/2,end_per_group/2,
26	 gregorian_days/1,
27	 big_gregorian_days/1,
28	 gregorian_seconds/1,
29	 day_of_the_week/1,
30	 day_of_the_week_calibrate/1,
31	 leap_years/1,
32	 last_day_of_the_month/1,
33	 local_time_to_universal_time_dst/1,
34	 iso_week_number/1,
35         system_time/1, rfc3339/1]).
36
37-define(START_YEAR, 1947).
38-define(END_YEAR, 2012).
39
40-define(BIG_START_YEAR, 20000000).
41-define(BIG_END_YEAR, 20000020).
42
43suite() -> [{ct_hooks,[ts_install_cth]}].
44
45all() ->
46    [gregorian_days, gregorian_seconds, day_of_the_week,
47     day_of_the_week_calibrate, leap_years,
48     last_day_of_the_month, local_time_to_universal_time_dst,
49     iso_week_number, system_time, rfc3339, big_gregorian_days].
50
51groups() ->
52    [].
53
54init_per_suite(Config) ->
55    Config.
56
57end_per_suite(_Config) ->
58    ok.
59
60init_per_group(_GroupName, Config) ->
61    Config.
62
63end_per_group(_GroupName, Config) ->
64    Config.
65
66%% Tests that date_to_gregorian_days and gregorian_days_to_date
67%% are each others inverses from ?START_YEAR-01-01 up to ?END_YEAR-01-01.
68%% At the same time valid_date is tested.
69gregorian_days(Config) when is_list(Config) ->
70    Days = calendar:date_to_gregorian_days({?START_YEAR, 1, 1}),
71    MaxDays = calendar:date_to_gregorian_days({?END_YEAR, 1, 1}),
72    check_gregorian_days(Days, MaxDays).
73
74%% Tests that date_to_gregorian_days and gregorian_days_to_date
75%% are each others inverses from ?BIG_START_YEAR-01-01 up to ?BIG_END_YEAR-01-01.
76%% At the same time valid_date is tested.
77big_gregorian_days(Config) when is_list(Config) ->
78    Days = calendar:date_to_gregorian_days({?BIG_START_YEAR, 1, 1}),
79    MaxDays = calendar:date_to_gregorian_days({?BIG_END_YEAR, 1, 1}),
80    check_gregorian_days(Days, MaxDays).
81
82%% Tests that datetime_to_gregorian_seconds and
83%% gregorian_seconds_to_date are each others inverses for a sampled
84%% number of seconds from ?START_YEAR-01-01 up to ?END_YEAR-01-01: We check
85%% every 2 days + 1 second.
86gregorian_seconds(Config) when is_list(Config) ->
87    Secs = calendar:datetime_to_gregorian_seconds({{?START_YEAR, 1, 1},
88						   {0, 0, 0}}),
89    MaxSecs = calendar:datetime_to_gregorian_seconds({{?END_YEAR, 1, 1},
90						      {0, 0, 0}}),
91    check_gregorian_seconds(Secs, MaxSecs).
92
93%% Tests that day_of_the_week reports correctly the day of the week from
94%% year ?START_YEAR up to ?END_YEAR.
95day_of_the_week(Config) when is_list(Config) ->
96    Days = calendar:date_to_gregorian_days({?START_YEAR, 1, 1}),
97    MaxDays = calendar:date_to_gregorian_days({?END_YEAR, 1, 1}),
98    DayNumber = calendar:day_of_the_week({?START_YEAR, 1, 1}),
99    check_day_of_the_week(Days, MaxDays, DayNumber).
100
101%% Tests that day_of_the_week for 1997-11-11 is Tuesday (2).
102day_of_the_week_calibrate(Config) when is_list(Config) ->
103    2 = calendar:day_of_the_week({1997, 11, 11}).
104
105%% Tests that is_leap_year reports correctly the leap years from
106%% year ?START_YEAR up to ?END_YEAR.
107leap_years(Config) when is_list(Config) ->
108    check_leap_years(?START_YEAR, ?END_YEAR).
109
110%% Tests that last_day_of_the_month reports correctly from
111%% year ?START_YEAR up to ?END_YEAR.
112last_day_of_the_month(Config) when is_list(Config) ->
113    check_last_day_of_the_month({?START_YEAR, 1}, {?END_YEAR, 1}).
114
115%% Tests local_time_to_universal_time_dst for MET.
116local_time_to_universal_time_dst(Config) when is_list(Config) ->
117    case os:type() of
118	{unix,_} ->
119	    case os:cmd("date '+%Z'") of
120		"SAST"++_ ->
121		    {comment, "Spoky time zone with zero-set DST, skipped"};
122		_ ->
123		    local_time_to_universal_time_dst_x(Config)
124	    end;
125	_ ->
126	    local_time_to_universal_time_dst_x(Config)
127    end.
128local_time_to_universal_time_dst_x(Config) when is_list(Config) ->
129    %% Assumes MET (UTC+1 / UTC+2(dst)
130    LtW   = {{2003,01,15},{14,00,00}}, % Winter
131    UtW   = {{2003,01,15},{13,00,00}}, %
132    UtWd  = {{2003,01,15},{12,00,00}}, % dst
133    LtS   = {{2003,07,15},{14,00,00}}, % Summer
134    UtS   = {{2003,07,15},{13,00,00}}, %
135    UtSd  = {{2003,07,15},{12,00,00}}, % dst
136    LtWS  = {{2003,03,30},{02,30,00}}, % Winter->Summer
137    UtWS  = {{2003,03,30},{01,30,00}}, %
138    UtWSd = {{2003,03,30},{00,30,00}}, % dst
139    LtSW  = {{2003,10,26},{02,30,00}}, % Summer->Winter
140    UtSW  = {{2003,10,26},{01,30,00}}, %
141    UtSWd = {{2003,10,26},{00,30,00}}, % dst
142    %%
143    UtW   = calendar:local_time_to_universal_time(LtW, false),
144    UtWd  = calendar:local_time_to_universal_time(LtW, true),
145    UtW   = calendar:local_time_to_universal_time(LtW, undefined),
146    %%
147    UtS   = calendar:local_time_to_universal_time(LtS, false),
148    UtSd  = calendar:local_time_to_universal_time(LtS, true),
149    UtSd  = calendar:local_time_to_universal_time(LtS, undefined),
150    %%
151    case calendar:local_time_to_universal_time(LtWS, false) of
152	UtWS ->
153	    UtWSd = calendar:local_time_to_universal_time(LtWS, true),
154	    []    = calendar:local_time_to_universal_time_dst(LtWS),
155	    %%
156	    UtSW  = calendar:local_time_to_universal_time(LtSW, false),
157	    UtSWd = calendar:local_time_to_universal_time(LtSW, true),
158	    [UtSWd, UtSW] = calendar:local_time_to_universal_time_dst(LtSW),
159	    ok;
160	{{1969,12,31},{23,59,59}} ->
161	    %% It seems that Apple has no intention of fixing this bug in
162	    %% Mac OS 10.3.9, and we have no intention of implementing a
163	    %% workaround.
164	    {comment,"Bug in mktime() in this OS"}
165    end.
166
167%% Test the iso week number calculation for all three possibilities:
168%%  When the date falls on the last week of the previous year,
169%%  when the date falls on a week within the given year and finally,
170%%  when the date falls on the first week of the next year.
171iso_week_number(Config) when is_list(Config) ->
172    check_iso_week_number().
173
174system_time(Config) when is_list(Config) ->
175    EpochDate = {{1970,1,1}, {0,0,0}},
176    Epoch = calendar:datetime_to_gregorian_seconds(EpochDate),
177    Y0 = {{0,1,1},{0,0,0}},
178
179    EpochDate = calendar:system_time_to_universal_time(0, second),
180    0 = calendar:datetime_to_gregorian_seconds(Y0),
181    Y0 = calendar:system_time_to_universal_time(-Epoch, second),
182
183    T = erlang:system_time(second),
184    UDate = calendar:system_time_to_universal_time(T, second),
185    LDate = erlang:universaltime_to_localtime(UDate),
186    LDate = calendar:system_time_to_local_time(T, second),
187
188    ok.
189
190rfc3339(Config) when is_list(Config) ->
191    Ms = [{unit, millisecond}],
192    Mys = [{unit, microsecond}],
193    Ns = [{unit, nanosecond}],
194    S = [{unit, second}],
195    D = [{time_designator, $\s}],
196    Z = [{offset, "Z"}],
197
198    "1985-04-12T23:20:50.520Z" = test_parse("1985-04-12T23:20:50.52Z", Ms),
199    "1985-04-12T23:20:50.520Z" = test_parse("1985-04-12t23:20:50.52z", Ms),
200    "1985-04-12T21:20:50.520Z" =
201        test_parse("1985-04-12T23:20:50.52+02:00", Ms),
202    "1985-04-12T23:20:50Z" = test_parse("1985-04-12T23:20:50.52Z", S),
203    "1985-04-12T23:20:50.520Z" = test_parse("1985-04-12T23:20:50.52Z", Ms),
204    "1985-04-12T23:20:50.520000Z" =
205        test_parse("1985-04-12t23:20:50.52z", Mys),
206    "1985-04-12 21:20:50.520000000Z" =
207        test_parse("1985-04-12 23:20:50.52+02:00", Ns++D),
208    "1985-04-12T23:20:50Z" = test_parse("1985-04-12T23:20:50.52Z"),
209    "1996-12-20T00:39:57Z" = test_parse("1996-12-19T16:39:57-08:00"),
210    "1991-01-01T00:00:00Z" = test_parse("1990-12-31T23:59:60Z"),
211    "1991-01-01T08:00:00Z" = test_parse("1990-12-31T23:59:60-08:00"),
212
213    "1996-12-20T00:39:57Z" = test_parse("1996-12-19T16:39:57-08:00"),
214    %% The leap second is not handled:
215    "1991-01-01T00:00:00Z" = test_parse("1990-12-31T23:59:60Z"),
216
217    "9999-12-31T23:59:59Z" = do_format_z(253402300799, []),
218    "9999-12-31T23:59:59.999Z" = do_format_z(253402300799*1000+999, Ms),
219    "9999-12-31T23:59:59.999999Z" =
220        do_format_z(253402300799*1000000+999999, Mys),
221    "9999-12-31T23:59:59.999999999Z" =
222        do_format_z(253402300799*1000000000+999999999, Ns),
223    {'EXIT', _} = (catch do_format_z(253402300799+1, [])),
224    {'EXIT', _} = (catch do_parse("9999-12-31T23:59:60Z", [])),
225    {'EXIT', _} = (catch do_format_z(253402300799*1000000000+999999999+1, Ns)),
226    {'EXIT', _} = (catch do_parse("2010-04-11T22:35:41", [])), % OTP-16514
227    253402300799 = do_parse("9999-12-31T23:59:59Z", []),
228
229    "0000-01-01T00:00:00Z" = test_parse("0000-01-01T00:00:00.0+00:00"),
230    "9999-12-31T00:00:00Z" = test_parse("9999-12-31T00:00:00.0+00:00"),
231    "1584-03-04T00:00:00Z" = test_parse("1584-03-04T00:00:00.0+00:00"),
232    "1900-01-01T00:00:00Z" = test_parse("1900-01-01T00:00:00.0+00:00"),
233    "2016-01-24T00:00:00Z" = test_parse("2016-01-24T00:00:00.0+00:00"),
234    "1970-01-01T00:00:00Z" = test_parse("1970-01-01T00:00:00Z"),
235    "1970-01-02T00:00:00Z" = test_parse("1970-01-01T23:59:60Z"),
236    "1970-01-02T00:00:00Z" = test_parse("1970-01-01T23:59:60.5Z"),
237    "1970-01-02T00:00:00Z" = test_parse("1970-01-01T23:59:60.55Z"),
238    "1970-01-02T00:00:00.550Z" = test_parse("1970-01-01T23:59:60.55Z", Ms),
239    "1970-01-02T00:00:00.550000Z" =
240        test_parse("1970-01-01T23:59:60.55Z", Mys),
241    "1970-01-02T00:00:00.550000000Z" =
242        test_parse("1970-01-01T23:59:60.55Z", Ns),
243    "1970-01-02T00:00:00.999999Z" =
244        test_parse("1970-01-01T23:59:60.999999Z", Mys),
245    "1970-01-02T00:00:01.000Z" =
246        test_parse("1970-01-01T23:59:60.999999Z", Ms),
247    "1970-01-01T00:00:00Z" = test_parse("1970-01-01T00:00:00+00:00"),
248    "1970-01-01T00:00:00Z" = test_parse("1970-01-01T00:00:00-00:00"),
249    "1969-12-31T00:01:00Z" = test_parse("1970-01-01T00:00:00+23:59"),
250    "1918-11-11T09:00:00.000000Z" =
251        test_parse("1918-11-11T11:00:00+02:00", Mys),
252    "1970-01-01T00:00:00.000001Z" =
253        test_parse("1970-01-01T00:00:00.000001Z", Mys),
254
255    test_time(erlang:system_time(second), []),
256    test_time(erlang:system_time(second), Z),
257    test_time(erlang:system_time(second), Z ++ S),
258    test_time(erlang:system_time(second), [{offset, "+02:20"}]),
259    test_time(erlang:system_time(millisecond), Ms),
260    test_time(erlang:system_time(microsecond), Mys++[{offset, "-02:20"}]),
261
262    946720800 = TO = do_parse("2000-01-01 10:00:00Z", []),
263    Str = "2000-01-01T10:02:00+00:02",
264    Str = do_format(TO, [{offset, 120}]),
265    "2000-01-01T10:02:00.000+00:02" =
266        do_format(TO * 1000, [{offset, 120 * 1000}]++Ms),
267    "2000-01-01T10:02:00.000000+00:02" =
268        do_format(TO * 1000 * 1000, [{offset, 120 * 1000 * 1000}]++Mys),
269    "2000-01-01T10:02:00.000000000+00:02" =
270        do_format(TO * 1000 * 1000 * 1000,
271                  [{offset, 120 * 1000 * 1000 * 1000}]++Ns),
272
273    NStr = "2000-01-01T09:58:00-00:02",
274    NStr = do_format(TO, [{offset, -120}]),
275    "2000-01-01T09:58:00.000-00:02" =
276        do_format(TO * 1000, [{offset, -120 * 1000}]++Ms),
277    "2000-01-01T09:58:00.000000-00:02" =
278        do_format(TO * 1000 * 1000, [{offset, -120 * 1000 * 1000}]++Mys),
279    "2000-01-01T09:58:00.000000000-00:02" =
280        do_format(TO * 1000 * 1000 * 1000,
281                  [{offset, -120 * 1000 * 1000 * 1000}]++Ns),
282
283    543210000 = do_parse("1970-01-01T00:00:00.54321Z", Ns),
284    54321000 = do_parse("1970-01-01T00:00:00.054321Z", Ns),
285    543210 = do_parse("1970-01-01T00:00:00.54321Z", Mys),
286    543 = do_parse("1970-01-01T00:00:00.54321Z", Ms),
287    0 = do_parse("1970-01-01T00:00:00.000001Z", Ms),
288    1 = do_parse("1970-01-01T00:00:00.000001Z", Mys),
289    1000 = do_parse("1970-01-01T00:00:00.000001Z", Ns),
290    0 = do_parse("1970-01-01Q00:00:00.00049Z", Ms),
291    1 = do_parse("1970-01-01Q00:00:00.0005Z", Ms),
292    6543210 = do_parse("1970-01-01T00:00:06.54321Z", Mys),
293    298815132000000 = do_parse("1979-06-21T12:12:12Z", Mys),
294    -1613826000000000 = do_parse("1918-11-11T11:00:00Z", Mys),
295    -1613833200000000 = do_parse("1918-11-11T11:00:00+02:00", Mys),
296    -1613833200000000 = do_parse("1918-11-11T09:00:00Z", Mys),
297
298    "1970-01-01T00:00:00.000000Z" = do_format_z(0, Mys),
299    "1970-01-01T00:00:01Z" = do_format_z(1, S),
300    "1970-01-01T00:00:00.001Z" = do_format_z(1, Ms),
301    "1970-01-01T00:00:00.000001Z" = do_format_z(1, Mys),
302    "1970-01-01T00:00:00.000000001Z" = do_format_z(1, Ns),
303    "1970-01-01T00:00:01.000000Z" = do_format_z(1000000, Mys),
304    "1970-01-01T00:00:00.543210Z" = do_format_z(543210, Mys),
305    "1970-01-01T00:00:00.543Z" = do_format_z(543, Ms),
306    "1970-01-01T00:00:00.543210000Z" = do_format_z(543210000, Ns),
307    "1970-01-01T00:00:06.543210Z" = do_format_z(6543210, Mys),
308    "1979-06-21T12:12:12.000000Z" = do_format_z(298815132000000, Mys),
309    "1918-11-11T13:00:00.000000Z" = do_format_z(-1613818800000000, Mys),
310    ok.
311
312%%
313%% LOCAL FUNCTIONS
314%%
315
316test_parse(String) ->
317    test_parse(String, []).
318
319test_parse(String, Options) ->
320    T = do_parse(String, Options),
321    calendar:system_time_to_rfc3339(T, [{offset, "Z"} | Options]).
322
323do_parse(String, Options) ->
324    calendar:rfc3339_to_system_time(String, Options).
325
326test_time(Time, Options) ->
327    F = calendar:system_time_to_rfc3339(Time, Options),
328    Time = calendar:rfc3339_to_system_time(F, Options).
329
330do_format_z(Time, Options) ->
331    do_format(Time, [{offset, "Z"}|Options]).
332
333do_format(Time, Options) ->
334    calendar:system_time_to_rfc3339(Time, Options).
335
336%% check_gregorian_days
337%%
338check_gregorian_days(Days, MaxDays) when Days < MaxDays ->
339    Date = calendar:gregorian_days_to_date(Days),
340    true = calendar:valid_date(Date),
341    Days = calendar:date_to_gregorian_days(Date),
342    check_gregorian_days(Days + 1, MaxDays);
343check_gregorian_days(_Days, _MaxDays) ->
344    ok.
345
346%% check_gregorian_seconds
347%%
348%% We increment with something prime (172801 = 2 days + 1 second).
349%%
350check_gregorian_seconds(Secs, MaxSecs) when Secs < MaxSecs ->
351    DateTime = calendar:gregorian_seconds_to_datetime(Secs),
352    Secs = calendar:datetime_to_gregorian_seconds(DateTime),
353    check_gregorian_seconds(Secs + 172801, MaxSecs);
354check_gregorian_seconds(_Secs, _MaxSecs) ->
355    ok.
356
357
358%% check_day_of_the_week
359%%
360check_day_of_the_week(Days, MaxDays, DayNumber) when Days < MaxDays ->
361    Date = calendar:gregorian_days_to_date(Days),
362    DayNumber = calendar:day_of_the_week(Date),
363    check_day_of_the_week(Days + 1, MaxDays,
364			  ((DayNumber rem 7) + 1));
365check_day_of_the_week(_Days, _MaxDays, _DayNumber) ->
366    ok.
367
368%% check_leap_years
369%%
370%% SYr must be larger than 1800, and EYr must be less than ?END_YEAR.
371%%
372check_leap_years(SYr, EYr) when SYr < EYr ->
373    Rem = SYr rem 4,
374    case Rem of
375	0 ->
376	    case SYr of
377		1900 ->
378		    false = calendar:is_leap_year(SYr);
379		2000 ->
380		    true = calendar:is_leap_year(SYr);
381		_  ->
382		    true = calendar:is_leap_year(SYr)
383	    end;
384	_ ->
385	    false = calendar:is_leap_year(SYr)
386    end,
387    check_leap_years(SYr + 1, EYr);
388check_leap_years(_SYr, _EYr) ->
389    ok.
390
391check_last_day_of_the_month({SYr, SMon}, {EYr, EMon}) when SYr < EYr ->
392    LastDay = calendar:last_day_of_the_month(SYr, SMon),
393    LastDay = case SMon of
394		  1 -> 31;
395		  2 ->
396		      case calendar:is_leap_year(SYr) of
397			  true -> 29;
398			  false  -> 28
399		      end;
400		  3 -> 31;
401		  4 -> 30;
402		  5 -> 31;
403		  6 -> 30;
404		  7 -> 31;
405		  8 -> 31;
406		  9 -> 30;
407		  10 -> 31;
408		  11 -> 30;
409		  12 -> 31
410	      end,
411    NYr = case SMon of
412	      12 -> SYr + 1;
413	      _ -> SYr
414	  end,
415    check_last_day_of_the_month({NYr, (SMon rem 12) + 1},
416				{EYr, EMon});
417check_last_day_of_the_month(_, _) ->
418    ok.
419
420%% check_iso_week_number
421%%
422check_iso_week_number() ->
423    {2004, 53} = calendar:iso_week_number({2005, 1, 1}),
424    {2007, 1} = calendar:iso_week_number({2007, 1, 1}),
425    {2009, 1} = calendar:iso_week_number({2008, 12, 29}).
426