o-clock-1.3.0: Type-safe time library.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Time.Timestamp

Description

This module introduces Timestamp data type and corresponding functions for operations with time.

Synopsis

Documentation

newtype Timestamp Source #

Similar to Time but has no units and can be negative.

Constructors

Timestamp Rational 

fromUnixTime :: Real a => a -> Timestamp Source #

Converts unix time to Timestamp.

timeDiff :: forall (unit :: Rat). KnownDivRat Second unit => Timestamp -> Timestamp -> (Ordering, Time unit) Source #

Returns the result of comparison of two Timestamps and the Time of that difference of given time unit.

>>> timeDiff @Second (Timestamp 4) (Timestamp 2)
(GT,2s)
>>> timeDiff @Minute (Timestamp 4) (Timestamp 2)
(GT,1/30m)
>>> timeDiff @Second (Timestamp 2) (Timestamp 4)
(LT,2s)
>>> timeDiff @Minute (Timestamp 2) (Timestamp 4)
(LT,1/30m)

timeAdd :: forall (unit :: Rat). KnownDivRat unit Second => Time unit -> Timestamp -> Timestamp Source #

Returns the result of addition of Time with Timestamp elements.

>>> sec 5 `timeAdd` (Timestamp 4)
Timestamp (9 % 1)
>>> minute 1 `timeAdd` (Timestamp 5)
Timestamp (65 % 1)

timeMul :: forall (unit :: Rat). RatioNat -> Time unit -> Time unit Source #

Returns the result of multiplying a number by a Time element.

(*:*) :: forall (unit :: Rat). KnownRat unit => RatioNat -> Time unit -> Time unit infixr 7 Source #

Operator version of timeMul.

>>> 3 *:* sec 5
15s
>>> 2 *:* 3 *:* sec 5
30s
>>> 3 *:* 5 *:* sec 7
105s
>>> ms 2000 +:+ 2 *:* sec 3
8s

timeDiv :: forall (unit :: Rat). KnownRat unit => Time unit -> Time unit -> RatioNat Source #

Returns the result of division of two Time elements.

(/:/) :: forall (unit :: Rat). KnownRat unit => Time unit -> Time unit -> RatioNat infix 7 Source #

Operator version of timeDiv.

>>> sec 15 /:/ sec 3
5 % 1

Other operators

(+:+) :: forall (unitResult :: Rat) (unitLeft :: Rat). KnownDivRat unitLeft unitResult => Time unitLeft -> Time unitResult -> Time unitResult infixl 6 Source #

Sums times of different units.

>>> minute 1 +:+ sec 1
61s

(-:-) :: forall (unitResult :: Rat) (unitLeft :: Rat). KnownDivRat unitLeft unitResult => Time unitLeft -> Time unitResult -> Time unitResult infixl 6 Source #

Substracts time amounts of different units. When the minuend is smaller than the subtrahend, this function will throw Underflow :: ArithException.

>>> minute 1 -:- sec 1
59s

(-%-) :: forall (unitResult :: Rat) (unitLeft :: Rat). KnownDivRat unitLeft unitResult => Time unitLeft -> Time unitResult -> (Ordering, Time unitResult) infix 6 Source #

Compute the difference between two amounts of time. The result is returned in two components: the ordering (which input is larger) and the numeric difference (how much larger). Unlike -:-, does not throw ArithException.

>>> sec 5 -%- sec 3
(GT,2s)
>>> sec 5 -%- sec 6
(LT,1s)