Add an UNSPEC_PROLOGUE_USE to prevent the link register from being considered dead.
[official-gcc.git] / gcc / ada / a-calend.adb
blob078e05c7d32f027d628486afcac072ea23f56451
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 -- --
10 -- Copyright (C) 1992-2001 Free Software Foundation, Inc. --
11 -- --
12 -- GNAT is free software; you can redistribute it and/or modify it under --
13 -- terms of the GNU General Public License as published by the Free Soft- --
14 -- ware Foundation; either version 2, or (at your option) any later ver- --
15 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
16 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
17 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
18 -- for more details. You should have received a copy of the GNU General --
19 -- Public License distributed with GNAT; see file COPYING. If not, write --
20 -- to the Free Software Foundation, 59 Temple Place - Suite 330, Boston, --
21 -- MA 02111-1307, USA. --
22 -- --
23 -- As a special exception, if other files instantiate generics from this --
24 -- unit, or you link this unit with other files to produce an executable, --
25 -- this unit does not by itself cause the resulting executable to be --
26 -- covered by the GNU General Public License. This exception does not --
27 -- however invalidate any other reasons why the executable file might be --
28 -- covered by the GNU Public License. --
29 -- --
30 -- GNAT was originally developed by the GNAT team at New York University. --
31 -- Extensive contributions were provided by Ada Core Technologies Inc. --
32 -- --
33 ------------------------------------------------------------------------------
35 with Unchecked_Conversion;
37 with System.OS_Primitives;
38 -- used for Clock
40 package body Ada.Calendar is
42 ------------------------------
43 -- Use of Pragma Unsuppress --
44 ------------------------------
46 -- This implementation of Calendar takes advantage of the permission in
47 -- Ada 95 of using arithmetic overflow checks to check for out of bounds
48 -- time values. This means that we must catch the constraint error that
49 -- results from arithmetic overflow, so we use pragma Unsuppress to make
50 -- sure that overflow is enabled, using software overflow checking if
51 -- necessary. That way, compiling Calendar with options to suppress this
52 -- checking will not affect its correctness.
54 ------------------------
55 -- Local Declarations --
56 ------------------------
58 type Char_Pointer is access Character;
59 subtype int is Integer;
60 subtype long is Long_Integer;
61 -- Synonyms for C types. We don't want to get them from Interfaces.C
62 -- because there is no point in loading that unit just for calendar.
64 type tm is record
65 tm_sec : int; -- seconds after the minute (0 .. 60)
66 tm_min : int; -- minutes after the hour (0 .. 59)
67 tm_hour : int; -- hours since midnight (0 .. 24)
68 tm_mday : int; -- day of the month (1 .. 31)
69 tm_mon : int; -- months since January (0 .. 11)
70 tm_year : int; -- years since 1900
71 tm_wday : int; -- days since Sunday (0 .. 6)
72 tm_yday : int; -- days since January 1 (0 .. 365)
73 tm_isdst : int; -- Daylight Savings Time flag (-1 .. +1)
74 tm_gmtoff : long; -- offset from CUT in seconds
75 tm_zone : Char_Pointer; -- timezone abbreviation
76 end record;
78 type tm_Pointer is access all tm;
80 subtype time_t is long;
82 type time_t_Pointer is access all time_t;
84 procedure localtime_r (C : time_t_Pointer; res : tm_Pointer);
85 pragma Import (C, localtime_r, "__gnat_localtime_r");
87 function mktime (TM : tm_Pointer) return time_t;
88 pragma Import (C, mktime);
89 -- mktime returns -1 in case the calendar time given by components of
90 -- TM.all cannot be represented.
92 -- The following constants are used in adjusting Ada dates so that they
93 -- fit into the range that can be handled by Unix (1970 - 2038). The trick
94 -- is that the number of days in any four year period in the Ada range of
95 -- years (1901 - 2099) has a constant number of days. This is because we
96 -- have the special case of 2000 which, contrary to the normal exception
97 -- for centuries, is a leap year after all.
99 Unix_Year_Min : constant := 1970;
100 Unix_Year_Max : constant := 2038;
102 Ada_Year_Min : constant := 1901;
103 Ada_Year_Max : constant := 2099;
105 -- Some basic constants used throughout
107 Days_In_Month : constant array (Month_Number) of Day_Number :=
108 (31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31);
110 Days_In_4_Years : constant := 365 * 3 + 366;
111 Seconds_In_4_Years : constant := 86_400 * Days_In_4_Years;
112 Seconds_In_4_YearsD : constant Duration := Duration (Seconds_In_4_Years);
114 ---------
115 -- "+" --
116 ---------
118 function "+" (Left : Time; Right : Duration) return Time is
119 pragma Unsuppress (Overflow_Check);
120 begin
121 return (Left + Time (Right));
123 exception
124 when Constraint_Error =>
125 raise Time_Error;
126 end "+";
128 function "+" (Left : Duration; Right : Time) return Time is
129 pragma Unsuppress (Overflow_Check);
130 begin
131 return (Time (Left) + Right);
133 exception
134 when Constraint_Error =>
135 raise Time_Error;
136 end "+";
138 ---------
139 -- "-" --
140 ---------
142 function "-" (Left : Time; Right : Duration) return Time is
143 pragma Unsuppress (Overflow_Check);
144 begin
145 return Left - Time (Right);
147 exception
148 when Constraint_Error =>
149 raise Time_Error;
150 end "-";
152 function "-" (Left : Time; Right : Time) return Duration is
153 pragma Unsuppress (Overflow_Check);
154 begin
155 return Duration (Left) - Duration (Right);
157 exception
158 when Constraint_Error =>
159 raise Time_Error;
160 end "-";
162 ---------
163 -- "<" --
164 ---------
166 function "<" (Left, Right : Time) return Boolean is
167 begin
168 return Duration (Left) < Duration (Right);
169 end "<";
171 ----------
172 -- "<=" --
173 ----------
175 function "<=" (Left, Right : Time) return Boolean is
176 begin
177 return Duration (Left) <= Duration (Right);
178 end "<=";
180 ---------
181 -- ">" --
182 ---------
184 function ">" (Left, Right : Time) return Boolean is
185 begin
186 return Duration (Left) > Duration (Right);
187 end ">";
189 ----------
190 -- ">=" --
191 ----------
193 function ">=" (Left, Right : Time) return Boolean is
194 begin
195 return Duration (Left) >= Duration (Right);
196 end ">=";
198 -----------
199 -- Clock --
200 -----------
202 function Clock return Time is
203 begin
204 return Time (System.OS_Primitives.Clock);
205 end Clock;
207 ---------
208 -- Day --
209 ---------
211 function Day (Date : Time) return Day_Number is
212 DY : Year_Number;
213 DM : Month_Number;
214 DD : Day_Number;
215 DS : Day_Duration;
217 begin
218 Split (Date, DY, DM, DD, DS);
219 return DD;
220 end Day;
222 -----------
223 -- Month --
224 -----------
226 function Month (Date : Time) return Month_Number is
227 DY : Year_Number;
228 DM : Month_Number;
229 DD : Day_Number;
230 DS : Day_Duration;
232 begin
233 Split (Date, DY, DM, DD, DS);
234 return DM;
235 end Month;
237 -------------
238 -- Seconds --
239 -------------
241 function Seconds (Date : Time) return Day_Duration is
242 DY : Year_Number;
243 DM : Month_Number;
244 DD : Day_Number;
245 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 -- The following declare the maximum duration value that can be
275 -- successfully converted to a 32-bit integer suitable for passing
276 -- to the localtime_r function. Note that we cannot assume that the
277 -- localtime_r function expands to accept 64-bit input on a 64-bit
278 -- machine, but we can count on a 32-bit range on all machines.
280 Max_Time : constant := 2 ** 31 - 1;
281 Max_TimeD : constant Duration := Duration (Max_Time);
283 -- Finally the actual variables used in the computation
285 D : Duration;
286 Frac_Sec : Duration;
287 Year_Val : Integer;
288 Adjusted_Seconds : aliased time_t;
289 Tm_Val : aliased tm;
291 begin
292 -- For us a time is simply a signed duration value, so we work with
293 -- this duration value directly. Note that it can be negative.
295 D := Duration (Date);
297 -- First of all, filter out completely ludicrous values. Remember
298 -- that we use the full stored range of duration values, which may
299 -- be significantly larger than the allowed range of Ada times. Note
300 -- that these checks are wider than required to make absolutely sure
301 -- that there are no end effects from time zone differences.
303 if D < LowD or else D > HighD then
304 raise Time_Error;
305 end if;
307 -- The unix localtime_r function is more or less exactly what we need
308 -- here. The less comes from the fact that it does not support the
309 -- required range of years (the guaranteed range available is only
310 -- EPOCH through EPOCH + N seconds). N is in practice 2 ** 31 - 1.
312 -- If we have a value outside this range, then we first adjust it
313 -- to be in the required range by adding multiples of four years.
314 -- For the range we are interested in, the number of days in any
315 -- consecutive four year period is constant. Then we do the split
316 -- on the adjusted value, and readjust the years value accordingly.
318 Year_Val := 0;
320 while D < 0.0 loop
321 D := D + Seconds_In_4_YearsD;
322 Year_Val := Year_Val - 4;
323 end loop;
325 while D > Max_TimeD loop
326 D := D - Seconds_In_4_YearsD;
327 Year_Val := Year_Val + 4;
328 end loop;
330 -- Now we need to take the value D, which is now non-negative, and
331 -- break it down into seconds (to pass to the localtime_r function)
332 -- and fractions of seconds (for the adjustment below).
334 -- Surprisingly there is no easy way to do this in Ada, and certainly
335 -- no easy way to do it and generate efficient code. Therefore we
336 -- do it at a low level, knowing that it is really represented as
337 -- an integer with units of Small
339 declare
340 type D_Int is range 0 .. 2 ** (Duration'Size - 1) - 1;
341 for D_Int'Size use Duration'Size;
343 Small_Div : constant D_Int := D_Int (1.0 / Duration'Small);
344 D_As_Int : D_Int;
346 function To_D_As_Int is new Unchecked_Conversion (Duration, D_Int);
347 function To_Duration is new Unchecked_Conversion (D_Int, Duration);
349 begin
350 D_As_Int := To_D_As_Int (D);
351 Adjusted_Seconds := time_t (D_As_Int / Small_Div);
352 Frac_Sec := To_Duration (D_As_Int rem Small_Div);
353 end;
355 localtime_r (Adjusted_Seconds'Unchecked_Access, Tm_Val'Unchecked_Access);
357 Year_Val := Tm_Val.tm_year + 1900 + Year_Val;
358 Month := Tm_Val.tm_mon + 1;
359 Day := Tm_Val.tm_mday;
361 -- The Seconds value is a little complex. The localtime function
362 -- returns the integral number of seconds, which is what we want,
363 -- but we want to retain the fractional part from the original
364 -- Time value, since this is typically stored more accurately.
366 Seconds := Duration (Tm_Val.tm_hour * 3600 +
367 Tm_Val.tm_min * 60 +
368 Tm_Val.tm_sec)
369 + Frac_Sec;
371 -- Note: the above expression is pretty horrible, one of these days
372 -- we should stop using time_of and do everything ourselves to avoid
373 -- these unnecessary divides and multiplies???.
375 -- The Year may still be out of range, since our entry test was
376 -- deliberately crude. Trying to make this entry test accurate is
377 -- tricky due to time zone adjustment issues affecting the exact
378 -- boundary. It is interesting to note that whether or not a given
379 -- Calendar.Time value gets Time_Error when split depends on the
380 -- current time zone setting.
382 if Year_Val not in Ada_Year_Min .. Ada_Year_Max then
383 raise Time_Error;
384 else
385 Year := Year_Val;
386 end if;
387 end Split;
389 -------------
390 -- Time_Of --
391 -------------
393 function Time_Of
394 (Year : Year_Number;
395 Month : Month_Number;
396 Day : Day_Number;
397 Seconds : Day_Duration := 0.0)
398 return Time
400 Result_Secs : aliased time_t;
401 TM_Val : aliased tm;
402 Int_Secs : constant Integer := Integer (Seconds);
404 Year_Val : Integer := Year;
405 Duration_Adjust : Duration := 0.0;
407 begin
408 -- The following checks are redundant with respect to the constraint
409 -- error checks that should normally be made on parameters, but we
410 -- decide to raise Constraint_Error in any case if bad values come
411 -- in (as a result of checks being off in the caller, or for other
412 -- erroneous or bounded error cases).
414 if not Year 'Valid
415 or else not Month 'Valid
416 or else not Day 'Valid
417 or else not Seconds'Valid
418 then
419 raise Constraint_Error;
420 end if;
422 -- Check for Day value too large (one might expect mktime to do this
423 -- check, as well as the basi checks we did with 'Valid, but it seems
424 -- that at least on some systems, this built-in check is too weak).
426 if Day > Days_In_Month (Month)
427 and then (Day /= 29 or Month /= 2 or Year mod 4 /= 0)
428 then
429 raise Time_Error;
430 end if;
432 TM_Val.tm_sec := Int_Secs mod 60;
433 TM_Val.tm_min := (Int_Secs / 60) mod 60;
434 TM_Val.tm_hour := (Int_Secs / 60) / 60;
435 TM_Val.tm_mday := Day;
436 TM_Val.tm_mon := Month - 1;
438 -- For the year, we have to adjust it to a year that Unix can handle.
439 -- We do this in four year steps, since the number of days in four
440 -- years is constant, so the timezone effect on the conversion from
441 -- local time to GMT is unaffected.
443 while Year_Val <= Unix_Year_Min loop
444 Year_Val := Year_Val + 4;
445 Duration_Adjust := Duration_Adjust - Seconds_In_4_YearsD;
446 end loop;
448 while Year_Val >= Unix_Year_Max loop
449 Year_Val := Year_Val - 4;
450 Duration_Adjust := Duration_Adjust + Seconds_In_4_YearsD;
451 end loop;
453 TM_Val.tm_year := Year_Val - 1900;
455 -- Since we do not have information on daylight savings,
456 -- rely on the default information.
458 TM_Val.tm_isdst := -1;
459 Result_Secs := mktime (TM_Val'Unchecked_Access);
461 -- That gives us the basic value in seconds. Two adjustments are
462 -- needed. First we must undo the year adjustment carried out above.
463 -- Second we put back the fraction seconds value since in general the
464 -- Day_Duration value we received has additional precision which we
465 -- do not want to lose in the constructed result.
467 return
468 Time (Duration (Result_Secs) +
469 Duration_Adjust +
470 (Seconds - Duration (Int_Secs)));
472 end Time_Of;
474 ----------
475 -- Year --
476 ----------
478 function Year (Date : Time) return Year_Number is
479 DY : Year_Number;
480 DM : Month_Number;
481 DD : Day_Number;
482 DS : Day_Duration;
484 begin
485 Split (Date, DY, DM, DD, DS);
486 return DY;
487 end Year;
489 end Ada.Calendar;