1------------------------------------------------------------------------------
2--                                                                          --
3--                         GNAT RUN-TIME COMPONENTS                         --
4--                                                                          --
5--                         A D A . C A L E N D A R                          --
6--                                                                          --
7--                                 B o d y                                  --
8--                                                                          --
9--          Copyright (C) 1992-2013, Free Software Foundation, Inc.         --
10--                                                                          --
11-- GNAT is free software;  you can  redistribute it  and/or modify it under --
12-- terms of the  GNU General Public License as published  by the Free Soft- --
13-- ware  Foundation;  either version 3,  or (at your option) any later ver- --
14-- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
15-- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
16-- or FITNESS FOR A PARTICULAR PURPOSE.                                     --
17--                                                                          --
18-- As a special exception under Section 7 of GPL version 3, you are granted --
19-- additional permissions described in the GCC Runtime Library Exception,   --
20-- version 3.1, as published by the Free Software Foundation.               --
21--                                                                          --
22-- You should have received a copy of the GNU General Public License and    --
23-- a copy of the GCC Runtime Library Exception along with this program;     --
24-- see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see    --
25-- <http://www.gnu.org/licenses/>.                                          --
26--                                                                          --
27-- GNAT was originally developed  by the GNAT team at  New York University. --
28-- Extensive contributions were provided by Ada Core Technologies Inc.      --
29--                                                                          --
30------------------------------------------------------------------------------
31
32with Ada.Unchecked_Conversion;
33
34with Interfaces.C;
35
36with System.OS_Primitives;
37
38package body Ada.Calendar is
39
40   --------------------------
41   -- Implementation Notes --
42   --------------------------
43
44   --  In complex algorithms, some variables of type Ada.Calendar.Time carry
45   --  suffix _S or _N to denote units of seconds or nanoseconds.
46   --
47   --  Because time is measured in different units and from different origins
48   --  on various targets, a system independent model is incorporated into
49   --  Ada.Calendar. The idea behind the design is to encapsulate all target
50   --  dependent machinery in a single package, thus providing a uniform
51   --  interface to all existing and any potential children.
52
53   --     package Ada.Calendar
54   --        procedure Split (5 parameters) -------+
55   --                                              | Call from local routine
56   --     private                                  |
57   --        package Formatting_Operations         |
58   --           procedure Split (11 parameters) <--+
59   --        end Formatting_Operations             |
60   --     end Ada.Calendar                         |
61   --                                              |
62   --     package Ada.Calendar.Formatting          | Call from child routine
63   --        procedure Split (9 or 10 parameters) -+
64   --     end Ada.Calendar.Formatting
65
66   --  The behaviour of the interfacing routines is controlled via various
67   --  flags. All new Ada 2005 types from children of Ada.Calendar are
68   --  emulated by a similar type. For instance, type Day_Number is replaced
69   --  by Integer in various routines. One ramification of this model is that
70   --  the caller site must perform validity checks on returned results.
71   --  The end result of this model is the lack of target specific files per
72   --  child of Ada.Calendar (a-calfor, a-calfor-vms, a-calfor-vxwors, etc).
73
74   -----------------------
75   -- Local Subprograms --
76   -----------------------
77
78   procedure Check_Within_Time_Bounds (T : Time_Rep);
79   --  Ensure that a time representation value falls withing the bounds of Ada
80   --  time. Leap seconds support is taken into account.
81
82   procedure Cumulative_Leap_Seconds
83     (Start_Date    : Time_Rep;
84      End_Date      : Time_Rep;
85      Elapsed_Leaps : out Natural;
86      Next_Leap     : out Time_Rep);
87   --  Elapsed_Leaps is the sum of the leap seconds that have occurred on or
88   --  after Start_Date and before (strictly before) End_Date. Next_Leap_Sec
89   --  represents the next leap second occurrence on or after End_Date. If
90   --  there are no leaps seconds after End_Date, End_Of_Time is returned.
91   --  End_Of_Time can be used as End_Date to count all the leap seconds that
92   --  have occurred on or after Start_Date.
93   --
94   --  Note: Any sub seconds of Start_Date and End_Date are discarded before
95   --  the calculations are done. For instance: if 113 seconds is a leap
96   --  second (it isn't) and 113.5 is input as an End_Date, the leap second
97   --  at 113 will not be counted in Leaps_Between, but it will be returned
98   --  as Next_Leap_Sec. Thus, if the caller wants to know if the End_Date is
99   --  a leap second, the comparison should be:
100   --
101   --     End_Date >= Next_Leap_Sec;
102   --
103   --  After_Last_Leap is designed so that this comparison works without
104   --  having to first check if Next_Leap_Sec is a valid leap second.
105
106   function Duration_To_Time_Rep is
107     new Ada.Unchecked_Conversion (Duration, Time_Rep);
108   --  Convert a duration value into a time representation value
109
110   function Time_Rep_To_Duration is
111     new Ada.Unchecked_Conversion (Time_Rep, Duration);
112   --  Convert a time representation value into a duration value
113
114   function UTC_Time_Offset
115     (Date        : Time;
116      Is_Historic : Boolean) return Long_Integer;
117   --  This routine acts as an Ada wrapper around __gnat_localtime_tzoff which
118   --  in turn utilizes various OS-dependent mechanisms to calculate the time
119   --  zone offset of a date. Formal parameter Date represents an arbitrary
120   --  time stamp, either in the past, now, or in the future. If the flag
121   --  Is_Historic is set, this routine would try to calculate to the best of
122   --  the OS's abilities the time zone offset that was or will be in effect
123   --  on Date. If the flag is set to False, the routine returns the current
124   --  time zone with Date effectively set to Clock.
125   --
126   --  NOTE: Targets which support localtime_r will aways return a historic
127   --  time zone even if flag Is_Historic is set to False because this is how
128   --  localtime_r operates.
129
130   -----------------
131   -- Local Types --
132   -----------------
133
134   --  An integer time duration. The type is used whenever a positive elapsed
135   --  duration is needed, for instance when splitting a time value. Here is
136   --  how Time_Rep and Time_Dur are related:
137
138   --            'First  Ada_Low                  Ada_High  'Last
139   --  Time_Rep: +-------+------------------------+---------+
140   --  Time_Dur:         +------------------------+---------+
141   --                    0                                  'Last
142
143   type Time_Dur is range 0 .. 2 ** 63 - 1;
144
145   --------------------------
146   -- Leap seconds control --
147   --------------------------
148
149   Flag : Integer;
150   pragma Import (C, Flag, "__gl_leap_seconds_support");
151   --  This imported value is used to determine whether the compilation had
152   --  binder flag "-y" present which enables leap seconds. A value of zero
153   --  signifies no leap seconds support while a value of one enables support.
154
155   Leap_Support : constant Boolean := (Flag = 1);
156   --  Flag to controls the usage of leap seconds in all Ada.Calendar routines
157
158   Leap_Seconds_Count : constant Natural := 25;
159
160   ---------------------
161   -- Local Constants --
162   ---------------------
163
164   Ada_Min_Year          : constant Year_Number := Year_Number'First;
165   Secs_In_Four_Years    : constant := (3 * 365 + 366) * Secs_In_Day;
166   Secs_In_Non_Leap_Year : constant := 365 * Secs_In_Day;
167   Nanos_In_Four_Years   : constant := Secs_In_Four_Years * Nano;
168
169   --  Lower and upper bound of Ada time. The zero (0) value of type Time is
170   --  positioned at year 2150. Note that the lower and upper bound account
171   --  for the non-leap centennial years.
172
173   Ada_Low  : constant Time_Rep := -(61 * 366 + 188 * 365) * Nanos_In_Day;
174   Ada_High : constant Time_Rep :=  (60 * 366 + 190 * 365) * Nanos_In_Day;
175
176   --  Even though the upper bound of time is 2399-12-31 23:59:59.999999999
177   --  UTC, it must be increased to include all leap seconds.
178
179   Ada_High_And_Leaps : constant Time_Rep :=
180     Ada_High + Time_Rep (Leap_Seconds_Count) * Nano;
181
182   --  Two constants used in the calculations of elapsed leap seconds.
183   --  End_Of_Time is later than Ada_High in time zone -28. Start_Of_Time
184   --  is earlier than Ada_Low in time zone +28.
185
186   End_Of_Time   : constant Time_Rep :=
187     Ada_High + Time_Rep (3) * Nanos_In_Day;
188   Start_Of_Time : constant Time_Rep :=
189     Ada_Low - Time_Rep (3) * Nanos_In_Day;
190
191   --  The Unix lower time bound expressed as nanoseconds since the start of
192   --  Ada time in UTC.
193
194   Unix_Min : constant Time_Rep :=
195     Ada_Low + Time_Rep (17 * 366 + 52 * 365) * Nanos_In_Day;
196
197   --  The Unix upper time bound expressed as nanoseconds since the start of
198   --  Ada time in UTC.
199
200   Unix_Max : constant Time_Rep :=
201     Ada_Low + Time_Rep (34 * 366 + 102 * 365) * Nanos_In_Day +
202     Time_Rep (Leap_Seconds_Count) * Nano;
203
204   Epoch_Offset : constant Time_Rep := (136 * 365 + 44 * 366) * Nanos_In_Day;
205   --  The difference between 2150-1-1 UTC and 1970-1-1 UTC expressed in
206   --  nanoseconds. Note that year 2100 is non-leap.
207
208   Cumulative_Days_Before_Month :
209     constant array (Month_Number) of Natural :=
210       (0, 31, 59, 90, 120, 151, 181, 212, 243, 273, 304, 334);
211
212   --  The following table contains the hard time values of all existing leap
213   --  seconds. The values are produced by the utility program xleaps.adb. This
214   --  must be updated when additional leap second times are defined.
215
216   Leap_Second_Times : constant array (1 .. Leap_Seconds_Count) of Time_Rep :=
217     (-5601484800000000000,
218      -5585587199000000000,
219      -5554051198000000000,
220      -5522515197000000000,
221      -5490979196000000000,
222      -5459356795000000000,
223      -5427820794000000000,
224      -5396284793000000000,
225      -5364748792000000000,
226      -5317487991000000000,
227      -5285951990000000000,
228      -5254415989000000000,
229      -5191257588000000000,
230      -5112287987000000000,
231      -5049129586000000000,
232      -5017593585000000000,
233      -4970332784000000000,
234      -4938796783000000000,
235      -4907260782000000000,
236      -4859827181000000000,
237      -4812566380000000000,
238      -4765132779000000000,
239      -4544207978000000000,
240      -4449513577000000000,
241      -4339180776000000000);
242
243   ---------
244   -- "+" --
245   ---------
246
247   function "+" (Left : Time; Right : Duration) return Time is
248      pragma Unsuppress (Overflow_Check);
249      Left_N : constant Time_Rep := Time_Rep (Left);
250   begin
251      return Time (Left_N + Duration_To_Time_Rep (Right));
252   exception
253      when Constraint_Error =>
254         raise Time_Error;
255   end "+";
256
257   function "+" (Left : Duration; Right : Time) return Time is
258   begin
259      return Right + Left;
260   end "+";
261
262   ---------
263   -- "-" --
264   ---------
265
266   function "-" (Left : Time; Right : Duration) return Time is
267      pragma Unsuppress (Overflow_Check);
268      Left_N : constant Time_Rep := Time_Rep (Left);
269   begin
270      return Time (Left_N - Duration_To_Time_Rep (Right));
271   exception
272      when Constraint_Error =>
273         raise Time_Error;
274   end "-";
275
276   function "-" (Left : Time; Right : Time) return Duration is
277      pragma Unsuppress (Overflow_Check);
278
279      Dur_Low  : constant Time_Rep := Duration_To_Time_Rep (Duration'First);
280      Dur_High : constant Time_Rep := Duration_To_Time_Rep (Duration'Last);
281      --  The bounds of type Duration expressed as time representations
282
283      Res_N : Time_Rep;
284
285   begin
286      Res_N := Time_Rep (Left) - Time_Rep (Right);
287
288      --  Due to the extended range of Ada time, "-" is capable of producing
289      --  results which may exceed the range of Duration. In order to prevent
290      --  the generation of bogus values by the Unchecked_Conversion, we apply
291      --  the following check.
292
293      if Res_N < Dur_Low or else Res_N > Dur_High then
294         raise Time_Error;
295      end if;
296
297      return Time_Rep_To_Duration (Res_N);
298
299   exception
300      when Constraint_Error =>
301         raise Time_Error;
302   end "-";
303
304   ---------
305   -- "<" --
306   ---------
307
308   function "<" (Left, Right : Time) return Boolean is
309   begin
310      return Time_Rep (Left) < Time_Rep (Right);
311   end "<";
312
313   ----------
314   -- "<=" --
315   ----------
316
317   function "<=" (Left, Right : Time) return Boolean is
318   begin
319      return Time_Rep (Left) <= Time_Rep (Right);
320   end "<=";
321
322   ---------
323   -- ">" --
324   ---------
325
326   function ">" (Left, Right : Time) return Boolean is
327   begin
328      return Time_Rep (Left) > Time_Rep (Right);
329   end ">";
330
331   ----------
332   -- ">=" --
333   ----------
334
335   function ">=" (Left, Right : Time) return Boolean is
336   begin
337      return Time_Rep (Left) >= Time_Rep (Right);
338   end ">=";
339
340   ------------------------------
341   -- Check_Within_Time_Bounds --
342   ------------------------------
343
344   procedure Check_Within_Time_Bounds (T : Time_Rep) is
345   begin
346      if Leap_Support then
347         if T < Ada_Low or else T > Ada_High_And_Leaps then
348            raise Time_Error;
349         end if;
350      else
351         if T < Ada_Low or else T > Ada_High then
352            raise Time_Error;
353         end if;
354      end if;
355   end Check_Within_Time_Bounds;
356
357   -----------
358   -- Clock --
359   -----------
360
361   function Clock return Time is
362      Elapsed_Leaps : Natural;
363      Next_Leap_N   : Time_Rep;
364
365      --  The system clock returns the time in UTC since the Unix Epoch of
366      --  1970-01-01 00:00:00.0. We perform an origin shift to the Ada Epoch
367      --  by adding the number of nanoseconds between the two origins.
368
369      Res_N : Time_Rep :=
370        Duration_To_Time_Rep (System.OS_Primitives.Clock) + Unix_Min;
371
372   begin
373      --  If the target supports leap seconds, determine the number of leap
374      --  seconds elapsed until this moment.
375
376      if Leap_Support then
377         Cumulative_Leap_Seconds
378           (Start_Of_Time, Res_N, Elapsed_Leaps, Next_Leap_N);
379
380         --  The system clock may fall exactly on a leap second
381
382         if Res_N >= Next_Leap_N then
383            Elapsed_Leaps := Elapsed_Leaps + 1;
384         end if;
385
386      --  The target does not support leap seconds
387
388      else
389         Elapsed_Leaps := 0;
390      end if;
391
392      Res_N := Res_N + Time_Rep (Elapsed_Leaps) * Nano;
393
394      return Time (Res_N);
395   end Clock;
396
397   -----------------------------
398   -- Cumulative_Leap_Seconds --
399   -----------------------------
400
401   procedure Cumulative_Leap_Seconds
402     (Start_Date    : Time_Rep;
403      End_Date      : Time_Rep;
404      Elapsed_Leaps : out Natural;
405      Next_Leap     : out Time_Rep)
406   is
407      End_Index   : Positive;
408      End_T       : Time_Rep := End_Date;
409      Start_Index : Positive;
410      Start_T     : Time_Rep := Start_Date;
411
412   begin
413      --  Both input dates must be normalized to UTC
414
415      pragma Assert (Leap_Support and then End_Date >= Start_Date);
416
417      Next_Leap := End_Of_Time;
418
419      --  Make sure that the end date does not exceed the upper bound
420      --  of Ada time.
421
422      if End_Date > Ada_High then
423         End_T := Ada_High;
424      end if;
425
426      --  Remove the sub seconds from both dates
427
428      Start_T := Start_T - (Start_T mod Nano);
429      End_T   := End_T   - (End_T   mod Nano);
430
431      --  Some trivial cases:
432      --                     Leap 1 . . . Leap N
433      --  ---+========+------+############+-------+========+-----
434      --     Start_T  End_T                       Start_T  End_T
435
436      if End_T < Leap_Second_Times (1) then
437         Elapsed_Leaps := 0;
438         Next_Leap     := Leap_Second_Times (1);
439         return;
440
441      elsif Start_T > Leap_Second_Times (Leap_Seconds_Count) then
442         Elapsed_Leaps := 0;
443         Next_Leap     := End_Of_Time;
444         return;
445      end if;
446
447      --  Perform the calculations only if the start date is within the leap
448      --  second occurrences table.
449
450      if Start_T <= Leap_Second_Times (Leap_Seconds_Count) then
451
452         --    1    2                  N - 1   N
453         --  +----+----+--  . . .  --+-------+---+
454         --  | T1 | T2 |             | N - 1 | N |
455         --  +----+----+--  . . .  --+-------+---+
456         --         ^                   ^
457         --         | Start_Index       | End_Index
458         --         +-------------------+
459         --             Leaps_Between
460
461         --  The idea behind the algorithm is to iterate and find two
462         --  closest dates which are after Start_T and End_T. Their
463         --  corresponding index difference denotes the number of leap
464         --  seconds elapsed.
465
466         Start_Index := 1;
467         loop
468            exit when Leap_Second_Times (Start_Index) >= Start_T;
469            Start_Index := Start_Index + 1;
470         end loop;
471
472         End_Index := Start_Index;
473         loop
474            exit when End_Index > Leap_Seconds_Count
475              or else Leap_Second_Times (End_Index) >= End_T;
476            End_Index := End_Index + 1;
477         end loop;
478
479         if End_Index <= Leap_Seconds_Count then
480            Next_Leap := Leap_Second_Times (End_Index);
481         end if;
482
483         Elapsed_Leaps := End_Index - Start_Index;
484
485      else
486         Elapsed_Leaps := 0;
487      end if;
488   end Cumulative_Leap_Seconds;
489
490   ---------
491   -- Day --
492   ---------
493
494   function Day (Date : Time) return Day_Number is
495      D : Day_Number;
496      Y : Year_Number;
497      M : Month_Number;
498      S : Day_Duration;
499      pragma Unreferenced (Y, M, S);
500   begin
501      Split (Date, Y, M, D, S);
502      return D;
503   end Day;
504
505   -------------
506   -- Is_Leap --
507   -------------
508
509   function Is_Leap (Year : Year_Number) return Boolean is
510   begin
511      --  Leap centennial years
512
513      if Year mod 400 = 0 then
514         return True;
515
516      --  Non-leap centennial years
517
518      elsif Year mod 100 = 0 then
519         return False;
520
521      --  Regular years
522
523      else
524         return Year mod 4 = 0;
525      end if;
526   end Is_Leap;
527
528   -----------
529   -- Month --
530   -----------
531
532   function Month (Date : Time) return Month_Number is
533      Y : Year_Number;
534      M : Month_Number;
535      D : Day_Number;
536      S : Day_Duration;
537      pragma Unreferenced (Y, D, S);
538   begin
539      Split (Date, Y, M, D, S);
540      return M;
541   end Month;
542
543   -------------
544   -- Seconds --
545   -------------
546
547   function Seconds (Date : Time) return Day_Duration is
548      Y : Year_Number;
549      M : Month_Number;
550      D : Day_Number;
551      S : Day_Duration;
552      pragma Unreferenced (Y, M, D);
553   begin
554      Split (Date, Y, M, D, S);
555      return S;
556   end Seconds;
557
558   -----------
559   -- Split --
560   -----------
561
562   procedure Split
563     (Date    : Time;
564      Year    : out Year_Number;
565      Month   : out Month_Number;
566      Day     : out Day_Number;
567      Seconds : out Day_Duration)
568   is
569      H  : Integer;
570      M  : Integer;
571      Se : Integer;
572      Ss : Duration;
573      Le : Boolean;
574
575      pragma Unreferenced (H, M, Se, Ss, Le);
576
577   begin
578      --  Even though the input time zone is UTC (0), the flag Use_TZ will
579      --  ensure that Split picks up the local time zone.
580
581      Formatting_Operations.Split
582        (Date        => Date,
583         Year        => Year,
584         Month       => Month,
585         Day         => Day,
586         Day_Secs    => Seconds,
587         Hour        => H,
588         Minute      => M,
589         Second      => Se,
590         Sub_Sec     => Ss,
591         Leap_Sec    => Le,
592         Use_TZ      => False,
593         Is_Historic => True,
594         Time_Zone   => 0);
595
596      --  Validity checks
597
598      if not Year'Valid    or else
599         not Month'Valid   or else
600         not Day'Valid     or else
601         not Seconds'Valid
602      then
603         raise Time_Error;
604      end if;
605   end Split;
606
607   -------------
608   -- Time_Of --
609   -------------
610
611   function Time_Of
612     (Year    : Year_Number;
613      Month   : Month_Number;
614      Day     : Day_Number;
615      Seconds : Day_Duration := 0.0) return Time
616   is
617      --  The values in the following constants are irrelevant, they are just
618      --  placeholders; the choice of constructing a Day_Duration value is
619      --  controlled by the Use_Day_Secs flag.
620
621      H  : constant Integer := 1;
622      M  : constant Integer := 1;
623      Se : constant Integer := 1;
624      Ss : constant Duration := 0.1;
625
626   begin
627      --  Validity checks
628
629      if not Year'Valid    or else
630         not Month'Valid   or else
631         not Day'Valid     or else
632         not Seconds'Valid
633      then
634         raise Time_Error;
635      end if;
636
637      --  Even though the input time zone is UTC (0), the flag Use_TZ will
638      --  ensure that Split picks up the local time zone.
639
640      return
641        Formatting_Operations.Time_Of
642          (Year         => Year,
643           Month        => Month,
644           Day          => Day,
645           Day_Secs     => Seconds,
646           Hour         => H,
647           Minute       => M,
648           Second       => Se,
649           Sub_Sec      => Ss,
650           Leap_Sec     => False,
651           Use_Day_Secs => True,
652           Use_TZ       => False,
653           Is_Historic  => True,
654           Time_Zone    => 0);
655   end Time_Of;
656
657   ---------------------
658   -- UTC_Time_Offset --
659   ---------------------
660
661   function UTC_Time_Offset
662     (Date        : Time;
663      Is_Historic : Boolean) return Long_Integer
664   is
665      --  The following constants denote February 28 during non-leap centennial
666      --  years, the units are nanoseconds.
667
668      T_2100_2_28 : constant Time_Rep := Ada_Low +
669                      (Time_Rep (49 * 366 + 150 * 365 + 59) * Secs_In_Day +
670                       Time_Rep (Leap_Seconds_Count)) * Nano;
671
672      T_2200_2_28 : constant Time_Rep := Ada_Low +
673                      (Time_Rep (73 * 366 + 226 * 365 + 59) * Secs_In_Day +
674                       Time_Rep (Leap_Seconds_Count)) * Nano;
675
676      T_2300_2_28 : constant Time_Rep := Ada_Low +
677                      (Time_Rep (97 * 366 + 302 * 365 + 59) * Secs_In_Day +
678                       Time_Rep (Leap_Seconds_Count)) * Nano;
679
680      --  56 years (14 leap years + 42 non-leap years) in nanoseconds:
681
682      Nanos_In_56_Years : constant := (14 * 366 + 42 * 365) * Nanos_In_Day;
683
684      type int_Pointer  is access all Interfaces.C.int;
685      type long_Pointer is access all Interfaces.C.long;
686
687      type time_t is
688        range -(2 ** (Standard'Address_Size - Integer'(1))) ..
689              +(2 ** (Standard'Address_Size - Integer'(1)) - 1);
690      type time_t_Pointer is access all time_t;
691
692      procedure localtime_tzoff
693        (timer       : time_t_Pointer;
694         is_historic : int_Pointer;
695         off         : long_Pointer);
696      pragma Import (C, localtime_tzoff, "__gnat_localtime_tzoff");
697      --  This routine is a interfacing wrapper around the library function
698      --  __gnat_localtime_tzoff. Parameter 'timer' represents a Unix-based
699      --  time equivalent of the input date. If flag 'is_historic' is set, this
700      --  routine would try to calculate to the best of the OS's abilities the
701      --  time zone offset that was or will be in effect on 'timer'. If the
702      --  flag is set to False, the routine returns the current time zone
703      --  regardless of what 'timer' designates. Parameter 'off' captures the
704      --  UTC offset of 'timer'.
705
706      Adj_Cent : Integer;
707      Date_N   : Time_Rep;
708      Flag     : aliased Interfaces.C.int;
709      Offset   : aliased Interfaces.C.long;
710      Secs_T   : aliased time_t;
711
712   --  Start of processing for UTC_Time_Offset
713
714   begin
715      Date_N := Time_Rep (Date);
716
717      --  Dates which are 56 years apart fall on the same day, day light saving
718      --  and so on. Non-leap centennial years violate this rule by one day and
719      --  as a consequence, special adjustment is needed.
720
721      Adj_Cent :=
722        (if    Date_N <= T_2100_2_28 then 0
723         elsif Date_N <= T_2200_2_28 then 1
724         elsif Date_N <= T_2300_2_28 then 2
725         else                             3);
726
727      if Adj_Cent > 0 then
728         Date_N := Date_N - Time_Rep (Adj_Cent) * Nanos_In_Day;
729      end if;
730
731      --  Shift the date within bounds of Unix time
732
733      while Date_N < Unix_Min loop
734         Date_N := Date_N + Nanos_In_56_Years;
735      end loop;
736
737      while Date_N >= Unix_Max loop
738         Date_N := Date_N - Nanos_In_56_Years;
739      end loop;
740
741      --  Perform a shift in origins from Ada to Unix
742
743      Date_N := Date_N - Unix_Min;
744
745      --  Convert the date into seconds
746
747      Secs_T := time_t (Date_N / Nano);
748
749      --  Determine whether to treat the input date as historical or not. A
750      --  value of "0" signifies that the date is NOT historic.
751
752      Flag := (if Is_Historic then 1 else 0);
753
754      localtime_tzoff
755        (Secs_T'Unchecked_Access,
756         Flag'Unchecked_Access,
757         Offset'Unchecked_Access);
758
759      return Long_Integer (Offset);
760   end UTC_Time_Offset;
761
762   ----------
763   -- Year --
764   ----------
765
766   function Year (Date : Time) return Year_Number is
767      Y : Year_Number;
768      M : Month_Number;
769      D : Day_Number;
770      S : Day_Duration;
771      pragma Unreferenced (M, D, S);
772   begin
773      Split (Date, Y, M, D, S);
774      return Y;
775   end Year;
776
777   --  The following packages assume that Time is a signed 64 bit integer
778   --  type, the units are nanoseconds and the origin is the start of Ada
779   --  time (1901-01-01 00:00:00.0 UTC).
780
781   ---------------------------
782   -- Arithmetic_Operations --
783   ---------------------------
784
785   package body Arithmetic_Operations is
786
787      ---------
788      -- Add --
789      ---------
790
791      function Add (Date : Time; Days : Long_Integer) return Time is
792         pragma Unsuppress (Overflow_Check);
793         Date_N : constant Time_Rep := Time_Rep (Date);
794      begin
795         return Time (Date_N + Time_Rep (Days) * Nanos_In_Day);
796      exception
797         when Constraint_Error =>
798            raise Time_Error;
799      end Add;
800
801      ----------------
802      -- Difference --
803      ----------------
804
805      procedure Difference
806        (Left         : Time;
807         Right        : Time;
808         Days         : out Long_Integer;
809         Seconds      : out Duration;
810         Leap_Seconds : out Integer)
811      is
812         Res_Dur       : Time_Dur;
813         Earlier       : Time_Rep;
814         Elapsed_Leaps : Natural;
815         Later         : Time_Rep;
816         Negate        : Boolean := False;
817         Next_Leap_N   : Time_Rep;
818         Sub_Secs      : Duration;
819         Sub_Secs_Diff : Time_Rep;
820
821      begin
822         --  Both input time values are assumed to be in UTC
823
824         if Left >= Right then
825            Later   := Time_Rep (Left);
826            Earlier := Time_Rep (Right);
827         else
828            Later   := Time_Rep (Right);
829            Earlier := Time_Rep (Left);
830            Negate  := True;
831         end if;
832
833         --  If the target supports leap seconds, process them
834
835         if Leap_Support then
836            Cumulative_Leap_Seconds
837              (Earlier, Later, Elapsed_Leaps, Next_Leap_N);
838
839            if Later >= Next_Leap_N then
840               Elapsed_Leaps := Elapsed_Leaps + 1;
841            end if;
842
843         --  The target does not support leap seconds
844
845         else
846            Elapsed_Leaps := 0;
847         end if;
848
849         --  Sub seconds processing. We add the resulting difference to one
850         --  of the input dates in order to account for any potential rounding
851         --  of the difference in the next step.
852
853         Sub_Secs_Diff := Later mod Nano - Earlier mod Nano;
854         Earlier       := Earlier + Sub_Secs_Diff;
855         Sub_Secs      := Duration (Sub_Secs_Diff) / Nano_F;
856
857         --  Difference processing. This operation should be able to calculate
858         --  the difference between opposite values which are close to the end
859         --  and start of Ada time. To accommodate the large range, we convert
860         --  to seconds. This action may potentially round the two values and
861         --  either add or drop a second. We compensate for this issue in the
862         --  previous step.
863
864         Res_Dur :=
865           Time_Dur (Later / Nano - Earlier / Nano) - Time_Dur (Elapsed_Leaps);
866
867         Days         := Long_Integer (Res_Dur / Secs_In_Day);
868         Seconds      := Duration (Res_Dur mod Secs_In_Day) + Sub_Secs;
869         Leap_Seconds := Integer (Elapsed_Leaps);
870
871         if Negate then
872            Days    := -Days;
873            Seconds := -Seconds;
874
875            if Leap_Seconds /= 0 then
876               Leap_Seconds := -Leap_Seconds;
877            end if;
878         end if;
879      end Difference;
880
881      --------------
882      -- Subtract --
883      --------------
884
885      function Subtract (Date : Time; Days : Long_Integer) return Time is
886         pragma Unsuppress (Overflow_Check);
887         Date_N : constant Time_Rep := Time_Rep (Date);
888      begin
889         return Time (Date_N - Time_Rep (Days) * Nanos_In_Day);
890      exception
891         when Constraint_Error =>
892            raise Time_Error;
893      end Subtract;
894
895   end Arithmetic_Operations;
896
897   ---------------------------
898   -- Conversion_Operations --
899   ---------------------------
900
901   package body Conversion_Operations is
902
903      -----------------
904      -- To_Ada_Time --
905      -----------------
906
907      function To_Ada_Time (Unix_Time : Long_Integer) return Time is
908         pragma Unsuppress (Overflow_Check);
909         Unix_Rep : constant Time_Rep := Time_Rep (Unix_Time) * Nano;
910      begin
911         return Time (Unix_Rep - Epoch_Offset);
912      exception
913         when Constraint_Error =>
914            raise Time_Error;
915      end To_Ada_Time;
916
917      -----------------
918      -- To_Ada_Time --
919      -----------------
920
921      function To_Ada_Time
922        (tm_year  : Integer;
923         tm_mon   : Integer;
924         tm_day   : Integer;
925         tm_hour  : Integer;
926         tm_min   : Integer;
927         tm_sec   : Integer;
928         tm_isdst : Integer) return Time
929      is
930         pragma Unsuppress (Overflow_Check);
931         Year   : Year_Number;
932         Month  : Month_Number;
933         Day    : Day_Number;
934         Second : Integer;
935         Leap   : Boolean;
936         Result : Time_Rep;
937
938      begin
939         --  Input processing
940
941         Year  := Year_Number (1900 + tm_year);
942         Month := Month_Number (1 + tm_mon);
943         Day   := Day_Number (tm_day);
944
945         --  Step 1: Validity checks of input values
946
947         if not Year'Valid or else not Month'Valid or else not Day'Valid
948           or else tm_hour  not in 0 .. 24
949           or else tm_min   not in 0 .. 59
950           or else tm_sec   not in 0 .. 60
951           or else tm_isdst not in -1 .. 1
952         then
953            raise Time_Error;
954         end if;
955
956         --  Step 2: Potential leap second
957
958         if tm_sec = 60 then
959            Leap   := True;
960            Second := 59;
961         else
962            Leap   := False;
963            Second := tm_sec;
964         end if;
965
966         --  Step 3: Calculate the time value
967
968         Result :=
969           Time_Rep
970             (Formatting_Operations.Time_Of
971               (Year         => Year,
972                Month        => Month,
973                Day          => Day,
974                Day_Secs     => 0.0,      --  Time is given in h:m:s
975                Hour         => tm_hour,
976                Minute       => tm_min,
977                Second       => Second,
978                Sub_Sec      => 0.0,      --  No precise sub second given
979                Leap_Sec     => Leap,
980                Use_Day_Secs => False,    --  Time is given in h:m:s
981                Use_TZ       => True,     --  Force usage of explicit time zone
982                Is_Historic  => True,
983                Time_Zone    => 0));      --  Place the value in UTC
984
985         --  Step 4: Daylight Savings Time
986
987         if tm_isdst = 1 then
988            Result := Result + Time_Rep (3_600) * Nano;
989         end if;
990
991         return Time (Result);
992
993      exception
994         when Constraint_Error =>
995            raise Time_Error;
996      end To_Ada_Time;
997
998      -----------------
999      -- To_Duration --
1000      -----------------
1001
1002      function To_Duration
1003        (tv_sec  : Long_Integer;
1004         tv_nsec : Long_Integer) return Duration
1005      is
1006         pragma Unsuppress (Overflow_Check);
1007      begin
1008         return Duration (tv_sec) + Duration (tv_nsec) / Nano_F;
1009      end To_Duration;
1010
1011      ------------------------
1012      -- To_Struct_Timespec --
1013      ------------------------
1014
1015      procedure To_Struct_Timespec
1016        (D       : Duration;
1017         tv_sec  : out Long_Integer;
1018         tv_nsec : out Long_Integer)
1019      is
1020         pragma Unsuppress (Overflow_Check);
1021         Secs      : Duration;
1022         Nano_Secs : Duration;
1023
1024      begin
1025         --  Seconds extraction, avoid potential rounding errors
1026
1027         Secs   := D - 0.5;
1028         tv_sec := Long_Integer (Secs);
1029
1030         --  Nanoseconds extraction
1031
1032         Nano_Secs := D - Duration (tv_sec);
1033         tv_nsec := Long_Integer (Nano_Secs * Nano);
1034      end To_Struct_Timespec;
1035
1036      ------------------
1037      -- To_Struct_Tm --
1038      ------------------
1039
1040      procedure To_Struct_Tm
1041        (T       : Time;
1042         tm_year : out Integer;
1043         tm_mon  : out Integer;
1044         tm_day  : out Integer;
1045         tm_hour : out Integer;
1046         tm_min  : out Integer;
1047         tm_sec  : out Integer)
1048      is
1049         pragma Unsuppress (Overflow_Check);
1050         Year      : Year_Number;
1051         Month     : Month_Number;
1052         Second    : Integer;
1053         Day_Secs  : Day_Duration;
1054         Sub_Sec   : Duration;
1055         Leap_Sec  : Boolean;
1056
1057      begin
1058         --  Step 1: Split the input time
1059
1060         Formatting_Operations.Split
1061           (Date        => T,
1062            Year        => Year,
1063            Month       => Month,
1064            Day         => tm_day,
1065            Day_Secs    => Day_Secs,
1066            Hour        => tm_hour,
1067            Minute      => tm_min,
1068            Second      => Second,
1069            Sub_Sec     => Sub_Sec,
1070            Leap_Sec    => Leap_Sec,
1071            Use_TZ      => True,
1072            Is_Historic => False,
1073            Time_Zone   => 0);
1074
1075         --  Step 2: Correct the year and month
1076
1077         tm_year := Year - 1900;
1078         tm_mon  := Month - 1;
1079
1080         --  Step 3: Handle leap second occurrences
1081
1082         tm_sec := (if Leap_Sec then 60 else Second);
1083      end To_Struct_Tm;
1084
1085      ------------------
1086      -- To_Unix_Time --
1087      ------------------
1088
1089      function To_Unix_Time (Ada_Time : Time) return Long_Integer is
1090         pragma Unsuppress (Overflow_Check);
1091         Ada_Rep : constant Time_Rep := Time_Rep (Ada_Time);
1092      begin
1093         return Long_Integer ((Ada_Rep + Epoch_Offset) / Nano);
1094      exception
1095         when Constraint_Error =>
1096            raise Time_Error;
1097      end To_Unix_Time;
1098   end Conversion_Operations;
1099
1100   ----------------------
1101   -- Delay_Operations --
1102   ----------------------
1103
1104   package body Delay_Operations is
1105
1106      -----------------
1107      -- To_Duration --
1108      -----------------
1109
1110      function To_Duration (Date : Time) return Duration is
1111         pragma Unsuppress (Overflow_Check);
1112
1113         Safe_Ada_High : constant Time_Rep := Ada_High - Epoch_Offset;
1114         --  This value represents a "safe" end of time. In order to perform a
1115         --  proper conversion to Unix duration, we will have to shift origins
1116         --  at one point. For very distant dates, this means an overflow check
1117         --  failure. To prevent this, the function returns the "safe" end of
1118         --  time (roughly 2219) which is still distant enough.
1119
1120         Elapsed_Leaps : Natural;
1121         Next_Leap_N   : Time_Rep;
1122         Res_N         : Time_Rep;
1123
1124      begin
1125         Res_N := Time_Rep (Date);
1126
1127         --  Step 1: If the target supports leap seconds, remove any leap
1128         --  seconds elapsed up to the input date.
1129
1130         if Leap_Support then
1131            Cumulative_Leap_Seconds
1132              (Start_Of_Time, Res_N, Elapsed_Leaps, Next_Leap_N);
1133
1134            --  The input time value may fall on a leap second occurrence
1135
1136            if Res_N >= Next_Leap_N then
1137               Elapsed_Leaps := Elapsed_Leaps + 1;
1138            end if;
1139
1140         --  The target does not support leap seconds
1141
1142         else
1143            Elapsed_Leaps := 0;
1144         end if;
1145
1146         Res_N := Res_N - Time_Rep (Elapsed_Leaps) * Nano;
1147
1148         --  Step 2: Perform a shift in origins to obtain a Unix equivalent of
1149         --  the input. Guard against very large delay values such as the end
1150         --  of time since the computation will overflow.
1151
1152         Res_N := (if Res_N > Safe_Ada_High then Safe_Ada_High
1153                                            else Res_N + Epoch_Offset);
1154
1155         return Time_Rep_To_Duration (Res_N);
1156      end To_Duration;
1157
1158   end Delay_Operations;
1159
1160   ---------------------------
1161   -- Formatting_Operations --
1162   ---------------------------
1163
1164   package body Formatting_Operations is
1165
1166      -----------------
1167      -- Day_Of_Week --
1168      -----------------
1169
1170      function Day_Of_Week (Date : Time) return Integer is
1171         Date_N    : constant Time_Rep := Time_Rep (Date);
1172         Time_Zone : constant Long_Integer := UTC_Time_Offset (Date, True);
1173         Ada_Low_N : Time_Rep;
1174         Day_Count : Long_Integer;
1175         Day_Dur   : Time_Dur;
1176         High_N    : Time_Rep;
1177         Low_N     : Time_Rep;
1178
1179      begin
1180         --  As declared, the Ada Epoch is set in UTC. For this calculation to
1181         --  work properly, both the Epoch and the input date must be in the
1182         --  same time zone. The following places the Epoch in the input date's
1183         --  time zone.
1184
1185         Ada_Low_N := Ada_Low - Time_Rep (Time_Zone) * Nano;
1186
1187         if Date_N > Ada_Low_N then
1188            High_N := Date_N;
1189            Low_N  := Ada_Low_N;
1190         else
1191            High_N := Ada_Low_N;
1192            Low_N  := Date_N;
1193         end if;
1194
1195         --  Determine the elapsed seconds since the start of Ada time
1196
1197         Day_Dur := Time_Dur (High_N / Nano - Low_N / Nano);
1198
1199         --  Count the number of days since the start of Ada time. 1901-01-01
1200         --  GMT was a Tuesday.
1201
1202         Day_Count := Long_Integer (Day_Dur / Secs_In_Day) + 1;
1203
1204         return Integer (Day_Count mod 7);
1205      end Day_Of_Week;
1206
1207      -----------
1208      -- Split --
1209      -----------
1210
1211      procedure Split
1212        (Date        : Time;
1213         Year        : out Year_Number;
1214         Month       : out Month_Number;
1215         Day         : out Day_Number;
1216         Day_Secs    : out Day_Duration;
1217         Hour        : out Integer;
1218         Minute      : out Integer;
1219         Second      : out Integer;
1220         Sub_Sec     : out Duration;
1221         Leap_Sec    : out Boolean;
1222         Use_TZ      : Boolean;
1223         Is_Historic : Boolean;
1224         Time_Zone   : Long_Integer)
1225      is
1226         --  The following constants represent the number of nanoseconds
1227         --  elapsed since the start of Ada time to and including the non
1228         --  leap centennial years.
1229
1230         Year_2101 : constant Time_Rep := Ada_Low +
1231                       Time_Rep (49 * 366 + 151 * 365) * Nanos_In_Day;
1232         Year_2201 : constant Time_Rep := Ada_Low +
1233                       Time_Rep (73 * 366 + 227 * 365) * Nanos_In_Day;
1234         Year_2301 : constant Time_Rep := Ada_Low +
1235                       Time_Rep (97 * 366 + 303 * 365) * Nanos_In_Day;
1236
1237         Date_Dur       : Time_Dur;
1238         Date_N         : Time_Rep;
1239         Day_Seconds    : Natural;
1240         Elapsed_Leaps  : Natural;
1241         Four_Year_Segs : Natural;
1242         Hour_Seconds   : Natural;
1243         Is_Leap_Year   : Boolean;
1244         Next_Leap_N    : Time_Rep;
1245         Rem_Years      : Natural;
1246         Sub_Sec_N      : Time_Rep;
1247         Year_Day       : Natural;
1248
1249      begin
1250         Date_N := Time_Rep (Date);
1251
1252         --  Step 1: Leap seconds processing in UTC
1253
1254         if Leap_Support then
1255            Cumulative_Leap_Seconds
1256              (Start_Of_Time, Date_N, Elapsed_Leaps, Next_Leap_N);
1257
1258            Leap_Sec := Date_N >= Next_Leap_N;
1259
1260            if Leap_Sec then
1261               Elapsed_Leaps := Elapsed_Leaps + 1;
1262            end if;
1263
1264         --  The target does not support leap seconds
1265
1266         else
1267            Elapsed_Leaps := 0;
1268            Leap_Sec      := False;
1269         end if;
1270
1271         Date_N := Date_N - Time_Rep (Elapsed_Leaps) * Nano;
1272
1273         --  Step 2: Time zone processing. This action converts the input date
1274         --  from GMT to the requested time zone. Applies from Ada 2005 on.
1275
1276         if Use_TZ then
1277            if Time_Zone /= 0 then
1278               Date_N := Date_N + Time_Rep (Time_Zone) * 60 * Nano;
1279            end if;
1280
1281         --  Ada 83 and 95
1282
1283         else
1284            declare
1285               Off : constant Long_Integer :=
1286                 UTC_Time_Offset (Time (Date_N), Is_Historic);
1287
1288            begin
1289               Date_N := Date_N + Time_Rep (Off) * Nano;
1290            end;
1291         end if;
1292
1293         --  Step 3: Non-leap centennial year adjustment in local time zone
1294
1295         --  In order for all divisions to work properly and to avoid more
1296         --  complicated arithmetic, we add fake February 29s to dates which
1297         --  occur after a non-leap centennial year.
1298
1299         if Date_N >= Year_2301 then
1300            Date_N := Date_N + Time_Rep (3) * Nanos_In_Day;
1301
1302         elsif Date_N >= Year_2201 then
1303            Date_N := Date_N + Time_Rep (2) * Nanos_In_Day;
1304
1305         elsif Date_N >= Year_2101 then
1306            Date_N := Date_N + Time_Rep (1) * Nanos_In_Day;
1307         end if;
1308
1309         --  Step 4: Sub second processing in local time zone
1310
1311         Sub_Sec_N := Date_N mod Nano;
1312         Sub_Sec   := Duration (Sub_Sec_N) / Nano_F;
1313         Date_N    := Date_N - Sub_Sec_N;
1314
1315         --  Convert Date_N into a time duration value, changing the units
1316         --  to seconds.
1317
1318         Date_Dur := Time_Dur (Date_N / Nano - Ada_Low / Nano);
1319
1320         --  Step 5: Year processing in local time zone. Determine the number
1321         --  of four year segments since the start of Ada time and the input
1322         --  date.
1323
1324         Four_Year_Segs := Natural (Date_Dur / Secs_In_Four_Years);
1325
1326         if Four_Year_Segs > 0 then
1327            Date_Dur := Date_Dur - Time_Dur (Four_Year_Segs) *
1328                                   Secs_In_Four_Years;
1329         end if;
1330
1331         --  Calculate the remaining non-leap years
1332
1333         Rem_Years := Natural (Date_Dur / Secs_In_Non_Leap_Year);
1334
1335         if Rem_Years > 3 then
1336            Rem_Years := 3;
1337         end if;
1338
1339         Date_Dur := Date_Dur - Time_Dur (Rem_Years) * Secs_In_Non_Leap_Year;
1340
1341         Year := Ada_Min_Year + Natural (4 * Four_Year_Segs + Rem_Years);
1342         Is_Leap_Year := Is_Leap (Year);
1343
1344         --  Step 6: Month and day processing in local time zone
1345
1346         Year_Day := Natural (Date_Dur / Secs_In_Day) + 1;
1347
1348         Month := 1;
1349
1350         --  Processing for months after January
1351
1352         if Year_Day > 31 then
1353            Month    := 2;
1354            Year_Day := Year_Day - 31;
1355
1356            --  Processing for a new month or a leap February
1357
1358            if Year_Day > 28
1359              and then (not Is_Leap_Year or else Year_Day > 29)
1360            then
1361               Month    := 3;
1362               Year_Day := Year_Day - 28;
1363
1364               if Is_Leap_Year then
1365                  Year_Day := Year_Day - 1;
1366               end if;
1367
1368               --  Remaining months
1369
1370               while Year_Day > Days_In_Month (Month) loop
1371                  Year_Day := Year_Day - Days_In_Month (Month);
1372                  Month    := Month + 1;
1373               end loop;
1374            end if;
1375         end if;
1376
1377         --  Step 7: Hour, minute, second and sub second processing in local
1378         --  time zone.
1379
1380         Day          := Day_Number (Year_Day);
1381         Day_Seconds  := Integer (Date_Dur mod Secs_In_Day);
1382         Day_Secs     := Duration (Day_Seconds) + Sub_Sec;
1383         Hour         := Day_Seconds / 3_600;
1384         Hour_Seconds := Day_Seconds mod 3_600;
1385         Minute       := Hour_Seconds / 60;
1386         Second       := Hour_Seconds mod 60;
1387
1388      exception
1389         when Constraint_Error =>
1390            raise Time_Error;
1391      end Split;
1392
1393      -------------
1394      -- Time_Of --
1395      -------------
1396
1397      function Time_Of
1398        (Year         : Year_Number;
1399         Month        : Month_Number;
1400         Day          : Day_Number;
1401         Day_Secs     : Day_Duration;
1402         Hour         : Integer;
1403         Minute       : Integer;
1404         Second       : Integer;
1405         Sub_Sec      : Duration;
1406         Leap_Sec     : Boolean;
1407         Use_Day_Secs : Boolean;
1408         Use_TZ       : Boolean;
1409         Is_Historic  : Boolean;
1410         Time_Zone    : Long_Integer) return Time
1411      is
1412         Count         : Integer;
1413         Elapsed_Leaps : Natural;
1414         Next_Leap_N   : Time_Rep;
1415         Res_N         : Time_Rep;
1416         Rounded_Res_N : Time_Rep;
1417
1418      begin
1419         --  Step 1: Check whether the day, month and year form a valid date
1420
1421         if Day > Days_In_Month (Month)
1422           and then (Day /= 29 or else Month /= 2 or else not Is_Leap (Year))
1423         then
1424            raise Time_Error;
1425         end if;
1426
1427         --  Start accumulating nanoseconds from the low bound of Ada time
1428
1429         Res_N := Ada_Low;
1430
1431         --  Step 2: Year processing and centennial year adjustment. Determine
1432         --  the number of four year segments since the start of Ada time and
1433         --  the input date.
1434
1435         Count := (Year - Year_Number'First) / 4;
1436
1437         for Four_Year_Segments in 1 .. Count loop
1438            Res_N := Res_N + Nanos_In_Four_Years;
1439         end loop;
1440
1441         --  Note that non-leap centennial years are automatically considered
1442         --  leap in the operation above. An adjustment of several days is
1443         --  required to compensate for this.
1444
1445         if Year > 2300 then
1446            Res_N := Res_N - Time_Rep (3) * Nanos_In_Day;
1447
1448         elsif Year > 2200 then
1449            Res_N := Res_N - Time_Rep (2) * Nanos_In_Day;
1450
1451         elsif Year > 2100 then
1452            Res_N := Res_N - Time_Rep (1) * Nanos_In_Day;
1453         end if;
1454
1455         --  Add the remaining non-leap years
1456
1457         Count := (Year - Year_Number'First) mod 4;
1458         Res_N := Res_N + Time_Rep (Count) * Secs_In_Non_Leap_Year * Nano;
1459
1460         --  Step 3: Day of month processing. Determine the number of days
1461         --  since the start of the current year. Do not add the current
1462         --  day since it has not elapsed yet.
1463
1464         Count := Cumulative_Days_Before_Month (Month) + Day - 1;
1465
1466         --  The input year is leap and we have passed February
1467
1468         if Is_Leap (Year)
1469           and then Month > 2
1470         then
1471            Count := Count + 1;
1472         end if;
1473
1474         Res_N := Res_N + Time_Rep (Count) * Nanos_In_Day;
1475
1476         --  Step 4: Hour, minute, second and sub second processing
1477
1478         if Use_Day_Secs then
1479            Res_N := Res_N + Duration_To_Time_Rep (Day_Secs);
1480
1481         else
1482            Res_N :=
1483              Res_N + Time_Rep (Hour * 3_600 + Minute * 60 + Second) * Nano;
1484
1485            if Sub_Sec = 1.0 then
1486               Res_N := Res_N + Time_Rep (1) * Nano;
1487            else
1488               Res_N := Res_N + Duration_To_Time_Rep (Sub_Sec);
1489            end if;
1490         end if;
1491
1492         --  At this point, the generated time value should be withing the
1493         --  bounds of Ada time.
1494
1495         Check_Within_Time_Bounds (Res_N);
1496
1497         --  Step 4: Time zone processing. At this point we have built an
1498         --  arbitrary time value which is not related to any time zone.
1499         --  For simplicity, the time value is normalized to GMT, producing
1500         --  a uniform representation which can be treated by arithmetic
1501         --  operations for instance without any additional corrections.
1502
1503         if Use_TZ then
1504            if Time_Zone /= 0 then
1505               Res_N := Res_N - Time_Rep (Time_Zone) * 60 * Nano;
1506            end if;
1507
1508         --  Ada 83 and 95
1509
1510         else
1511            declare
1512               Cur_Off   : constant Long_Integer :=
1513                 UTC_Time_Offset (Time (Res_N), Is_Historic);
1514               Cur_Res_N : constant Time_Rep :=
1515                 Res_N - Time_Rep (Cur_Off) * Nano;
1516               Off       : constant Long_Integer :=
1517                 UTC_Time_Offset (Time (Cur_Res_N), Is_Historic);
1518
1519            begin
1520               Res_N := Res_N - Time_Rep (Off) * Nano;
1521            end;
1522         end if;
1523
1524         --  Step 5: Leap seconds processing in GMT
1525
1526         if Leap_Support then
1527            Cumulative_Leap_Seconds
1528              (Start_Of_Time, Res_N, Elapsed_Leaps, Next_Leap_N);
1529
1530            Res_N := Res_N + Time_Rep (Elapsed_Leaps) * Nano;
1531
1532            --  An Ada 2005 caller requesting an explicit leap second or an
1533            --  Ada 95 caller accounting for an invisible leap second.
1534
1535            if Leap_Sec or else Res_N >= Next_Leap_N then
1536               Res_N := Res_N + Time_Rep (1) * Nano;
1537            end if;
1538
1539            --  Leap second validity check
1540
1541            Rounded_Res_N := Res_N - (Res_N mod Nano);
1542
1543            if Use_TZ
1544              and then Leap_Sec
1545              and then Rounded_Res_N /= Next_Leap_N
1546            then
1547               raise Time_Error;
1548            end if;
1549         end if;
1550
1551         return Time (Res_N);
1552      end Time_Of;
1553
1554   end Formatting_Operations;
1555
1556   ---------------------------
1557   -- Time_Zones_Operations --
1558   ---------------------------
1559
1560   package body Time_Zones_Operations is
1561
1562      ---------------------
1563      -- UTC_Time_Offset --
1564      ---------------------
1565
1566      function UTC_Time_Offset (Date : Time) return Long_Integer is
1567      begin
1568         return UTC_Time_Offset (Date, True);
1569      end UTC_Time_Offset;
1570
1571   end Time_Zones_Operations;
1572
1573--  Start of elaboration code for Ada.Calendar
1574
1575begin
1576   System.OS_Primitives.Initialize;
1577
1578end Ada.Calendar;
1579