Concerning Time.TimeDiff

Simon Marlow simonmar@microsoft.com
Wed, 18 Jun 2003 11:22:55 +0100


 
Oops, forgot to attach the code.

----------------------------------------------------------------------------
-- * ClockTime

-- | A representation of absolute time, measured as picoseconds since
--   the epoch, where the epoch is 1 January 1970 00:10 TAI.
newtype ClockTime
  = ClockTime { ctPicoseconds :: Integer }
  deriving (Eq, Ord, Num, Enum, Integral, Show, Read)

-- | returns the current absolute time
getClockTime :: IO ClockTime

-- | Difference between two 'ClockTime's
newtype TimeDiff
  = TimeDiff { tdPicoseconds :: Integer }
  deriving (Eq, Ord, Num, Enum, Integral, Show, Read)

-- | An empty 'TimeDiff'
noTimeDiff :: TimeDiff

-- | Returns the difference between two 'ClockTime's
diffClockTimes :: ClockTime -> ClockTime -> TimeDiff

-- | Adds a 'TimeDiff' to a 'ClockTime'
addToClockTime :: ClockTime -> TimeDiff -> 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 a POSIX
    time_t.

  - TimeDiff is now an absolute measure of time period, as compared to
    the Haskell 98 TimeDiff which was underspecified in this respect.
  
Invariants:

  t1 `addToClockTime` (t2 `diffClockTimes` t1) == t2
  t1 `addToClockTime` noTimeDiff == t1
  t1 `diffClockTimes` t1 == noTimeDiff

-}

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

data Timezone -- abstract

-- | Make a 'Timezone'
-- TODO: do we need to specify daylight savings time too?
timezoneFromOffset :: Int    -> Timezone
timezoneFromName   :: String -> Timezone

timezoneOffset :: Timezone -> Int
timezoneName   :: Timezone -> String

-- | Convert a 'ClockTime' to a 'CalendarTime' in the current timezone
clockTimeToCalendarTime :: ClockTime -> IO CalendarTime

-- | Convert a 'ClockTime' to a 'CalendarTime' in UTC
clockTimeToUTCTime :: 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?
-}