OSDN Git Service

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