Remove old autovect-branch by moving to "dead" directory.
[official-gcc.git] / old-autovect-branch / gcc / ada / a-calend.adb
blob581295818e1d717b7d380d17fa71cf461681cd04
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-2005, 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 2, 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. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING. If not, write --
19 -- to the Free Software Foundation, 51 Franklin Street, Fifth Floor, --
20 -- Boston, MA 02110-1301, USA. --
21 -- --
22 -- As a special exception, if other files instantiate generics from this --
23 -- unit, or you link this unit with other files to produce an executable, --
24 -- this unit does not by itself cause the resulting executable to be --
25 -- covered by the GNU General Public License. This exception does not --
26 -- however invalidate any other reasons why the executable file might be --
27 -- covered by the GNU Public License. --
28 -- --
29 -- GNAT was originally developed by the GNAT team at New York University. --
30 -- Extensive contributions were provided by Ada Core Technologies Inc. --
31 -- --
32 ------------------------------------------------------------------------------
34 with Unchecked_Conversion;
36 with System.OS_Primitives;
37 -- used for Clock
39 package body Ada.Calendar is
41 ------------------------------
42 -- Use of Pragma Unsuppress --
43 ------------------------------
45 -- This implementation of Calendar takes advantage of the permission in
46 -- Ada 95 of using arithmetic overflow checks to check for out of bounds
47 -- time values. This means that we must catch the constraint error that
48 -- results from arithmetic overflow, so we use pragma Unsuppress to make
49 -- sure that overflow is enabled, using software overflow checking if
50 -- necessary. That way, compiling Calendar with options to suppress this
51 -- checking will not affect its correctness.
53 ------------------------
54 -- Local Declarations --
55 ------------------------
57 type Char_Pointer is access Character;
58 subtype int is Integer;
59 subtype long is Long_Integer;
60 -- Synonyms for C types. We don't want to get them from Interfaces.C
61 -- because there is no point in loading that unit just for calendar.
63 type tm is record
64 tm_sec : int; -- seconds after the minute (0 .. 60)
65 tm_min : int; -- minutes after the hour (0 .. 59)
66 tm_hour : int; -- hours since midnight (0 .. 24)
67 tm_mday : int; -- day of the month (1 .. 31)
68 tm_mon : int; -- months since January (0 .. 11)
69 tm_year : int; -- years since 1900
70 tm_wday : int; -- days since Sunday (0 .. 6)
71 tm_yday : int; -- days since January 1 (0 .. 365)
72 tm_isdst : int; -- Daylight Savings Time flag (-1 .. +1)
73 tm_gmtoff : long; -- offset from CUT in seconds
74 tm_zone : Char_Pointer; -- timezone abbreviation
75 end record;
77 type tm_Pointer is access all tm;
79 subtype time_t is long;
81 type time_t_Pointer is access all time_t;
83 procedure localtime_r (C : time_t_Pointer; res : tm_Pointer);
84 pragma Import (C, localtime_r, "__gnat_localtime_r");
86 function mktime (TM : tm_Pointer) return time_t;
87 pragma Import (C, mktime);
88 -- mktime returns -1 in case the calendar time given by components of
89 -- TM.all cannot be represented.
91 -- The following constants are used in adjusting Ada dates so that they
92 -- fit into a 56 year range that can be handled by Unix (1970 included -
93 -- 2026 excluded). Dates that are not in this 56 year range are shifted
94 -- by multiples of 56 years to fit in this range.
96 -- The trick is that the number of days in any four year period in the Ada
97 -- range of years (1901 - 2099) has a constant number of days. This is
98 -- because we have the special case of 2000 which, contrary to the normal
99 -- exception for centuries, is a leap year after all. 56 has been chosen,
100 -- because it is not only a multiple of 4, but also a multiple of 7. Thus
101 -- two dates 56 years apart fall on the same day of the week, and the
102 -- Daylight Saving Time change dates are usually the same for these two
103 -- years.
105 Unix_Year_Min : constant := 1970;
106 Unix_Year_Max : constant := 2026;
108 Ada_Year_Min : constant := 1901;
109 Ada_Year_Max : constant := 2099;
111 -- Some basic constants used throughout
113 Days_In_Month : constant array (Month_Number) of Day_Number :=
114 (31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31);
116 Days_In_4_Years : constant := 365 * 3 + 366;
117 Seconds_In_4_Years : constant := 86_400 * Days_In_4_Years;
118 Seconds_In_56_Years : constant := Seconds_In_4_Years * 14;
119 Seconds_In_56_YearsD : constant := Duration (Seconds_In_56_Years);
121 ---------
122 -- "+" --
123 ---------
125 function "+" (Left : Time; Right : Duration) return Time is
126 pragma Unsuppress (Overflow_Check);
127 begin
128 return (Left + Time (Right));
129 exception
130 when Constraint_Error =>
131 raise Time_Error;
132 end "+";
134 function "+" (Left : Duration; Right : Time) return Time is
135 pragma Unsuppress (Overflow_Check);
136 begin
137 return (Time (Left) + Right);
138 exception
139 when Constraint_Error =>
140 raise Time_Error;
141 end "+";
143 ---------
144 -- "-" --
145 ---------
147 function "-" (Left : Time; Right : Duration) return Time is
148 pragma Unsuppress (Overflow_Check);
149 begin
150 return Left - Time (Right);
151 exception
152 when Constraint_Error =>
153 raise Time_Error;
154 end "-";
156 function "-" (Left : Time; Right : Time) return Duration is
157 pragma Unsuppress (Overflow_Check);
158 begin
159 return Duration (Left) - Duration (Right);
160 exception
161 when Constraint_Error =>
162 raise Time_Error;
163 end "-";
165 ---------
166 -- "<" --
167 ---------
169 function "<" (Left, Right : Time) return Boolean is
170 begin
171 return Duration (Left) < Duration (Right);
172 end "<";
174 ----------
175 -- "<=" --
176 ----------
178 function "<=" (Left, Right : Time) return Boolean is
179 begin
180 return Duration (Left) <= Duration (Right);
181 end "<=";
183 ---------
184 -- ">" --
185 ---------
187 function ">" (Left, Right : Time) return Boolean is
188 begin
189 return Duration (Left) > Duration (Right);
190 end ">";
192 ----------
193 -- ">=" --
194 ----------
196 function ">=" (Left, Right : Time) return Boolean is
197 begin
198 return Duration (Left) >= Duration (Right);
199 end ">=";
201 -----------
202 -- Clock --
203 -----------
205 function Clock return Time is
206 begin
207 return Time (System.OS_Primitives.Clock);
208 end Clock;
210 ---------
211 -- Day --
212 ---------
214 function Day (Date : Time) return Day_Number is
215 DY : Year_Number;
216 DM : Month_Number;
217 DD : Day_Number;
218 DS : Day_Duration;
219 begin
220 Split (Date, DY, DM, DD, DS);
221 return DD;
222 end Day;
224 -----------
225 -- Month --
226 -----------
228 function Month (Date : Time) return Month_Number is
229 DY : Year_Number;
230 DM : Month_Number;
231 DD : Day_Number;
232 DS : Day_Duration;
233 begin
234 Split (Date, DY, DM, DD, DS);
235 return DM;
236 end Month;
238 -------------
239 -- Seconds --
240 -------------
242 function Seconds (Date : Time) return Day_Duration is
243 DY : Year_Number;
244 DM : Month_Number;
245 DD : Day_Number;
246 DS : Day_Duration;
247 begin
248 Split (Date, DY, DM, DD, DS);
249 return DS;
250 end Seconds;
252 -----------
253 -- Split --
254 -----------
256 procedure Split
257 (Date : Time;
258 Year : out Year_Number;
259 Month : out Month_Number;
260 Day : out Day_Number;
261 Seconds : out Day_Duration)
263 -- The following declare bounds for duration that are comfortably
264 -- wider than the maximum allowed output result for the Ada range
265 -- of representable split values. These are used for a quick check
266 -- that the value is not wildly out of range.
268 Low : constant := (Ada_Year_Min - Unix_Year_Min - 2) * 365 * 86_400;
269 High : constant := (Ada_Year_Max - Unix_Year_Min + 2) * 365 * 86_400;
271 LowD : constant Duration := Duration (Low);
272 HighD : constant Duration := Duration (High);
274 -- Finally the actual variables used in the computation
276 D : Duration;
277 Frac_Sec : Duration;
278 Year_Val : Integer;
279 Adjusted_Seconds : aliased time_t;
280 Tm_Val : aliased tm;
282 begin
283 -- For us a time is simply a signed duration value, so we work with
284 -- this duration value directly. Note that it can be negative.
286 D := Duration (Date);
288 -- First of all, filter out completely ludicrous values. Remember that
289 -- we use the full stored range of duration values, which may be
290 -- significantly larger than the allowed range of Ada times. Note that
291 -- these checks are wider than required to make absolutely sure that
292 -- there are no end effects from time zone differences.
294 if D < LowD or else D > HighD then
295 raise Time_Error;
296 end if;
298 -- The unix localtime_r function is more or less exactly what we need
299 -- here. The less comes from the fact that it does not support the
300 -- required range of years (the guaranteed range available is only
301 -- EPOCH through EPOCH + N seconds). N is in practice 2 ** 31 - 1.
303 -- If we have a value outside this range, then we first adjust it to be
304 -- in the required range by adding multiples of 56 years. For the range
305 -- we are interested in, the number of days in any consecutive 56 year
306 -- period is constant. Then we do the split on the adjusted value, and
307 -- readjust the years value accordingly.
309 Year_Val := 0;
311 while D < 0.0 loop
312 D := D + Seconds_In_56_YearsD;
313 Year_Val := Year_Val - 56;
314 end loop;
316 while D >= Seconds_In_56_YearsD loop
317 D := D - Seconds_In_56_YearsD;
318 Year_Val := Year_Val + 56;
319 end loop;
321 -- Now we need to take the value D, which is now non-negative, and
322 -- break it down into seconds (to pass to the localtime_r function) and
323 -- fractions of seconds (for the adjustment below).
325 -- Surprisingly there is no easy way to do this in Ada, and certainly
326 -- no easy way to do it and generate efficient code. Therefore we do it
327 -- at a low level, knowing that it is really represented as an integer
328 -- with units of Small
330 declare
331 type D_Int is range 0 .. 2 ** (Duration'Size - 1) - 1;
332 for D_Int'Size use Duration'Size;
334 Small_Div : constant D_Int := D_Int (1.0 / Duration'Small);
335 D_As_Int : D_Int;
337 function To_D_As_Int is new Unchecked_Conversion (Duration, D_Int);
338 function To_Duration is new Unchecked_Conversion (D_Int, Duration);
340 begin
341 D_As_Int := To_D_As_Int (D);
342 Adjusted_Seconds := time_t (D_As_Int / Small_Div);
343 Frac_Sec := To_Duration (D_As_Int rem Small_Div);
344 end;
346 localtime_r (Adjusted_Seconds'Unchecked_Access, Tm_Val'Unchecked_Access);
348 Year_Val := Tm_Val.tm_year + 1900 + Year_Val;
349 Month := Tm_Val.tm_mon + 1;
350 Day := Tm_Val.tm_mday;
352 -- The Seconds value is a little complex. The localtime function
353 -- returns the integral number of seconds, which is what we want, but
354 -- we want to retain the fractional part from the original Time value,
355 -- since this is typically stored more accurately.
357 Seconds := Duration (Tm_Val.tm_hour * 3600 +
358 Tm_Val.tm_min * 60 +
359 Tm_Val.tm_sec)
360 + Frac_Sec;
362 -- Note: the above expression is pretty horrible, one of these days we
363 -- should stop using time_of and do everything ourselves to avoid these
364 -- unnecessary divides and multiplies???.
366 -- The Year may still be out of range, since our entry test was
367 -- deliberately crude. Trying to make this entry test accurate is
368 -- tricky due to time zone adjustment issues affecting the exact
369 -- boundary. It is interesting to note that whether or not a given
370 -- Calendar.Time value gets Time_Error when split depends on the
371 -- current time zone setting.
373 if Year_Val not in Ada_Year_Min .. Ada_Year_Max then
374 raise Time_Error;
375 else
376 Year := Year_Val;
377 end if;
378 end Split;
380 -------------
381 -- Time_Of --
382 -------------
384 function Time_Of
385 (Year : Year_Number;
386 Month : Month_Number;
387 Day : Day_Number;
388 Seconds : Day_Duration := 0.0)
389 return Time
391 Result_Secs : aliased time_t;
392 TM_Val : aliased tm;
393 Int_Secs : constant Integer := Integer (Seconds);
395 Year_Val : Integer := Year;
396 Duration_Adjust : Duration := 0.0;
398 begin
399 -- The following checks are redundant with respect to the constraint
400 -- error checks that should normally be made on parameters, but we
401 -- decide to raise Constraint_Error in any case if bad values come in
402 -- (as a result of checks being off in the caller, or for other
403 -- erroneous or bounded error cases).
405 if not Year 'Valid
406 or else not Month 'Valid
407 or else not Day 'Valid
408 or else not Seconds'Valid
409 then
410 raise Constraint_Error;
411 end if;
413 -- Check for Day value too large (one might expect mktime to do this
414 -- check, as well as the basic checks we did with 'Valid, but it seems
415 -- that at least on some systems, this built-in check is too weak).
417 if Day > Days_In_Month (Month)
418 and then (Day /= 29 or Month /= 2 or Year mod 4 /= 0)
419 then
420 raise Time_Error;
421 end if;
423 TM_Val.tm_sec := Int_Secs mod 60;
424 TM_Val.tm_min := (Int_Secs / 60) mod 60;
425 TM_Val.tm_hour := (Int_Secs / 60) / 60;
426 TM_Val.tm_mday := Day;
427 TM_Val.tm_mon := Month - 1;
429 -- For the year, we have to adjust it to a year that Unix can handle.
430 -- We do this in 56 year steps, since the number of days in 56 years is
431 -- constant, so the timezone effect on the conversion from local time
432 -- to GMT is unaffected; also the DST change dates are usually not
433 -- modified.
435 while Year_Val < Unix_Year_Min loop
436 Year_Val := Year_Val + 56;
437 Duration_Adjust := Duration_Adjust - Seconds_In_56_YearsD;
438 end loop;
440 while Year_Val >= Unix_Year_Max loop
441 Year_Val := Year_Val - 56;
442 Duration_Adjust := Duration_Adjust + Seconds_In_56_YearsD;
443 end loop;
445 TM_Val.tm_year := Year_Val - 1900;
447 -- Since we do not have information on daylight savings, rely on the
448 -- default information.
450 TM_Val.tm_isdst := -1;
451 Result_Secs := mktime (TM_Val'Unchecked_Access);
453 -- That gives us the basic value in seconds. Two adjustments are
454 -- needed. First we must undo the year adjustment carried out above.
455 -- Second we put back the fraction seconds value since in general the
456 -- Day_Duration value we received has additional precision which we do
457 -- not want to lose in the constructed result.
459 return
460 Time (Duration (Result_Secs) +
461 Duration_Adjust +
462 (Seconds - Duration (Int_Secs)));
463 end Time_Of;
465 ----------
466 -- Year --
467 ----------
469 function Year (Date : Time) return Year_Number is
470 DY : Year_Number;
471 DM : Month_Number;
472 DD : Day_Number;
473 DS : Day_Duration;
474 begin
475 Split (Date, DY, DM, DD, DS);
476 return DY;
477 end Year;
479 begin
480 System.OS_Primitives.Initialize;
481 end Ada.Calendar;