Commit 42907632 by Hristian Kirtchev Committed by Arnaud Charlet

a-calend-vms.ads, [...]: New version of Ada.Calendar which supports the new…

a-calend-vms.ads, [...]: New version of Ada.Calendar which supports the new upper bound of Ada time...

2007-04-06  Hristian Kirtchev  <kirtchev@adacore.com>
	    Vincent Celier  <celier@adacore.com>

	* a-calend-vms.ads, a-calend.ads, a-calend.adb, a-calend-vms.adb:
	New version of Ada.Calendar which supports the new upper bound of Ada
	time (2399-12-31 86_399.999999999).
	The following modifications have been made to the package:
	 - New representation of time as count of nanoseconds since the start of
	   Ada time (1901-1-1 0.0).
	 - Target independent Split and Time_Of routines which service both
	   Ada 95 and Ada 2005 code.
	 - Target independent interface to the Ada 2005 children of Calendar.
	 - Integrated leap seconds into Ada 95 and Ada 2005 mode.
	 - Handling of non-leap centenial years.
	 - Updated clock function.
	 - Updated arithmetic and comparison operators.

	* a-caldel.adb (To_Duration): Add call to target independent routine in
	Ada.Calendar to handle the conversion of time to duration.

	* sysdep.c (__gnat_localtime_tzoff): Test timezone before setting off
	(UTC Offset).
	If timezone is obviously incorrect (outside of -14 hours .. 14 hours),
	set off to 0.
	(__gnat_localtime_tzoff for Lynx and VxWorks): Even though these
	targets do not have a natural time zone, GMT is used as a default.
	(__gnat_get_task_options): New.

	* a-direct.adb (Modification_Time): Add with and use clauses for
	Ada.Calendar and Ada.
	Calendar.Formatting. Remove with clause for Ada.Unchecked_Conversion
	since it is no longer needed.
	(Duration_To_Time): Removed.
	(OS_Time_To_Long_Integer): Removed.
	(Modification_Time): Rewritten to use Ada.Calendar and Ada.Calendar.
	Formatting Time_Of routines which automatically handle time zones,
	buffer periods and leap seconds.

	* a-calari.ads, a-calari.adb ("+", "-", Difference): Add calls to
	target independent routines in Ada.Calendar.

	* a-calfor.ads, a-calfor.adb: 
	Code cleanup and addition of validity checks in various routines.
	(Day_Of_Week, Split, Time_Of): Add call to target independent routine in
	Ada.Calendar.

	* a-catizo.ads, a-catizo.adb (UTC_Time_Offset): Add call to target
	independent routine in Ada.Calendar.

From-SVN: r123543
parent 3d3bf932
...@@ -31,26 +31,29 @@ ...@@ -31,26 +31,29 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
with Unchecked_Conversion;
package body Ada.Calendar.Arithmetic is package body Ada.Calendar.Arithmetic is
use Leap_Sec_Ops; --------------------------
-- Implementation Notes --
--------------------------
Day_Duration : constant Duration := 86_400.0; -- All operations in this package are target and time representation
-- independent, thus only one source file is needed for multiple targets.
--------- ---------
-- "+" -- -- "+" --
--------- ---------
function "+" (Left : Time; Right : Day_Count) return Time is function "+" (Left : Time; Right : Day_Count) return Time is
R : constant Long_Integer := Long_Integer (Right);
begin begin
return Left + Integer (Right) * Day_Duration; return Arithmetic_Operations.Add (Left, R);
end "+"; end "+";
function "+" (Left : Day_Count; Right : Time) return Time is function "+" (Left : Day_Count; Right : Time) return Time is
L : constant Long_Integer := Long_Integer (Left);
begin begin
return Integer (Left) * Day_Duration + Right; return Arithmetic_Operations.Add (Right, L);
end "+"; end "+";
--------- ---------
...@@ -58,18 +61,19 @@ package body Ada.Calendar.Arithmetic is ...@@ -58,18 +61,19 @@ package body Ada.Calendar.Arithmetic is
--------- ---------
function "-" (Left : Time; Right : Day_Count) return Time is function "-" (Left : Time; Right : Day_Count) return Time is
R : constant Long_Integer := Long_Integer (Right);
begin begin
return Left - Integer (Right) * Day_Duration; return Arithmetic_Operations.Subtract (Left, R);
end "-"; end "-";
function "-" (Left, Right : Time) return Day_Count is function "-" (Left, Right : Time) return Day_Count is
Days : Day_Count; Days : Long_Integer;
Seconds : Duration; Seconds : Duration;
Leap_Seconds : Leap_Seconds_Count; Leap_Seconds : Integer;
begin begin
Difference (Left, Right, Days, Seconds, Leap_Seconds); Arithmetic_Operations.Difference
return Days; (Left, Right, Days, Seconds, Leap_Seconds);
return Day_Count (Days);
end "-"; end "-";
---------------- ----------------
...@@ -77,66 +81,19 @@ package body Ada.Calendar.Arithmetic is ...@@ -77,66 +81,19 @@ package body Ada.Calendar.Arithmetic is
---------------- ----------------
procedure Difference procedure Difference
(Left, Right : Time; (Left : Time;
Right : Time;
Days : out Day_Count; Days : out Day_Count;
Seconds : out Duration; Seconds : out Duration;
Leap_Seconds : out Leap_Seconds_Count) Leap_Seconds : out Leap_Seconds_Count)
is is
Diff : Duration; Op_Days : Long_Integer;
Earlier : Time; Op_Leaps : Integer;
Later : Time;
Leaps_Dur : Duration;
Negate : Boolean;
Next_Leap : Time;
Secs_Diff : Long_Integer;
Sub_Seconds : Duration;
begin begin
if Left >= Right then Arithmetic_Operations.Difference
Later := Left; (Left, Right, Op_Days, Seconds, Op_Leaps);
Earlier := Right; Days := Day_Count (Op_Days);
Negate := False; Leap_Seconds := Leap_Seconds_Count (Op_Leaps);
else
Later := Right;
Earlier := Left;
Negate := True;
end if;
Diff := Later - Earlier;
Cumulative_Leap_Secs (Earlier, Later, Leaps_Dur, Next_Leap);
if Later >= Next_Leap then
Leaps_Dur := Leaps_Dur + 1.0;
end if;
Diff := Diff - Leaps_Dur;
declare
type D_Int is range 0 .. 2 ** (Duration'Size - 1) - 1;
for D_Int'Size use Duration'Size;
Small_Div : constant D_Int := D_Int (1.0 / Duration'Small);
D_As_Int : D_Int;
function To_D_As_Int is new Unchecked_Conversion (Duration, D_Int);
function To_Duration is new Unchecked_Conversion (D_Int, Duration);
begin
D_As_Int := To_D_As_Int (Diff);
Secs_Diff := Long_Integer (D_As_Int / Small_Div);
Sub_Seconds := To_Duration (D_As_Int rem Small_Div);
end;
Days := Day_Count (Secs_Diff / 86_400);
Seconds := Duration (Secs_Diff mod 86_400) + Sub_Seconds;
Leap_Seconds := Leap_Seconds_Count (Leaps_Dur);
if Negate then
Days := -Days;
Seconds := -Seconds;
Leap_Seconds := -Leap_Seconds;
end if;
end Difference; end Difference;
end Ada.Calendar.Arithmetic; end Ada.Calendar.Arithmetic;
...@@ -6,7 +6,7 @@ ...@@ -6,7 +6,7 @@
-- -- -- --
-- S p e c -- -- S p e c --
-- -- -- --
-- Copyright (C) 2005 - 2006, Free Software Foundation, Inc. -- -- Copyright (C) 2005-2006, Free Software Foundation, Inc. --
-- -- -- --
-- This specification is derived from the Ada Reference Manual for use with -- -- This specification is derived from the Ada Reference Manual for use with --
-- GNAT. The copyright notice above, and the license provisions that follow -- -- GNAT. The copyright notice above, and the license provisions that follow --
...@@ -35,26 +35,51 @@ ...@@ -35,26 +35,51 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
-- This package provides arithmetic operations of time values using days
-- and leap seconds. Ada.Calendar.Arithmetic is defined in the Ada 2005
-- RM (9.6.1).
package Ada.Calendar.Arithmetic is package Ada.Calendar.Arithmetic is
-- Arithmetic on days: -- Arithmetic on days:
-- Rough estimate on the number of days over the range of Ada time
type Day_Count is range type Day_Count is range
-(366 * (1 + Year_Number'Last - Year_Number'First)) -(366 * (1 + Year_Number'Last - Year_Number'First))
.. ..
+(366 * (1 + Year_Number'Last - Year_Number'First)); +(366 * (1 + Year_Number'Last - Year_Number'First));
-- Negative leap seconds occur whenever the astronomical time is faster
-- than the atomic time or as a result of Difference when Left < Right.
subtype Leap_Seconds_Count is Integer range -2047 .. 2047; subtype Leap_Seconds_Count is Integer range -2047 .. 2047;
procedure Difference procedure Difference
(Left, Right : Time; (Left : Time;
Right : Time;
Days : out Day_Count; Days : out Day_Count;
Seconds : out Duration; Seconds : out Duration;
Leap_Seconds : out Leap_Seconds_Count); Leap_Seconds : out Leap_Seconds_Count);
-- Returns the difference between Left and Right. Days is the number of
-- days of difference, Seconds is the remainder seconds of difference
-- excluding leap seconds, and Leap_Seconds is the number of leap seconds.
-- If Left < Right, then Seconds <= 0.0, Days <= 0, and Leap_Seconds <= 0,
-- otherwise all values are nonnegative. The absolute value of Seconds is
-- always less than 86_400.0. For the returned values, if Days = 0, then
-- Seconds + Duration (Leap_Seconds) = Calendar."-" (Left, Right)
function "+" (Left : Time; Right : Day_Count) return Time;
function "+" (Left : Day_Count; Right : Time) return Time;
-- Adds a number of days to a time value. Time_Error is raised if the
-- result is not representable as a value of type Time.
function "-" (Left : Time; Right : Day_Count) return Time;
-- Subtracts a number of days from a time value. Time_Error is raised if
-- the result is not representable as a value of type Time.
function "+" (Left : Time; Right : Day_Count) return Time; function "-" (Left : Time; Right : Time) return Day_Count;
function "+" (Left : Day_Count; Right : Time) return Time; -- Subtracts two time values, and returns the number of days between them.
function "-" (Left : Time; Right : Day_Count) return Time; -- This is the same value that Difference would return in Days.
function "-" (Left, Right : Time) return Day_Count;
end Ada.Calendar.Arithmetic; end Ada.Calendar.Arithmetic;
...@@ -7,7 +7,7 @@ ...@@ -7,7 +7,7 @@
-- B o d y -- -- B o d y --
-- -- -- --
-- Copyright (C) 1991-1994, Florida State University -- -- Copyright (C) 1991-1994, Florida State University --
-- Copyright (C) 1995-2005, AdaCore -- -- Copyright (C) 1995-2006, AdaCore --
-- -- -- --
-- GNARL is free software; you can redistribute it and/or modify it under -- -- GNARL is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- -- -- terms of the GNU General Public License as published by the Free Soft- --
...@@ -54,12 +54,12 @@ package body Ada.Calendar.Delays is ...@@ -54,12 +54,12 @@ package body Ada.Calendar.Delays is
use System.Traces; use System.Traces;
-- Earlier, the following operations were implemented using -- Earlier, System.Time_Opeations was used to implement the following
-- System.Time_Operations. The idea was to avoid sucking in the tasking -- operations. The idea was to avoid sucking in the tasking packages. This
-- packages. This did not work. Logically, we can't have it both ways. -- did not work. Logically, we can't have it both ways. There is no way to
-- There is no way to implement time delays that will have correct task -- implement time delays that will have correct task semantics without
-- semantics without reference to the tasking run-time system. -- reference to the tasking run-time system. To achieve this goal, we now
-- To achieve this goal, we now use soft links. -- use soft links.
----------------------- -----------------------
-- Local Subprograms -- -- Local Subprograms --
...@@ -120,18 +120,23 @@ package body Ada.Calendar.Delays is ...@@ -120,18 +120,23 @@ package body Ada.Calendar.Delays is
function To_Duration (T : Time) return Duration is function To_Duration (T : Time) return Duration is
begin begin
return Duration (T); -- Since time has multiple representations on different platforms, a
-- target independent operation in Ada.Calendar is used to perform
-- this conversion.
return Delays_Operations.To_Duration (T);
end To_Duration; end To_Duration;
begin begin
-- Set up the Timed_Delay soft link to the non tasking version -- Set up the Timed_Delay soft link to the non tasking version if it has
-- if it has not been already set. -- not been already set.
-- If tasking is present, Timed_Delay has already set this soft -- If tasking is present, Timed_Delay has already set this soft link, or
-- link, or this will be overriden during the elaboration of -- this will be overriden during the elaboration of
-- System.Tasking.Initialization -- System.Tasking.Initialization
if SSL.Timed_Delay = null then if SSL.Timed_Delay = null then
SSL.Timed_Delay := Timed_Delay_NT'Access; SSL.Timed_Delay := Timed_Delay_NT'Access;
end if; end if;
end Ada.Calendar.Delays; end Ada.Calendar.Delays;
...@@ -44,11 +44,12 @@ package Ada.Calendar is ...@@ -44,11 +44,12 @@ package Ada.Calendar is
type Time is private; type Time is private;
-- Declarations representing limits of allowed local time values. Note that -- Declarations representing limits of allowed local time values. Note
-- these do NOT constrain the possible stored values of time which may well -- that these do NOT constrain the possible stored values of time which
-- permit a larger range of times (this is explicitly allowed in Ada 95). -- may well permit a larger range of times (this is explicitly allowed
-- in Ada 95).
subtype Year_Number is Integer range 1901 .. 2099; subtype Year_Number is Integer range 1901 .. 2399;
subtype Month_Number is Integer range 1 .. 12; subtype Month_Number is Integer range 1 .. 12;
subtype Day_Number is Integer range 1 .. 31; subtype Day_Number is Integer range 1 .. 31;
...@@ -72,8 +73,7 @@ package Ada.Calendar is ...@@ -72,8 +73,7 @@ package Ada.Calendar is
(Year : Year_Number; (Year : Year_Number;
Month : Month_Number; Month : Month_Number;
Day : Day_Number; Day : Day_Number;
Seconds : Day_Duration := 0.0) Seconds : Day_Duration := 0.0) return Time;
return Time;
function "+" (Left : Time; Right : Duration) return Time; function "+" (Left : Time; Right : Duration) return Time;
function "+" (Left : Duration; Right : Time) return Time; function "+" (Left : Duration; Right : Time) return Time;
...@@ -87,10 +87,7 @@ package Ada.Calendar is ...@@ -87,10 +87,7 @@ package Ada.Calendar is
Time_Error : exception; Time_Error : exception;
Unimplemented : exception;
private private
pragma Inline (Clock); pragma Inline (Clock);
pragma Inline (Year); pragma Inline (Year);
...@@ -105,81 +102,107 @@ private ...@@ -105,81 +102,107 @@ private
pragma Inline (">"); pragma Inline (">");
pragma Inline (">="); pragma Inline (">=");
-- Time is represented as the number of 100-nanosecond (ns) units offset -- Although the units are 100 nanoseconds, for the purpose of better
-- from the system base date and time, which is 00:00 o'clock, -- readability, this unit will be called "mili".
-- November 17, 1858 (the Smithsonian base date and time for the
-- astronomic calendar). Mili : constant := 10_000_000;
Milis_In_Day : constant := 864_000_000_000;
Secs_In_Day : constant := 86_400;
-- Time is represented as the number of 100-nanosecond (ns) units from the
-- system base date and time 1858-11-17 0.0 (the Smithsonian base date and
-- time for the astronomic calendar).
-- The time value stored is typically a GMT value, as provided in standard -- The time value stored is typically a GMT value, as provided in standard
-- Unix environments. If this is the case then Split and Time_Of perform -- Unix environments. If this is the case then Split and Time_Of perform
-- required conversions to and from local times. -- required conversions to and from local times.
type Time is new OSP.OS_Time;
-- Notwithstanding this definition, Time is not quite the same as OS_Time. -- Notwithstanding this definition, Time is not quite the same as OS_Time.
-- Relative Time is positive, whereas relative OS_Time is negative, -- Relative Time is positive, whereas relative OS_Time is negative,
-- but this declaration makes for easier conversion. -- but this declaration makes for easier conversion.
-- The following package provides handling of leap seconds. It is type Time is new OSP.OS_Time;
-- used by Ada.Calendar.Arithmetic and Ada.Calendar.Formatting, both
-- Ada 2005 children of Ada.Calendar. -- The range of Ada time expressed as milis since the VMS Epoch
package Leap_Sec_Ops is Ada_Low : constant Time := (10 * 366 + 32 * 365 + 45) * Milis_In_Day;
Ada_High : constant Time := (131 * 366 + 410 * 365 + 45) * Milis_In_Day;
After_Last_Leap : constant Time := Time'Last;
-- Bigger by far than any leap second value. Not within range of Days_In_Month : constant array (Month_Number) of Day_Number :=
-- Ada.Calendar specified dates. (31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31);
procedure Cumulative_Leap_Secs Invalid_Time_Zone_Offset : Long_Integer;
(Start_Date : Time; pragma Import (C, Invalid_Time_Zone_Offset, "__gnat_invalid_tzoff");
End_Date : Time;
Leaps_Between : out Duration; function Is_Leap (Year : Year_Number) return Boolean;
Next_Leap_Sec : out Time); -- Determine whether a given year is leap
-- Leaps_Between is the sum of the leap seconds that have occured
-- on or after Start_Date and before (strictly before) End_Date. -- The following packages provide a target independent interface to the
-- Next_Leap_Sec represents the next leap second occurence on or -- children of Calendar - Arithmetic, Formatting and Time_Zones.
-- after End_Date. If there are no leaps seconds after End_Date,
-- After_Last_Leap is returned. This does not provide info about -- NOTE: Delays does not need a target independent interface because
-- the next leap second (pos/neg or ?). After_Last_Leap can be used -- VMS already has a target specific file for that package.
-- as End_Date to count all the leap seconds that have occured on
-- or after Start_Date. package Arithmetic_Operations is
-- function Add (Date : Time; Days : Long_Integer) return Time;
-- Important Notes: any fractional parts of Start_Date and End_Date -- Add X number of days to a time value
-- are discarded before the calculations are done. For instance: if
-- 113 seconds is a leap second (it isn't) and 113.5 is input as an procedure Difference
-- End_Date, the leap second at 113 will not be counted in (Left : Time;
-- Leaps_Between, but it will be returned as Next_Leap_Sec. Thus, if Right : Time;
-- the caller wants to know if the End_Date is a leap second, the Days : out Long_Integer;
-- comparison should be: Seconds : out Duration;
-- Leap_Seconds : out Integer);
-- End_Date >= Next_Leap_Sec; -- Calculate the difference between two time values in terms of days,
-- -- seconds and leap seconds elapsed. The leap seconds are not included
-- After_Last_Leap is designed so that this comparison works without -- in the seconds returned. If Left is greater than Right, the returned
-- having to first check if Next_Leap_Sec is a valid leap second. -- values are positive, negative otherwise.
function All_Leap_Seconds return Duration; function Subtract (Date : Time; Days : Long_Integer) return Time;
-- Returns the sum off all of the leap seoncds. -- Subtract X number of days from a time value
end Arithmetic_Operations;
end Leap_Sec_Ops;
package Formatting_Operations is
procedure Split_With_Offset function Day_Of_Week (Date : Time) return Integer;
(Date : Time; -- Determine which day of week Date falls on. The returned values are
Year : out Year_Number; -- within the range of 0 .. 6 (Monday .. Sunday).
Month : out Month_Number;
Day : out Day_Number; procedure Split
Seconds : out Day_Duration; (Date : Time;
Offset : out Long_Integer); Year : out Year_Number;
-- Split_W_Offset has the same spec as Split with the addition of an Month : out Month_Number;
-- offset value which give the offset of the local time zone from UTC Day : out Day_Number;
-- at the input Date. This value comes for free during the implementation Day_Secs : out Day_Duration;
-- of Split and is needed by UTC_Time_Offset. The returned Offset time Hour : out Integer;
-- is straight from the C tm struct and is in seconds. If the system Minute : out Integer;
-- dependent code has no way to find the offset it will return the value Second : out Integer;
-- Invalid_TZ_Offset declared below. Otherwise no checking is done, so Sub_Sec : out Duration;
-- it is up to the user to check both for Invalid_TZ_Offset and otherwise Leap_Sec : out Boolean;
-- for a value that is acceptable. Time_Zone : Long_Integer);
-- Split a time value into its components
Invalid_TZ_Offset : Long_Integer;
pragma Import (C, Invalid_TZ_Offset, "__gnat_invalid_tzoff"); function Time_Of
(Year : Year_Number;
Month : Month_Number;
Day : Day_Number;
Day_Secs : Day_Duration;
Hour : Integer;
Minute : Integer;
Second : Integer;
Sub_Sec : Duration;
Leap_Sec : Boolean;
Leap_Checks : Boolean;
Use_Day_Secs : Boolean;
Time_Zone : Long_Integer) return Time;
-- Given all the components of a date, return the corresponding time
-- value. Set Use_Day_Secs to use the value in Day_Secs, otherwise the
-- day duration will be calculated from Hour, Minute, Second and Sub_
-- Sec. Set flag Leap_Checks to verify the validity of a leap second.
end Formatting_Operations;
package Time_Zones_Operations is
function UTC_Time_Offset (Date : Time) return Long_Integer;
-- Return the offset in seconds from GMT
end Time_Zones_Operations;
end Ada.Calendar; end Ada.Calendar;
...@@ -6,7 +6,7 @@ ...@@ -6,7 +6,7 @@
-- -- -- --
-- S p e c -- -- S p e c --
-- -- -- --
-- Copyright (C) 2005 - 2006, Free Software Foundation, Inc. -- -- Copyright (C) 2005-2006, Free Software Foundation, Inc. --
-- -- -- --
-- This specification is derived from the Ada Reference Manual for use with -- -- This specification is derived from the Ada Reference Manual for use with --
-- GNAT. The copyright notice above, and the license provisions that follow -- -- GNAT. The copyright notice above, and the license provisions that follow --
...@@ -35,6 +35,10 @@ ...@@ -35,6 +35,10 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
-- This package provides additional components to Time, as well as new
-- Time_Of and Split routines which handle time zones and leap seconds.
-- This package is defined in the Ada 2005 RM (9.6.1).
with Ada.Calendar.Time_Zones; with Ada.Calendar.Time_Zones;
package Ada.Calendar.Formatting is package Ada.Calendar.Formatting is
...@@ -84,6 +88,12 @@ package Ada.Calendar.Formatting is ...@@ -84,6 +88,12 @@ package Ada.Calendar.Formatting is
Minute : Minute_Number; Minute : Minute_Number;
Second : Second_Number := 0; Second : Second_Number := 0;
Sub_Second : Second_Duration := 0.0) return Day_Duration; Sub_Second : Second_Duration := 0.0) return Day_Duration;
-- Returns a Day_Duration value for the combination of the given Hour,
-- Minute, Second, and Sub_Second. This value can be used in Ada.Calendar.
-- Time_Of as well as the argument to Calendar."+" and Calendar."–". If
-- Seconds_Of is called with a Sub_Second value of 1.0, the value returned
-- is equal to the value of Seconds_Of for the next second with a Sub_
-- Second value of 0.0.
procedure Split procedure Split
(Seconds : Day_Duration; (Seconds : Day_Duration;
...@@ -91,6 +101,9 @@ package Ada.Calendar.Formatting is ...@@ -91,6 +101,9 @@ package Ada.Calendar.Formatting is
Minute : out Minute_Number; Minute : out Minute_Number;
Second : out Second_Number; Second : out Second_Number;
Sub_Second : out Second_Duration); Sub_Second : out Second_Duration);
-- Splits Seconds into Hour, Minute, Second and Sub_Second in such a way
-- that the resulting values all belong to their respective subtypes. The
-- value returned in the Sub_Second parameter is always less than 1.0.
procedure Split procedure Split
(Date : Time; (Date : Time;
...@@ -102,6 +115,9 @@ package Ada.Calendar.Formatting is ...@@ -102,6 +115,9 @@ package Ada.Calendar.Formatting is
Second : out Second_Number; Second : out Second_Number;
Sub_Second : out Second_Duration; Sub_Second : out Second_Duration;
Time_Zone : Time_Zones.Time_Offset := 0); Time_Zone : Time_Zones.Time_Offset := 0);
-- Splits Date into its constituent parts (Year, Month, Day, Hour, Minute,
-- Second, Sub_Second), relative to the specified time zone offset. The
-- value returned in the Sub_Second parameter is always less than 1.0.
function Time_Of function Time_Of
(Year : Year_Number; (Year : Year_Number;
...@@ -113,6 +129,14 @@ package Ada.Calendar.Formatting is ...@@ -113,6 +129,14 @@ package Ada.Calendar.Formatting is
Sub_Second : Second_Duration := 0.0; Sub_Second : Second_Duration := 0.0;
Leap_Second : Boolean := False; Leap_Second : Boolean := False;
Time_Zone : Time_Zones.Time_Offset := 0) return Time; Time_Zone : Time_Zones.Time_Offset := 0) return Time;
-- If Leap_Second is False, returns a Time built from the date and time
-- values, relative to the specified time zone offset. If Leap_Second is
-- True, returns the Time that represents the time within the leap second
-- that is one second later than the time specified by the parameters.
-- Time_Error is raised if the parameters do not form a proper date or
-- time. If Time_Of is called with a Sub_Second value of 1.0, the value
-- returned is equal to the value of Time_Of for the next second with a
-- Sub_Second value of 0.0.
function Time_Of function Time_Of
(Year : Year_Number; (Year : Year_Number;
...@@ -121,6 +145,14 @@ package Ada.Calendar.Formatting is ...@@ -121,6 +145,14 @@ package Ada.Calendar.Formatting is
Seconds : Day_Duration := 0.0; Seconds : Day_Duration := 0.0;
Leap_Second : Boolean := False; Leap_Second : Boolean := False;
Time_Zone : Time_Zones.Time_Offset := 0) return Time; Time_Zone : Time_Zones.Time_Offset := 0) return Time;
-- If Leap_Second is False, returns a Time built from the date and time
-- values, relative to the specified time zone offset. If Leap_Second is
-- True, returns the Time that represents the time within the leap second
-- that is one second later than the time specified by the parameters.
-- Time_Error is raised if the parameters do not form a proper date or
-- time. If Time_Of is called with a Seconds value of 86_400.0, the value
-- returned is equal to the value of Time_Of for the next day with a
-- Seconds value of 0.0.
procedure Split procedure Split
(Date : Time; (Date : Time;
...@@ -133,6 +165,14 @@ package Ada.Calendar.Formatting is ...@@ -133,6 +165,14 @@ package Ada.Calendar.Formatting is
Sub_Second : out Second_Duration; Sub_Second : out Second_Duration;
Leap_Second : out Boolean; Leap_Second : out Boolean;
Time_Zone : Time_Zones.Time_Offset := 0); Time_Zone : Time_Zones.Time_Offset := 0);
-- If Date does not represent a time within a leap second, splits Date
-- into its constituent parts (Year, Month, Day, Hour, Minute, Second,
-- Sub_Second), relative to the specified time zone offset, and sets
-- Leap_Second to False. If Date represents a time within a leap second,
-- set the constituent parts to values corresponding to a time one second
-- earlier than that given by Date, relative to the specified time zone
-- offset, and sets Leap_Seconds to True. The value returned in the
-- Sub_Second parameter is always less than 1.0.
procedure Split procedure Split
(Date : Time; (Date : Time;
...@@ -142,6 +182,14 @@ package Ada.Calendar.Formatting is ...@@ -142,6 +182,14 @@ package Ada.Calendar.Formatting is
Seconds : out Day_Duration; Seconds : out Day_Duration;
Leap_Second : out Boolean; Leap_Second : out Boolean;
Time_Zone : Time_Zones.Time_Offset := 0); Time_Zone : Time_Zones.Time_Offset := 0);
-- If Date does not represent a time within a leap second, splits Date
-- into its constituent parts (Year, Month, Day, Seconds), relative to the
-- specified time zone offset, and sets Leap_Second to False. If Date
-- represents a time within a leap second, set the constituent parts to
-- values corresponding to a time one second earlier than that given by
-- Date, relative to the specified time zone offset, and sets Leap_Seconds
-- to True. The value returned in the Seconds parameter is always less
-- than 86_400.0.
-- Simple image and value -- Simple image and value
...@@ -149,15 +197,39 @@ package Ada.Calendar.Formatting is ...@@ -149,15 +197,39 @@ package Ada.Calendar.Formatting is
(Date : Time; (Date : Time;
Include_Time_Fraction : Boolean := False; Include_Time_Fraction : Boolean := False;
Time_Zone : Time_Zones.Time_Offset := 0) return String; Time_Zone : Time_Zones.Time_Offset := 0) return String;
-- Returns a string form of the Date relative to the given Time_Zone. The
-- format is "Year-Month-Day Hour:Minute:Second", where the Year is a
-- 4-digit value, and all others are 2-digit values, of the functions
-- defined in Ada.Calendar and Ada.Calendar.Formatting, including a
-- leading zero, if needed. The separators between the values are a minus,
-- another minus, a colon, and a single space between the Day and Hour. If
-- Include_Time_Fraction is True, the integer part of Sub_Seconds*100 is
-- suffixed to the string as a point followed by a 2-digit value.
function Value function Value
(Date : String; (Date : String;
Time_Zone : Time_Zones.Time_Offset := 0) return Time; Time_Zone : Time_Zones.Time_Offset := 0) return Time;
-- Returns a Time value for the image given as Date, relative to the given
-- time zone. Constraint_Error is raised if the string is not formatted as
-- described for Image, or the function cannot interpret the given string
-- as a Time value.
function Image function Image
(Elapsed_Time : Duration; (Elapsed_Time : Duration;
Include_Time_Fraction : Boolean := False) return String; Include_Time_Fraction : Boolean := False) return String;
-- Returns a string form of the Elapsed_Time. The format is "Hour:Minute:
-- Second", where all values are 2-digit values, including a leading zero,
-- if needed. The separators between the values are colons. If Include_
-- Time_Fraction is True, the integer part of Sub_Seconds*100 is suffixed
-- to the string as a point followed by a 2-digit value. If Elapsed_Time <
-- 0.0, the result is Image (abs Elapsed_Time, Include_Time_Fraction)
-- prefixed with a minus sign. If abs Elapsed_Time represents 100 hours or
-- more, the result is implementation-defined.
function Value (Elapsed_Time : String) return Duration; function Value (Elapsed_Time : String) return Duration;
-- Returns a Duration value for the image given as Elapsed_Time.
-- Constraint_Error is raised if the string is not formatted as described
-- for Image, or the function cannot interpret the given string as a
-- Duration value.
end Ada.Calendar.Formatting; end Ada.Calendar.Formatting;
...@@ -33,35 +33,39 @@ ...@@ -33,35 +33,39 @@
package body Ada.Calendar.Time_Zones is package body Ada.Calendar.Time_Zones is
--------------------------
-- Implementation Notes --
--------------------------
-- All operations in this package are target and time representation
-- independent, thus only one source file is needed for multiple targets.
--------------------- ---------------------
-- UTC_Time_Offset -- -- UTC_Time_Offset --
--------------------- ---------------------
function UTC_Time_Offset (Date : Time := Clock) return Time_Offset is function UTC_Time_Offset (Date : Time := Clock) return Time_Offset is
Year : Year_Number; Offset_L : constant Long_Integer :=
Month : Month_Number; Time_Zones_Operations.UTC_Time_Offset (Date);
Day : Day_Number; Offset : Time_Offset;
Seconds : Day_Duration;
Offset : Long_Integer;
begin begin
Split_With_Offset (Date, Year, Month, Day, Seconds, Offset); if Offset_L = Invalid_Time_Zone_Offset then
-- The system dependent code does not support time zones
if Offset = Invalid_TZ_Offset then
raise Unknown_Zone_Error; raise Unknown_Zone_Error;
end if; end if;
Offset := Offset / 60; -- The offset returned by Time_Zones_Operations.UTC_Time_Offset is in
-- seconds, the returned value needs to be in minutes.
Offset := Time_Offset (Offset_L / 60);
-- Validity checks
if Offset < Long_Integer (Time_Offset'First) if not Offset'Valid then
or else Offset > Long_Integer (Time_Offset'Last)
then
raise Unknown_Zone_Error; raise Unknown_Zone_Error;
end if; end if;
return Time_Offset (Offset); return Offset;
end UTC_Time_Offset; end UTC_Time_Offset;
end Ada.Calendar.Time_Zones; end Ada.Calendar.Time_Zones;
...@@ -6,7 +6,7 @@ ...@@ -6,7 +6,7 @@
-- -- -- --
-- S p e c -- -- S p e c --
-- -- -- --
-- Copyright (C) 2005 - 2006, Free Software Foundation, Inc. -- -- Copyright (C) 2005-2006, Free Software Foundation, Inc. --
-- -- -- --
-- This specification is derived from the Ada Reference Manual for use with -- -- This specification is derived from the Ada Reference Manual for use with --
-- GNAT. The copyright notice above, and the license provisions that follow -- -- GNAT. The copyright notice above, and the license provisions that follow --
...@@ -35,6 +35,9 @@ ...@@ -35,6 +35,9 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
-- This package provides routines to determine the offset of dates to GMT.
-- It is defined in the Ada 2005 RM (9.6.1).
package Ada.Calendar.Time_Zones is package Ada.Calendar.Time_Zones is
-- Time zone manipulation -- Time zone manipulation
...@@ -44,5 +47,9 @@ package Ada.Calendar.Time_Zones is ...@@ -44,5 +47,9 @@ package Ada.Calendar.Time_Zones is
Unknown_Zone_Error : exception; Unknown_Zone_Error : exception;
function UTC_Time_Offset (Date : Time := Clock) return Time_Offset; function UTC_Time_Offset (Date : Time := Clock) return Time_Offset;
-- Returns, as a number of minutes, the difference between the
-- implementation-defined time zone of Calendar, and UTC time, at the time
-- Date. If the time zone of the Calendar implementation is unknown, then
-- Unknown_Zone_Error is raised.
end Ada.Calendar.Time_Zones; end Ada.Calendar.Time_Zones;
...@@ -31,10 +31,11 @@ ...@@ -31,10 +31,11 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
with Ada.Calendar; use Ada.Calendar;
with Ada.Calendar.Formatting; use Ada.Calendar.Formatting;
with Ada.Directories.Validity; use Ada.Directories.Validity; with Ada.Directories.Validity; use Ada.Directories.Validity;
with Ada.Strings.Unbounded; use Ada.Strings.Unbounded; with Ada.Strings.Unbounded; use Ada.Strings.Unbounded;
with Ada.Unchecked_Deallocation; with Ada.Unchecked_Deallocation;
with Ada.Unchecked_Conversion;
with Ada.Characters.Handling; use Ada.Characters.Handling; with Ada.Characters.Handling; use Ada.Characters.Handling;
with GNAT.Directory_Operations; use GNAT.Directory_Operations; with GNAT.Directory_Operations; use GNAT.Directory_Operations;
...@@ -46,13 +47,6 @@ with System; ...@@ -46,13 +47,6 @@ with System;
package body Ada.Directories is package body Ada.Directories is
function Duration_To_Time is new
Ada.Unchecked_Conversion (Duration, Ada.Calendar.Time);
function OS_Time_To_Long_Integer is new
Ada.Unchecked_Conversion (OS_Time, Long_Integer);
-- These two unchecked conversions are used in function Modification_Time
-- to convert an OS_Time to a Calendar.Time.
type Search_Data is record type Search_Data is record
Is_Valid : Boolean := False; Is_Valid : Boolean := False;
Name : Ada.Strings.Unbounded.Unbounded_String; Name : Ada.Strings.Unbounded.Unbounded_String;
...@@ -724,7 +718,7 @@ package body Ada.Directories is ...@@ -724,7 +718,7 @@ package body Ada.Directories is
-- Modification_Time -- -- Modification_Time --
----------------------- -----------------------
function Modification_Time (Name : String) return Ada.Calendar.Time is function Modification_Time (Name : String) return Time is
Date : OS_Time; Date : OS_Time;
Year : Year_Type; Year : Year_Type;
Month : Month_Type; Month : Month_Type;
...@@ -732,8 +726,7 @@ package body Ada.Directories is ...@@ -732,8 +726,7 @@ package body Ada.Directories is
Hour : Hour_Type; Hour : Hour_Type;
Minute : Minute_Type; Minute : Minute_Type;
Second : Second_Type; Second : Second_Type;
Result : Time;
Result : Ada.Calendar.Time;
begin begin
-- First, the invalid cases -- First, the invalid cases
...@@ -744,26 +737,31 @@ package body Ada.Directories is ...@@ -744,26 +737,31 @@ package body Ada.Directories is
else else
Date := File_Time_Stamp (Name); Date := File_Time_Stamp (Name);
-- ??? This implementation should be revisited when AI 00351 has -- Break down the time stamp into its constituents relative to GMT.
-- implemented. -- This version of Split does not recognize leap seconds or buffer
-- space for time zone processing.
if OpenVMS then GM_Split (Date, Year, Month, Day, Hour, Minute, Second);
-- On OpenVMS, OS_Time is in local time -- On OpenVMS, the resulting time value must be in the local time
-- zone. Ada.Calendar.Time_Of is exactly what we need. Note that
-- in both cases, the sub seconds are set to zero (0.0) because the
-- time stamp does not store them in its value.
GM_Split (Date, Year, Month, Day, Hour, Minute, Second); if OpenVMS then
Result :=
Ada.Calendar.Time_Of
(Year, Month, Day, Seconds_Of (Hour, Minute, Second, 0.0));
return Ada.Calendar.Time_Of -- On Unix and Windows, the result must be in GMT. Ada.Calendar.
(Year, Month, Day, -- Formatting.Time_Of with default time zone of zero (0) is the
Duration (Second + 60 * (Minute + 60 * Hour))); -- routine of choice.
else else
-- On Unix and Windows, OS_Time is in GMT Result := Time_Of (Year, Month, Day, Hour, Minute, Second, 0.0);
Result :=
Duration_To_Time (Duration (OS_Time_To_Long_Integer (Date)));
return Result;
end if; end if;
return Result;
end if; end if;
end Modification_Time; end Modification_Time;
......
...@@ -687,7 +687,7 @@ get_gmtoff (void) ...@@ -687,7 +687,7 @@ get_gmtoff (void)
/* This value is returned as the time zone offset when a valid value /* This value is returned as the time zone offset when a valid value
cannot be determined. It is simply a bizarre value that will never cannot be determined. It is simply a bizarre value that will never
occur. It is 3 days plus 73 seconds (offset is in seconds. */ occur. It is 3 days plus 73 seconds (offset is in seconds). */
long __gnat_invalid_tzoff = 259273; long __gnat_invalid_tzoff = 259273;
...@@ -755,8 +755,9 @@ __gnat_localtime_tzoff (const time_t *, struct tm *, long *); ...@@ -755,8 +755,9 @@ __gnat_localtime_tzoff (const time_t *, struct tm *, long *);
struct tm * struct tm *
__gnat_localtime_tzoff (const time_t *timer, struct tm *tp, long *off) __gnat_localtime_tzoff (const time_t *timer, struct tm *tp, long *off)
{ {
/* Treat all time values in GMT */
localtime_r (tp, timer); localtime_r (tp, timer);
*off = __gnat_invalid_tzoff; *off = 0;
return NULL; return NULL;
} }
...@@ -779,17 +780,60 @@ __gnat_localtime_tzoff (const time_t *timer, struct tm *tp, long *off) ...@@ -779,17 +780,60 @@ __gnat_localtime_tzoff (const time_t *timer, struct tm *tp, long *off)
/* AIX, HPUX, SGI Irix, Sun Solaris */ /* AIX, HPUX, SGI Irix, Sun Solaris */
#if defined (_AIX) || defined (__hpux__) || defined (sgi) || defined (sun) #if defined (_AIX) || defined (__hpux__) || defined (sgi) || defined (sun)
*off = (long) -timezone; /* The contents of external variable "timezone" may not always be
if (tp->tm_isdst > 0) initialized. Instead of returning an incorrect offset, treat the local
*off = *off + 3600; time zone as 0 (UTC). The value of 28 hours is the maximum valid offset
allowed by Ada.Calendar.Time_Zones. */
if ((timezone < -28 * 3600) || (timezone > 28 * 3600))
*off = 0;
else
{
*off = (long) -timezone;
if (tp->tm_isdst > 0)
*off = *off + 3600;
}
/* Lynx - Treat all time values in GMT */
#elif defined (__Lynx__)
*off = 0;
/* VxWorks */
#elif defined (__vxworks)
#include <stdlib.h>
{
/* Try to read the environment variable TIMEZONE. The variable may not have
been initialize, in that case return an offset of zero (0) for UTC. */
char *tz_str = getenv ("TIMEZONE");
/* Lynx, VXWorks */ if ((tz_str == NULL) || (*tz_str == '\0'))
#elif defined (__Lynx__) || defined (__vxworks) *off = 0;
*off = __gnat_invalid_tzoff; else
{
char *tz_start, *tz_end;
/* The format of the data contained in TIMEZONE is N::U:S:E where N is the
name of the time zone, U are the minutes difference from UTC, S is the
start of DST in mmddhh and E is the end of DST in mmddhh. Extracting
the value of U involves setting two pointers, one at the beginning and
one at the end of the value. The end pointer is then set to null in
order to delimit a string slice for atol to process. */
tz_start = index (tz_str, ':') + 2;
tz_end = index (tz_start, ':');
tz_end = '\0';
/* The Ada layer expects an offset in seconds */
*off = atol (tz_start) * 60;
}
}
/* Darwin, Free BSD, Linux, Tru64 */ /* Darwin, Free BSD, Linux, Tru64, where there exists a component tm_gmtoff
#else in struct tm */
#elif defined (__APPLE__) || defined (__FreeBSD__) || defined (linux) ||\
(defined (__alpha__) && defined (__osf__))
*off = tp->tm_gmtoff; *off = tp->tm_gmtoff;
/* All other platforms: Treat all time values in GMT */
#else
*off = 0;
#endif #endif
return NULL; return NULL;
} }
...@@ -797,3 +841,59 @@ __gnat_localtime_tzoff (const time_t *timer, struct tm *tp, long *off) ...@@ -797,3 +841,59 @@ __gnat_localtime_tzoff (const time_t *timer, struct tm *tp, long *off)
#endif #endif
#endif #endif
#endif #endif
#ifdef __vxworks
#include <taskLib.h>
/* __gnat_get_task_options is used by s-taprop.adb only for VxWorks. This
function returns the options to be set when creating a new task. It fetches
the options assigned to the current task (parent), so offering some user
level control over the options for a task hierarchy. It forces VX_FP_TASK
because it is almost always required. */
extern int __gnat_get_task_options (void);
int
__gnat_get_task_options (void)
{
int options;
/* Get the options for the task creator */
taskOptionsGet (taskIdSelf (), &options);
/* Force VX_FP_TASK because it is almost always required */
options |= VX_FP_TASK;
/* Mask those bits that are not under user control */
#ifdef VX_USR_TASK_OPTIONS
return options & VX_USR_TASK_OPTIONS;
#else
return options;
#endif
}
#endif
#ifdef __Lynx__
/*
The following code works around a problem in LynxOS version 4.2. As
of that version, the symbol pthread_mutex_lock has been removed
from libc and replaced with an inline C function in a system
header.
LynuxWorks has indicated that this is a bug and that they intend to
put that symbol back in libc in a future patch level, following
which this patch can be removed. However, for the time being we use
a wrapper which can be imported from the runtime.
*/
#include <pthread.h>
int
__gnat_pthread_mutex_lock (pthread_mutex_t *mutex)
{
return pthread_mutex_lock (mutex);
}
#endif /* __Lynx__ */
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment