time since the epoch

Peter Thiemann thiemann@informatik.uni-freiburg.de
06 Feb 2003 12:40:14 -0800


I've been running into similar problems, and I've also been pointed to
the TimeExt library that George Russell was talking about. However, in
the end, I had to implement something by myself. Much unfortunately
though, my program relies on an undocumented feature of GHC's
implementation of TimeDiff in the Time library.

John's code illustrates TimeDiff's deficiencies perfectly:

    JM> the haskell 98 time library is horribly broken, if you are using ghc,
    JM> you can deconstruct the time constructor which has an Integer containing
    JM> the number of seconds since epoch... otherwise you can use

    JM> epoch :: ClockTime
    JM> epoch = toClockTime $ CalendarTime { ctYear = 1970, ctMonth = January,
    JM> ctDay = 0, ctHour = 0, ctMin = 0, ctSec = 0, ctTZ = 0, ctPicosec = 0,
    JM> ctWDay = undefined, ctYDay = undefined, ctTZName = undefined, ctIsDST =
    JM> undefined}

    JM> and TimeDiff,

    JM> unfortunatly you have to condense the TimeDiff to seconds, which is
    JM> unfeasable...

Ha! After playing with this, I discovered that only the seconds were
set and all other fields remained untouched. At least in ghc's
implementation. Interestingly, TimeDiff derives Eq and Ord, but I'd
better not ask for their implementation...

There is also a more fundamental problem with the TimeDiff data
type. While seconds, minutes, hours, and days are clearly specified
amounts of time, the duration of a month or a year may vary depending
on the reference point where the time difference is applied.

My conclusion is that time differences really should be measured in
seconds and picoseconds. 

type TimeDiff = (Integer, Integer)

    JM> we really should fix the Haskell time library. I propose adding:

    JM> toRawTime :: ClockTime -> (Integer,Integer) 
    JM> fromRawTime :: (Integer,Integer) -> ClockTime

    JM> where the integers are the number of seconds and picoseconds since
    JM> epoch, these would be enough to make the time library useful. 
    JM> I dont supose this could be considered a typo in the haskell 98 report?
    JM> it is an embarasing thing for a language to not be able to do...

Hmm, this is underspecified!
As another poster said, (pointing out http://cr.yp.to/libtai, but it
is better to look at http://cr.yp.to/time.html, which has a discussion
on UTC vs TAI vs UNIX time) the official source of time is TAI, so it
is best to base a time library
*on the number of TAI seconds since a reference date*
(which is btw what the libtai is all about).
For compatibility with UNIX time, "Arthur David Olson's popular time
library uses an epoch of 1970-01-01 00:00:10 TAI"
[http://cr.yp.to/proto/utctai.html]. 
So this mostly means that you need to set your system clock correctly:-)

Hence, a suitable specification for 
    JM> toRawTime :: ClockTime -> (Integer,Integer) 
could be number of seconds since reference point, given as a pair
(full seconds, picoseconds). This function *may* involve a time zone
calculation for those that do not run their system clock on TAI (or UTC).
    JM> fromRawTime :: (Integer,Integer) -> ClockTime
with
  toRawTime . fromRawTime == id
and
  fromRawTime . toRawTime ~~ id
  (the internal representation of ClockTime may have less precision,
  so the difference would be less than system dependent constant,
  which could also be supplied by the library)

Given these two raw ingredients, everything else can be computed
from that. In addition, it would be nice to have parsing functions for
various time and date formats (which is what I ended up writing
myself for the ISO8601 format).

Cheers,
-Peter