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
This commit is contained in:
Hristian Kirtchev 2007-04-06 11:15:21 +02:00 committed by Arnaud Charlet
parent 3d3bf932b9
commit 4290763286
13 changed files with 2921 additions and 1399 deletions

View File

@ -31,26 +31,29 @@
-- --
------------------------------------------------------------------------------
with Unchecked_Conversion;
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
R : constant Long_Integer := Long_Integer (Right);
begin
return Left + Integer (Right) * Day_Duration;
return Arithmetic_Operations.Add (Left, R);
end "+";
function "+" (Left : Day_Count; Right : Time) return Time is
L : constant Long_Integer := Long_Integer (Left);
begin
return Integer (Left) * Day_Duration + Right;
return Arithmetic_Operations.Add (Right, L);
end "+";
---------
@ -58,18 +61,19 @@ package body Ada.Calendar.Arithmetic is
---------
function "-" (Left : Time; Right : Day_Count) return Time is
R : constant Long_Integer := Long_Integer (Right);
begin
return Left - Integer (Right) * Day_Duration;
return Arithmetic_Operations.Subtract (Left, R);
end "-";
function "-" (Left, Right : Time) return Day_Count is
Days : Day_Count;
Days : Long_Integer;
Seconds : Duration;
Leap_Seconds : Leap_Seconds_Count;
Leap_Seconds : Integer;
begin
Difference (Left, Right, Days, Seconds, Leap_Seconds);
return Days;
Arithmetic_Operations.Difference
(Left, Right, Days, Seconds, Leap_Seconds);
return Day_Count (Days);
end "-";
----------------
@ -77,66 +81,19 @@ package body Ada.Calendar.Arithmetic is
----------------
procedure Difference
(Left, Right : Time;
(Left : Time;
Right : Time;
Days : out Day_Count;
Seconds : out Duration;
Leap_Seconds : out Leap_Seconds_Count)
is
Diff : Duration;
Earlier : Time;
Later : Time;
Leaps_Dur : Duration;
Negate : Boolean;
Next_Leap : Time;
Secs_Diff : Long_Integer;
Sub_Seconds : Duration;
Op_Days : Long_Integer;
Op_Leaps : Integer;
begin
if Left >= Right then
Later := Left;
Earlier := Right;
Negate := False;
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;
Arithmetic_Operations.Difference
(Left, Right, Op_Days, Seconds, Op_Leaps);
Days := Day_Count (Op_Days);
Leap_Seconds := Leap_Seconds_Count (Op_Leaps);
end Difference;
end Ada.Calendar.Arithmetic;

View File

@ -6,7 +6,7 @@
-- --
-- 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 --
-- GNAT. The copyright notice above, and the license provisions that follow --
@ -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
-- Arithmetic on days:
-- Rough estimate on the number of days over the range of Ada time
type Day_Count is range
-(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;
procedure Difference
(Left, Right : Time;
(Left : Time;
Right : Time;
Days : out Day_Count;
Seconds : out Duration;
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;
function "-" (Left : Time; Right : Day_Count) return Time;
function "-" (Left, Right : Time) return Day_Count;
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 : Time) return Day_Count;
-- Subtracts two time values, and returns the number of days between them.
-- This is the same value that Difference would return in Days.
end Ada.Calendar.Arithmetic;

View File

@ -7,7 +7,7 @@
-- B o d y --
-- --
-- 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 --
-- terms of the GNU General Public License as published by the Free Soft- --
@ -54,12 +54,12 @@ package body Ada.Calendar.Delays is
use System.Traces;
-- Earlier, the following operations were implemented using
-- System.Time_Operations. The idea was to avoid sucking in the tasking
-- packages. This did not work. Logically, we can't have it both ways.
-- There is no way to implement time delays that will have correct task
-- semantics without reference to the tasking run-time system.
-- To achieve this goal, we now use soft links.
-- Earlier, System.Time_Opeations was used to implement the following
-- operations. The idea was to avoid sucking in the tasking packages. This
-- did not work. Logically, we can't have it both ways. There is no way to
-- implement time delays that will have correct task semantics without
-- reference to the tasking run-time system. To achieve this goal, we now
-- use soft links.
-----------------------
-- Local Subprograms --
@ -120,18 +120,23 @@ package body Ada.Calendar.Delays is
function To_Duration (T : Time) return Duration is
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;
begin
-- Set up the Timed_Delay soft link to the non tasking version
-- if it has not been already set.
-- Set up the Timed_Delay soft link to the non tasking version if it has
-- not been already set.
-- If tasking is present, Timed_Delay has already set this soft
-- link, or this will be overriden during the elaboration of
-- If tasking is present, Timed_Delay has already set this soft link, or
-- this will be overriden during the elaboration of
-- System.Tasking.Initialization
if SSL.Timed_Delay = null then
SSL.Timed_Delay := Timed_Delay_NT'Access;
end if;
end Ada.Calendar.Delays;

File diff suppressed because it is too large Load Diff

View File

@ -44,11 +44,12 @@ package Ada.Calendar is
type Time is private;
-- Declarations representing limits of allowed local time values. Note that
-- these do NOT constrain the possible stored values of time which may well
-- permit a larger range of times (this is explicitly allowed in Ada 95).
-- Declarations representing limits of allowed local time values. Note
-- that these do NOT constrain the possible stored values of time which
-- 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 Day_Number is Integer range 1 .. 31;
@ -72,8 +73,7 @@ package Ada.Calendar is
(Year : Year_Number;
Month : Month_Number;
Day : Day_Number;
Seconds : Day_Duration := 0.0)
return Time;
Seconds : Day_Duration := 0.0) return Time;
function "+" (Left : Time; Right : Duration) return Time;
function "+" (Left : Duration; Right : Time) return Time;
@ -87,10 +87,7 @@ package Ada.Calendar is
Time_Error : exception;
Unimplemented : exception;
private
pragma Inline (Clock);
pragma Inline (Year);
@ -105,81 +102,107 @@ private
pragma Inline (">");
pragma Inline (">=");
-- Time is represented as the number of 100-nanosecond (ns) units offset
-- from the system base date and time, which is 00:00 o'clock,
-- November 17, 1858 (the Smithsonian base date and time for the
-- astronomic calendar).
-- Although the units are 100 nanoseconds, for the purpose of better
-- readability, this unit will be called "mili".
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
-- Unix environments. If this is the case then Split and Time_Of perform
-- 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.
-- Relative Time is positive, whereas relative OS_Time is negative,
-- but this declaration makes for easier conversion.
-- The following package provides handling of leap seconds. It is
-- used by Ada.Calendar.Arithmetic and Ada.Calendar.Formatting, both
-- Ada 2005 children of Ada.Calendar.
type Time is new OSP.OS_Time;
package Leap_Sec_Ops is
-- The range of Ada time expressed as milis since the VMS Epoch
After_Last_Leap : constant Time := Time'Last;
-- Bigger by far than any leap second value. Not within range of
-- Ada.Calendar specified dates.
Ada_Low : constant Time := (10 * 366 + 32 * 365 + 45) * Milis_In_Day;
Ada_High : constant Time := (131 * 366 + 410 * 365 + 45) * Milis_In_Day;
procedure Cumulative_Leap_Secs
(Start_Date : Time;
End_Date : Time;
Leaps_Between : out Duration;
Next_Leap_Sec : out Time);
-- Leaps_Between is the sum of the leap seconds that have occured
-- on or after Start_Date and before (strictly before) End_Date.
-- Next_Leap_Sec represents the next leap second occurence on or
-- after End_Date. If there are no leaps seconds after End_Date,
-- After_Last_Leap is returned. This does not provide info about
-- the next leap second (pos/neg or ?). After_Last_Leap can be used
-- as End_Date to count all the leap seconds that have occured on
-- or after Start_Date.
--
-- Important Notes: any fractional parts of Start_Date and End_Date
-- 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
-- End_Date, the leap second at 113 will not be counted in
-- Leaps_Between, but it will be returned as Next_Leap_Sec. Thus, if
-- the caller wants to know if the End_Date is a leap second, the
-- comparison should be:
--
-- End_Date >= Next_Leap_Sec;
--
-- After_Last_Leap is designed so that this comparison works without
-- having to first check if Next_Leap_Sec is a valid leap second.
Days_In_Month : constant array (Month_Number) of Day_Number :=
(31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31);
function All_Leap_Seconds return Duration;
-- Returns the sum off all of the leap seoncds.
Invalid_Time_Zone_Offset : Long_Integer;
pragma Import (C, Invalid_Time_Zone_Offset, "__gnat_invalid_tzoff");
end Leap_Sec_Ops;
function Is_Leap (Year : Year_Number) return Boolean;
-- Determine whether a given year is leap
procedure Split_With_Offset
(Date : Time;
Year : out Year_Number;
Month : out Month_Number;
Day : out Day_Number;
Seconds : out Day_Duration;
Offset : out Long_Integer);
-- Split_W_Offset has the same spec as Split with the addition of an
-- offset value which give the offset of the local time zone from UTC
-- at the input Date. This value comes for free during the implementation
-- of Split and is needed by UTC_Time_Offset. The returned Offset time
-- is straight from the C tm struct and is in seconds. If the system
-- dependent code has no way to find the offset it will return the value
-- Invalid_TZ_Offset declared below. Otherwise no checking is done, so
-- it is up to the user to check both for Invalid_TZ_Offset and otherwise
-- for a value that is acceptable.
-- The following packages provide a target independent interface to the
-- children of Calendar - Arithmetic, Formatting and Time_Zones.
Invalid_TZ_Offset : Long_Integer;
pragma Import (C, Invalid_TZ_Offset, "__gnat_invalid_tzoff");
-- NOTE: Delays does not need a target independent interface because
-- VMS already has a target specific file for that package.
package Arithmetic_Operations is
function Add (Date : Time; Days : Long_Integer) return Time;
-- Add X number of days to a time value
procedure Difference
(Left : Time;
Right : Time;
Days : out Long_Integer;
Seconds : out Duration;
Leap_Seconds : out Integer);
-- Calculate the difference between two time values in terms of days,
-- seconds and leap seconds elapsed. The leap seconds are not included
-- in the seconds returned. If Left is greater than Right, the returned
-- values are positive, negative otherwise.
function Subtract (Date : Time; Days : Long_Integer) return Time;
-- Subtract X number of days from a time value
end Arithmetic_Operations;
package Formatting_Operations is
function Day_Of_Week (Date : Time) return Integer;
-- Determine which day of week Date falls on. The returned values are
-- within the range of 0 .. 6 (Monday .. Sunday).
procedure Split
(Date : Time;
Year : out Year_Number;
Month : out Month_Number;
Day : out Day_Number;
Day_Secs : out Day_Duration;
Hour : out Integer;
Minute : out Integer;
Second : out Integer;
Sub_Sec : out Duration;
Leap_Sec : out Boolean;
Time_Zone : Long_Integer);
-- Split a time value into its components
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;

File diff suppressed because it is too large Load Diff

View File

@ -43,13 +43,17 @@ package Ada.Calendar is
-- these do NOT constrain the possible stored values of time which 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 Day_Number is Integer range 1 .. 31;
-- A Day_Duration value of 86_400.0 designates a new day
subtype Day_Duration is Duration range 0.0 .. 86_400.0;
function Clock return Time;
-- The returned time value is the number of nanoseconds since the start
-- of Ada time (1901-1-1 0.0 GMT).
function Year (Date : Time) return Year_Number;
function Month (Date : Time) return Month_Number;
@ -62,6 +66,10 @@ package Ada.Calendar is
Month : out Month_Number;
Day : out Day_Number;
Seconds : out Day_Duration);
-- Break down a time value into its date components set in the current
-- time zone. If Split is called on a time value created using Ada 2005
-- Time_Of in some arbitrary time zone, the input value always will be
-- interpreted as some point in time relative to the local time zone.
function Time_Of
(Year : Year_Number;
@ -87,6 +95,10 @@ package Ada.Calendar is
function "+" (Left : Duration; Right : Time) return Time;
function "-" (Left : Time; Right : Duration) return Time;
function "-" (Left : Time; Right : Time) return Duration;
-- The first three functions will raise Time_Error if the resulting time
-- value is less than the start of Ada time in GMT or greater than the
-- end of Ada time in GMT. The last function will raise Time_Error if the
-- resulting difference cannot fit into a duration value.
function "<" (Left, Right : Time) return Boolean;
function "<=" (Left, Right : Time) return Boolean;
@ -110,83 +122,183 @@ private
pragma Inline (">");
pragma Inline (">=");
-- Time is represented as a signed duration from the base point which is
-- what Unix calls the EPOCH (i.e. 12 midnight (24:00:00), Dec 31st, 1969,
-- or if you prefer 0:00:00 on Jan 1st, 1970). Since Ada allows dates
-- before this EPOCH value, the stored duration value may be negative.
-- The units used in this version of Ada.Calendar are nanoseconds. The
-- following constants provide values used in conversions of seconds or
-- days to the underlying units.
-- 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
-- required conversions to and from local times. The range of times that
-- can be stored in Time values depends on the declaration of the type
-- Duration, which must at least cover the required Ada range represented
-- by the declaration of Year_Number, but may be larger (we take full
-- advantage of the new permission in Ada 95 to store time values outside
-- the range that would be acceptable to Split). The Duration type is a
-- real value representing a time interval in seconds.
Nano : constant := 1_000_000_000;
Nano_F : constant := 1_000_000_000.0;
Nanos_In_Day : constant := 86_400_000_000_000;
Secs_In_Day : constant := 86_400;
type Time is new Duration;
----------------------------
-- Implementation of Time --
----------------------------
-- The following package provides handling of leap seconds. It is
-- used by Ada.Calendar.Arithmetic and Ada.Calendar.Formatting, both
-- Ada 2005 children of Ada.Calendar.
-- Time is represented as an unsigned 64 bit integer count of nanoseconds
-- since the start of Ada time (1901-1-1 0.0 GMT). Time values produced
-- by Time_Of are internaly normalized to GMT regardless of their local
-- time zone. This representation ensures correct handling of leap seconds
-- as well as performing arithmetic. In Ada 95, Split will treat a time
-- value as being in the local time zone and break it down accordingly.
-- In Ada 2005, Split will treat a time value as being in the designated
-- time zone by the corresponding formal parameter or in GMT by default.
-- The size of the type is large enough to cover the Ada 2005 range of
-- time (1901-1-1 0.0 GMT - 2399-12-31-86_399.999999999 GMT).
package Leap_Sec_Ops is
------------------
-- Leap seconds --
------------------
After_Last_Leap : constant Time := Time'Last;
-- Bigger by far than any leap second value. Not within range of
-- Ada.Calendar specified dates.
-- Due to Earth's slowdown, the astronomical time is not as precise as the
-- International Atomic Time. To compensate for this inaccuracy, a single
-- leap second is added after the last day of June or December. The count
-- of seconds during those occurences becomes:
procedure Cumulative_Leap_Secs
(Start_Date : Time;
End_Date : Time;
Leaps_Between : out Duration;
Next_Leap_Sec : out Time);
-- Leaps_Between is the sum of the leap seconds that have occured
-- on or after Start_Date and before (strictly before) End_Date.
-- Next_Leap_Sec represents the next leap second occurence on or
-- after End_Date. If there are no leaps seconds after End_Date,
-- After_Last_Leap is returned. This does not provide info about
-- the next leap second (pos/neg or ?). After_Last_Leap can be used
-- as End_Date to count all the leap seconds that have occured on
-- or after Start_Date.
--
-- Important Notes: any fractional parts of Start_Date and End_Date
-- 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
-- End_Date, the leap second at 113 will not be counted in
-- Leaps_Between, but it will be returned as Next_Leap_Sec. Thus, if
-- the caller wants to know if the End_Date is a leap second, the
-- comparison should be:
--
-- End_Date >= Next_Leap_Sec;
--
-- After_Last_Leap is designed so that this comparison works without
-- having to first check if Next_Leap_Sec is a valid leap second.
-- ... 58, 59, leap second 60, 1, 2 ...
function All_Leap_Seconds return Duration;
-- Returns the sum off all of the leap seoncds.
-- Unlike leap days, leap seconds occur simultaneously around the world.
-- In other words, if a leap second occurs at 23:59:60 GMT, it also occurs
-- on 18:59:60 -5 or 2:59:60 +2 on the next day.
-- Leap seconds do not follow a formula. The International Earth Rotation
-- and Reference System Service decides when to add one. Leap seconds are
-- included in the representation of time in Ada 95 mode. As a result,
-- the following two time values will conceptually differ by two seconds:
end Leap_Sec_Ops;
-- Time_Of (1972, 7, 1, 0.0) - Time_Of (1972, 6, 30, 86_399.0) = 2 secs
procedure Split_With_Offset
(Date : Time;
Year : out Year_Number;
Month : out Month_Number;
Day : out Day_Number;
Seconds : out Day_Duration;
Offset : out Long_Integer);
-- Split_W_Offset has the same spec as Split with the addition of an
-- offset value which give the offset of the local time zone from UTC
-- at the input Date. This value comes for free during the implementation
-- of Split and is needed by UTC_Time_Offset. The returned Offset time
-- is straight from the C tm struct and is in seconds. If the system
-- dependent code has no way to find the offset it will return the value
-- Invalid_TZ_Offset declared below. Otherwise no checking is done, so
-- it is up to the user to check both for Invalid_TZ_Offset and otherwise
-- for a value that is acceptable.
-- When a new leap second is added, the following steps must be carried
-- out:
Invalid_TZ_Offset : Long_Integer;
pragma Import (C, Invalid_TZ_Offset, "__gnat_invalid_tzoff");
-- 1) Increment Leap_Seconds_Count by one
-- 2) Add an entry to the end of table Leap_Second_Dates
-- The algorithms that build the actual leap second values and discover
-- how many leap seconds have occured between two dates do not need any
-- modification.
------------------------------
-- Non-leap centenial years --
------------------------------
-- Over the range of Ada time, centenial years 2100, 2200 and 2300 are
-- non-leap. As a consequence, seven non-leap years occur over the period
-- of year - 4 to year + 4. Internaly, routines Split and Time_Of add or
-- subtract a "fake" February 29 to facilitate the arithmetic involved.
-- This small "cheat" remains hidden and the following calculations do
-- produce the correct difference.
-- Time_Of (2100, 3, 1, 0.0) - Time_Of (2100, 2, 28, 0.0) = 1 day
-- Time_Of (2101, 1, 1, 0.0) - Time_Of (2100, 12, 31, 0.0) = 1 day
type Time_Rep is mod 2 ** 64;
type Time is new Time_Rep;
-- Due to boundary time values and time zones, two days of buffer space
-- are set aside at both end points of Ada time:
-- Abs zero Hard low Soft low Soft high Hard high
-- +---------+============+#################+============+----------->
-- Buffer 1 Real Ada time Buffer 2
-- A time value in a any time zone may not excede the hard bounds of Ada
-- time, while a value in GMT may not go over the soft bounds.
Buffer_D : constant Duration := 2.0 * Secs_In_Day;
Buffer_N : constant Time := 2 * Nanos_In_Day;
-- Lower and upper bound of Ada time shifted by two days from the absolute
-- zero. Note that the upper bound includes the non-leap centenial years.
Ada_Low : constant Time := Buffer_N;
Ada_High : constant Time := (121 * 366 + 378 * 365) * Nanos_In_Day +
Buffer_N;
-- Both of these hard bounds are 28 hours before and after their regular
-- counterpart. The value of 28 is taken from Ada.Calendar.Time_Zones.
Hard_Ada_Low : constant Time := Ada_Low - 100_800 * Nano;
Hard_Ada_High : constant Time := Ada_High + 100_800 * Nano;
Days_In_Month : constant array (Month_Number) of Day_Number :=
(31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31);
Invalid_Time_Zone_Offset : Long_Integer;
pragma Import (C, Invalid_Time_Zone_Offset, "__gnat_invalid_tzoff");
function Is_Leap (Year : Year_Number) return Boolean;
-- Determine whether a given year is leap
-- The following packages provide a target independent interface to the
-- children of Calendar - Arithmetic, Delays, Formatting and Time_Zones.
package Arithmetic_Operations is
function Add (Date : Time; Days : Long_Integer) return Time;
-- Add X number of days to a time value
procedure Difference
(Left : Time;
Right : Time;
Days : out Long_Integer;
Seconds : out Duration;
Leap_Seconds : out Integer);
-- Calculate the difference between two time values in terms of days,
-- seconds and leap seconds elapsed. The leap seconds are not included
-- in the seconds returned. If Left is greater than Right, the returned
-- values are positive, negative otherwise.
function Subtract (Date : Time; Days : Long_Integer) return Time;
-- Subtract X number of days from a time value
end Arithmetic_Operations;
package Delays_Operations is
function To_Duration (Ada_Time : Time) return Duration;
-- Given a time value in nanoseconds since 1901, convert it into a
-- duration value giving the number of nanoseconds since the Unix Epoch.
end Delays_Operations;
package Formatting_Operations is
function Day_Of_Week (Date : Time) return Integer;
-- Determine which day of week Date falls on. The returned values are
-- within the range of 0 .. 6 (Monday .. Sunday).
procedure Split
(Date : Time;
Year : out Year_Number;
Month : out Month_Number;
Day : out Day_Number;
Day_Secs : out Day_Duration;
Hour : out Integer;
Minute : out Integer;
Second : out Integer;
Sub_Sec : out Duration;
Leap_Sec : out Boolean;
Time_Zone : Long_Integer);
-- Split a time value into its components
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;

View File

@ -33,33 +33,15 @@
with Ada.Calendar; use Ada.Calendar;
with Ada.Calendar.Time_Zones; use Ada.Calendar.Time_Zones;
with Unchecked_Conversion;
package body Ada.Calendar.Formatting is
use Leap_Sec_Ops;
--------------------------
-- Implementation Notes --
--------------------------
Days_In_4_Years : constant := 365 * 3 + 366;
Seconds_In_Day : constant := 86_400;
Seconds_In_4_Years : constant := Days_In_4_Years * Seconds_In_Day;
Seconds_In_Non_Leap_Year : constant := 365 * Seconds_In_Day;
-- Exact time bounds for the range of Ada time: January 1, 1901 -
-- December 31, 2099. These bounds are based on the Unix Time of Epoc,
-- January 1, 1970. Start of Time is -69 years from TOE while End of
-- time is +130 years and one second from TOE.
Start_Of_Time : constant Time :=
Time (-(17 * Seconds_In_4_Years +
Seconds_In_Non_Leap_Year));
End_Of_Time : constant Time :=
Time (32 * Seconds_In_4_Years +
2 * Seconds_In_Non_Leap_Year) +
All_Leap_Seconds;
Days_In_Month : constant array (Month_Number) of Day_Number :=
(31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31);
-- All operations in this package are target and time representation
-- independent, thus only one source file is needed for multiple targets.
procedure Check_Char (S : String; C : Character; Index : Integer);
-- Subsidiary to the two versions of Value. Determine whether the
@ -102,19 +84,18 @@ package body Ada.Calendar.Formatting is
(Date : Time;
Time_Zone : Time_Zones.Time_Offset := 0) return Day_Number
is
Year : Year_Number;
Month : Month_Number;
Day : Day_Number;
Hour : Hour_Number;
Minute : Minute_Number;
Second : Second_Number;
Sub_Second : Second_Duration;
Leap_Second : Boolean;
Y : Year_Number;
Mo : Month_Number;
D : Day_Number;
H : Hour_Number;
Mi : Minute_Number;
Se : Second_Number;
Ss : Second_Duration;
Le : Boolean;
begin
Split (Date, Year, Month, Day,
Hour, Minute, Second, Sub_Second, Leap_Second, Time_Zone);
return Day;
Split (Date, Y, Mo, D, H, Mi, Se, Ss, Le, Time_Zone);
return D;
end Day;
-----------------
@ -122,51 +103,8 @@ package body Ada.Calendar.Formatting is
-----------------
function Day_Of_Week (Date : Time) return Day_Name is
Year : Year_Number;
Month : Month_Number;
Day : Day_Number;
Hour : Hour_Number;
Minute : Minute_Number;
Second : Second_Number;
Sub_Second : Second_Duration;
Leap_Second : Boolean;
D : Duration;
Day_Count : Long_Long_Integer;
Midday_Date : Time;
Secs_Count : Long_Long_Integer;
begin
-- Split the Date to obtain the year, month and day, then build a time
-- value for the middle of the same day, so that we don't have to worry
-- about leap seconds in the subsequent arithmetic.
Split (Date, Year, Month, Day,
Hour, Minute, Second, Sub_Second, Leap_Second);
Midday_Date := Time_Of (Year, Month, Day, 12, 0, 0);
D := Midday_Date - Start_Of_Time;
-- D is a positive Duration value counting seconds since 1901. Convert
-- it into an integer for ease of arithmetic.
declare
type D_Int is range 0 .. 2 ** (Duration'Size - 1) - 1;
for D_Int'Size use Duration'Size;
function To_D_Int is new Unchecked_Conversion (Duration, D_Int);
D_As_Int : constant D_Int := To_D_Int (D);
Small_Div : constant D_Int := D_Int (1.0 / Duration'Small);
begin
Secs_Count := Long_Long_Integer (D_As_Int / Small_Div);
end;
Day_Count := Secs_Count / Seconds_In_Day;
Day_Count := Day_Count + 1; -- Jan 1, 1901 was a Tuesday;
return Day_Name'Val (Day_Count mod 7);
return Day_Name'Val (Formatting_Operations.Day_Of_Week (Date));
end Day_Of_Week;
----------
@ -177,19 +115,18 @@ package body Ada.Calendar.Formatting is
(Date : Time;
Time_Zone : Time_Zones.Time_Offset := 0) return Hour_Number
is
Year : Year_Number;
Month : Month_Number;
Day : Day_Number;
Hour : Hour_Number;
Minute : Minute_Number;
Second : Second_Number;
Sub_Second : Second_Duration;
Leap_Second : Boolean;
Y : Year_Number;
Mo : Month_Number;
D : Day_Number;
H : Hour_Number;
Mi : Minute_Number;
Se : Second_Number;
Ss : Second_Duration;
Le : Boolean;
begin
Split (Date, Year, Month, Day,
Hour, Minute, Second, Sub_Second, Leap_Second, Time_Zone);
return Hour;
Split (Date, Y, Mo, D, H, Mi, Se, Ss, Le, Time_Zone);
return H;
end Hour;
-----------
@ -377,19 +314,17 @@ package body Ada.Calendar.Formatting is
(Date : Time;
Time_Zone : Time_Zones.Time_Offset := 0) return Minute_Number
is
Year : Year_Number;
Month : Month_Number;
Day : Day_Number;
Hour : Hour_Number;
Minute : Minute_Number;
Second : Second_Number;
Sub_Second : Second_Duration;
Leap_Second : Boolean;
Y : Year_Number;
Mo : Month_Number;
D : Day_Number;
H : Hour_Number;
Mi : Minute_Number;
Se : Second_Number;
Ss : Second_Duration;
Le : Boolean;
begin
Split (Date, Year, Month, Day,
Hour, Minute, Second, Sub_Second, Leap_Second, Time_Zone);
return Minute;
Split (Date, Y, Mo, D, H, Mi, Se, Ss, Le, Time_Zone);
return Mi;
end Minute;
-----------
@ -400,19 +335,17 @@ package body Ada.Calendar.Formatting is
(Date : Time;
Time_Zone : Time_Zones.Time_Offset := 0) return Month_Number
is
Year : Year_Number;
Month : Month_Number;
Day : Day_Number;
Hour : Hour_Number;
Minute : Minute_Number;
Second : Second_Number;
Sub_Second : Second_Duration;
Leap_Second : Boolean;
Y : Year_Number;
Mo : Month_Number;
D : Day_Number;
H : Hour_Number;
Mi : Minute_Number;
Se : Second_Number;
Ss : Second_Duration;
Le : Boolean;
begin
Split (Date, Year, Month, Day,
Hour, Minute, Second, Sub_Second, Leap_Second, Time_Zone);
return Month;
Split (Date, Y, Mo, D, H, Mi, Se, Ss, Le, Time_Zone);
return Mo;
end Month;
------------
@ -420,19 +353,17 @@ package body Ada.Calendar.Formatting is
------------
function Second (Date : Time) return Second_Number is
Year : Year_Number;
Month : Month_Number;
Day : Day_Number;
Hour : Hour_Number;
Minute : Minute_Number;
Second : Second_Number;
Sub_Second : Second_Duration;
Leap_Second : Boolean;
Y : Year_Number;
Mo : Month_Number;
D : Day_Number;
H : Hour_Number;
Mi : Minute_Number;
Se : Second_Number;
Ss : Second_Duration;
Le : Boolean;
begin
Split (Date, Year, Month, Day,
Hour, Minute, Second, Sub_Second, Leap_Second);
return Second;
Split (Date, Y, Mo, D, H, Mi, Se, Ss, Le);
return Se;
end Second;
----------------
@ -456,9 +387,9 @@ package body Ada.Calendar.Formatting is
raise Constraint_Error;
end if;
return Day_Duration (Hour * 3600) +
Day_Duration (Minute * 60) +
Day_Duration (Second) +
return Day_Duration (Hour * 3_600) +
Day_Duration (Minute * 60) +
Day_Duration (Second) +
Sub_Second;
end Seconds_Of;
@ -489,10 +420,20 @@ package body Ada.Calendar.Formatting is
end if;
Sub_Second := Second_Duration (Seconds - Day_Duration (Secs));
Hour := Hour_Number (Secs / 3600);
Secs := Secs mod 3600;
Hour := Hour_Number (Secs / 3_600);
Secs := Secs mod 3_600;
Minute := Minute_Number (Secs / 60);
Second := Second_Number (Secs mod 60);
-- Validity checks
if not Hour'Valid
or else not Minute'Valid
or else not Second'Valid
or else not Sub_Second'Valid
then
raise Time_Error;
end if;
end Split;
-----------
@ -508,16 +449,25 @@ package body Ada.Calendar.Formatting is
Leap_Second : out Boolean;
Time_Zone : Time_Zones.Time_Offset := 0)
is
Hour : Hour_Number;
Minute : Minute_Number;
Second : Second_Number;
Sub_Second : Second_Duration;
H : Integer;
M : Integer;
Se : Integer;
Su : Duration;
Tz : constant Long_Integer := Long_Integer (Time_Zone);
begin
Split (Date, Year, Month, Day,
Hour, Minute, Second, Sub_Second, Leap_Second, Time_Zone);
Formatting_Operations.Split
(Date, Year, Month, Day, Seconds, H, M, Se, Su, Leap_Second, Tz);
Seconds := Seconds_Of (Hour, Minute, Second, Sub_Second);
-- Validity checks
if not Year'Valid
or else not Month'Valid
or else not Day'Valid
or else not Seconds'Valid
then
raise Time_Error;
end if;
end Split;
-----------
@ -535,11 +485,27 @@ package body Ada.Calendar.Formatting is
Sub_Second : out Second_Duration;
Time_Zone : Time_Zones.Time_Offset := 0)
is
Leap_Second : Boolean;
Dd : Day_Duration;
Le : Boolean;
Tz : constant Long_Integer := Long_Integer (Time_Zone);
begin
Split (Date, Year, Month, Day,
Hour, Minute, Second, Sub_Second, Leap_Second, Time_Zone);
Formatting_Operations.Split
(Date, Year, Month, Day, Dd,
Hour, Minute, Second, Sub_Second, Le, Tz);
-- Validity checks
if not Year'Valid
or else not Month'Valid
or else not Day'Valid
or else not Hour'Valid
or else not Minute'Valid
or else not Second'Valid
or else not Sub_Second'Valid
then
raise Time_Error;
end if;
end Split;
-----------
@ -558,139 +524,26 @@ package body Ada.Calendar.Formatting is
Leap_Second : out Boolean;
Time_Zone : Time_Zones.Time_Offset := 0)
is
Ada_Year_Min : constant Year_Number := Year_Number'First;
Day_In_Year : Integer;
Day_Second : Integer;
Elapsed_Leaps : Duration;
Hour_Second : Integer;
In_Leap_Year : Boolean;
Modified_Date : Time;
Next_Leap : Time;
Remaining_Years : Integer;
Seconds_Count : Long_Long_Integer;
Dd : Day_Duration;
Tz : constant Long_Integer := Long_Integer (Time_Zone);
begin
-- Our measurement of time is the number of seconds that have elapsed
-- since the Unix TOE. To calculate a UTC date from this we do a
-- sequence of divides and mods to get the components of a date based
-- on 86,400 seconds in each day. Since, UTC time depends upon the
-- occasional insertion of leap seconds, the number of leap seconds
-- that have been added prior to the input time are then subtracted
-- from the previous calculation. In fact, it is easier to do the
-- subtraction first, so a more accurate discription of what is
-- actually done, is that the number of added leap seconds is looked
-- up using the input Time value, than that number of seconds is
-- subtracted before the sequence of divides and mods.
--
-- If the input date turns out to be a leap second, we don't add it to
-- date (we want to return 23:59:59) but we set the Leap_Second output
-- to true.
Formatting_Operations.Split
(Date, Year, Month, Day, Dd,
Hour, Minute, Second, Sub_Second, Leap_Second, Tz);
-- Is there a need to account for a difference from Unix time prior
-- to the first leap second ???
-- Validity checks
-- Step 1: Determine the number of leap seconds since the start
-- of Ada time and the input date as well as the next leap second
-- occurence and process accordingly.
Cumulative_Leap_Secs (Start_Of_Time, Date, Elapsed_Leaps, Next_Leap);
Leap_Second := Date >= Next_Leap;
Modified_Date := Date - Elapsed_Leaps;
if Leap_Second then
Modified_Date := Modified_Date - Duration (1.0);
end if;
-- Step 2: Process the time zone
Modified_Date := Modified_Date + Duration (Time_Zone * 60);
-- Step 3: Sanity check on the calculated date. Since the leap
-- seconds and the time zone have been eliminated, the result needs
-- to be within the range of Ada time.
if Modified_Date < Start_Of_Time
or else Modified_Date >= (End_Of_Time - All_Leap_Seconds)
if not Year'Valid
or else not Month'Valid
or else not Day'Valid
or else not Hour'Valid
or else not Minute'Valid
or else not Second'Valid
or else not Sub_Second'Valid
then
raise Time_Error;
end if;
Modified_Date := Modified_Date - Start_Of_Time;
declare
type D_Int is range 0 .. 2 ** (Duration'Size - 1) - 1;
for D_Int'Size use Duration'Size;
function To_D_Int is new Unchecked_Conversion (Duration, D_Int);
function To_Duration is new Unchecked_Conversion (D_Int, Duration);
function To_Duration is new Unchecked_Conversion (Time, Duration);
D_As_Int : constant D_Int := To_D_Int (To_Duration (Modified_Date));
Small_Div : constant D_Int := D_Int (1.0 / Duration'Small);
begin
Seconds_Count := Long_Long_Integer (D_As_Int / Small_Div);
Sub_Second := Second_Duration
(To_Duration (D_As_Int rem Small_Div));
end;
-- Step 4: Calculate the number of years since the start of Ada time.
-- First consider sequences of four years, then the remaining years.
Year := Ada_Year_Min + 4 * Integer (Seconds_Count / Seconds_In_4_Years);
Seconds_Count := Seconds_Count mod Seconds_In_4_Years;
Remaining_Years := Integer (Seconds_Count / Seconds_In_Non_Leap_Year);
if Remaining_Years > 3 then
Remaining_Years := 3;
end if;
Year := Year + Remaining_Years;
-- Remove the seconds elapsed in those remaining years
Seconds_Count := Seconds_Count - Long_Long_Integer
(Remaining_Years * Seconds_In_Non_Leap_Year);
In_Leap_Year := (Year mod 4) = 0;
-- Step 5: Month and day processing. Determine the day to which the
-- remaining seconds map to.
Day_In_Year := Integer (Seconds_Count / Seconds_In_Day) + 1;
Month := 1;
if Day_In_Year > 31 then
Month := 2;
Day_In_Year := Day_In_Year - 31;
if Day_In_Year > 28
and then ((not In_Leap_Year)
or else Day_In_Year > 29)
then
Month := 3;
Day_In_Year := Day_In_Year - 28;
if In_Leap_Year then
Day_In_Year := Day_In_Year - 1;
end if;
while Day_In_Year > Days_In_Month (Month) loop
Day_In_Year := Day_In_Year - Days_In_Month (Month);
Month := Month + 1;
end loop;
end if;
end if;
-- Step 6: Hour, minute and second processing
Day := Day_In_Year;
Day_Second := Integer (Seconds_Count mod Seconds_In_Day);
Hour := Day_Second / 3600;
Hour_Second := Day_Second mod 3600;
Minute := Hour_Second / 60;
Second := Hour_Second mod 60;
end Split;
----------------
@ -698,20 +551,17 @@ package body Ada.Calendar.Formatting is
----------------
function Sub_Second (Date : Time) return Second_Duration is
Year : Year_Number;
Month : Month_Number;
Day : Day_Number;
Hour : Hour_Number;
Minute : Minute_Number;
Second : Second_Number;
Sub_Second : Second_Duration;
Leap_Second : Boolean;
Y : Year_Number;
Mo : Month_Number;
D : Day_Number;
H : Hour_Number;
Mi : Minute_Number;
Se : Second_Number;
Ss : Second_Duration;
Le : Boolean;
begin
Split (Date, Year, Month, Day,
Hour, Minute, Second, Sub_Second, Leap_Second);
return Sub_Second;
Split (Date, Y, Mo, D, H, Mi, Se, Ss, Le);
return Ss;
end Sub_Second;
-------------
@ -726,79 +576,56 @@ package body Ada.Calendar.Formatting is
Leap_Second : Boolean := False;
Time_Zone : Time_Zones.Time_Offset := 0) return Time
is
Hour : Hour_Number;
Minute : Minute_Number;
Sec_Num : Second_Number;
Sub_Sec : Second_Duration;
Whole_Part : Integer;
Adj_Year : Year_Number := Year;
Adj_Month : Month_Number := Month;
Adj_Day : Day_Number := Day;
H : constant Integer := 1;
M : constant Integer := 1;
Se : constant Integer := 1;
Ss : constant Duration := 0.1;
Tz : constant Long_Integer := Long_Integer (Time_Zone);
begin
if not Seconds'Valid then
-- Validity checks
if not Year'Valid
or else not Month'Valid
or else not Day'Valid
or else not Seconds'Valid
or else not Time_Zone'Valid
then
raise Constraint_Error;
end if;
-- The fact that Seconds can go to 86,400 creates all this extra work.
-- Perhaps a Time_Of just like the next one but allowing the Second_
-- Number input to reach 60 should become an internal version that this
-- and the next version call.... but for now we do the ugly bumping up
-- of Day, Month and Year;
-- A Seconds value of 86_400 denotes a new day. This case requires an
-- adjustment to the input values.
if Seconds = 86_400.0 then
declare
Adj_Year : Year_Number := Year;
Adj_Month : Month_Number := Month;
Adj_Day : Day_Number := Day;
if Day < Days_In_Month (Month)
or else (Is_Leap (Year)
and then Month = 2)
then
Adj_Day := Day + 1;
else
Adj_Day := 1;
begin
Hour := 0;
Minute := 0;
Sec_Num := 0;
Sub_Sec := 0.0;
if Day < Days_In_Month (Month)
or else (Month = 2
and then Year mod 4 = 0)
then
Adj_Day := Day + 1;
if Month < 12 then
Adj_Month := Month + 1;
else
Adj_Day := 1;
if Month < 12 then
Adj_Month := Month + 1;
else
Adj_Month := 1;
Adj_Year := Year + 1;
end if;
Adj_Month := 1;
Adj_Year := Year + 1;
end if;
return Time_Of (Adj_Year, Adj_Month, Adj_Day, Hour, Minute,
Sec_Num, Sub_Sec, Leap_Second, Time_Zone);
end;
end if;
end if;
declare
type D_Int is range 0 .. 2 ** (Duration'Size - 1) - 1;
for D_Int'Size use Duration'Size;
function To_D_Int is new Unchecked_Conversion (Duration, D_Int);
function To_Duration is new Unchecked_Conversion (D_Int, Duration);
D_As_Int : constant D_Int := To_D_Int (Seconds);
Small_Div : constant D_Int := D_Int (1.0 / Duration'Small);
begin
Whole_Part := Integer (D_As_Int / Small_Div);
Sub_Sec := Second_Duration
(To_Duration (D_As_Int rem Small_Div));
end;
Hour := Hour_Number (Whole_Part / 3600);
Whole_Part := Whole_Part mod 3600;
Minute := Minute_Number (Whole_Part / 60);
Sec_Num := Second_Number (Whole_Part mod 60);
return Time_Of (Year, Month, Day,
Hour, Minute, Sec_Num, Sub_Sec, Leap_Second, Time_Zone);
return
Formatting_Operations.Time_Of
(Adj_Year, Adj_Month, Adj_Day, Seconds, H, M, Se, Ss,
Leap_Sec => Leap_Second,
Leap_Checks => True,
Use_Day_Secs => True,
Time_Zone => Tz);
end Time_Of;
-------------
@ -816,23 +643,11 @@ package body Ada.Calendar.Formatting is
Leap_Second : Boolean := False;
Time_Zone : Time_Zones.Time_Offset := 0) return Time
is
Cumulative_Days_Before_Month :
constant array (Month_Number) of Natural :=
(0, 31, 59, 90, 120, 151, 181, 212, 243, 273, 304, 334);
Ada_Year_Min : constant Year_Number := Year_Number'First;
Count : Integer;
Elapsed_Leap_Seconds : Duration;
Fractional_Second : Duration;
Next_Leap : Time;
Result : Time;
Dd : constant Day_Duration := Day_Duration'First;
Tz : constant Long_Integer := Long_Integer (Time_Zone);
begin
-- The following checks are redundant with respect to the constraint
-- error checks that should normally be made on parameters, but we
-- decide to raise Constraint_Error in any case if bad values come in
-- (as a result of checks being off in the caller, or for other
-- erroneous or bounded error cases).
-- Validity checks
if not Year'Valid
or else not Month'Valid
@ -846,99 +661,13 @@ package body Ada.Calendar.Formatting is
raise Constraint_Error;
end if;
-- Start the accumulation from the beginning of Ada time
Result := Start_Of_Time;
-- Step 1: Determine the number of leap and non-leap years since 1901
-- and the input date.
-- Count the number of four year segments
Count := (Year - Ada_Year_Min) / 4;
Result := Result + Duration (Count * Seconds_In_4_Years);
-- Count the number of remaining non-leap years
Count := (Year - Ada_Year_Min) mod 4;
Result := Result + Duration (Count * Seconds_In_Non_Leap_Year);
-- Step 2: Determine the number of days elapsed singe the start of the
-- input year and add them to the result.
-- Do not include the current day since it is not over yet
Count := Cumulative_Days_Before_Month (Month) + Day - 1;
-- The input year is a leap year and we have passed February
if (Year mod 4) = 0
and then Month > 2
then
Count := Count + 1;
end if;
Result := Result + Duration (Count * Seconds_In_Day);
-- Step 3: Hour, minute and second processing
Result := Result + Duration (Hour * 3600) +
Duration (Minute * 60) +
Duration (Second);
-- The sub second may designate a whole second
if Sub_Second = 1.0 then
Result := Result + Duration (1.0);
Fractional_Second := 0.0;
else
Fractional_Second := Sub_Second;
end if;
-- Step 4: Time zone processing
Result := Result - Duration (Time_Zone * 60);
-- Step 5: The caller wants a leap second
if Leap_Second then
Result := Result + Duration (1.0);
end if;
-- Step 6: Calculate the number of leap seconds occured since the
-- start of Ada time and the current point in time. The following
-- is an approximation which does not yet count leap seconds. It
-- can be pushed beyond 1 leap second, but not more.
Cumulative_Leap_Secs
(Start_Of_Time, Result, Elapsed_Leap_Seconds, Next_Leap);
Result := Result + Elapsed_Leap_Seconds;
-- Step 7: Validity check of a leap second occurence. It requires an
-- additional comparison to Next_Leap to ensure that we landed right
-- on a valid occurence and that Elapsed_Leap_Seconds did not shoot
-- past it.
if Leap_Second
and then
not (Result >= Next_Leap
and then Result - Duration (1.0) < Next_Leap)
then
raise Time_Error;
end if;
-- Step 8: Final sanity check on the calculated duration value
if Result < Start_Of_Time
or else Result >= End_Of_Time
then
raise Time_Error;
end if;
-- Step 9: Lastly, add the sub second part
return Result + Fractional_Second;
return
Formatting_Operations.Time_Of
(Year, Month, Day, Dd, Hour, Minute, Second, Sub_Second,
Leap_Sec => Leap_Second,
Leap_Checks => True,
Use_Day_Secs => False,
Time_Zone => Tz);
end Time_Of;
-----------
@ -1117,19 +846,18 @@ package body Ada.Calendar.Formatting is
(Date : Time;
Time_Zone : Time_Zones.Time_Offset := 0) return Year_Number
is
Year : Year_Number;
Month : Month_Number;
Day : Day_Number;
Hour : Hour_Number;
Minute : Minute_Number;
Second : Second_Number;
Sub_Second : Second_Duration;
Leap_Second : Boolean;
Y : Year_Number;
Mo : Month_Number;
D : Day_Number;
H : Hour_Number;
Mi : Minute_Number;
Se : Second_Number;
Ss : Second_Duration;
Le : Boolean;
begin
Split (Date, Year, Month, Day,
Hour, Minute, Second, Sub_Second, Leap_Second, Time_Zone);
return Year;
Split (Date, Y, Mo, D, H, Mi, Se, Ss, Le, Time_Zone);
return Y;
end Year;
end Ada.Calendar.Formatting;

View File

@ -6,7 +6,7 @@
-- --
-- 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 --
-- GNAT. The copyright notice above, and the license provisions that follow --
@ -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;
package Ada.Calendar.Formatting is
@ -84,6 +88,12 @@ package Ada.Calendar.Formatting is
Minute : Minute_Number;
Second : Second_Number := 0;
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
(Seconds : Day_Duration;
@ -91,6 +101,9 @@ package Ada.Calendar.Formatting is
Minute : out Minute_Number;
Second : out Second_Number;
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
(Date : Time;
@ -102,6 +115,9 @@ package Ada.Calendar.Formatting is
Second : out Second_Number;
Sub_Second : out Second_Duration;
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
(Year : Year_Number;
@ -113,6 +129,14 @@ package Ada.Calendar.Formatting is
Sub_Second : Second_Duration := 0.0;
Leap_Second : Boolean := False;
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
(Year : Year_Number;
@ -121,6 +145,14 @@ package Ada.Calendar.Formatting is
Seconds : Day_Duration := 0.0;
Leap_Second : Boolean := False;
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
(Date : Time;
@ -133,6 +165,14 @@ package Ada.Calendar.Formatting is
Sub_Second : out Second_Duration;
Leap_Second : out Boolean;
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
(Date : Time;
@ -142,6 +182,14 @@ package Ada.Calendar.Formatting is
Seconds : out Day_Duration;
Leap_Second : out Boolean;
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
@ -149,15 +197,39 @@ package Ada.Calendar.Formatting is
(Date : Time;
Include_Time_Fraction : Boolean := False;
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
(Date : String;
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
(Elapsed_Time : Duration;
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;
-- 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;

View File

@ -33,35 +33,39 @@
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 --
---------------------
function UTC_Time_Offset (Date : Time := Clock) return Time_Offset is
Year : Year_Number;
Month : Month_Number;
Day : Day_Number;
Seconds : Day_Duration;
Offset : Long_Integer;
Offset_L : constant Long_Integer :=
Time_Zones_Operations.UTC_Time_Offset (Date);
Offset : Time_Offset;
begin
Split_With_Offset (Date, Year, Month, Day, Seconds, Offset);
-- The system dependent code does not support time zones
if Offset = Invalid_TZ_Offset then
if Offset_L = Invalid_Time_Zone_Offset then
raise Unknown_Zone_Error;
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.
if Offset < Long_Integer (Time_Offset'First)
or else Offset > Long_Integer (Time_Offset'Last)
then
Offset := Time_Offset (Offset_L / 60);
-- Validity checks
if not Offset'Valid then
raise Unknown_Zone_Error;
end if;
return Time_Offset (Offset);
return Offset;
end UTC_Time_Offset;
end Ada.Calendar.Time_Zones;

View File

@ -6,7 +6,7 @@
-- --
-- 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 --
-- GNAT. The copyright notice above, and the license provisions that follow --
@ -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
-- Time zone manipulation
@ -44,5 +47,9 @@ package Ada.Calendar.Time_Zones is
Unknown_Zone_Error : exception;
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;

View File

@ -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.Strings.Unbounded; use Ada.Strings.Unbounded;
with Ada.Unchecked_Deallocation;
with Ada.Unchecked_Conversion;
with Ada.Characters.Handling; use Ada.Characters.Handling;
with GNAT.Directory_Operations; use GNAT.Directory_Operations;
@ -46,13 +47,6 @@ with System;
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
Is_Valid : Boolean := False;
Name : Ada.Strings.Unbounded.Unbounded_String;
@ -724,7 +718,7 @@ package body Ada.Directories is
-- Modification_Time --
-----------------------
function Modification_Time (Name : String) return Ada.Calendar.Time is
function Modification_Time (Name : String) return Time is
Date : OS_Time;
Year : Year_Type;
Month : Month_Type;
@ -732,8 +726,7 @@ package body Ada.Directories is
Hour : Hour_Type;
Minute : Minute_Type;
Second : Second_Type;
Result : Ada.Calendar.Time;
Result : Time;
begin
-- First, the invalid cases
@ -744,26 +737,31 @@ package body Ada.Directories is
else
Date := File_Time_Stamp (Name);
-- ??? This implementation should be revisited when AI 00351 has
-- implemented.
-- Break down the time stamp into its constituents relative to GMT.
-- This version of Split does not recognize leap seconds or buffer
-- space for time zone processing.
GM_Split (Date, Year, Month, Day, Hour, Minute, Second);
-- 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.
if OpenVMS then
Result :=
Ada.Calendar.Time_Of
(Year, Month, Day, Seconds_Of (Hour, Minute, Second, 0.0));
-- On OpenVMS, OS_Time is in local time
GM_Split (Date, Year, Month, Day, Hour, Minute, Second);
return Ada.Calendar.Time_Of
(Year, Month, Day,
Duration (Second + 60 * (Minute + 60 * Hour)));
-- On Unix and Windows, the result must be in GMT. Ada.Calendar.
-- Formatting.Time_Of with default time zone of zero (0) is the
-- routine of choice.
else
-- On Unix and Windows, OS_Time is in GMT
Result :=
Duration_To_Time (Duration (OS_Time_To_Long_Integer (Date)));
return Result;
Result := Time_Of (Year, Month, Day, Hour, Minute, Second, 0.0);
end if;
return Result;
end if;
end Modification_Time;

View File

@ -687,7 +687,7 @@ get_gmtoff (void)
/* 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
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;
@ -755,8 +755,9 @@ __gnat_localtime_tzoff (const time_t *, struct tm *, long *);
struct tm *
__gnat_localtime_tzoff (const time_t *timer, struct tm *tp, long *off)
{
/* Treat all time values in GMT */
localtime_r (tp, timer);
*off = __gnat_invalid_tzoff;
*off = 0;
return NULL;
}
@ -779,17 +780,60 @@ __gnat_localtime_tzoff (const time_t *timer, struct tm *tp, long *off)
/* AIX, HPUX, SGI Irix, Sun Solaris */
#if defined (_AIX) || defined (__hpux__) || defined (sgi) || defined (sun)
*off = (long) -timezone;
if (tp->tm_isdst > 0)
*off = *off + 3600;
/* The contents of external variable "timezone" may not always be
initialized. Instead of returning an incorrect offset, treat the local
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;
/* Lynx, VXWorks */
#elif defined (__Lynx__) || defined (__vxworks)
*off = __gnat_invalid_tzoff;
/* 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");
/* Darwin, Free BSD, Linux, Tru64 */
#else
if ((tz_str == NULL) || (*tz_str == '\0'))
*off = 0;
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, where there exists a component tm_gmtoff
in struct tm */
#elif defined (__APPLE__) || defined (__FreeBSD__) || defined (linux) ||\
(defined (__alpha__) && defined (__osf__))
*off = tp->tm_gmtoff;
/* All other platforms: Treat all time values in GMT */
#else
*off = 0;
#endif
return NULL;
}
@ -797,3 +841,59 @@ __gnat_localtime_tzoff (const time_t *timer, struct tm *tp, long *off)
#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__ */