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

Data.Thyme.Clock

Description

Types and functions for UTC and UT1.

If you don't care about leap seconds, keep to UTCTime and NominalDiffTime for your clock calculations, and you'll be fine.

Data.Thyme.Time provides Num, Real, Fractional and RealFrac instances for DiffTime and NominalDiffTime, but their use is discouraged. See Data.Thyme.Docs for details.

Use fromSeconds and toSeconds to convert between DiffTime / NominalDiffTime and other numeric types; use fromSeconds' for literals to avoid type defaulting warnings.

Synopsis

UTC

data UTCTime Source #

Coördinated universal time (UTCTime) is the most commonly used standard for civil timekeeping. It is synchronised with TAI (AbsoluteTime) and both tick in increments of SI seconds, but UTC includes occasional leap-seconds to keep it close to UT1 (UniversalTime).

> utcTime # UTCView (gregorian # YearMonthDay 2016 1 15) (timeOfDay # TimeOfDay 12 34 56.78)
2016-01-15 12:34:56.78 UTC

> UTCTime (gregorian # YearMonthDay 2016 1 15) (timeOfDay # TimeOfDay 12 34 56.78)
2016-01-15 12:34:56.78 UTC

> mkUTCTime 2016 1 15  12 34 56.78
2016-01-15 12:34:56.78 UTC

UTCTime is an AffineSpace with NominalDiffTime as its Diff. See Data.Thyme.Docs for details.

> let t0 = mkUTCTime 2016 1 15  23 59 0
> let t1 = mkUTCTime 2016 1 16  00  1 1
> let dt = t1 .-. t0
> dt
121s :: NominalDiffTime

> t1 .+^ dt
2016-01-16 00:03:02 UTC

> t1 .+^ 3 *^ dt
2016-01-16 00:07:04 UTC

To decompose a UTCTime into a separate Day and time-of-day, use utcTime. To convert to a local time zone, see zonedTime or utcLocalTime.

Notes

Internally UTCTime is just a 64-bit count of microseconds since the Modified Julian Day epoch, so (.+^), (.-.) et cetera ought to be fast.

UTCTime cannot represent leap seconds. If leap seconds matter, use AbsoluteTime from Data.Thyme.Clock.TAI instead, along with absoluteTime' and UTCView for presentation.

Instances

Instances details
Arbitrary UTCTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

CoArbitrary UTCTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Methods

coarbitrary :: UTCTime -> Gen b -> Gen b #

FromJSON UTCTime Source # 
Instance details

Defined in Data.Thyme.Format.Aeson

ToJSON UTCTime Source # 
Instance details

Defined in Data.Thyme.Format.Aeson

Data UTCTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Methods

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

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

toConstr :: UTCTime -> Constr #

dataTypeOf :: UTCTime -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded UTCTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Enum UTCTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Generic UTCTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Associated Types

type Rep UTCTime :: Type -> Type #

Methods

from :: UTCTime -> Rep UTCTime x #

to :: Rep UTCTime x -> UTCTime #

Ix UTCTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Read UTCTime Source # 
Instance details

Defined in Data.Thyme.Format

Show UTCTime Source # 
Instance details

Defined in Data.Thyme.LocalTime

NFData UTCTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Methods

rnf :: UTCTime -> () #

Eq UTCTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Methods

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

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

Ord UTCTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Hashable UTCTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Methods

hashWithSalt :: Int -> UTCTime -> Int #

hash :: UTCTime -> Int #

Random UTCTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Methods

randomR :: RandomGen g => (UTCTime, UTCTime) -> g -> (UTCTime, g) #

random :: RandomGen g => g -> (UTCTime, g) #

randomRs :: RandomGen g => (UTCTime, UTCTime) -> g -> [UTCTime] #

randoms :: RandomGen g => g -> [UTCTime] #

FormatTime UTCTime Source # 
Instance details

Defined in Data.Thyme.Format

Methods

showsTime :: TimeLocale -> UTCTime -> (Char -> ShowS) -> Char -> ShowS Source #

ParseTime UTCTime Source # 
Instance details

Defined in Data.Thyme.Format

Unbox UTCTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

AffineSpace UTCTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Associated Types

type Diff UTCTime #

Thyme UTCTime UTCTime Source # 
Instance details

Defined in Data.Thyme.Time.Core

Methods

thyme :: Iso' UTCTime0 UTCTime Source #

Vector Vector UTCTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

MVector MVector UTCTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

type Rep UTCTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

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

Defined in Data.Thyme.Clock.Internal

type Diff UTCTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

newtype MVector s UTCTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

utctDay :: UTCTime -> Day Source #

Accessor for the calendar Day component of an UTCTime.

utctDay = view _utctDay

utctDayTime :: UTCTime -> DiffTime Source #

Accessor for the time-of-day DiffTime component of an UTCTime.

utctDayTime = view _utctDayTime

_utctDay :: Lens' UTCTime Day Source #

Lens' for the calendar Day component of a UTCTime.

_utctDayTime :: Lens' UTCTime DiffTime Source #

Lens' for the time-of-day DiffTime component of a UTCTime.

pattern UTCTime :: Day -> DiffTime -> UTCTime Source #

mkUTCTime :: Year -> Month -> DayOfMonth -> Hour -> Minute -> Double -> UTCTime Source #

Construct a UTCTime from a gregorian date and time-of-day.

mkUTCTime yy mm dd h m s ≡ utcTime # UTCView
    (gregorian # YearMonthDay yy mm dd)
    (timeOfDay # TimeOfDay h m (fromSeconds s))

utcTime :: Iso' UTCTime UTCView Source #

View UTCTime as an UTCView, comprising a Day along with a DiffTime offset since midnight.

This is an improper lens: utcvDayTime outside the range of [zeroV, posixDayLength) will carry over into utcvDay, with the expected behaviour.

> view utcTime <$> getCurrentTime
UTCView {utcvDay = 2016-01-15, utcvDayTime = 49322.287688s}

> utcTime # UTCView (gregorian # YearMonthDay 2016 1 15) (timeOfDay # TimeOfDay 12 34 56.78)
2016-01-15 12:34:56.78 UTC

With {-# LANGUAGE ViewPatterns #-}, you can write: e.g.

f :: UTCTime -> (Day, DiffTime)
f (view utcTime -> UTCView day dt) = (day, dt)

data UTCView Source #

Unpacked UTCTime, partly for compatibility with time.

As of GHC 7.10, you can also use the UTCTime pattern synonym.

Constructors

UTCView 

Fields

Instances

Instances details
Data UTCView Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Methods

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

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

toConstr :: UTCView -> Constr #

dataTypeOf :: UTCView -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic UTCView Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Associated Types

type Rep UTCView :: Type -> Type #

Methods

from :: UTCView -> Rep UTCView x #

to :: Rep UTCView x -> UTCView #

Read UTCView Source # 
Instance details

Defined in Data.Thyme.Format

Show UTCView Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

NFData UTCView Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Methods

rnf :: UTCView -> () #

Eq UTCView Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Methods

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

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

Ord UTCView Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Hashable UTCView Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Methods

hashWithSalt :: Int -> UTCView -> Int #

hash :: UTCView -> Int #

Unbox UTCView Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Thyme UTCTime UTCView Source # 
Instance details

Defined in Data.Thyme.Time.Core

Methods

thyme :: Iso' UTCTime UTCView Source #

Vector Vector UTCView Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

MVector MVector UTCView Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

type Rep UTCView Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

type Rep UTCView = D1 ('MetaData "UTCView" "Data.Thyme.Clock.Internal" "thyme-0.4-HyK6SfK4MlBKX4LjgMsZJ4" 'False) (C1 ('MetaCons "UTCView" 'PrefixI 'True) (S1 ('MetaSel ('Just "utcvDay") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Day) :*: S1 ('MetaSel ('Just "utcvDayTime") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 DiffTime)))
newtype Vector UTCView Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

newtype MVector s UTCView Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

_utcvDay :: Lens' UTCView Day Source #

Lens' for the calendar Day component of a UTCView.

_utcvDayTime :: Lens' UTCView DiffTime Source #

Lens' for the time-of-day DiffTime component of a UTCView.

data NominalDiffTime Source #

The nominal interval between two UTCTimes, which does not take leap seconds into account.

For example, the difference between 23:59:59 and 00:00:01 on the following day is always 2 seconds of NominalDiffTime, regardless of whether a leap-second took place.

NominalDiffTime is an instance of AdditiveGroup as well as VectorSpace, with Rational as its Scalar. We do not provide Num, Real, Fractional nor RealFrac instances here. See Data.Thyme.Docs for details.

> let d = fromSeconds' 2 :: NominalDiffTime
> d
2s
> d ^/ 3
0.666667s

See also: UTCTime.

Instances

Instances details
Arbitrary NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

CoArbitrary NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Methods

coarbitrary :: NominalDiffTime -> Gen b -> Gen b #

Data NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Methods

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

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

toConstr :: NominalDiffTime -> Constr #

dataTypeOf :: NominalDiffTime -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Enum NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Generic NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Associated Types

type Rep NominalDiffTime :: Type -> Type #

Ix NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Num NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Time

Read NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Fractional NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Time

Real NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Time

RealFrac NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Time

Show NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

NFData NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Methods

rnf :: NominalDiffTime -> () #

Eq NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Ord NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Hashable NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Random NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

TimeDiff NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Unbox NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

AdditiveGroup NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

HasBasis NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Associated Types

type Basis NominalDiffTime #

VectorSpace NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Associated Types

type Scalar NominalDiffTime #

Thyme NominalDiffTime NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Time.Core

Vector Vector NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

MVector MVector NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

type Rep NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

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

Defined in Data.Thyme.Clock.Internal

type Basis NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

type Scalar NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

newtype MVector s NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

getCurrentTime :: IO UTCTime Source #

Get the current UTC date and time from the local system clock.

> getCurrentTime
2016-01-15 13:42:02.287688 UTC

See also: getZonedTime, getPOSIXTime.

Absolute intervals

data DiffTime Source #

An interval or duration of time, as would be measured by a stopwatch.

DiffTime is an instance of AdditiveGroup as well as VectorSpace, with Rational as its Scalar. We do not provide Num, Real, Fractional nor RealFrac instances here. See Data.Thyme.Docs for details.

> fromSeconds' 100 :: DiffTime
100s
> fromSeconds' 100 ^+^ fromSeconds' 100 ^* 4
500s
> fromSeconds' 100 ^-^ fromSeconds' 100 ^/ 4
75s

Instances

Instances details
Arbitrary DiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

CoArbitrary DiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Methods

coarbitrary :: DiffTime -> Gen b -> Gen b #

Data DiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Methods

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

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

toConstr :: DiffTime -> Constr #

dataTypeOf :: DiffTime -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded DiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Enum DiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Generic DiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Associated Types

type Rep DiffTime :: Type -> Type #

Methods

from :: DiffTime -> Rep DiffTime x #

to :: Rep DiffTime x -> DiffTime #

Ix DiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Num DiffTime Source # 
Instance details

Defined in Data.Thyme.Time

Read DiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Fractional DiffTime Source # 
Instance details

Defined in Data.Thyme.Time

Real DiffTime Source # 
Instance details

Defined in Data.Thyme.Time

RealFrac DiffTime Source # 
Instance details

Defined in Data.Thyme.Time

Methods

properFraction :: Integral b => DiffTime -> (b, DiffTime) #

truncate :: Integral b => DiffTime -> b #

round :: Integral b => DiffTime -> b #

ceiling :: Integral b => DiffTime -> b #

floor :: Integral b => DiffTime -> b #

Show DiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

NFData DiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Methods

rnf :: DiffTime -> () #

Eq DiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Ord DiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Hashable DiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Methods

hashWithSalt :: Int -> DiffTime -> Int #

hash :: DiffTime -> Int #

Random DiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Methods

randomR :: RandomGen g => (DiffTime, DiffTime) -> g -> (DiffTime, g) #

random :: RandomGen g => g -> (DiffTime, g) #

randomRs :: RandomGen g => (DiffTime, DiffTime) -> g -> [DiffTime] #

randoms :: RandomGen g => g -> [DiffTime] #

TimeDiff DiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Unbox DiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

AdditiveGroup DiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

HasBasis DiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Associated Types

type Basis DiffTime #

VectorSpace DiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Associated Types

type Scalar DiffTime #

Thyme DiffTime DiffTime Source # 
Instance details

Defined in Data.Thyme.Time.Core

Vector Vector DiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

MVector MVector DiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

type Rep DiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

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

Defined in Data.Thyme.Clock.Internal

type Basis DiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

type Basis DiffTime = ()
type Scalar DiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

newtype MVector s DiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Time interval conversion

class (HasBasis t, Basis t ~ (), Scalar t ~ Rational) => TimeDiff t where Source #

Time intervals, encompassing both DiffTime and NominalDiffTime.

Notes

Still affected by http://hackage.haskell.org/trac/ghc/ticket/7611?

Methods

microseconds :: Iso' t Int64 Source #

Conversion between TimeDiff and Int64 microseconds.

> (fromSeconds' 3 :: DiffTime) ^. microseconds
3000000

> microseconds # 4000000 :: DiffTime
4s

Instances

Instances details
TimeDiff DiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

TimeDiff NominalDiffTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

toSeconds :: (TimeDiff t, Fractional n) => t -> n Source #

Convert a time interval to some Fractional type.

fromSeconds :: (Real n, TimeDiff t) => n -> t Source #

Make a time interval from some Real type.

Try to make sure n is one of Float, Double, Int, Int64 or Integer, for which rewrite RULES have been provided.

toSeconds' :: TimeDiff t => t -> Rational Source #

Type-restricted toSeconds to avoid constraint-defaulting warnings.

fromSeconds' :: TimeDiff t => Rational -> t Source #

Type-restricted fromSeconds to avoid constraint-defaulting warnings.

picoseconds :: TimeDiff t => Iso' t Integer Source #

Conversion between TimeDiff and picoseconds. In the reverse direction, picoseconds are rounded to the nearest microsecond.

Universal Time

data UniversalTime Source #

The principal form of universal time, namely UT1.

UT1 is defined by the rotation of the Earth around its axis relative to the Sun. The length of each UT1 day varies and is never exactly 86400 SI seconds, unlike UTC or TAI.

The difference between UT1 and UTC is DUT1.

Instances

Instances details
Arbitrary UniversalTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

CoArbitrary UniversalTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Methods

coarbitrary :: UniversalTime -> Gen b -> Gen b #

Data UniversalTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Methods

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

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

toConstr :: UniversalTime -> Constr #

dataTypeOf :: UniversalTime -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded UniversalTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Enum UniversalTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Generic UniversalTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Associated Types

type Rep UniversalTime :: Type -> Type #

Ix UniversalTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

NFData UniversalTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Methods

rnf :: UniversalTime -> () #

Eq UniversalTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Ord UniversalTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Hashable UniversalTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Random UniversalTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

FormatTime UniversalTime Source # 
Instance details

Defined in Data.Thyme.Format

ParseTime UniversalTime Source # 
Instance details

Defined in Data.Thyme.Format

Unbox UniversalTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

Thyme UniversalTime UniversalTime Source # 
Instance details

Defined in Data.Thyme.Time.Core

Vector Vector UniversalTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

MVector MVector UniversalTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

type Rep UniversalTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

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

Defined in Data.Thyme.Clock.Internal

newtype MVector s UniversalTime Source # 
Instance details

Defined in Data.Thyme.Clock.Internal

modJulianDate :: Iso' UniversalTime Rational Source #

Convert between UniversalTime and the fractional number of days since the Modified Julian Date epoch.

Compatibility

mkModJulianDate :: Rational -> UniversalTime Source #

Construct a UniversalTime from the fractional number of days since the Modified Julian Date epoch.

mkModJulianDate = review modJulianDate

secondsToDiffTime :: Int64 -> DiffTime Source #

Construct a DiffTime from some number of seconds.

This is just fromSeconds with a more constrained type.

secondsToDiffTime = fromSeconds

picosecondsToDiffTime :: Integer -> DiffTime Source #

Construct a DiffTime from some number of picoseconds. The input will be rounded to the nearest microsecond.

picosecondsToDiffTime a = microseconds # quot (a + signum a * 500000) 1000000

unUTCTime :: UTCTime -> UTCView Source #

Decompose a UTCTime into a UTCView.

unUTCTime = view utcTime

With {-# LANGUAGE ViewPatterns #-}, you can write: e.g.

f :: UTCTime -> (Day, DiffTime)
f (unUTCTime -> UTCView day dt) = (day, dt)

For GHC 7.8 or later, there is also the pattern synonym UTCTime.

addUTCTime :: NominalDiffTime -> UTCTime -> UTCTime Source #

Add a duration to a point in time.

addUTCTime = flip (.+^)
addUTCTime d t ≡ t .+^ d

See also the AffineSpace instance for UTCTime.

diffUTCTime :: UTCTime -> UTCTime -> NominalDiffTime Source #

The duration difference between two time points.

diffUTCTime = (.-.)
diffUTCTime a b = a .-. b

See also the AffineSpace instance for UTCTime.