Safe Haskell | None |
---|---|
Language | GHC2021 |
Polysemy.Time.Data.TimeUnit
Description
TimeUnit Class and Data Types, Internal
Synopsis
- newtype FromSeconds a = FromSeconds a
- class TimeUnit u where
- nanos :: NanoSeconds
- toNanos :: u -> NanoSeconds
- fromNanos :: NanoSeconds -> u
- newtype Years = Years {}
- newtype Months = Months {}
- newtype Weeks = Weeks {}
- newtype Days = Days {}
- newtype Hours = Hours {}
- newtype Minutes = Minutes {}
- newtype Seconds = Seconds {}
- newtype MilliSeconds = MilliSeconds {}
- newtype MicroSeconds = MicroSeconds {}
- newtype NanoSeconds = NanoSeconds {}
- convert :: (TimeUnit a, TimeUnit b) => a -> b
- type AddTimeUnit t u1 u2 = (TimeUnit u1, TimeUnit u2, Torsor t u2)
- addTimeUnit :: AddTimeUnit t u1 u2 => u1 -> t -> t
- secondsFrac :: TimeUnit u => u -> Double
Documentation
newtype FromSeconds a Source #
For deriving via.
Constructors
FromSeconds a |
Instances
class TimeUnit u where Source #
Types that represent an amount of time that can be converted to each other.
The methods are internal, the API function is convert
.
Minimal complete definition
Methods
nanos :: NanoSeconds Source #
toNanos :: u -> NanoSeconds Source #
default toNanos :: Integral u => u -> NanoSeconds Source #
fromNanos :: NanoSeconds -> u Source #
default fromNanos :: Integral u => NanoSeconds -> u Source #
Instances
Data types used to specify time spans, e.g. for sleeping.
Years.
Instances
FromJSON Years Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit | |||||
ToJSON Years Source # | |||||
Enum Years Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit | |||||
Generic Years Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Associated Types
| |||||
Num Years Source # | |||||
Integral Years Source # | |||||
Real Years Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods toRational :: Years -> Rational # | |||||
Show Years Source # | |||||
Eq Years Source # | |||||
Ord Years Source # | |||||
Additive Years Source # | |||||
type Rep Years Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit |
Months.
Instances
FromJSON Months Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit | |||||
ToJSON Months Source # | |||||
Enum Months Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit | |||||
Generic Months Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Associated Types
| |||||
Num Months Source # | |||||
Integral Months Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit | |||||
Real Months Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods toRational :: Months -> Rational # | |||||
Show Months Source # | |||||
Eq Months Source # | |||||
Ord Months Source # | |||||
Additive Months Source # | |||||
type Rep Months Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit |
Weeks.
Instances
FromJSON Weeks Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit | |||||
ToJSON Weeks Source # | |||||
Enum Weeks Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit | |||||
Generic Weeks Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Associated Types
| |||||
Num Weeks Source # | |||||
Integral Weeks Source # | |||||
Real Weeks Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods toRational :: Weeks -> Rational # | |||||
Show Weeks Source # | |||||
Eq Weeks Source # | |||||
Ord Weeks Source # | |||||
TimeUnit Weeks Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods nanos :: NanoSeconds Source # toNanos :: Weeks -> NanoSeconds Source # fromNanos :: NanoSeconds -> Weeks Source # | |||||
Additive Weeks Source # | |||||
type Rep Weeks Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit |
Days.
Instances
FromJSON Days Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit | |||||
ToJSON Days Source # | |||||
Enum Days Source # | |||||
Generic Days Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Associated Types
| |||||
Num Days Source # | |||||
Integral Days Source # | |||||
Real Days Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods toRational :: Days -> Rational # | |||||
Show Days Source # | |||||
Eq Days Source # | |||||
Ord Days Source # | |||||
TimeUnit Days Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods nanos :: NanoSeconds Source # toNanos :: Days -> NanoSeconds Source # fromNanos :: NanoSeconds -> Days Source # | |||||
Additive Days Source # | |||||
type Rep Days Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit |
Hours.
Instances
FromJSON Hours Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit | |||||
ToJSON Hours Source # | |||||
Enum Hours Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit | |||||
Generic Hours Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Associated Types
| |||||
Num Hours Source # | |||||
Integral Hours Source # | |||||
Real Hours Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods toRational :: Hours -> Rational # | |||||
Show Hours Source # | |||||
Eq Hours Source # | |||||
Ord Hours Source # | |||||
TimeUnit Hours Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods nanos :: NanoSeconds Source # toNanos :: Hours -> NanoSeconds Source # fromNanos :: NanoSeconds -> Hours Source # | |||||
Additive Hours Source # | |||||
type Rep Hours Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit |
Minutes.
Instances
FromJSON Minutes Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit | |||||
ToJSON Minutes Source # | |||||
Enum Minutes Source # | |||||
Generic Minutes Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Associated Types
| |||||
Num Minutes Source # | |||||
Integral Minutes Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit | |||||
Real Minutes Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods toRational :: Minutes -> Rational # | |||||
Show Minutes Source # | |||||
Eq Minutes Source # | |||||
Ord Minutes Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit | |||||
TimeUnit Minutes Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods nanos :: NanoSeconds Source # toNanos :: Minutes -> NanoSeconds Source # fromNanos :: NanoSeconds -> Minutes Source # | |||||
Additive Minutes Source # | |||||
type Rep Minutes Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit |
Seconds.
Instances
FromJSON Seconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit | |||||
ToJSON Seconds Source # | |||||
Enum Seconds Source # | |||||
Generic Seconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Associated Types
| |||||
Num Seconds Source # | |||||
Integral Seconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit | |||||
Real Seconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods toRational :: Seconds -> Rational # | |||||
Show Seconds Source # | |||||
Eq Seconds Source # | |||||
Ord Seconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit | |||||
TimeUnit Seconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods nanos :: NanoSeconds Source # toNanos :: Seconds -> NanoSeconds Source # fromNanos :: NanoSeconds -> Seconds Source # | |||||
Additive Seconds Source # | |||||
type Rep Seconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit |
newtype MilliSeconds Source #
Milliseconds.
Constructors
MilliSeconds | |
Fields |
Instances
newtype MicroSeconds Source #
Microseconds.
Constructors
MicroSeconds | |
Fields |
Instances
FromJSON MicroSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit | |||||
ToJSON MicroSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods toJSON :: MicroSeconds -> Value # toEncoding :: MicroSeconds -> Encoding # toJSONList :: [MicroSeconds] -> Value # toEncodingList :: [MicroSeconds] -> Encoding # omitField :: MicroSeconds -> Bool # | |||||
Enum MicroSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods succ :: MicroSeconds -> MicroSeconds # pred :: MicroSeconds -> MicroSeconds # toEnum :: Int -> MicroSeconds # fromEnum :: MicroSeconds -> Int # enumFrom :: MicroSeconds -> [MicroSeconds] # enumFromThen :: MicroSeconds -> MicroSeconds -> [MicroSeconds] # enumFromTo :: MicroSeconds -> MicroSeconds -> [MicroSeconds] # enumFromThenTo :: MicroSeconds -> MicroSeconds -> MicroSeconds -> [MicroSeconds] # | |||||
Generic MicroSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Associated Types
| |||||
Num MicroSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods (+) :: MicroSeconds -> MicroSeconds -> MicroSeconds # (-) :: MicroSeconds -> MicroSeconds -> MicroSeconds # (*) :: MicroSeconds -> MicroSeconds -> MicroSeconds # negate :: MicroSeconds -> MicroSeconds # abs :: MicroSeconds -> MicroSeconds # signum :: MicroSeconds -> MicroSeconds # fromInteger :: Integer -> MicroSeconds # | |||||
Fractional MicroSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods (/) :: MicroSeconds -> MicroSeconds -> MicroSeconds # recip :: MicroSeconds -> MicroSeconds # fromRational :: Rational -> MicroSeconds # | |||||
Integral MicroSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods quot :: MicroSeconds -> MicroSeconds -> MicroSeconds # rem :: MicroSeconds -> MicroSeconds -> MicroSeconds # div :: MicroSeconds -> MicroSeconds -> MicroSeconds # mod :: MicroSeconds -> MicroSeconds -> MicroSeconds # quotRem :: MicroSeconds -> MicroSeconds -> (MicroSeconds, MicroSeconds) # divMod :: MicroSeconds -> MicroSeconds -> (MicroSeconds, MicroSeconds) # toInteger :: MicroSeconds -> Integer # | |||||
Real MicroSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods toRational :: MicroSeconds -> Rational # | |||||
Show MicroSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods showsPrec :: Int -> MicroSeconds -> ShowS # show :: MicroSeconds -> String # showList :: [MicroSeconds] -> ShowS # | |||||
Eq MicroSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit | |||||
Ord MicroSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods compare :: MicroSeconds -> MicroSeconds -> Ordering # (<) :: MicroSeconds -> MicroSeconds -> Bool # (<=) :: MicroSeconds -> MicroSeconds -> Bool # (>) :: MicroSeconds -> MicroSeconds -> Bool # (>=) :: MicroSeconds -> MicroSeconds -> Bool # max :: MicroSeconds -> MicroSeconds -> MicroSeconds # min :: MicroSeconds -> MicroSeconds -> MicroSeconds # | |||||
TimeUnit MicroSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods nanos :: NanoSeconds Source # toNanos :: MicroSeconds -> NanoSeconds Source # fromNanos :: NanoSeconds -> MicroSeconds Source # | |||||
Additive MicroSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods zero :: MicroSeconds # invert :: MicroSeconds -> MicroSeconds # plus :: MicroSeconds -> MicroSeconds -> MicroSeconds # minus :: MicroSeconds -> MicroSeconds -> MicroSeconds # | |||||
type Rep MicroSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit type Rep MicroSeconds = D1 ('MetaData "MicroSeconds" "Polysemy.Time.Data.TimeUnit" "polysemy-time-0.7.0.1-JuShpFGkFIKBk6OfIeQaxf" 'True) (C1 ('MetaCons "MicroSeconds" 'PrefixI 'True) (S1 ('MetaSel ('Just "unMicroSeconds") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64))) |
newtype NanoSeconds Source #
Nanoseconds. This is the base unit for all conversions.
Constructors
NanoSeconds | |
Fields |
Instances
FromJSON NanoSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit | |||||
ToJSON NanoSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods toJSON :: NanoSeconds -> Value # toEncoding :: NanoSeconds -> Encoding # toJSONList :: [NanoSeconds] -> Value # toEncodingList :: [NanoSeconds] -> Encoding # omitField :: NanoSeconds -> Bool # | |||||
Enum NanoSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods succ :: NanoSeconds -> NanoSeconds # pred :: NanoSeconds -> NanoSeconds # toEnum :: Int -> NanoSeconds # fromEnum :: NanoSeconds -> Int # enumFrom :: NanoSeconds -> [NanoSeconds] # enumFromThen :: NanoSeconds -> NanoSeconds -> [NanoSeconds] # enumFromTo :: NanoSeconds -> NanoSeconds -> [NanoSeconds] # enumFromThenTo :: NanoSeconds -> NanoSeconds -> NanoSeconds -> [NanoSeconds] # | |||||
Generic NanoSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Associated Types
| |||||
Num NanoSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods (+) :: NanoSeconds -> NanoSeconds -> NanoSeconds # (-) :: NanoSeconds -> NanoSeconds -> NanoSeconds # (*) :: NanoSeconds -> NanoSeconds -> NanoSeconds # negate :: NanoSeconds -> NanoSeconds # abs :: NanoSeconds -> NanoSeconds # signum :: NanoSeconds -> NanoSeconds # fromInteger :: Integer -> NanoSeconds # | |||||
Fractional NanoSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods (/) :: NanoSeconds -> NanoSeconds -> NanoSeconds # recip :: NanoSeconds -> NanoSeconds # fromRational :: Rational -> NanoSeconds # | |||||
Integral NanoSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods quot :: NanoSeconds -> NanoSeconds -> NanoSeconds # rem :: NanoSeconds -> NanoSeconds -> NanoSeconds # div :: NanoSeconds -> NanoSeconds -> NanoSeconds # mod :: NanoSeconds -> NanoSeconds -> NanoSeconds # quotRem :: NanoSeconds -> NanoSeconds -> (NanoSeconds, NanoSeconds) # divMod :: NanoSeconds -> NanoSeconds -> (NanoSeconds, NanoSeconds) # toInteger :: NanoSeconds -> Integer # | |||||
Real NanoSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods toRational :: NanoSeconds -> Rational # | |||||
Show NanoSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods showsPrec :: Int -> NanoSeconds -> ShowS # show :: NanoSeconds -> String # showList :: [NanoSeconds] -> ShowS # | |||||
Eq NanoSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit | |||||
Ord NanoSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods compare :: NanoSeconds -> NanoSeconds -> Ordering # (<) :: NanoSeconds -> NanoSeconds -> Bool # (<=) :: NanoSeconds -> NanoSeconds -> Bool # (>) :: NanoSeconds -> NanoSeconds -> Bool # (>=) :: NanoSeconds -> NanoSeconds -> Bool # max :: NanoSeconds -> NanoSeconds -> NanoSeconds # min :: NanoSeconds -> NanoSeconds -> NanoSeconds # | |||||
TimeUnit NanoSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods nanos :: NanoSeconds Source # toNanos :: NanoSeconds -> NanoSeconds Source # fromNanos :: NanoSeconds -> NanoSeconds Source # | |||||
Additive NanoSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods zero :: NanoSeconds # invert :: NanoSeconds -> NanoSeconds # plus :: NanoSeconds -> NanoSeconds -> NanoSeconds # minus :: NanoSeconds -> NanoSeconds -> NanoSeconds # | |||||
Scaling NanoSeconds Int64 Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit Methods scale :: Int64 -> NanoSeconds -> NanoSeconds # | |||||
type Rep NanoSeconds Source # | |||||
Defined in Polysemy.Time.Data.TimeUnit type Rep NanoSeconds = D1 ('MetaData "NanoSeconds" "Polysemy.Time.Data.TimeUnit" "polysemy-time-0.7.0.1-JuShpFGkFIKBk6OfIeQaxf" 'True) (C1 ('MetaCons "NanoSeconds" 'PrefixI 'True) (S1 ('MetaSel ('Just "unNanoSeconds") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64))) |
convert :: (TimeUnit a, TimeUnit b) => a -> b Source #
Convert between different time spans.
>>>
convert (picosecondsToDiffTime 50000000) :: MicroSeconds
MicroSeconds {unMicroSeconds = 50}
>>>
convert (MilliSeconds 5) :: MicroSeconds
MicroSeconds 5000
type AddTimeUnit t u1 u2 = (TimeUnit u1, TimeUnit u2, Torsor t u2) Source #
Convenience alias for addTimeUnit
.
addTimeUnit :: AddTimeUnit t u1 u2 => u1 -> t -> t Source #
Add a time unit to an instant.
secondsFrac :: TimeUnit u => u -> Double Source #
Convert a unit into a number of seconds, keeping the subsecond part as fractional digits.