thyme-0.4: A faster time library
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Thyme.Clock.TAI

Description

International Atomic Time (TAI) and conversion to/from UTC, accounting for leap seconds.

Synopsis

Documentation

data AbsoluteTime Source #

Temps Atomique International (TAI). Note that for most applications UTCTime is perfectly sufficient, and much more convenient to use.

Internally this is the number of seconds since taiEpoch. TAI days are exactly 86400 SI seconds long.

Instances

Instances details
Arbitrary AbsoluteTime Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

CoArbitrary AbsoluteTime Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

Methods

coarbitrary :: AbsoluteTime -> Gen b -> Gen b #

Data AbsoluteTime Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AbsoluteTime -> c AbsoluteTime #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AbsoluteTime #

toConstr :: AbsoluteTime -> Constr #

dataTypeOf :: AbsoluteTime -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AbsoluteTime) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AbsoluteTime) #

gmapT :: (forall b. Data b => b -> b) -> AbsoluteTime -> AbsoluteTime #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AbsoluteTime -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AbsoluteTime -> r #

gmapQ :: (forall d. Data d => d -> u) -> AbsoluteTime -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AbsoluteTime -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AbsoluteTime -> m AbsoluteTime #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AbsoluteTime -> m AbsoluteTime #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AbsoluteTime -> m AbsoluteTime #

Bounded AbsoluteTime Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

Enum AbsoluteTime Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

Generic AbsoluteTime Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

Associated Types

type Rep AbsoluteTime :: Type -> Type #

Ix AbsoluteTime Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

Show AbsoluteTime Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

NFData AbsoluteTime Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

Methods

rnf :: AbsoluteTime -> () #

Eq AbsoluteTime Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

Ord AbsoluteTime Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

Hashable AbsoluteTime Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

Random AbsoluteTime Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

FormatTime AbsoluteTime Source # 
Instance details

Defined in Data.Thyme.Format

ParseTime AbsoluteTime Source # 
Instance details

Defined in Data.Thyme.Format

Unbox AbsoluteTime Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

AffineSpace AbsoluteTime Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

Associated Types

type Diff AbsoluteTime #

Thyme AbsoluteTime AbsoluteTime Source # 
Instance details

Defined in Data.Thyme.Time.Core

Vector Vector AbsoluteTime Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

MVector MVector AbsoluteTime Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

type Rep AbsoluteTime Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

type Rep AbsoluteTime = D1 ('MetaData "AbsoluteTime" "Data.Thyme.Clock.TAI" "thyme-0.4-HyK6SfK4MlBKX4LjgMsZJ4" 'True) (C1 ('MetaCons "AbsoluteTime" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DiffTime)))
newtype Vector AbsoluteTime Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

type Diff AbsoluteTime Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

newtype MVector s AbsoluteTime Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

taiEpoch :: AbsoluteTime Source #

The Modified Julian Day epoch, which is 1858-11-17 00:00:00 TAI.

data TAIUTCMap Source #

A table of TAIUTCRows for converting between TAI and UTC.

The two Maps are keyed on the corresponding instants in UTC and TAI from which the TAIUTCRow becomes applicable. The UTCTime key of the first Map is always at midnight.

No table is provided here because leap seconds are unpredictable, and any program shipped with such a table could become out-of-date in as little as 6 months. See parseTAIUTCDAT for details.

Instances

Instances details
Data TAIUTCMap Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TAIUTCMap -> c TAIUTCMap #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TAIUTCMap #

toConstr :: TAIUTCMap -> Constr #

dataTypeOf :: TAIUTCMap -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TAIUTCMap) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TAIUTCMap) #

gmapT :: (forall b. Data b => b -> b) -> TAIUTCMap -> TAIUTCMap #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TAIUTCMap -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TAIUTCMap -> r #

gmapQ :: (forall d. Data d => d -> u) -> TAIUTCMap -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TAIUTCMap -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TAIUTCMap -> m TAIUTCMap #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TAIUTCMap -> m TAIUTCMap #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TAIUTCMap -> m TAIUTCMap #

Generic TAIUTCMap Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

Associated Types

type Rep TAIUTCMap :: Type -> Type #

Show TAIUTCMap Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

Eq TAIUTCMap Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

Ord TAIUTCMap Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

type Rep TAIUTCMap Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

data TAIUTCRow Source #

Each line of tai-utc.dat (see parseTAIUTCDAT) specifies the difference between TAI and UTC for a particular period. For example:

1968 FEB  1 =JD 2439887.5  TAI-UTC=   4.2131700 S + (MJD - 39126.) X 0.002592 S

says that from 1968-02-01 00:00:00 (Julian Date 2439887.5; or Modified Julian Date 39887.0), the difference between TAI and UTC is 4.2131700s (the additive part) plus a scaled component that increases for each day beyond MJD 39126 (the base) by 0.002592s (the coefficient). In general, the latter half of each line is of the form:

TAI-UTC= additive S + (MJD - base) X coefficient S

TAIUTCRow a b c is a normalised version of the above, with the base multiplied by 86400s, and the coefficient divided by the same. This allows us to use the internal representation of UTCTime—seconds since the MJD epoch—as the MJD term without further rescaling.

Note that between 1961-01-01 and 1972-01-01, each UTC second was actually slightly longer than one TAI (or SI) second. For the first year this was at the rate of exactly 1.000000015 TAI (or SI) seconds per UTC second, but was subject to irregular updates. Since leap seconds came into effect on 1972-01-01, the additive part has always been an intergral number of seconds, and the coefficient has always been zero.

To convert between TAI and UTC, we refer to the definition:

TAI - UTC = a + (MJD - b) * c

Using UTC for MJD (with b and c scaled as described above):

TAI = UTC + a + (UTC - b) * c
TAI - a + b * c = UTC + UTC * c
(TAI - a + b * c) / (1 + c) = UTC

This is implemented by absoluteTime and absoluteTime'.

Further reading:

Constructors

TAIUTCRow !DiffTime !UTCTime !Rational

Each row comprises of an additive component, the base of the scaled component, and the coefficient of the scaled component.

Instances

Instances details
Data TAIUTCRow Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TAIUTCRow -> c TAIUTCRow #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TAIUTCRow #

toConstr :: TAIUTCRow -> Constr #

dataTypeOf :: TAIUTCRow -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TAIUTCRow) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TAIUTCRow) #

gmapT :: (forall b. Data b => b -> b) -> TAIUTCRow -> TAIUTCRow #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TAIUTCRow -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TAIUTCRow -> r #

gmapQ :: (forall d. Data d => d -> u) -> TAIUTCRow -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TAIUTCRow -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TAIUTCRow -> m TAIUTCRow #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TAIUTCRow -> m TAIUTCRow #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TAIUTCRow -> m TAIUTCRow #

Generic TAIUTCRow Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

Associated Types

type Rep TAIUTCRow :: Type -> Type #

Show TAIUTCRow Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

Eq TAIUTCRow Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

Ord TAIUTCRow Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

type Rep TAIUTCRow Source # 
Instance details

Defined in Data.Thyme.Clock.TAI

absoluteTime :: TAIUTCMap -> Iso' UTCTime AbsoluteTime Source #

Convert between UTCTime and AbsoluteTime using a TAIUTCMap.

Since UTCTime cannot represent a time-of-day of 86400s or more, any conversion from AbsoluteTime that happens to be during a leap second will overflow into the next day.

See parseTAIUTCDAT for how to obtain the tum :: TAIUTCMap below.

> let jul1 = utcTime # UTCView (gregorian # YearMonthDay 2015 7 1) zeroV
> jul1 & absoluteTime tum %~ (.-^ fromSeconds 1.1)
2015-06-30 23:59:59.9 UTC

absoluteTime' :: TAIUTCMap -> Iso' UTCView AbsoluteTime Source #

Convert between UTCView and TAI AbsoluteTime using a TAIUTCMap.

Unlike absoluteTime, UTCView can represent a time-of-day greater than 86400s, and this gives the correct results during a leap second.

See parseTAIUTCDAT for how to obtain the tum :: TAIUTCMap below.

> let jul1 = UTCView (gregorian # YearMonthDay 2015 7 1) zeroV
> jul1 & absoluteTime' tum %~ (.-^ fromSeconds 0.1)
UTCView {utcvDay = 2015-06-30, utcvDayTime = 86400.9s}

However keep in mind that currently there is no standard way to get the TAI on most platforms. Simply converting the result of getCurrentTime (which calls gettimeofday(2)) to AbsoluteTime during a leap second will still give non-monotonic times.

utcDayLength :: TAIUTCMap -> Day -> DiffTime Source #

Using a TAIUTCMap, lookup the DiffTime length of the UTC Day.

See parseTAIUTCDAT for how to obtain the tum :: TAIUTCMap below.

> utcDayLength tum . view _utctDay <$> getCurrentTime
86400s
> utcDayLength tum $ gregorian # YearMonthDay 2015 6 30
86401s

parseTAIUTCRow :: Parser (UTCTime, TAIUTCRow) Source #

attoparsec Parser for a single line of tai-utc.dat.

Returns the starting UTCTime and the normalised TAIUTCRow.

Compatibility

diffAbsoluteTime :: AbsoluteTime -> AbsoluteTime -> DiffTime Source #

The duration difference between two AbsoluteTimes.

diffAbsoluteTime = (.-.)
diffAbsoluteTime a b ≡ a .-. b

See also the AffineSpace instance for AbsoluteTime.