Time library discussion (reprise)

Simon Marlow simonmar at microsoft.com
Wed Nov 12 11:41:42 EST 2003


 
> As I understand it, calendar time calculations into the
> future are _always_ inaccurate, because UTC is not
> continuous. Either you'll get an incorrect "duration" or
> you'll get an incorrect "point in time". It can't be helped.
> 
> The C++ time library of the Boost effort has a very
> interesting discussion of this topic, available here:
> 
>     http://boost.org/libs/date_time/doc/Tradeoffs.html

Thanks for the link, that's a very good summary of some of the issues.

The tradeoffs page seems to indicate that you can do calculations with TAI times, but I couldn't see how to do that with the
library, and it looks like ptime is equivalent to a POSIX time_t.

They have an interesting separation between calendar calculations (day resolution) and time calculations (sub-second resolution?).
I couldn't immediately see the reason for that.  Is this something we should be doing too?

Anyway, I've attached the current state of the proposal below.  As far as I'm aware, this proposal is just fine with the caveats
listed in the comments, and additionally with the caveat that I'm not sure if the full generality of the timezone manipluation
provided can be implemented on top of the existing Unix APIs, so we might have to scale it back a bit.

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.

    On systems which run their clocks on time_t time, the library will
    do its best to convert to TAI time for a ClockTime.  The effect
    is that the ClockTime might be incorrect by up to 1 second around
    the time of a leap second (it depends on how your system adjusts
    its clock when a leap second occurs).  

    Regardless of what the system supports, calculations on values of
    type ClockTime are well-defined and deterministic.  Inaccuracies
    only occur at the boundaries:

     - getClockTime might be inaccurate on Unix systems, for the
       reasons mentioned above.

     - Converting a ClockTime representing a future time into a 
       UTC-based CalendarTime might be inaccurate because of the
       lack of knowledge of future leap seconds.  This problem
       will be present in any library providing UTC operations.
-}

{- 
TODO: maybe also provide

   toPosixTime :: ClockTime -> Integer
   fromPosixTime :: Integer -> ClockTime 
-}

-- -------------------------------------------------------------------------
-- * 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 at .
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 
-- current timezone is taken from the @TZ@ environment variable, or
-- the system default if @TZ@ is not set.
getCurrentTimezone :: IO Timezone

{- 
  TODO; we also might want to allow rfc2822 style timezones. of the form
  "+nnnn" where nnnn is the offset from GMT. convienince routines to
  convert to/from rfc2822 time strings might be handy too. this is all
  not as important as it could be done in an add-in library, but might
  get common usage.
-}

-- -------------------------------------------------------------------------
-- * CalendarTime

data CalendarTime 
 = 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.  
--
--   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: 
 
   - 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 = normalizeCalendarTime t{ ctDays = 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.
-}



More information about the Libraries mailing list