Time library
Simon Marlow
simonmar@microsoft.com
Thu, 31 Jul 2003 12:42:00 +0100
The discussion on the new Time library has petered out a little; I want
to get this settled and implemented, so let's try to round it off.
When we last left the discussion, the conclusion was that having a
ClockTime defined in terms of TAI was not implementable, because we
can't tell whether the system clock is running POSIX time_t or a variant
that is correct and includes leap seconds. (please correct me if I'm
wrong).
If the system clock is running POSIX time_t, then it is possible to
determine the correct TAI time, given a table of leap seconds. There
was some feeling that it shouldn't be our responsibility to do this,
that the system should provide us with correct time in the first place.
I'm inclined to agree (it's less work for those of us who have to
implement this stuff after all :-).
So, given this, I've updated the proposal to include everything
discussed so far and to note the fact that having a correct ClockTime is
at the mercy of the system.
Complete proposal below, please comment.
Cheers,
Simon
--
------------------------------------------------------------------------
-
-- * ClockTime
-- | A representation of absolute time, measured as picoseconds since
-- the epoch, where the epoch is 1 January 1970 00:10 TAI.
data ClockTime -- abstract
instance of (Eq, Ord, Num, Enum, Integral, Show, Read)
-- | returns the current absolute time
getClockTime :: IO ClockTime
{-
Rationale:
- Our ClockTime is defined in terms of TAI, because this provides an
absolute time scale and can be used for accurate time
calculations.
However, this is not always implementable. Many systems run their
system clocks on a time scale that ignores leap seconds. For
example, POSIX's time_t uses a broken notion of "seconds since the
epoch", defined by a formula in terms of UTC time ignoring leap
seconds.
The effect of time_t is that the epoch moves forward in absolute
terms each time there is a leap second. A system whose clock is
following time_t must move its clock back by one second when a
leap second occurs (the NTP client usually does this).
ClockTime uses the system time, and on systems which run their
system clocks according to POSIX time_t, ClockTime will be
equivalent to time_t. =20
Of course, regardless of whether ClockTime is based on TAI or not,
conversions between ClockTime and CalendarTime will yield the
correct results. If your system clock is set correctly, then
obtaining the current time as a CalendarTime will give you the
correct local time.
-}
--
------------------------------------------------------------------------
-
-- * Timezone
data Timezone -- abstract
-- | Make a 'Timezone' from an offset, in seconds relative to UTC,
-- which must be smaller in magnitude than @+/-12*60*60@.
timezoneFromUTCOffset :: Int -> Timezone
-- | Make a 'Timezone' from a standard timezone name (eg. GMT, PDT).
-- TAI is a valid timezone name.
timezoneFromName :: String -> Maybe Timezone
-- | Return the offset in seconds of the specified timezone relative
-- to UTC. If the timezone is TAI, returns 'Nothing', because TAI
-- cannot be represented as a fixed offset relative to UTC.
timezoneUTCOffset :: Timezone -> Maybe Int
-- | Return the timezone name corresponding to a 'Timezone' value.
--
-- Some timezones may not correspond to a name, or the name of the
timezone
-- may not be known (some systems cannot convert easily from UTC offsets
to
-- timezone names), in which case 'timezoneName' returns 'Nothing'.
timezoneName :: Timezone -> Maybe String
-- | Returns the current timezone from the environment. On Unix, the=20
-- current timezone is taken from the @TZ@ environment variable, or
-- the system default if @TZ@ is not set.
getCurrentTimezone :: IO Timezone
------------------------------------------------------------------------
----
-- * CalendarTime
data CalendarTime=20
=3D CalendarTime {
ctYear :: Int,
ctMonth :: Month,
ctDay :: Int,
ctHour :: Int,
ctMin :: Int,
ctSec :: Int,
ctPicosec :: Integer,
ctTZ :: Timezone
}
deriving (Eq, Ord, Read, Show)
-- | Converts a 'ClockTime' to a 'CalendarTime' in UTC. =20
--
-- Note that this function may produce unpredictable results for
-- times sufficiently far in the future, because it is not known
-- when leap seconds will need to be added to or subtracted from
-- UTC. Note that this doesn't apply if the timezone is TAI.
--
clockTimeToUTCTime :: ClockTime -> CalendarTime
-- | Converts a 'ClockTime' to a 'CalendarTime' in the current timezone.
-- Caveats for 'clockTimeToUTCTime' also apply here.
clockTimeToCalendarTime :: ClockTime -> IO CalendarTime
-- | Converts a 'ClockTime' to a 'CalendarTime' in the specified
timezone.
-- Caveats for 'clockTimeToUTCTime' also apply here.
clockTimeToCalendarTimeTZ :: Timezone -> ClockTime -> CalendarTime
-- | Convert a 'CalendarTime' to a 'ClockTime'. Some values of
-- 'CalendarTime' do not represent a valid 'ClockTime', hence this
-- function returns a 'Maybe' type.
calendarTimeToClockTime :: CalendarTime -> Maybe ClockTime
{-
TODO: add isDSTCalendarTime? (returns True if the specified
CalendarTime is in daylight savings). How do we say "what's the
current timezone in X", taking into account DST?
-}
{-
TODO: should we have
getLeapSeconds :: [ClockTime]
a possibly infinite list of leap seconds in strictly increasing
order. This would allow simple conversion between TAI and UTC.
-}
{-
OPTIONAL: these are hard to implement, and require
careful specification (see rationale below):
addPicoseconds :: CalendarTime -> Integer -> CalendarTime
addSeconds :: CalendarTime -> Integer -> CalendarTime
addMinutes :: CalendarTime -> Integer -> CalendarTime
addDays :: CalendarTime -> Integer -> CalendarTime
addWeeks :: CalendarTime -> Integer -> CalendarTime
addMonths :: CalendarTime -> Integer -> CalendarTime
addYears :: CalendarTime -> Integer -> CalendarTime
Rationale:=20
=20
- Adding "irregular" time differences should be done on
CalendarTimes, because these operations depend on the timezone.
- Need to define the meaning when the offset doesn't exist.
eg. adding a day at the end of the month clearly rolls over
into the next month. But what about adding a month to
January 31st?
- Note that addPicoseconds and addSeconds cannot be implemented
without access to leap second tables. However, all the others
can be implemented using simple calendar arithmetic (including
leap years). If the timezone is TAI, then addPicoseconds and
addSeconds can be implemented without leap second knowledge, of
course.
OR: we could provide
normalizeCalendarTime :: CalendarTime -> CalendarTime
where the following invariant holds:
forall t . isJust (calendarTimeToClockTime (normalizeCalendarTime
t))
that is, normalizeCalendarTime turns a possibly invalid CalendarTime
into a valid one.
The intention is that addDays could be implemented as:
addDays t days =3D normalizeCalendarTime t{ ctDays =3D ctDays t + =
days }
We still need to specify what exactly normalizeCalendarTime does,
however. Presumably it needs to know about leap seconds, for example,
but
only for rolling over the seconds and picoseconds fields. The other
fields of CalendarTime can be normalised using ordinary calendar
calculations.
-}