1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 1996-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).
21
22%% local and universal time, time conversions
23
24-export([date_to_gregorian_days/1,
25	 date_to_gregorian_days/3,
26	 datetime_to_gregorian_seconds/1,
27	 day_of_the_week/1,
28	 day_of_the_week/3,
29	 gregorian_days_to_date/1,
30	 gregorian_seconds_to_datetime/1,
31	 is_leap_year/1,
32	 iso_week_number/0,
33	 iso_week_number/1,
34	 last_day_of_the_month/2,
35	 local_time/0,
36	 local_time_to_universal_time/1,
37	 local_time_to_universal_time/2,
38	 local_time_to_universal_time_dst/1,
39	 now_to_datetime/1,			% = now_to_universal_time/1
40	 now_to_local_time/1,
41	 now_to_universal_time/1,
42         rfc3339_to_system_time/1,
43         rfc3339_to_system_time/2,
44	 seconds_to_daystime/1,
45	 seconds_to_time/1,
46         system_time_to_local_time/2,
47         system_time_to_universal_time/2,
48         system_time_to_rfc3339/1,
49         system_time_to_rfc3339/2,
50	 time_difference/2,
51	 time_to_seconds/1,
52	 universal_time/0,
53	 universal_time_to_local_time/1,
54	 valid_date/1,
55	 valid_date/3]).
56
57-deprecated([{local_time_to_universal_time,1,
58              "use calendar:local_time_to_universal_time_dst/1 instead"}]).
59
60-define(SECONDS_PER_MINUTE, 60).
61-define(SECONDS_PER_HOUR, 3600).
62-define(SECONDS_PER_DAY, 86400).
63-define(DAYS_PER_YEAR, 365).
64-define(DAYS_PER_LEAP_YEAR, 366).
65%% -define(DAYS_PER_4YEARS, 1461).
66%% -define(DAYS_PER_100YEARS, 36524).
67%% -define(DAYS_PER_400YEARS, 146097).
68-define(DAYS_FROM_0_TO_1970, 719528).
69-define(DAYS_FROM_0_TO_10000, 2932897).
70-define(SECONDS_FROM_0_TO_1970, (?DAYS_FROM_0_TO_1970*?SECONDS_PER_DAY)).
71-define(SECONDS_FROM_0_TO_10000, (?DAYS_FROM_0_TO_10000*?SECONDS_PER_DAY)).
72
73%%----------------------------------------------------------------------
74%% Types
75%%----------------------------------------------------------------------
76
77-export_type([date/0, time/0, datetime/0, datetime1970/0]).
78
79-type year()     :: non_neg_integer().
80-type year1970() :: 1970..10000.	% should probably be 1970..
81-type month()    :: 1..12.
82-type day()      :: 1..31.
83-type hour()     :: 0..23.
84-type minute()   :: 0..59.
85-type second()   :: 0..59.
86-type daynum()   :: 1..7.
87-type ldom()     :: 28 | 29 | 30 | 31. % last day of month
88-type weeknum()  :: 1..53.
89
90-type date()           :: {year(),month(),day()}.
91-type time()           :: {hour(),minute(),second()}.
92-type datetime()       :: {date(),time()}.
93-type datetime1970()   :: {{year1970(),month(),day()},time()}.
94-type yearweeknum()    :: {year(),weeknum()}.
95
96-type rfc3339_string() :: [byte(), ...].
97%% By design 'native' is not supported:
98-type rfc3339_time_unit() :: 'microsecond'
99                           | 'millisecond'
100                           | 'nanosecond'
101                           | 'second'.
102
103%%----------------------------------------------------------------------
104
105%% All dates are according the the Gregorian calendar. In this module
106%% the Gregorian calendar is extended back to year 0 for convenience.
107%%
108%% A year Y is a leap year if and only if either
109%%
110%%        (1)    Y is divisible by 4, but not by 100, or
111%%        (2)    Y is divisible by 400.
112%%
113%% Hence, e.g. 1996 is a leap year, 1900 is not, but 2000 is.
114%%
115
116%%
117%% EXPORTS
118%%
119
120%% date_to_gregorian_days(Year, Month, Day) = Integer
121%% date_to_gregorian_days({Year, Month, Day}) = Integer
122%%
123%% Computes the total number of days starting from year 0,
124%% January 1st.
125%%
126%% df/2 catches the case Year<0
127-spec date_to_gregorian_days(Year, Month, Day) -> Days when
128      Year :: year(),
129      Month :: month(),
130      Day :: day(),
131      Days :: non_neg_integer().
132date_to_gregorian_days(Year, Month, Day) when is_integer(Day), Day > 0 ->
133    Last = last_day_of_the_month(Year, Month),
134    if
135	Day =< Last ->
136	    dy(Year) + dm(Month) + df(Year, Month) + Day - 1
137    end.
138
139-spec date_to_gregorian_days(Date) -> Days when
140      Date :: date(),
141      Days :: non_neg_integer().
142date_to_gregorian_days({Year, Month, Day}) ->
143    date_to_gregorian_days(Year, Month, Day).
144
145
146%% datetime_to_gregorian_seconds(DateTime) = Integer
147%%
148%% Computes the total number of seconds starting from year 0,
149%% January 1st.
150%%
151-spec datetime_to_gregorian_seconds(DateTime) -> Seconds when
152      DateTime :: datetime(),
153      Seconds :: non_neg_integer().
154datetime_to_gregorian_seconds({Date, Time}) ->
155    ?SECONDS_PER_DAY*date_to_gregorian_days(Date) +
156	time_to_seconds(Time).
157
158
159%% day_of_the_week(Year, Month, Day)
160%% day_of_the_week({Year, Month, Day})
161%%
162%% Returns: 1 | .. | 7. Monday = 1, Tuesday = 2, ..., Sunday = 7.
163%%
164-spec day_of_the_week(Year, Month, Day) -> daynum() when
165      Year :: year(),
166      Month :: month(),
167      Day :: day().
168day_of_the_week(Year, Month, Day) ->
169    (date_to_gregorian_days(Year, Month, Day) + 5) rem 7 + 1.
170
171-spec day_of_the_week(Date) -> daynum() when
172      Date:: date().
173day_of_the_week({Year, Month, Day}) ->
174    day_of_the_week(Year, Month, Day).
175
176
177%% gregorian_days_to_date(Days) = {Year, Month, Day}
178%%
179-spec gregorian_days_to_date(Days) -> date() when
180      Days :: non_neg_integer().
181gregorian_days_to_date(Days) ->
182    {Year, DayOfYear} = day_to_year(Days),
183    {Month, DayOfMonth} = year_day_to_date(Year, DayOfYear),
184    {Year, Month, DayOfMonth}.
185
186
187%% gregorian_seconds_to_datetime(Secs)
188%%
189-spec gregorian_seconds_to_datetime(Seconds) -> datetime() when
190      Seconds :: non_neg_integer().
191gregorian_seconds_to_datetime(Secs) when Secs >= 0 ->
192    Days = Secs div ?SECONDS_PER_DAY,
193    Rest = Secs rem ?SECONDS_PER_DAY,
194    {gregorian_days_to_date(Days), seconds_to_time(Rest)}.
195
196
197%% is_leap_year(Year) = true | false
198%%
199-spec is_leap_year(Year) -> boolean() when
200      Year :: year().
201is_leap_year(Y) when is_integer(Y), Y >= 0 ->
202    is_leap_year1(Y).
203
204-spec is_leap_year1(year()) -> boolean().
205is_leap_year1(Year) when Year rem 4 =:= 0, Year rem 100 > 0 ->
206    true;
207is_leap_year1(Year) when Year rem 400 =:= 0 ->
208    true;
209is_leap_year1(_) -> false.
210
211
212%%
213%% Calculates the iso week number for the current date.
214%%
215-spec iso_week_number() -> yearweeknum().
216iso_week_number() ->
217    {Date, _} = local_time(),
218    iso_week_number(Date).
219
220
221%%
222%% Calculates the iso week number for the given date.
223%%
224-spec iso_week_number(Date) -> yearweeknum() when
225      Date :: date().
226iso_week_number({Year, Month, Day}) ->
227    D = date_to_gregorian_days({Year, Month, Day}),
228    W01_1_Year = gregorian_days_of_iso_w01_1(Year),
229    W01_1_NextYear = gregorian_days_of_iso_w01_1(Year + 1),
230    if W01_1_Year =< D andalso D < W01_1_NextYear ->
231	    % Current Year Week 01..52(,53)
232	    {Year, (D - W01_1_Year) div 7 + 1};
233	D < W01_1_Year ->
234	    % Previous Year 52 or 53
235	    PWN = case day_of_the_week(Year - 1, 1, 1) of
236		4 -> 53;
237		_ -> case day_of_the_week(Year - 1, 12, 31) of
238			4 -> 53;
239			_ -> 52
240		     end
241		end,
242	    {Year - 1, PWN};
243	W01_1_NextYear =< D ->
244	    % Next Year, Week 01
245	    {Year + 1, 1}
246    end.
247
248
249%% last_day_of_the_month(Year, Month)
250%%
251%% Returns the number of days in a month.
252%%
253-spec last_day_of_the_month(Year, Month) -> LastDay when
254      Year :: year(),
255      Month :: month(),
256      LastDay :: ldom().
257last_day_of_the_month(Y, M) when is_integer(Y), Y >= 0 ->
258    last_day_of_the_month1(Y, M).
259
260-spec last_day_of_the_month1(year(),month()) -> ldom().
261last_day_of_the_month1(_, 4) -> 30;
262last_day_of_the_month1(_, 6) -> 30;
263last_day_of_the_month1(_, 9) -> 30;
264last_day_of_the_month1(_,11) -> 30;
265last_day_of_the_month1(Y, 2) ->
266   case is_leap_year(Y) of
267      true -> 29;
268      _    -> 28
269   end;
270last_day_of_the_month1(_, M) when is_integer(M), M > 0, M < 13 ->
271    31.
272
273
274%% local_time()
275%%
276%% Returns: {date(), time()}, date() = {Y, M, D}, time() = {H, M, S}.
277-spec local_time() -> datetime().
278local_time() ->
279    erlang:localtime().
280
281
282%% local_time_to_universal_time(DateTime)
283%%
284-spec local_time_to_universal_time(DateTime1) -> DateTime2 when
285      DateTime1 :: datetime1970(),
286      DateTime2 :: datetime1970().
287local_time_to_universal_time(DateTime) ->
288    erlang:localtime_to_universaltime(DateTime).
289
290-spec local_time_to_universal_time(datetime1970(),
291				   'true' | 'false' | 'undefined') ->
292                                          datetime1970().
293local_time_to_universal_time(DateTime, IsDst) ->
294    erlang:localtime_to_universaltime(DateTime, IsDst).
295
296-spec local_time_to_universal_time_dst(DateTime1) -> [DateTime] when
297      DateTime1 :: datetime1970(),
298      DateTime :: datetime1970().
299local_time_to_universal_time_dst(DateTime) ->
300    %% Reverse check the universal times
301    {UtDst, LtDst} =
302        try
303            UtDst0 = erlang:localtime_to_universaltime(DateTime, true),
304            {UtDst0, erlang:universaltime_to_localtime(UtDst0)}
305        catch error:badarg -> {error, error}
306        end,
307    {Ut, Lt} =
308        try
309            Ut0 = erlang:localtime_to_universaltime(DateTime, false),
310            {Ut0, erlang:universaltime_to_localtime(Ut0)}
311        catch error:badarg -> {error, error}
312        end,
313    %% Return the valid universal times
314    case {LtDst,Lt} of
315	{DateTime,DateTime} when UtDst =/= Ut ->
316	    [UtDst,Ut];
317	{DateTime,_} ->
318	    [UtDst];
319	{_,DateTime} ->
320	    [Ut];
321	{_,_} ->
322	    []
323    end.
324
325%% now_to_universal_time(Now)
326%% now_to_datetime(Now)
327%%
328%% Convert from erlang:timestamp() to UTC.
329%%
330%% Args: Now = now(); now() = {MegaSec, Sec, MilliSec}, MegaSec = Sec
331%% = MilliSec = integer()
332%% Returns: {date(), time()}, date() = {Y, M, D}, time() = {H, M, S}.
333%%
334-spec now_to_datetime(Now) -> datetime1970() when
335      Now :: erlang:timestamp().
336now_to_datetime({MSec, Sec, _uSec}) ->
337    system_time_to_datetime(MSec*1000000 + Sec).
338
339-spec now_to_universal_time(Now) -> datetime1970() when
340      Now :: erlang:timestamp().
341now_to_universal_time(Now) ->
342    now_to_datetime(Now).
343
344
345%% now_to_local_time(Now)
346%%
347%% Args: Now = now()
348%%
349-spec now_to_local_time(Now) -> datetime1970() when
350      Now :: erlang:timestamp().
351now_to_local_time({MSec, Sec, _uSec}) ->
352    erlang:universaltime_to_localtime(
353      now_to_universal_time({MSec, Sec, _uSec})).
354
355-spec rfc3339_to_system_time(DateTimeString) -> integer() when
356      DateTimeString :: rfc3339_string().
357
358rfc3339_to_system_time(DateTimeString) ->
359    rfc3339_to_system_time(DateTimeString, []).
360
361-spec rfc3339_to_system_time(DateTimeString, Options) -> integer() when
362      DateTimeString :: rfc3339_string(),
363      Options :: [Option],
364      Option :: {'unit', rfc3339_time_unit()}.
365
366rfc3339_to_system_time(DateTimeString, Options) ->
367    Unit = proplists:get_value(unit, Options, second),
368    %% _T is the character separating the date and the time:
369    [Y1, Y2, Y3, Y4, $-, Mon1, Mon2, $-, D1, D2, _T,
370     H1, H2, $:, Min1, Min2, $:, S1, S2 | TimeStr] = DateTimeString,
371    Hour = list_to_integer([H1, H2]),
372    Min = list_to_integer([Min1, Min2]),
373    Sec = list_to_integer([S1, S2]),
374    Year = list_to_integer([Y1, Y2, Y3, Y4]),
375    Month = list_to_integer([Mon1, Mon2]),
376    Day = list_to_integer([D1, D2]),
377    DateTime = {{Year, Month, Day}, {Hour, Min, Sec}},
378    IsFractionChar = fun(C) -> C >= $0 andalso C =< $9 orelse C =:= $. end,
379    {FractionStr, UtcOffset} = lists:splitwith(IsFractionChar, TimeStr),
380    Time = datetime_to_system_time(DateTime),
381    Secs = Time - offset_string_adjustment(Time, second, UtcOffset),
382    check(DateTimeString, Options, Secs),
383    ScaledEpoch = erlang:convert_time_unit(Secs, second, Unit),
384    ScaledEpoch + copy_sign(fraction(Unit, FractionStr), ScaledEpoch).
385
386
387
388%% seconds_to_daystime(Secs) = {Days, {Hour, Minute, Second}}
389%%
390-spec seconds_to_daystime(Seconds) -> {Days, Time} when
391      Seconds :: integer(),
392      Days :: integer(),
393      Time :: time().
394seconds_to_daystime(Secs) ->
395    Days0 = Secs div ?SECONDS_PER_DAY,
396    Secs0 = Secs rem ?SECONDS_PER_DAY,
397    if
398	Secs0 < 0 ->
399	    {Days0 - 1, seconds_to_time(Secs0 + ?SECONDS_PER_DAY)};
400	true ->
401	    {Days0, seconds_to_time(Secs0)}
402    end.
403
404
405%%
406%% seconds_to_time(Secs)
407%%
408%% Wraps.
409%%
410-type secs_per_day() :: 0..?SECONDS_PER_DAY.
411-spec seconds_to_time(Seconds) -> time() when
412      Seconds :: secs_per_day().
413seconds_to_time(Secs) when Secs >= 0, Secs < ?SECONDS_PER_DAY ->
414    Secs0 = Secs rem ?SECONDS_PER_DAY,
415    Hour = Secs0 div ?SECONDS_PER_HOUR,
416    Secs1 = Secs0 rem ?SECONDS_PER_HOUR,
417    Minute =  Secs1 div ?SECONDS_PER_MINUTE,
418    Second =  Secs1 rem ?SECONDS_PER_MINUTE,
419    {Hour, Minute, Second}.
420
421-spec system_time_to_local_time(Time, TimeUnit) -> datetime() when
422      Time :: integer(),
423      TimeUnit :: erlang:time_unit().
424
425system_time_to_local_time(Time, TimeUnit) ->
426    UniversalDate = system_time_to_universal_time(Time, TimeUnit),
427    erlang:universaltime_to_localtime(UniversalDate).
428
429-spec system_time_to_universal_time(Time, TimeUnit) -> datetime() when
430      Time :: integer(),
431      TimeUnit :: erlang:time_unit().
432
433system_time_to_universal_time(Time, TimeUnit) ->
434    Secs = erlang:convert_time_unit(Time, TimeUnit, second),
435    system_time_to_datetime(Secs).
436
437-spec system_time_to_rfc3339(Time) -> DateTimeString when
438      Time :: integer(),
439      DateTimeString :: rfc3339_string().
440
441system_time_to_rfc3339(Time) ->
442    system_time_to_rfc3339(Time, []).
443
444-type offset() :: [byte()] | (Time :: integer()).
445-spec system_time_to_rfc3339(Time, Options) -> DateTimeString when
446      Time :: integer(), % Since Epoch
447      Options :: [Option],
448      Option :: {'offset', offset()}
449              | {'time_designator', byte()}
450              | {'unit', rfc3339_time_unit()},
451      DateTimeString :: rfc3339_string().
452
453system_time_to_rfc3339(Time, Options) ->
454    Unit = proplists:get_value(unit, Options, second),
455    OffsetOption = proplists:get_value(offset, Options, ""),
456    T = proplists:get_value(time_designator, Options, $T),
457    AdjustmentSecs = offset_adjustment(Time, Unit, OffsetOption),
458    Offset = offset(OffsetOption, AdjustmentSecs),
459    Adjustment = erlang:convert_time_unit(AdjustmentSecs, second, Unit),
460    AdjustedTime = Time + Adjustment,
461    Factor = factor(Unit),
462    Secs = AdjustedTime div Factor,
463    check(Time, Options, Secs),
464    DateTime = system_time_to_datetime(Secs),
465    {{Year, Month, Day}, {Hour, Min, Sec}} = DateTime,
466    FractionStr = fraction_str(Factor, AdjustedTime),
467    L = [pad4(Year), "-", pad2(Month), "-", pad2(Day), [T],
468         pad2(Hour), ":", pad2(Min), ":", pad2(Sec), FractionStr, Offset],
469    lists:append(L).
470
471%% time_difference(T1, T2) = Tdiff
472%%
473%% Returns the difference between two {Date, Time} structures.
474%%
475%% T1 = T2 = {Date, Time}, Tdiff = {Day, {Hour, Min, Sec}},
476%% Date = {Year, Month, Day}, Time = {Hour, Minute, Sec},
477%% Year = Month = Day = Hour = Minute = Sec = integer()
478%%
479-spec time_difference(T1, T2) -> {Days, Time} when
480      T1 :: datetime(),
481      T2 :: datetime(),
482      Days :: integer(),
483      Time :: time().
484time_difference({{Y1, Mo1, D1}, {H1, Mi1, S1}},
485		{{Y2, Mo2, D2}, {H2, Mi2, S2}}) ->
486    Secs = datetime_to_gregorian_seconds({{Y2, Mo2, D2}, {H2, Mi2, S2}}) -
487	datetime_to_gregorian_seconds({{Y1, Mo1, D1}, {H1, Mi1, S1}}),
488    seconds_to_daystime(Secs).
489
490
491%%
492%% time_to_seconds(Time)
493%%
494-spec time_to_seconds(Time) -> secs_per_day() when
495      Time :: time().
496time_to_seconds({H, M, S}) when is_integer(H), is_integer(M), is_integer(S) ->
497    H * ?SECONDS_PER_HOUR +
498	M * ?SECONDS_PER_MINUTE + S.
499
500
501%% universal_time()
502%%
503%% Returns: {date(), time()}, date() = {Y, M, D}, time() = {H, M, S}.
504-spec universal_time() -> datetime().
505universal_time() ->
506    erlang:universaltime().
507
508
509%% universal_time_to_local_time(DateTime)
510%%
511-spec universal_time_to_local_time(DateTime) -> datetime() when
512      DateTime :: datetime1970().
513universal_time_to_local_time(DateTime) ->
514    erlang:universaltime_to_localtime(DateTime).
515
516
517%% valid_date(Year, Month, Day) = true | false
518%% valid_date({Year, Month, Day}) = true | false
519%%
520-spec valid_date(Year, Month, Day) -> boolean() when
521      Year :: integer(),
522      Month :: integer(),
523      Day :: integer().
524valid_date(Y, M, D) when is_integer(Y), is_integer(M), is_integer(D) ->
525    valid_date1(Y, M, D).
526
527-spec valid_date1(integer(), integer(), integer()) -> boolean().
528valid_date1(Y, M, D) when Y >= 0, M > 0, M < 13, D > 0 ->
529    D =< last_day_of_the_month(Y, M);
530valid_date1(_, _, _) ->
531    false.
532
533-spec valid_date(Date) -> boolean() when
534      Date :: date().
535valid_date({Y, M, D}) ->
536    valid_date(Y, M, D).
537
538
539%%
540%%  LOCAL FUNCTIONS
541%%
542-type day_of_year() :: 0..365.
543
544%% day_to_year(DayOfEpoch) = {Year, DayOfYear}
545%%
546%% The idea here is to first set the upper and lower bounds for a year,
547%% and then adjust a range by interpolation search. Although complexity
548%% of the algorithm is log(log(n)), at most 1 or 2 recursive steps
549%% are taken.
550%%
551-spec day_to_year(non_neg_integer()) -> {year(), day_of_year()}.
552day_to_year(DayOfEpoch) when DayOfEpoch >= 0 ->
553    YMax = DayOfEpoch div ?DAYS_PER_YEAR,
554    YMin = DayOfEpoch div ?DAYS_PER_LEAP_YEAR,
555    {Y1, D1} = dty(YMin, YMax, DayOfEpoch, dy(YMin), dy(YMax)),
556    {Y1, DayOfEpoch - D1}.
557
558-spec dty(year(), year(), non_neg_integer(), non_neg_integer(),
559    non_neg_integer()) ->
560		{year(), non_neg_integer()}.
561dty(Min, Max, _D1, DMin, _DMax) when Min == Max ->
562    {Min, DMin};
563dty(Min, Max, D1, DMin, DMax) ->
564    Diff = Max - Min,
565    Mid = Min + (Diff * (D1 - DMin)) div (DMax - DMin),
566    MidLength =
567        case is_leap_year(Mid) of
568            true -> ?DAYS_PER_LEAP_YEAR;
569            false -> ?DAYS_PER_YEAR
570        end,
571    case dy(Mid) of
572        D2 when D1 < D2 ->
573            NewMax = Mid - 1,
574            dty(Min, NewMax, D1, DMin, dy(NewMax));
575        D2 when D1 - D2 >= MidLength ->
576            NewMin = Mid + 1,
577            dty(NewMin, Max, D1, dy(NewMin), DMax);
578        D2 ->
579            {Mid, D2}
580    end.
581
582%%
583%% The Gregorian days of the iso week 01 day 1 for a given year.
584%%
585-spec gregorian_days_of_iso_w01_1(year()) -> non_neg_integer().
586gregorian_days_of_iso_w01_1(Year) ->
587    D0101 = date_to_gregorian_days(Year, 1, 1),
588    DOW = day_of_the_week(Year, 1, 1),
589    if DOW =< 4 ->
590	D0101 - DOW + 1;
591    true ->
592	D0101 + 7 - DOW + 1
593    end.
594
595%% year_day_to_date(Year, DayOfYear)  = {Month,  DayOfMonth}
596%%
597%% Note: 1 is the first day of the month.
598%%
599-spec year_day_to_date(year(), day_of_year()) -> {month(), day()}.
600year_day_to_date(Year, DayOfYear) ->
601    ExtraDay = case is_leap_year(Year) of
602		   true ->
603		       1;
604		   false ->
605		       0
606	       end,
607    {Month, Day} = year_day_to_date2(ExtraDay, DayOfYear),
608    {Month, Day + 1}.
609
610
611%% Note: 0 is the first day of the month
612%%
613-spec year_day_to_date2(0 | 1, day_of_year()) -> {month(), 0..30}.
614year_day_to_date2(_, Day) when Day < 31 ->
615    {1, Day};
616year_day_to_date2(E, Day) when 31 =< Day, Day < 59 + E ->
617    {2, Day - 31};
618year_day_to_date2(E, Day) when 59 + E =< Day, Day < 90 + E ->
619    {3, Day - (59 + E)};
620year_day_to_date2(E, Day) when 90 + E =< Day, Day < 120 + E ->
621    {4, Day - (90 + E)};
622year_day_to_date2(E, Day) when 120 + E =< Day, Day < 151 + E ->
623    {5, Day - (120 + E)};
624year_day_to_date2(E, Day) when 151 + E =< Day, Day < 181 + E ->
625    {6, Day - (151 + E)};
626year_day_to_date2(E, Day) when 181 + E =< Day, Day < 212 + E ->
627    {7, Day - (181 + E)};
628year_day_to_date2(E, Day) when 212 + E =< Day, Day < 243 + E ->
629    {8, Day - (212 + E)};
630year_day_to_date2(E, Day) when 243 + E =< Day, Day < 273 + E ->
631    {9, Day - (243 + E)};
632year_day_to_date2(E, Day) when 273 + E =< Day, Day < 304 + E ->
633    {10, Day - (273 + E)};
634year_day_to_date2(E, Day) when 304 + E =< Day, Day < 334 + E ->
635    {11, Day - (304 + E)};
636year_day_to_date2(E, Day) when 334 + E =< Day ->
637    {12, Day - (334 + E)}.
638
639%% dy(Year)
640%%
641%% Days in previous years.
642%%
643-spec dy(integer()) -> non_neg_integer().
644dy(Y) when Y =< 0 ->
645    0;
646dy(Y) ->
647    X = Y - 1,
648    (X div 4) - (X div 100) + (X div 400) +
649	X*?DAYS_PER_YEAR + ?DAYS_PER_LEAP_YEAR.
650
651%%  dm(Month)
652%%
653%%  Returns the total number of days in all months
654%%  preceeding Month, for an ordinary year.
655%%
656-spec dm(month()) ->
657	     0 | 31 | 59 | 90 | 120 | 151 | 181 | 212 | 243 | 273 | 304 | 334.
658dm(1) -> 0;    dm(2) ->  31;   dm(3) ->   59;   dm(4) ->  90;
659dm(5) -> 120;  dm(6) ->  151;  dm(7) ->  181;   dm(8) -> 212;
660dm(9) -> 243;  dm(10) -> 273;  dm(11) -> 304;  dm(12) -> 334.
661
662%%  df(Year, Month)
663%%
664%%  Accounts for an extra day in February if Year is
665%%  a leap year, and if Month > 2.
666%%
667-spec df(year(), month()) -> 0 | 1.
668df(_, Month) when Month < 3 ->
669    0;
670df(Year, _) ->
671    case is_leap_year(Year) of
672	true -> 1;
673	false  -> 0
674    end.
675
676check(_Arg, _Options, Secs) when Secs >= - ?SECONDS_FROM_0_TO_1970,
677                                 Secs < ?SECONDS_FROM_0_TO_10000 ->
678    ok;
679check(Arg, Options, _Secs) ->
680    erlang:error({badarg, [Arg, Options]}).
681
682datetime_to_system_time(DateTime) ->
683    datetime_to_gregorian_seconds(DateTime) - ?SECONDS_FROM_0_TO_1970.
684
685system_time_to_datetime(Seconds) ->
686    gregorian_seconds_to_datetime(Seconds + ?SECONDS_FROM_0_TO_1970).
687
688offset(OffsetOption, Secs0) when OffsetOption =:= "";
689                                 is_integer(OffsetOption) ->
690    Sign = case Secs0 < 0 of
691               true -> $-;
692               false -> $+
693           end,
694    Secs = abs(Secs0),
695    Hour = Secs div 3600,
696    Min = (Secs rem 3600) div 60,
697    [Sign | lists:append([pad2(Hour), ":", pad2(Min)])];
698offset(OffsetOption, _Secs) ->
699    OffsetOption.
700
701offset_adjustment(Time, Unit, "") ->
702    local_offset(Time, Unit);
703offset_adjustment(Time, Unit, OffsetString) when is_list(OffsetString) ->
704    offset_string_adjustment(Time, Unit, OffsetString);
705offset_adjustment(_Time, Unit, Offset) when is_integer(Offset) ->
706    erlang:convert_time_unit(Offset, Unit, second).
707
708offset_string_adjustment(_Time, _Unit, "Z") ->
709    0;
710offset_string_adjustment(_Time, _Unit, "z") ->
711    0;
712offset_string_adjustment(_Time, _Unit, Tz) ->
713    [Sign, H1, H2, $:, M1, M2] = Tz,
714    Hour = list_to_integer([H1, H2]),
715    Min = list_to_integer([M1, M2]),
716    Adjustment = 3600 * Hour + 60 * Min,
717    case Sign of
718        $- -> -Adjustment;
719        $+ -> Adjustment
720    end.
721
722local_offset(SystemTime, Unit) ->
723    %% Not optimized for special cases.
724    UniversalTime = system_time_to_universal_time(SystemTime, Unit),
725    LocalTime = erlang:universaltime_to_localtime(UniversalTime),
726    LocalSecs = datetime_to_gregorian_seconds(LocalTime),
727    UniversalSecs = datetime_to_gregorian_seconds(UniversalTime),
728    LocalSecs - UniversalSecs.
729
730fraction_str(1, _Time) ->
731    "";
732fraction_str(Factor, Time) ->
733    Fraction = Time rem Factor,
734    S = integer_to_list(abs(Fraction)),
735    [$. | pad(log10(Factor) - length(S), S)].
736
737fraction(second, _) ->
738    0;
739fraction(_, "") ->
740    0;
741fraction(Unit, FractionStr) ->
742    round(factor(Unit) * list_to_float([$0|FractionStr])).
743
744copy_sign(N1, N2) when N2 < 0 -> -N1;
745copy_sign(N1, _N2) -> N1.
746
747factor(second)      -> 1;
748factor(millisecond) -> 1000;
749factor(microsecond) -> 1000000;
750factor(nanosecond)  -> 1000000000.
751
752log10(1000) -> 3;
753log10(1000000) -> 6;
754log10(1000000000) -> 9.
755
756pad(0, S) ->
757    S;
758pad(I, S) ->
759    [$0 | pad(I - 1, S)].
760
761pad2(N) when N < 10 ->
762    [$0 | integer_to_list(N)];
763pad2(N) ->
764    integer_to_list(N).
765
766pad4(N) when N < 10 ->
767    [$0, $0, $0 | integer_to_list(N)];
768pad4(N) when N < 100 ->
769    [$0, $0 | integer_to_list(N)];
770pad4(N) when N < 1000 ->
771    [$0 | integer_to_list(N)];
772pad4(N) ->
773    integer_to_list(N).
774