Concerning Time.TimeDiff

Simon Marlow simonmar@microsoft.com
Fri, 20 Jun 2003 15:20:39 +0100


New version of the System.Time proposal attached below.  I've incorporated most of the comments so far.  Changes relative to the
last version:

   - ClockTime is now abstract

   - TimeDiff and associated operations have gone altogether, since
     ClockTime is an instance of Num they aren't necessary.  This
     is perhaps controversial, since there is less type safety now
     (you can mix time differences with absolute times), but the
     alternative is to remove the Num instance from ClockTime.
   
   - Timezone offsets are in minutes (apparently this is necessary - 
     if someone could provide a reference I'd be grateful).  It's
     just occurred to me that since TAI is a valid timezone name, 
     it isn't always sensible to ask what the "timezone offset" is.

   - added getCurrentTimezone

   - added clockTimeToCalendarTimeTZ
 
   - added notes to clockTimeToCalendarTime about possible problems
     with times in the future.

   - added notes about possible normalizeCalendarTime operation.

Thanks for all the input so far, I think we might be converging!

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:

  - 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.
    Our ClockTime is defined so as to avoid this brokenness, but it
    means that a ClockTime cannot trivially be converted to UTC based
    times such as the POSIX time_t.
-}

-- -------------------------------------------------------------------------
-- * Timezone

data Timezone -- abstract

-- | Make a 'Timezone' from an offset, in minutes relative to UTC,
-- which must be less than @24*60@.
timezoneFromOffset :: Int    -> Timezone

-- | Make a 'Timezone' from a standard timezone name (eg. GMT, PDT).
-- TAI is a valid timezone name.
timezoneFromName   :: String -> Timezone

-- | Return the offset in minutes of the specified timezone relative
--   to UTC.
timezoneOffset :: Timezone -> Int

-- | Return the timezone name corresponding to a 'Timezone' value.
timezoneName   :: Timezone -> 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

-----------------------------------------------------------------------------
-- * 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

{-
 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?

  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.
-}