tai64-0.2.0: Tai64 Labels for Haskell

Copyright(c) 2015-2016 Kim Altintop <kim.altintop@gmail.com>
LicenseMPL
MaintainerKim Altintop <kim.altintop@gmail.com>
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010
Extensions
  • Cpp
  • MonoLocalBinds
  • TypeFamilies
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • KindSignatures
  • GeneralizedNewtypeDeriving
  • ExplicitNamespaces

Data.Time.Clock.TAI64

Contents

Description

Implementation of TAI64 labels as specified by http://cr.yp.to/libtai/tai64.html

Mainly useful for working with logfiles generated by "multilog" (part of the daemontools suite) or "svlogd" (part of the runit suite).

Synopsis

Documentation

data TAI64 Source #

Representation of a TAI64 label with full precision

Instances

Bounded TAI64 Source # 
Eq TAI64 Source # 

Methods

(==) :: TAI64 -> TAI64 -> Bool #

(/=) :: TAI64 -> TAI64 -> Bool #

Ord TAI64 Source # 

Methods

compare :: TAI64 -> TAI64 -> Ordering #

(<) :: TAI64 -> TAI64 -> Bool #

(<=) :: TAI64 -> TAI64 -> Bool #

(>) :: TAI64 -> TAI64 -> Bool #

(>=) :: TAI64 -> TAI64 -> Bool #

max :: TAI64 -> TAI64 -> TAI64 #

min :: TAI64 -> TAI64 -> TAI64 #

Show TAI64 Source # 

Methods

showsPrec :: Int -> TAI64 -> ShowS #

show :: TAI64 -> String #

showList :: [TAI64] -> ShowS #

Arbitrary TAI64 Source # 

Methods

arbitrary :: Gen TAI64 #

shrink :: TAI64 -> [TAI64] #

Unbox TAI64 Source # 
Vector Vector TAI64 Source # 
MVector MVector TAI64 Source # 
data Vector TAI64 Source # 
data MVector s TAI64 Source # 

tai64 :: Word64 -> Word32 -> Word32 -> TAI64 Source #

Construct a TAI64 from seconds, nanoseconds and attoseconds

taiSecs :: TAI64 -> Word64 Source #

Seconds of real time.

Integer s refers to

  * the TAI second beginning exactly 2^62 - s seconds before the
    beginning of 1970 TAI, if s is between 0 inclusive and 2^62 exclusive;
  * or the TAI second beginning exactly s - 2^62 seconds after the
    beginning of 1970 TAI, if s is between 2^62 inclusive and 2^63
    exclusive.

Integers 2^63 and larger are reserved for future extensions. Under many
cosmological theories, the integers under 2^63 are adequate to cover the
entire expected lifetime of the universe; in this case no extensions will
be necessary.

taiNanos :: TAI64 -> Word32 Source #

Nanoseconds [0 .. 999999999]

taiAttos :: TAI64 -> Word32 Source #

Attoseconds [0 .. 999999999]

addTAI64 :: DiffTime -> TAI64 -> TAI64 Source #

addTAI64 a b = a + b

Properties:

\d (PicosecondResolution t) -> addTAI64 d t === fromAbsoluteTime (addAbsoluteTime d (toAbsoluteTime t))

diffTAI64 :: TAI64 -> TAI64 -> DiffTime Source #

diffTAI64 a b = a - b

Properties:

\(PicosecondResolution a) (PicosecondResolution b) -> b <= a && toAbsoluteTime b >= taiEpoch ==> diffTAI64 a b === diffAbsoluteTime (toAbsoluteTime a) (toAbsoluteTime b)

sumTAI64 :: TAI64 -> TAI64 -> TAI64 Source #

sumTAI64 a b = a + b

Properties:

sumTAI64 a b >= a
sumTAI64 a minBound === a
sumTAI64 b a === sumTAI64 a b
(a `sumTAI64` b) `sumTAI64` c === a `sumTAI64` (b `sumTAI64` c)

subTAI64 :: TAI64 -> TAI64 -> TAI64 Source #

subTAI64 a b = a - b

Properties:

subTAI64 a b <= a
b >= a ==> subTAI64 a b === minBound
subTAI64 a minBound === a

toAbsoluteTime :: TAI64 -> AbsoluteTime Source #

Convert a TAI64 label to AbsoluteTime.

Note that AbsoluteTime has only picosecond resolution, hence the conversion is lossy.

Properties:

\(PicosecondResolution x) -> (fromAbsoluteTime . toAbsoluteTime) x === x

fromAbsoluteTime :: AbsoluteTime -> TAI64 Source #

Obtain a TAI64 label from AbsoluteTime.

Properties:

(toAbsoluteTime . fromAbsoluteTime) x === x

libtai compatibility

libtai employs a means of dealing with leap seconds which is broken in several ways. As an artifact of this, the taia_now function employed by both daemontools and runit produces "taistamps" which do not consider leap seconds, but are offset from 1970-01-01 00:00:00 UTC by 10s + 500ns (the purpose of the latter is unclear, as conversion functions seem to ignore it). Obviously, this violates it's own spec, yet (perhaps ironically) allows conversion back to UTC or local time without the need for a leap second table.

For compatibility and convenience, we provide some machinery to deal with TAI64 labels generated by these programs.

data Libtai Source #

Represents a TAI64 label obtained by ignoring leap seconds, and offset from 1970-01-01 00:00:00 UTC by 10.0000005s

Instances

Bounded Libtai Source # 
Eq Libtai Source # 

Methods

(==) :: Libtai -> Libtai -> Bool #

(/=) :: Libtai -> Libtai -> Bool #

Ord Libtai Source # 
Show Libtai Source # 
Arbitrary Libtai Source # 
Unbox Libtai Source # 
Vector Vector Libtai Source # 
MVector MVector Libtai Source # 
data Vector Libtai Source # 
data MVector s Libtai Source # 

libtai :: TAI64 -> Libtai Source #

Tag a TAI64 value as being created by a libtai-compatible program.

Note that this lowers precision to nanoseconds.

unLibtai :: LeapSecondTable -> Libtai -> TAI64 Source #

Obtain a proper TAI64 from Libtai

Note that this is relatively expensive, as it needs to convert to UTCTime first before applying the LeapSecondTable.

taia_now :: IO Libtai Source #

Obtain the current time as Libtai.

This is (bug-)compatible with the function of the same name from libtai: we just obtain the current POSIXTime and apply an offset of 10.0000005s.

tai64nlocal :: Libtai -> IO ZonedTime Source #

Obtain the local time corresponding to Libtai.

This is compatible with the program of the same name from the daemontools suite.

>>> let tai64n  = "4000000057693ef01cf4d1a4" -- generated by 'tai64n' from 'daemontools'
>>> let Right t = libtai <$> fromText tai64n
>>> let cest    = TimeZone (60 * 2) True "CEST"
>>> utcToZonedTime cest (libtaiToUTC t)
2016-06-21 15:19:34.4858065 CEST

libtaiToUTC :: Libtai -> UTCTime Source #

Obtain the UTCTime used to generate Libtai.

libtaiToPOSIX :: Libtai -> POSIXTime Source #

Obtain the POSIXTime used to generate Libtai.

libtaiLabel :: Libtai -> Label Source #

Obtain a Label for Libtai. Note that this is always TAI64N.

>>> let tai64n  = "4000000057693ef01cf4d1a4" -- generated by 'tai64n' from 'daemontools'
>>> toText . libtaiLabel . libtai <$> fromText tai64n
Right "4000000057693ef01cf4d1a4"

sumLibtai :: Libtai -> Libtai -> Libtai Source #

Addition of Libtai values.

subLibtai :: Libtai -> Libtai -> Libtai Source #

Subtraction of Libtai values.

diffLibtai :: Libtai -> Libtai -> DiffTime Source #

Subtraction of Libtai values, yielding DiffTime.

External representation

data Label Source #

A TAI64 label with precision as denoted by the data constructor. This is used to render the "external" (cf. toText, toByteString) respectively binary representation.

Constructors

TAI64S !TAI64 
TAI64N !TAI64 
TAI64NA !TAI64 

Instances

Eq Label Source # 

Methods

(==) :: Label -> Label -> Bool #

(/=) :: Label -> Label -> Bool #

Ord Label Source # 

Methods

compare :: Label -> Label -> Ordering #

(<) :: Label -> Label -> Bool #

(<=) :: Label -> Label -> Bool #

(>) :: Label -> Label -> Bool #

(>=) :: Label -> Label -> Bool #

max :: Label -> Label -> Label #

min :: Label -> Label -> Label #

Show Label Source # 

Methods

showsPrec :: Int -> Label -> ShowS #

show :: Label -> String #

showList :: [Label] -> ShowS #

Arbitrary Label Source # 

Methods

arbitrary :: Gen Label #

shrink :: Label -> [Label] #

Binary Label Source #

External representation of a Label

  • TAI64S: eight 8-bit bytes, big-endian, encoding the second
  • TAI64N: twelve 8-bit bytes, big-endian, encoding the second, followed by the nanosecond
  • TAI64NA: sixteen 8-bit bytes, big-endian, encoding the second, followed by the nanosecond, followed by the attosecond

Properties:

(Binary.decode . Binary.encode) x == x

Methods

put :: Label -> Put #

get :: Get Label #

putList :: [Label] -> Put #

fromLabel :: Label -> TAI64 Source #

Get the TAI64 stamp from the Label, truncated to the precision as denoted by the Label's data constructor.

toText :: Label -> Text Source #

Render a textual (ie. hexadecimal) representation of the external TAI64{N,NA} format of the given Label

Properties:

(fromText . toText) x === Right (fromLabel x)

fromText :: Text -> Either String TAI64 Source #

Parse a TAI64 label from it's textual (hexadecimal) representation.

Properties:

let x' = toText x in fromText x' === fromText ("@" <> x')

toByteString :: Label -> ByteString Source #

Render a textual (ie. hexadecimal) representation of the external TAI64{N,NA} format of the given Label

Properties:

(fromByteString . toByteString) x === Right (fromLabel x)

fromByteString :: ByteString -> Either String TAI64 Source #

Parse a TAI64 label from it's textual (hexadecimal) representation.

Properties:

let x' = toByteString x in fromByteString x' === fromByteString ("@" <> x')

parse :: ParseInput a => Parser a TAI64 Source #

Attoparsec parser for the textual TAI64 format, generalized so it works for both Text and ByteString input.

parseText :: Parser Text TAI64 Source #

Type-specialisation of parse