| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Time.Units
Description
This module contains time unit data structures and functions to work with time.
Synopsis
- newtype Time (rat :: Rat) = Time {}
- type Second = 1 / 1
- type Millisecond = Second / 1000
- type Microsecond = Millisecond / 1000
- type Nanosecond = Microsecond / 1000
- type Picosecond = Nanosecond / 1000
- type Minute = 60 * Second
- type Hour = 60 * Minute
- type Day = 24 * Hour
- type Week = 7 * Day
- type Fortnight = 2 * Week
- type family UnitName (unit :: Rat) :: Symbol
- type KnownUnitName unit = KnownSymbol (UnitName unit)
- type KnownRatName unit = (KnownUnitName unit, KnownRat unit)
- unitNameVal :: forall (unit :: Rat). KnownUnitName unit => String
- time :: RatioNat -> Time unit
- floorUnit :: forall (unit :: Rat). Time unit -> Time unit
- floorRat :: forall (unit :: Rat) b. Integral b => Time unit -> b
- toNum :: forall (unitTo :: Rat) n (unit :: Rat). (KnownDivRat unit unitTo, Num n) => Time unit -> n
- sec :: RatioNat -> Time Second
- ms :: RatioNat -> Time Millisecond
- mcs :: RatioNat -> Time Microsecond
- ns :: RatioNat -> Time Nanosecond
- ps :: RatioNat -> Time Picosecond
- minute :: RatioNat -> Time Minute
- hour :: RatioNat -> Time Hour
- day :: RatioNat -> Time Day
- week :: RatioNat -> Time Week
- fortnight :: RatioNat -> Time Fortnight
- toUnit :: forall (unitTo :: Rat) (unitFrom :: Rat). KnownDivRat unitFrom unitTo => Time unitFrom -> Time unitTo
- threadDelay :: forall (unit :: Rat) m. (KnownDivRat unit Microsecond, MonadIO m) => Time unit -> m ()
- getCPUTime :: forall (unit :: Rat) m. (KnownDivRat Picosecond unit, MonadIO m) => m (Time unit)
- timeout :: forall (unit :: Rat) m a. (MonadIO m, KnownDivRat unit Microsecond) => Time unit -> IO a -> m (Maybe a)
Time
newtype Time (rat :: Rat) Source #
Time unit is represented as type level rational multiplier with kind Rat.
Instances
| Enum (Time rat) Source # | |
| Eq (Time rat) Source # | |
| Ord (Time rat) Source # | |
| Defined in Time.Units | |
| KnownUnitName unit => Read (Time unit) Source # | |
| KnownUnitName unit => Show (Time unit) Source # | |
| Generic (Time rat) Source # | |
| Semigroup (Time rat) Source # | Addition is associative binary operation for  | 
| Monoid (Time rat) Source # | |
| type Rep (Time rat) Source # | |
| Defined in Time.Units | |
Time data types
type Millisecond = Second / 1000 Source #
type Microsecond = Millisecond / 1000 Source #
type Nanosecond = Microsecond / 1000 Source #
type Picosecond = Nanosecond / 1000 Source #
type family UnitName (unit :: Rat) :: Symbol Source #
Type family for prettier show of time units.
Instances
| type UnitName (1 :% 1) Source # | |
| Defined in Time.Units | |
| type UnitName (1 :% 1000) Source # | |
| Defined in Time.Units | |
| type UnitName (1 :% 1000000) Source # | |
| Defined in Time.Units | |
| type UnitName (1 :% 1000000000) Source # | |
| Defined in Time.Units | |
| type UnitName (1 :% 1000000000000) Source # | |
| Defined in Time.Units | |
| type UnitName (60 :% 1) Source # | |
| Defined in Time.Units | |
| type UnitName (3600 :% 1) Source # | |
| Defined in Time.Units | |
| type UnitName (86400 :% 1) Source # | |
| Defined in Time.Units | |
| type UnitName (604800 :% 1) Source # | |
| Defined in Time.Units | |
| type UnitName (1209600 :% 1) Source # | |
| Defined in Time.Units | |
type KnownUnitName unit = KnownSymbol (UnitName unit) Source #
Constraint alias for KnownSymbol UnitName.
type KnownRatName unit = (KnownUnitName unit, KnownRat unit) Source #
Constraint alias for KnownUnitName and KnownRat for time unit.
unitNameVal :: forall (unit :: Rat). KnownUnitName unit => String Source #
Creation helpers
floorRat :: forall (unit :: Rat) b. Integral b => Time unit -> b Source #
Returns the greatest integer not greater than given Time.
toNum :: forall (unitTo :: Rat) n (unit :: Rat). (KnownDivRat unit unitTo, Num n) => Time unit -> n Source #
Convert time to the Num in given units.
For example, instead of writing
foo :: POSIXTime foo = 10800 -- 3 hours
one can write more safe implementation:
foo = toNum @Second $ hour 3
Examples:
>>>toNum @Second @Natural $ hour 310800
>>>toNum @Minute @Int $ hour 3180
>>>toNum @Hour @Natural $ hour 33
ms :: RatioNat -> Time Millisecond Source #
Creates Millisecond from given Natural.
>>>ms 4242ms
mcs :: RatioNat -> Time Microsecond Source #
Creates Microsecond from given Natural.
>>>mcs 4242mcs
ns :: RatioNat -> Time Nanosecond Source #
Creates Nanosecond from given Natural.
>>>ns 4242ns
ps :: RatioNat -> Time Picosecond Source #
Creates Picosecond from given Natural.
>>>ps 4242ps
Functions
toUnit :: forall (unitTo :: Rat) (unitFrom :: Rat). KnownDivRat unitFrom unitTo => Time unitFrom -> Time unitTo Source #
Converts from one time unit to another time unit.
>>>toUnit @Hour (minute 120)2h
>>>toUnit @Second (ms 7)7/1000s
>>>toUnit @Week (Time @Day 45)6+3/7w
>>>toUnit @Second @Minute (Time 3)180s
>>>toUnit (day 42000000) :: Time Second3628800000000s
threadDelay :: forall (unit :: Rat) m. (KnownDivRat unit Microsecond, MonadIO m) => Time unit -> m () Source #
Convenient version of threadDelay which takes
 any time-unit and operates in any MonadIO.
>>> threadDelay $ sec 2 >>> threadDelay (2 :: Time Second) >>> threadDelay @Second 2
getCPUTime :: forall (unit :: Rat) m. (KnownDivRat Picosecond unit, MonadIO m) => m (Time unit) Source #
Similar to getCPUTime but returns the CPU time used by the current
 program in the given time unit.
 The precision of this result is implementation-dependent.
>>> getCPUTime @Second 1064046949/1000000000s
Arguments
| :: forall (unit :: Rat). (MonadIO m, KnownDivRat unit Microsecond) | |
| => Time unit | time | 
| -> IO a | 
 | 
| -> m (Maybe a) | returns  | 
Similar to timeout but receiving any time unit
instead of number of microseconds.
>>> timeout (sec 1) (putStrLn "Hello O'Clock") Hello O'Clock Just ()
>>> timeout (ps 1) (putStrLn "Hello O'Clock") Nothing
>>> timeout (mcs 1) (putStrLn "Hello O'Clock") HellNothing