{-# options_haddock prune #-}

-- |TimeUnit Class and Data Types, Internal
module Polysemy.Time.Data.TimeUnit where

import Data.Time (DiffTime, NominalDiffTime, diffTimeToPicoseconds, picosecondsToDiffTime)
import qualified GHC.Real as Real
import Torsor (Additive, Scaling, Torsor, add, scale)

import Polysemy.Time.Json (json)

-- |For deriving via.
newtype FromSeconds a =
  FromSeconds a
  deriving stock (FromSeconds a -> FromSeconds a -> Bool
forall a. Eq a => FromSeconds a -> FromSeconds a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FromSeconds a -> FromSeconds a -> Bool
$c/= :: forall a. Eq a => FromSeconds a -> FromSeconds a -> Bool
== :: FromSeconds a -> FromSeconds a -> Bool
$c== :: forall a. Eq a => FromSeconds a -> FromSeconds a -> Bool
Eq, Int -> FromSeconds a -> ShowS
forall a. Show a => Int -> FromSeconds a -> ShowS
forall a. Show a => [FromSeconds a] -> ShowS
forall a. Show a => FromSeconds a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FromSeconds a] -> ShowS
$cshowList :: forall a. Show a => [FromSeconds a] -> ShowS
show :: FromSeconds a -> String
$cshow :: forall a. Show a => FromSeconds a -> String
showsPrec :: Int -> FromSeconds a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> FromSeconds a -> ShowS
Show)
  deriving newtype (Integer -> FromSeconds a
FromSeconds a -> FromSeconds a
FromSeconds a -> FromSeconds a -> FromSeconds a
forall a. Num a => Integer -> FromSeconds a
forall a. Num a => FromSeconds a -> FromSeconds a
forall a. Num a => FromSeconds a -> FromSeconds a -> FromSeconds a
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> FromSeconds a
$cfromInteger :: forall a. Num a => Integer -> FromSeconds a
signum :: FromSeconds a -> FromSeconds a
$csignum :: forall a. Num a => FromSeconds a -> FromSeconds a
abs :: FromSeconds a -> FromSeconds a
$cabs :: forall a. Num a => FromSeconds a -> FromSeconds a
negate :: FromSeconds a -> FromSeconds a
$cnegate :: forall a. Num a => FromSeconds a -> FromSeconds a
* :: FromSeconds a -> FromSeconds a -> FromSeconds a
$c* :: forall a. Num a => FromSeconds a -> FromSeconds a -> FromSeconds a
- :: FromSeconds a -> FromSeconds a -> FromSeconds a
$c- :: forall a. Num a => FromSeconds a -> FromSeconds a -> FromSeconds a
+ :: FromSeconds a -> FromSeconds a -> FromSeconds a
$c+ :: forall a. Num a => FromSeconds a -> FromSeconds a -> FromSeconds a
Num)

instance (Integral a, TimeUnit a) => Fractional (FromSeconds a) where
  fromRational :: Rational -> FromSeconds a
fromRational Rational
secs =
    forall a. a -> FromSeconds a
FromSeconds (forall a b. (TimeUnit a, TimeUnit b) => a -> b
convert (Int64 -> NanoSeconds
NanoSeconds (forall a b. (RealFrac a, Integral b) => a -> b
round (Rational
1e9 forall a. Num a => a -> a -> a
* Rational
secs))))
  FromSeconds a
a / :: FromSeconds a -> FromSeconds a -> FromSeconds a
/ FromSeconds a
b =
    forall a. a -> FromSeconds a
FromSeconds (a
a forall a. Integral a => a -> a -> a
`Real.div` a
b)

-- |Types that represent an amount of time that can be converted to each other.
-- The methods are internal, the API function is 'convert'.
class TimeUnit u where
  nanos :: NanoSeconds

  toNanos :: u -> NanoSeconds
  default toNanos :: Integral u => u -> NanoSeconds
  toNanos u
u =
    forall v s. Scaling v s => s -> v -> v
scale (forall a b. (Integral a, Num b) => a -> b
fromIntegral u
u) (forall u. TimeUnit u => NanoSeconds
nanos @u)

  fromNanos :: NanoSeconds -> u
  default fromNanos :: Integral u => NanoSeconds -> u
  fromNanos NanoSeconds
n =
    forall a b. (Integral a, Num b) => a -> b
fromIntegral (NanoSeconds
n forall a. Integral a => a -> a -> a
`Real.div` (forall u. TimeUnit u => NanoSeconds
nanos @u))

-- * Data types used to specify time spans, e.g. for sleeping.

-- |Years.
newtype Years =
  Years { Years -> Int64
unYear :: Int64 }
  deriving stock (Years -> Years -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Years -> Years -> Bool
$c/= :: Years -> Years -> Bool
== :: Years -> Years -> Bool
$c== :: Years -> Years -> Bool
Eq, Int -> Years -> ShowS
[Years] -> ShowS
Years -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Years] -> ShowS
$cshowList :: [Years] -> ShowS
show :: Years -> String
$cshow :: Years -> String
showsPrec :: Int -> Years -> ShowS
$cshowsPrec :: Int -> Years -> ShowS
Show, forall x. Rep Years x -> Years
forall x. Years -> Rep Years x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Years x -> Years
$cfrom :: forall x. Years -> Rep Years x
Generic)
  deriving newtype (Integer -> Years
Years -> Years
Years -> Years -> Years
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Years
$cfromInteger :: Integer -> Years
signum :: Years -> Years
$csignum :: Years -> Years
abs :: Years -> Years
$cabs :: Years -> Years
negate :: Years -> Years
$cnegate :: Years -> Years
* :: Years -> Years -> Years
$c* :: Years -> Years -> Years
- :: Years -> Years -> Years
$c- :: Years -> Years -> Years
+ :: Years -> Years -> Years
$c+ :: Years -> Years -> Years
Num, Num Years
Ord Years
Years -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Years -> Rational
$ctoRational :: Years -> Rational
Real, Int -> Years
Years -> Int
Years -> [Years]
Years -> Years
Years -> Years -> [Years]
Years -> Years -> Years -> [Years]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Years -> Years -> Years -> [Years]
$cenumFromThenTo :: Years -> Years -> Years -> [Years]
enumFromTo :: Years -> Years -> [Years]
$cenumFromTo :: Years -> Years -> [Years]
enumFromThen :: Years -> Years -> [Years]
$cenumFromThen :: Years -> Years -> [Years]
enumFrom :: Years -> [Years]
$cenumFrom :: Years -> [Years]
fromEnum :: Years -> Int
$cfromEnum :: Years -> Int
toEnum :: Int -> Years
$ctoEnum :: Int -> Years
pred :: Years -> Years
$cpred :: Years -> Years
succ :: Years -> Years
$csucc :: Years -> Years
Enum, Enum Years
Real Years
Years -> Integer
Years -> Years -> (Years, Years)
Years -> Years -> Years
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: Years -> Integer
$ctoInteger :: Years -> Integer
divMod :: Years -> Years -> (Years, Years)
$cdivMod :: Years -> Years -> (Years, Years)
quotRem :: Years -> Years -> (Years, Years)
$cquotRem :: Years -> Years -> (Years, Years)
mod :: Years -> Years -> Years
$cmod :: Years -> Years -> Years
div :: Years -> Years -> Years
$cdiv :: Years -> Years -> Years
rem :: Years -> Years -> Years
$crem :: Years -> Years -> Years
quot :: Years -> Years -> Years
$cquot :: Years -> Years -> Years
Integral, Eq Years
Years -> Years -> Bool
Years -> Years -> Ordering
Years -> Years -> Years
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Years -> Years -> Years
$cmin :: Years -> Years -> Years
max :: Years -> Years -> Years
$cmax :: Years -> Years -> Years
>= :: Years -> Years -> Bool
$c>= :: Years -> Years -> Bool
> :: Years -> Years -> Bool
$c> :: Years -> Years -> Bool
<= :: Years -> Years -> Bool
$c<= :: Years -> Years -> Bool
< :: Years -> Years -> Bool
$c< :: Years -> Years -> Bool
compare :: Years -> Years -> Ordering
$ccompare :: Years -> Years -> Ordering
Ord, Years
Years -> Years
Years -> Years -> Years
forall v.
v -> (v -> v) -> (v -> v -> v) -> (v -> v -> v) -> Additive v
minus :: Years -> Years -> Years
$cminus :: Years -> Years -> Years
plus :: Years -> Years -> Years
$cplus :: Years -> Years -> Years
invert :: Years -> Years
$cinvert :: Years -> Years
zero :: Years
$czero :: Years
Additive)

-- |Months.
newtype Months =
  Months { Months -> Int64
unMonths :: Int64 }
  deriving stock (Months -> Months -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Months -> Months -> Bool
$c/= :: Months -> Months -> Bool
== :: Months -> Months -> Bool
$c== :: Months -> Months -> Bool
Eq, Int -> Months -> ShowS
[Months] -> ShowS
Months -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Months] -> ShowS
$cshowList :: [Months] -> ShowS
show :: Months -> String
$cshow :: Months -> String
showsPrec :: Int -> Months -> ShowS
$cshowsPrec :: Int -> Months -> ShowS
Show, forall x. Rep Months x -> Months
forall x. Months -> Rep Months x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Months x -> Months
$cfrom :: forall x. Months -> Rep Months x
Generic)
  deriving newtype (Integer -> Months
Months -> Months
Months -> Months -> Months
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Months
$cfromInteger :: Integer -> Months
signum :: Months -> Months
$csignum :: Months -> Months
abs :: Months -> Months
$cabs :: Months -> Months
negate :: Months -> Months
$cnegate :: Months -> Months
* :: Months -> Months -> Months
$c* :: Months -> Months -> Months
- :: Months -> Months -> Months
$c- :: Months -> Months -> Months
+ :: Months -> Months -> Months
$c+ :: Months -> Months -> Months
Num, Num Months
Ord Months
Months -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Months -> Rational
$ctoRational :: Months -> Rational
Real, Int -> Months
Months -> Int
Months -> [Months]
Months -> Months
Months -> Months -> [Months]
Months -> Months -> Months -> [Months]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Months -> Months -> Months -> [Months]
$cenumFromThenTo :: Months -> Months -> Months -> [Months]
enumFromTo :: Months -> Months -> [Months]
$cenumFromTo :: Months -> Months -> [Months]
enumFromThen :: Months -> Months -> [Months]
$cenumFromThen :: Months -> Months -> [Months]
enumFrom :: Months -> [Months]
$cenumFrom :: Months -> [Months]
fromEnum :: Months -> Int
$cfromEnum :: Months -> Int
toEnum :: Int -> Months
$ctoEnum :: Int -> Months
pred :: Months -> Months
$cpred :: Months -> Months
succ :: Months -> Months
$csucc :: Months -> Months
Enum, Enum Months
Real Months
Months -> Integer
Months -> Months -> (Months, Months)
Months -> Months -> Months
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: Months -> Integer
$ctoInteger :: Months -> Integer
divMod :: Months -> Months -> (Months, Months)
$cdivMod :: Months -> Months -> (Months, Months)
quotRem :: Months -> Months -> (Months, Months)
$cquotRem :: Months -> Months -> (Months, Months)
mod :: Months -> Months -> Months
$cmod :: Months -> Months -> Months
div :: Months -> Months -> Months
$cdiv :: Months -> Months -> Months
rem :: Months -> Months -> Months
$crem :: Months -> Months -> Months
quot :: Months -> Months -> Months
$cquot :: Months -> Months -> Months
Integral, Eq Months
Months -> Months -> Bool
Months -> Months -> Ordering
Months -> Months -> Months
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Months -> Months -> Months
$cmin :: Months -> Months -> Months
max :: Months -> Months -> Months
$cmax :: Months -> Months -> Months
>= :: Months -> Months -> Bool
$c>= :: Months -> Months -> Bool
> :: Months -> Months -> Bool
$c> :: Months -> Months -> Bool
<= :: Months -> Months -> Bool
$c<= :: Months -> Months -> Bool
< :: Months -> Months -> Bool
$c< :: Months -> Months -> Bool
compare :: Months -> Months -> Ordering
$ccompare :: Months -> Months -> Ordering
Ord, Months
Months -> Months
Months -> Months -> Months
forall v.
v -> (v -> v) -> (v -> v -> v) -> (v -> v -> v) -> Additive v
minus :: Months -> Months -> Months
$cminus :: Months -> Months -> Months
plus :: Months -> Months -> Months
$cplus :: Months -> Months -> Months
invert :: Months -> Months
$cinvert :: Months -> Months
zero :: Months
$czero :: Months
Additive)

-- |Weeks.
newtype Weeks =
  Weeks { Weeks -> Int64
unWeeks :: Int64 }
  deriving stock (Weeks -> Weeks -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Weeks -> Weeks -> Bool
$c/= :: Weeks -> Weeks -> Bool
== :: Weeks -> Weeks -> Bool
$c== :: Weeks -> Weeks -> Bool
Eq, Int -> Weeks -> ShowS
[Weeks] -> ShowS
Weeks -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Weeks] -> ShowS
$cshowList :: [Weeks] -> ShowS
show :: Weeks -> String
$cshow :: Weeks -> String
showsPrec :: Int -> Weeks -> ShowS
$cshowsPrec :: Int -> Weeks -> ShowS
Show, forall x. Rep Weeks x -> Weeks
forall x. Weeks -> Rep Weeks x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Weeks x -> Weeks
$cfrom :: forall x. Weeks -> Rep Weeks x
Generic)
  deriving newtype (Integer -> Weeks
Weeks -> Weeks
Weeks -> Weeks -> Weeks
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Weeks
$cfromInteger :: Integer -> Weeks
signum :: Weeks -> Weeks
$csignum :: Weeks -> Weeks
abs :: Weeks -> Weeks
$cabs :: Weeks -> Weeks
negate :: Weeks -> Weeks
$cnegate :: Weeks -> Weeks
* :: Weeks -> Weeks -> Weeks
$c* :: Weeks -> Weeks -> Weeks
- :: Weeks -> Weeks -> Weeks
$c- :: Weeks -> Weeks -> Weeks
+ :: Weeks -> Weeks -> Weeks
$c+ :: Weeks -> Weeks -> Weeks
Num, Num Weeks
Ord Weeks
Weeks -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Weeks -> Rational
$ctoRational :: Weeks -> Rational
Real, Int -> Weeks
Weeks -> Int
Weeks -> [Weeks]
Weeks -> Weeks
Weeks -> Weeks -> [Weeks]
Weeks -> Weeks -> Weeks -> [Weeks]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Weeks -> Weeks -> Weeks -> [Weeks]
$cenumFromThenTo :: Weeks -> Weeks -> Weeks -> [Weeks]
enumFromTo :: Weeks -> Weeks -> [Weeks]
$cenumFromTo :: Weeks -> Weeks -> [Weeks]
enumFromThen :: Weeks -> Weeks -> [Weeks]
$cenumFromThen :: Weeks -> Weeks -> [Weeks]
enumFrom :: Weeks -> [Weeks]
$cenumFrom :: Weeks -> [Weeks]
fromEnum :: Weeks -> Int
$cfromEnum :: Weeks -> Int
toEnum :: Int -> Weeks
$ctoEnum :: Int -> Weeks
pred :: Weeks -> Weeks
$cpred :: Weeks -> Weeks
succ :: Weeks -> Weeks
$csucc :: Weeks -> Weeks
Enum, Enum Weeks
Real Weeks
Weeks -> Integer
Weeks -> Weeks -> (Weeks, Weeks)
Weeks -> Weeks -> Weeks
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: Weeks -> Integer
$ctoInteger :: Weeks -> Integer
divMod :: Weeks -> Weeks -> (Weeks, Weeks)
$cdivMod :: Weeks -> Weeks -> (Weeks, Weeks)
quotRem :: Weeks -> Weeks -> (Weeks, Weeks)
$cquotRem :: Weeks -> Weeks -> (Weeks, Weeks)
mod :: Weeks -> Weeks -> Weeks
$cmod :: Weeks -> Weeks -> Weeks
div :: Weeks -> Weeks -> Weeks
$cdiv :: Weeks -> Weeks -> Weeks
rem :: Weeks -> Weeks -> Weeks
$crem :: Weeks -> Weeks -> Weeks
quot :: Weeks -> Weeks -> Weeks
$cquot :: Weeks -> Weeks -> Weeks
Integral, Eq Weeks
Weeks -> Weeks -> Bool
Weeks -> Weeks -> Ordering
Weeks -> Weeks -> Weeks
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Weeks -> Weeks -> Weeks
$cmin :: Weeks -> Weeks -> Weeks
max :: Weeks -> Weeks -> Weeks
$cmax :: Weeks -> Weeks -> Weeks
>= :: Weeks -> Weeks -> Bool
$c>= :: Weeks -> Weeks -> Bool
> :: Weeks -> Weeks -> Bool
$c> :: Weeks -> Weeks -> Bool
<= :: Weeks -> Weeks -> Bool
$c<= :: Weeks -> Weeks -> Bool
< :: Weeks -> Weeks -> Bool
$c< :: Weeks -> Weeks -> Bool
compare :: Weeks -> Weeks -> Ordering
$ccompare :: Weeks -> Weeks -> Ordering
Ord, Weeks
Weeks -> Weeks
Weeks -> Weeks -> Weeks
forall v.
v -> (v -> v) -> (v -> v -> v) -> (v -> v -> v) -> Additive v
minus :: Weeks -> Weeks -> Weeks
$cminus :: Weeks -> Weeks -> Weeks
plus :: Weeks -> Weeks -> Weeks
$cplus :: Weeks -> Weeks -> Weeks
invert :: Weeks -> Weeks
$cinvert :: Weeks -> Weeks
zero :: Weeks
$czero :: Weeks
Additive)

instance TimeUnit Weeks where
  nanos :: NanoSeconds
nanos =
    Int64 -> NanoSeconds
NanoSeconds Int64
604800000000000

-- |Days.
newtype Days =
  Days { Days -> Int64
unDays :: Int64 }
  deriving stock (Days -> Days -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Days -> Days -> Bool
$c/= :: Days -> Days -> Bool
== :: Days -> Days -> Bool
$c== :: Days -> Days -> Bool
Eq, Int -> Days -> ShowS
[Days] -> ShowS
Days -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Days] -> ShowS
$cshowList :: [Days] -> ShowS
show :: Days -> String
$cshow :: Days -> String
showsPrec :: Int -> Days -> ShowS
$cshowsPrec :: Int -> Days -> ShowS
Show, forall x. Rep Days x -> Days
forall x. Days -> Rep Days x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Days x -> Days
$cfrom :: forall x. Days -> Rep Days x
Generic)
  deriving newtype (Integer -> Days
Days -> Days
Days -> Days -> Days
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Days
$cfromInteger :: Integer -> Days
signum :: Days -> Days
$csignum :: Days -> Days
abs :: Days -> Days
$cabs :: Days -> Days
negate :: Days -> Days
$cnegate :: Days -> Days
* :: Days -> Days -> Days
$c* :: Days -> Days -> Days
- :: Days -> Days -> Days
$c- :: Days -> Days -> Days
+ :: Days -> Days -> Days
$c+ :: Days -> Days -> Days
Num, Num Days
Ord Days
Days -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Days -> Rational
$ctoRational :: Days -> Rational
Real, Int -> Days
Days -> Int
Days -> [Days]
Days -> Days
Days -> Days -> [Days]
Days -> Days -> Days -> [Days]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Days -> Days -> Days -> [Days]
$cenumFromThenTo :: Days -> Days -> Days -> [Days]
enumFromTo :: Days -> Days -> [Days]
$cenumFromTo :: Days -> Days -> [Days]
enumFromThen :: Days -> Days -> [Days]
$cenumFromThen :: Days -> Days -> [Days]
enumFrom :: Days -> [Days]
$cenumFrom :: Days -> [Days]
fromEnum :: Days -> Int
$cfromEnum :: Days -> Int
toEnum :: Int -> Days
$ctoEnum :: Int -> Days
pred :: Days -> Days
$cpred :: Days -> Days
succ :: Days -> Days
$csucc :: Days -> Days
Enum, Enum Days
Real Days
Days -> Integer
Days -> Days -> (Days, Days)
Days -> Days -> Days
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: Days -> Integer
$ctoInteger :: Days -> Integer
divMod :: Days -> Days -> (Days, Days)
$cdivMod :: Days -> Days -> (Days, Days)
quotRem :: Days -> Days -> (Days, Days)
$cquotRem :: Days -> Days -> (Days, Days)
mod :: Days -> Days -> Days
$cmod :: Days -> Days -> Days
div :: Days -> Days -> Days
$cdiv :: Days -> Days -> Days
rem :: Days -> Days -> Days
$crem :: Days -> Days -> Days
quot :: Days -> Days -> Days
$cquot :: Days -> Days -> Days
Integral, Eq Days
Days -> Days -> Bool
Days -> Days -> Ordering
Days -> Days -> Days
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Days -> Days -> Days
$cmin :: Days -> Days -> Days
max :: Days -> Days -> Days
$cmax :: Days -> Days -> Days
>= :: Days -> Days -> Bool
$c>= :: Days -> Days -> Bool
> :: Days -> Days -> Bool
$c> :: Days -> Days -> Bool
<= :: Days -> Days -> Bool
$c<= :: Days -> Days -> Bool
< :: Days -> Days -> Bool
$c< :: Days -> Days -> Bool
compare :: Days -> Days -> Ordering
$ccompare :: Days -> Days -> Ordering
Ord, Days
Days -> Days
Days -> Days -> Days
forall v.
v -> (v -> v) -> (v -> v -> v) -> (v -> v -> v) -> Additive v
minus :: Days -> Days -> Days
$cminus :: Days -> Days -> Days
plus :: Days -> Days -> Days
$cplus :: Days -> Days -> Days
invert :: Days -> Days
$cinvert :: Days -> Days
zero :: Days
$czero :: Days
Additive)

instance TimeUnit Days where
  nanos :: NanoSeconds
nanos =
    Int64 -> NanoSeconds
NanoSeconds Int64
86400000000000

-- |Hours.
newtype Hours =
  Hours { Hours -> Int64
unHours :: Int64 }
  deriving stock (Hours -> Hours -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hours -> Hours -> Bool
$c/= :: Hours -> Hours -> Bool
== :: Hours -> Hours -> Bool
$c== :: Hours -> Hours -> Bool
Eq, Int -> Hours -> ShowS
[Hours] -> ShowS
Hours -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Hours] -> ShowS
$cshowList :: [Hours] -> ShowS
show :: Hours -> String
$cshow :: Hours -> String
showsPrec :: Int -> Hours -> ShowS
$cshowsPrec :: Int -> Hours -> ShowS
Show, forall x. Rep Hours x -> Hours
forall x. Hours -> Rep Hours x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Hours x -> Hours
$cfrom :: forall x. Hours -> Rep Hours x
Generic)
  deriving newtype (Integer -> Hours
Hours -> Hours
Hours -> Hours -> Hours
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Hours
$cfromInteger :: Integer -> Hours
signum :: Hours -> Hours
$csignum :: Hours -> Hours
abs :: Hours -> Hours
$cabs :: Hours -> Hours
negate :: Hours -> Hours
$cnegate :: Hours -> Hours
* :: Hours -> Hours -> Hours
$c* :: Hours -> Hours -> Hours
- :: Hours -> Hours -> Hours
$c- :: Hours -> Hours -> Hours
+ :: Hours -> Hours -> Hours
$c+ :: Hours -> Hours -> Hours
Num, Num Hours
Ord Hours
Hours -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Hours -> Rational
$ctoRational :: Hours -> Rational
Real, Int -> Hours
Hours -> Int
Hours -> [Hours]
Hours -> Hours
Hours -> Hours -> [Hours]
Hours -> Hours -> Hours -> [Hours]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Hours -> Hours -> Hours -> [Hours]
$cenumFromThenTo :: Hours -> Hours -> Hours -> [Hours]
enumFromTo :: Hours -> Hours -> [Hours]
$cenumFromTo :: Hours -> Hours -> [Hours]
enumFromThen :: Hours -> Hours -> [Hours]
$cenumFromThen :: Hours -> Hours -> [Hours]
enumFrom :: Hours -> [Hours]
$cenumFrom :: Hours -> [Hours]
fromEnum :: Hours -> Int
$cfromEnum :: Hours -> Int
toEnum :: Int -> Hours
$ctoEnum :: Int -> Hours
pred :: Hours -> Hours
$cpred :: Hours -> Hours
succ :: Hours -> Hours
$csucc :: Hours -> Hours
Enum, Enum Hours
Real Hours
Hours -> Integer
Hours -> Hours -> (Hours, Hours)
Hours -> Hours -> Hours
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: Hours -> Integer
$ctoInteger :: Hours -> Integer
divMod :: Hours -> Hours -> (Hours, Hours)
$cdivMod :: Hours -> Hours -> (Hours, Hours)
quotRem :: Hours -> Hours -> (Hours, Hours)
$cquotRem :: Hours -> Hours -> (Hours, Hours)
mod :: Hours -> Hours -> Hours
$cmod :: Hours -> Hours -> Hours
div :: Hours -> Hours -> Hours
$cdiv :: Hours -> Hours -> Hours
rem :: Hours -> Hours -> Hours
$crem :: Hours -> Hours -> Hours
quot :: Hours -> Hours -> Hours
$cquot :: Hours -> Hours -> Hours
Integral, Eq Hours
Hours -> Hours -> Bool
Hours -> Hours -> Ordering
Hours -> Hours -> Hours
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Hours -> Hours -> Hours
$cmin :: Hours -> Hours -> Hours
max :: Hours -> Hours -> Hours
$cmax :: Hours -> Hours -> Hours
>= :: Hours -> Hours -> Bool
$c>= :: Hours -> Hours -> Bool
> :: Hours -> Hours -> Bool
$c> :: Hours -> Hours -> Bool
<= :: Hours -> Hours -> Bool
$c<= :: Hours -> Hours -> Bool
< :: Hours -> Hours -> Bool
$c< :: Hours -> Hours -> Bool
compare :: Hours -> Hours -> Ordering
$ccompare :: Hours -> Hours -> Ordering
Ord, Hours
Hours -> Hours
Hours -> Hours -> Hours
forall v.
v -> (v -> v) -> (v -> v -> v) -> (v -> v -> v) -> Additive v
minus :: Hours -> Hours -> Hours
$cminus :: Hours -> Hours -> Hours
plus :: Hours -> Hours -> Hours
$cplus :: Hours -> Hours -> Hours
invert :: Hours -> Hours
$cinvert :: Hours -> Hours
zero :: Hours
$czero :: Hours
Additive)

instance TimeUnit Hours where
  nanos :: NanoSeconds
nanos =
    Int64 -> NanoSeconds
NanoSeconds Int64
3600000000000

-- |Minutes.
newtype Minutes =
  Minutes { Minutes -> Int64
unMinutes :: Int64 }
  deriving stock (Minutes -> Minutes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Minutes -> Minutes -> Bool
$c/= :: Minutes -> Minutes -> Bool
== :: Minutes -> Minutes -> Bool
$c== :: Minutes -> Minutes -> Bool
Eq, Int -> Minutes -> ShowS
[Minutes] -> ShowS
Minutes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Minutes] -> ShowS
$cshowList :: [Minutes] -> ShowS
show :: Minutes -> String
$cshow :: Minutes -> String
showsPrec :: Int -> Minutes -> ShowS
$cshowsPrec :: Int -> Minutes -> ShowS
Show, forall x. Rep Minutes x -> Minutes
forall x. Minutes -> Rep Minutes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Minutes x -> Minutes
$cfrom :: forall x. Minutes -> Rep Minutes x
Generic)
  deriving newtype (Integer -> Minutes
Minutes -> Minutes
Minutes -> Minutes -> Minutes
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Minutes
$cfromInteger :: Integer -> Minutes
signum :: Minutes -> Minutes
$csignum :: Minutes -> Minutes
abs :: Minutes -> Minutes
$cabs :: Minutes -> Minutes
negate :: Minutes -> Minutes
$cnegate :: Minutes -> Minutes
* :: Minutes -> Minutes -> Minutes
$c* :: Minutes -> Minutes -> Minutes
- :: Minutes -> Minutes -> Minutes
$c- :: Minutes -> Minutes -> Minutes
+ :: Minutes -> Minutes -> Minutes
$c+ :: Minutes -> Minutes -> Minutes
Num, Num Minutes
Ord Minutes
Minutes -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Minutes -> Rational
$ctoRational :: Minutes -> Rational
Real, Int -> Minutes
Minutes -> Int
Minutes -> [Minutes]
Minutes -> Minutes
Minutes -> Minutes -> [Minutes]
Minutes -> Minutes -> Minutes -> [Minutes]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Minutes -> Minutes -> Minutes -> [Minutes]
$cenumFromThenTo :: Minutes -> Minutes -> Minutes -> [Minutes]
enumFromTo :: Minutes -> Minutes -> [Minutes]
$cenumFromTo :: Minutes -> Minutes -> [Minutes]
enumFromThen :: Minutes -> Minutes -> [Minutes]
$cenumFromThen :: Minutes -> Minutes -> [Minutes]
enumFrom :: Minutes -> [Minutes]
$cenumFrom :: Minutes -> [Minutes]
fromEnum :: Minutes -> Int
$cfromEnum :: Minutes -> Int
toEnum :: Int -> Minutes
$ctoEnum :: Int -> Minutes
pred :: Minutes -> Minutes
$cpred :: Minutes -> Minutes
succ :: Minutes -> Minutes
$csucc :: Minutes -> Minutes
Enum, Enum Minutes
Real Minutes
Minutes -> Integer
Minutes -> Minutes -> (Minutes, Minutes)
Minutes -> Minutes -> Minutes
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: Minutes -> Integer
$ctoInteger :: Minutes -> Integer
divMod :: Minutes -> Minutes -> (Minutes, Minutes)
$cdivMod :: Minutes -> Minutes -> (Minutes, Minutes)
quotRem :: Minutes -> Minutes -> (Minutes, Minutes)
$cquotRem :: Minutes -> Minutes -> (Minutes, Minutes)
mod :: Minutes -> Minutes -> Minutes
$cmod :: Minutes -> Minutes -> Minutes
div :: Minutes -> Minutes -> Minutes
$cdiv :: Minutes -> Minutes -> Minutes
rem :: Minutes -> Minutes -> Minutes
$crem :: Minutes -> Minutes -> Minutes
quot :: Minutes -> Minutes -> Minutes
$cquot :: Minutes -> Minutes -> Minutes
Integral, Eq Minutes
Minutes -> Minutes -> Bool
Minutes -> Minutes -> Ordering
Minutes -> Minutes -> Minutes
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Minutes -> Minutes -> Minutes
$cmin :: Minutes -> Minutes -> Minutes
max :: Minutes -> Minutes -> Minutes
$cmax :: Minutes -> Minutes -> Minutes
>= :: Minutes -> Minutes -> Bool
$c>= :: Minutes -> Minutes -> Bool
> :: Minutes -> Minutes -> Bool
$c> :: Minutes -> Minutes -> Bool
<= :: Minutes -> Minutes -> Bool
$c<= :: Minutes -> Minutes -> Bool
< :: Minutes -> Minutes -> Bool
$c< :: Minutes -> Minutes -> Bool
compare :: Minutes -> Minutes -> Ordering
$ccompare :: Minutes -> Minutes -> Ordering
Ord, Minutes
Minutes -> Minutes
Minutes -> Minutes -> Minutes
forall v.
v -> (v -> v) -> (v -> v -> v) -> (v -> v -> v) -> Additive v
minus :: Minutes -> Minutes -> Minutes
$cminus :: Minutes -> Minutes -> Minutes
plus :: Minutes -> Minutes -> Minutes
$cplus :: Minutes -> Minutes -> Minutes
invert :: Minutes -> Minutes
$cinvert :: Minutes -> Minutes
zero :: Minutes
$czero :: Minutes
Additive)

instance TimeUnit Minutes where
  nanos :: NanoSeconds
nanos =
    Int64 -> NanoSeconds
NanoSeconds Int64
60000000000

-- |Seconds.
newtype Seconds =
  Seconds { Seconds -> Int64
unSeconds :: Int64 }
  deriving stock (Seconds -> Seconds -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Seconds -> Seconds -> Bool
$c/= :: Seconds -> Seconds -> Bool
== :: Seconds -> Seconds -> Bool
$c== :: Seconds -> Seconds -> Bool
Eq, Int -> Seconds -> ShowS
[Seconds] -> ShowS
Seconds -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Seconds] -> ShowS
$cshowList :: [Seconds] -> ShowS
show :: Seconds -> String
$cshow :: Seconds -> String
showsPrec :: Int -> Seconds -> ShowS
$cshowsPrec :: Int -> Seconds -> ShowS
Show, forall x. Rep Seconds x -> Seconds
forall x. Seconds -> Rep Seconds x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Seconds x -> Seconds
$cfrom :: forall x. Seconds -> Rep Seconds x
Generic)
  deriving newtype (Integer -> Seconds
Seconds -> Seconds
Seconds -> Seconds -> Seconds
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Seconds
$cfromInteger :: Integer -> Seconds
signum :: Seconds -> Seconds
$csignum :: Seconds -> Seconds
abs :: Seconds -> Seconds
$cabs :: Seconds -> Seconds
negate :: Seconds -> Seconds
$cnegate :: Seconds -> Seconds
* :: Seconds -> Seconds -> Seconds
$c* :: Seconds -> Seconds -> Seconds
- :: Seconds -> Seconds -> Seconds
$c- :: Seconds -> Seconds -> Seconds
+ :: Seconds -> Seconds -> Seconds
$c+ :: Seconds -> Seconds -> Seconds
Num, Num Seconds
Ord Seconds
Seconds -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Seconds -> Rational
$ctoRational :: Seconds -> Rational
Real, Int -> Seconds
Seconds -> Int
Seconds -> [Seconds]
Seconds -> Seconds
Seconds -> Seconds -> [Seconds]
Seconds -> Seconds -> Seconds -> [Seconds]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Seconds -> Seconds -> Seconds -> [Seconds]
$cenumFromThenTo :: Seconds -> Seconds -> Seconds -> [Seconds]
enumFromTo :: Seconds -> Seconds -> [Seconds]
$cenumFromTo :: Seconds -> Seconds -> [Seconds]
enumFromThen :: Seconds -> Seconds -> [Seconds]
$cenumFromThen :: Seconds -> Seconds -> [Seconds]
enumFrom :: Seconds -> [Seconds]
$cenumFrom :: Seconds -> [Seconds]
fromEnum :: Seconds -> Int
$cfromEnum :: Seconds -> Int
toEnum :: Int -> Seconds
$ctoEnum :: Int -> Seconds
pred :: Seconds -> Seconds
$cpred :: Seconds -> Seconds
succ :: Seconds -> Seconds
$csucc :: Seconds -> Seconds
Enum, Enum Seconds
Real Seconds
Seconds -> Integer
Seconds -> Seconds -> (Seconds, Seconds)
Seconds -> Seconds -> Seconds
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: Seconds -> Integer
$ctoInteger :: Seconds -> Integer
divMod :: Seconds -> Seconds -> (Seconds, Seconds)
$cdivMod :: Seconds -> Seconds -> (Seconds, Seconds)
quotRem :: Seconds -> Seconds -> (Seconds, Seconds)
$cquotRem :: Seconds -> Seconds -> (Seconds, Seconds)
mod :: Seconds -> Seconds -> Seconds
$cmod :: Seconds -> Seconds -> Seconds
div :: Seconds -> Seconds -> Seconds
$cdiv :: Seconds -> Seconds -> Seconds
rem :: Seconds -> Seconds -> Seconds
$crem :: Seconds -> Seconds -> Seconds
quot :: Seconds -> Seconds -> Seconds
$cquot :: Seconds -> Seconds -> Seconds
Integral, Eq Seconds
Seconds -> Seconds -> Bool
Seconds -> Seconds -> Ordering
Seconds -> Seconds -> Seconds
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Seconds -> Seconds -> Seconds
$cmin :: Seconds -> Seconds -> Seconds
max :: Seconds -> Seconds -> Seconds
$cmax :: Seconds -> Seconds -> Seconds
>= :: Seconds -> Seconds -> Bool
$c>= :: Seconds -> Seconds -> Bool
> :: Seconds -> Seconds -> Bool
$c> :: Seconds -> Seconds -> Bool
<= :: Seconds -> Seconds -> Bool
$c<= :: Seconds -> Seconds -> Bool
< :: Seconds -> Seconds -> Bool
$c< :: Seconds -> Seconds -> Bool
compare :: Seconds -> Seconds -> Ordering
$ccompare :: Seconds -> Seconds -> Ordering
Ord, Seconds
Seconds -> Seconds
Seconds -> Seconds -> Seconds
forall v.
v -> (v -> v) -> (v -> v -> v) -> (v -> v -> v) -> Additive v
minus :: Seconds -> Seconds -> Seconds
$cminus :: Seconds -> Seconds -> Seconds
plus :: Seconds -> Seconds -> Seconds
$cplus :: Seconds -> Seconds -> Seconds
invert :: Seconds -> Seconds
$cinvert :: Seconds -> Seconds
zero :: Seconds
$czero :: Seconds
Additive)

instance TimeUnit Seconds where
  nanos :: NanoSeconds
nanos =
    Int64 -> NanoSeconds
NanoSeconds Int64
1000000000

-- |Milliseconds.
newtype MilliSeconds =
  MilliSeconds { MilliSeconds -> Int64
unMilliSeconds :: Int64 }
  deriving stock (MilliSeconds -> MilliSeconds -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MilliSeconds -> MilliSeconds -> Bool
$c/= :: MilliSeconds -> MilliSeconds -> Bool
== :: MilliSeconds -> MilliSeconds -> Bool
$c== :: MilliSeconds -> MilliSeconds -> Bool
Eq, Int -> MilliSeconds -> ShowS
[MilliSeconds] -> ShowS
MilliSeconds -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MilliSeconds] -> ShowS
$cshowList :: [MilliSeconds] -> ShowS
show :: MilliSeconds -> String
$cshow :: MilliSeconds -> String
showsPrec :: Int -> MilliSeconds -> ShowS
$cshowsPrec :: Int -> MilliSeconds -> ShowS
Show, forall x. Rep MilliSeconds x -> MilliSeconds
forall x. MilliSeconds -> Rep MilliSeconds x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MilliSeconds x -> MilliSeconds
$cfrom :: forall x. MilliSeconds -> Rep MilliSeconds x
Generic)
  deriving newtype (Integer -> MilliSeconds
MilliSeconds -> MilliSeconds
MilliSeconds -> MilliSeconds -> MilliSeconds
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> MilliSeconds
$cfromInteger :: Integer -> MilliSeconds
signum :: MilliSeconds -> MilliSeconds
$csignum :: MilliSeconds -> MilliSeconds
abs :: MilliSeconds -> MilliSeconds
$cabs :: MilliSeconds -> MilliSeconds
negate :: MilliSeconds -> MilliSeconds
$cnegate :: MilliSeconds -> MilliSeconds
* :: MilliSeconds -> MilliSeconds -> MilliSeconds
$c* :: MilliSeconds -> MilliSeconds -> MilliSeconds
- :: MilliSeconds -> MilliSeconds -> MilliSeconds
$c- :: MilliSeconds -> MilliSeconds -> MilliSeconds
+ :: MilliSeconds -> MilliSeconds -> MilliSeconds
$c+ :: MilliSeconds -> MilliSeconds -> MilliSeconds
Num, Num MilliSeconds
Ord MilliSeconds
MilliSeconds -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: MilliSeconds -> Rational
$ctoRational :: MilliSeconds -> Rational
Real, Int -> MilliSeconds
MilliSeconds -> Int
MilliSeconds -> [MilliSeconds]
MilliSeconds -> MilliSeconds
MilliSeconds -> MilliSeconds -> [MilliSeconds]
MilliSeconds -> MilliSeconds -> MilliSeconds -> [MilliSeconds]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: MilliSeconds -> MilliSeconds -> MilliSeconds -> [MilliSeconds]
$cenumFromThenTo :: MilliSeconds -> MilliSeconds -> MilliSeconds -> [MilliSeconds]
enumFromTo :: MilliSeconds -> MilliSeconds -> [MilliSeconds]
$cenumFromTo :: MilliSeconds -> MilliSeconds -> [MilliSeconds]
enumFromThen :: MilliSeconds -> MilliSeconds -> [MilliSeconds]
$cenumFromThen :: MilliSeconds -> MilliSeconds -> [MilliSeconds]
enumFrom :: MilliSeconds -> [MilliSeconds]
$cenumFrom :: MilliSeconds -> [MilliSeconds]
fromEnum :: MilliSeconds -> Int
$cfromEnum :: MilliSeconds -> Int
toEnum :: Int -> MilliSeconds
$ctoEnum :: Int -> MilliSeconds
pred :: MilliSeconds -> MilliSeconds
$cpred :: MilliSeconds -> MilliSeconds
succ :: MilliSeconds -> MilliSeconds
$csucc :: MilliSeconds -> MilliSeconds
Enum, Enum MilliSeconds
Real MilliSeconds
MilliSeconds -> Integer
MilliSeconds -> MilliSeconds -> (MilliSeconds, MilliSeconds)
MilliSeconds -> MilliSeconds -> MilliSeconds
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: MilliSeconds -> Integer
$ctoInteger :: MilliSeconds -> Integer
divMod :: MilliSeconds -> MilliSeconds -> (MilliSeconds, MilliSeconds)
$cdivMod :: MilliSeconds -> MilliSeconds -> (MilliSeconds, MilliSeconds)
quotRem :: MilliSeconds -> MilliSeconds -> (MilliSeconds, MilliSeconds)
$cquotRem :: MilliSeconds -> MilliSeconds -> (MilliSeconds, MilliSeconds)
mod :: MilliSeconds -> MilliSeconds -> MilliSeconds
$cmod :: MilliSeconds -> MilliSeconds -> MilliSeconds
div :: MilliSeconds -> MilliSeconds -> MilliSeconds
$cdiv :: MilliSeconds -> MilliSeconds -> MilliSeconds
rem :: MilliSeconds -> MilliSeconds -> MilliSeconds
$crem :: MilliSeconds -> MilliSeconds -> MilliSeconds
quot :: MilliSeconds -> MilliSeconds -> MilliSeconds
$cquot :: MilliSeconds -> MilliSeconds -> MilliSeconds
Integral, Eq MilliSeconds
MilliSeconds -> MilliSeconds -> Bool
MilliSeconds -> MilliSeconds -> Ordering
MilliSeconds -> MilliSeconds -> MilliSeconds
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MilliSeconds -> MilliSeconds -> MilliSeconds
$cmin :: MilliSeconds -> MilliSeconds -> MilliSeconds
max :: MilliSeconds -> MilliSeconds -> MilliSeconds
$cmax :: MilliSeconds -> MilliSeconds -> MilliSeconds
>= :: MilliSeconds -> MilliSeconds -> Bool
$c>= :: MilliSeconds -> MilliSeconds -> Bool
> :: MilliSeconds -> MilliSeconds -> Bool
$c> :: MilliSeconds -> MilliSeconds -> Bool
<= :: MilliSeconds -> MilliSeconds -> Bool
$c<= :: MilliSeconds -> MilliSeconds -> Bool
< :: MilliSeconds -> MilliSeconds -> Bool
$c< :: MilliSeconds -> MilliSeconds -> Bool
compare :: MilliSeconds -> MilliSeconds -> Ordering
$ccompare :: MilliSeconds -> MilliSeconds -> Ordering
Ord, MilliSeconds
MilliSeconds -> MilliSeconds
MilliSeconds -> MilliSeconds -> MilliSeconds
forall v.
v -> (v -> v) -> (v -> v -> v) -> (v -> v -> v) -> Additive v
minus :: MilliSeconds -> MilliSeconds -> MilliSeconds
$cminus :: MilliSeconds -> MilliSeconds -> MilliSeconds
plus :: MilliSeconds -> MilliSeconds -> MilliSeconds
$cplus :: MilliSeconds -> MilliSeconds -> MilliSeconds
invert :: MilliSeconds -> MilliSeconds
$cinvert :: MilliSeconds -> MilliSeconds
zero :: MilliSeconds
$czero :: MilliSeconds
Additive)
  deriving (Num MilliSeconds
Rational -> MilliSeconds
MilliSeconds -> MilliSeconds
MilliSeconds -> MilliSeconds -> MilliSeconds
forall a.
Num a
-> (a -> a -> a) -> (a -> a) -> (Rational -> a) -> Fractional a
fromRational :: Rational -> MilliSeconds
$cfromRational :: Rational -> MilliSeconds
recip :: MilliSeconds -> MilliSeconds
$crecip :: MilliSeconds -> MilliSeconds
/ :: MilliSeconds -> MilliSeconds -> MilliSeconds
$c/ :: MilliSeconds -> MilliSeconds -> MilliSeconds
Fractional) via (FromSeconds MilliSeconds)

instance TimeUnit MilliSeconds where
  nanos :: NanoSeconds
nanos =
    Int64 -> NanoSeconds
NanoSeconds Int64
1000000

-- |Microseconds.
newtype MicroSeconds =
  MicroSeconds { MicroSeconds -> Int64
unMicroSeconds :: Int64 }
  deriving stock (MicroSeconds -> MicroSeconds -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MicroSeconds -> MicroSeconds -> Bool
$c/= :: MicroSeconds -> MicroSeconds -> Bool
== :: MicroSeconds -> MicroSeconds -> Bool
$c== :: MicroSeconds -> MicroSeconds -> Bool
Eq, Int -> MicroSeconds -> ShowS
[MicroSeconds] -> ShowS
MicroSeconds -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MicroSeconds] -> ShowS
$cshowList :: [MicroSeconds] -> ShowS
show :: MicroSeconds -> String
$cshow :: MicroSeconds -> String
showsPrec :: Int -> MicroSeconds -> ShowS
$cshowsPrec :: Int -> MicroSeconds -> ShowS
Show, forall x. Rep MicroSeconds x -> MicroSeconds
forall x. MicroSeconds -> Rep MicroSeconds x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MicroSeconds x -> MicroSeconds
$cfrom :: forall x. MicroSeconds -> Rep MicroSeconds x
Generic)
  deriving newtype (Integer -> MicroSeconds
MicroSeconds -> MicroSeconds
MicroSeconds -> MicroSeconds -> MicroSeconds
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> MicroSeconds
$cfromInteger :: Integer -> MicroSeconds
signum :: MicroSeconds -> MicroSeconds
$csignum :: MicroSeconds -> MicroSeconds
abs :: MicroSeconds -> MicroSeconds
$cabs :: MicroSeconds -> MicroSeconds
negate :: MicroSeconds -> MicroSeconds
$cnegate :: MicroSeconds -> MicroSeconds
* :: MicroSeconds -> MicroSeconds -> MicroSeconds
$c* :: MicroSeconds -> MicroSeconds -> MicroSeconds
- :: MicroSeconds -> MicroSeconds -> MicroSeconds
$c- :: MicroSeconds -> MicroSeconds -> MicroSeconds
+ :: MicroSeconds -> MicroSeconds -> MicroSeconds
$c+ :: MicroSeconds -> MicroSeconds -> MicroSeconds
Num, Num MicroSeconds
Ord MicroSeconds
MicroSeconds -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: MicroSeconds -> Rational
$ctoRational :: MicroSeconds -> Rational
Real, Int -> MicroSeconds
MicroSeconds -> Int
MicroSeconds -> [MicroSeconds]
MicroSeconds -> MicroSeconds
MicroSeconds -> MicroSeconds -> [MicroSeconds]
MicroSeconds -> MicroSeconds -> MicroSeconds -> [MicroSeconds]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: MicroSeconds -> MicroSeconds -> MicroSeconds -> [MicroSeconds]
$cenumFromThenTo :: MicroSeconds -> MicroSeconds -> MicroSeconds -> [MicroSeconds]
enumFromTo :: MicroSeconds -> MicroSeconds -> [MicroSeconds]
$cenumFromTo :: MicroSeconds -> MicroSeconds -> [MicroSeconds]
enumFromThen :: MicroSeconds -> MicroSeconds -> [MicroSeconds]
$cenumFromThen :: MicroSeconds -> MicroSeconds -> [MicroSeconds]
enumFrom :: MicroSeconds -> [MicroSeconds]
$cenumFrom :: MicroSeconds -> [MicroSeconds]
fromEnum :: MicroSeconds -> Int
$cfromEnum :: MicroSeconds -> Int
toEnum :: Int -> MicroSeconds
$ctoEnum :: Int -> MicroSeconds
pred :: MicroSeconds -> MicroSeconds
$cpred :: MicroSeconds -> MicroSeconds
succ :: MicroSeconds -> MicroSeconds
$csucc :: MicroSeconds -> MicroSeconds
Enum, Enum MicroSeconds
Real MicroSeconds
MicroSeconds -> Integer
MicroSeconds -> MicroSeconds -> (MicroSeconds, MicroSeconds)
MicroSeconds -> MicroSeconds -> MicroSeconds
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: MicroSeconds -> Integer
$ctoInteger :: MicroSeconds -> Integer
divMod :: MicroSeconds -> MicroSeconds -> (MicroSeconds, MicroSeconds)
$cdivMod :: MicroSeconds -> MicroSeconds -> (MicroSeconds, MicroSeconds)
quotRem :: MicroSeconds -> MicroSeconds -> (MicroSeconds, MicroSeconds)
$cquotRem :: MicroSeconds -> MicroSeconds -> (MicroSeconds, MicroSeconds)
mod :: MicroSeconds -> MicroSeconds -> MicroSeconds
$cmod :: MicroSeconds -> MicroSeconds -> MicroSeconds
div :: MicroSeconds -> MicroSeconds -> MicroSeconds
$cdiv :: MicroSeconds -> MicroSeconds -> MicroSeconds
rem :: MicroSeconds -> MicroSeconds -> MicroSeconds
$crem :: MicroSeconds -> MicroSeconds -> MicroSeconds
quot :: MicroSeconds -> MicroSeconds -> MicroSeconds
$cquot :: MicroSeconds -> MicroSeconds -> MicroSeconds
Integral, Eq MicroSeconds
MicroSeconds -> MicroSeconds -> Bool
MicroSeconds -> MicroSeconds -> Ordering
MicroSeconds -> MicroSeconds -> MicroSeconds
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MicroSeconds -> MicroSeconds -> MicroSeconds
$cmin :: MicroSeconds -> MicroSeconds -> MicroSeconds
max :: MicroSeconds -> MicroSeconds -> MicroSeconds
$cmax :: MicroSeconds -> MicroSeconds -> MicroSeconds
>= :: MicroSeconds -> MicroSeconds -> Bool
$c>= :: MicroSeconds -> MicroSeconds -> Bool
> :: MicroSeconds -> MicroSeconds -> Bool
$c> :: MicroSeconds -> MicroSeconds -> Bool
<= :: MicroSeconds -> MicroSeconds -> Bool
$c<= :: MicroSeconds -> MicroSeconds -> Bool
< :: MicroSeconds -> MicroSeconds -> Bool
$c< :: MicroSeconds -> MicroSeconds -> Bool
compare :: MicroSeconds -> MicroSeconds -> Ordering
$ccompare :: MicroSeconds -> MicroSeconds -> Ordering
Ord, MicroSeconds
MicroSeconds -> MicroSeconds
MicroSeconds -> MicroSeconds -> MicroSeconds
forall v.
v -> (v -> v) -> (v -> v -> v) -> (v -> v -> v) -> Additive v
minus :: MicroSeconds -> MicroSeconds -> MicroSeconds
$cminus :: MicroSeconds -> MicroSeconds -> MicroSeconds
plus :: MicroSeconds -> MicroSeconds -> MicroSeconds
$cplus :: MicroSeconds -> MicroSeconds -> MicroSeconds
invert :: MicroSeconds -> MicroSeconds
$cinvert :: MicroSeconds -> MicroSeconds
zero :: MicroSeconds
$czero :: MicroSeconds
Additive)
  deriving (Num MicroSeconds
Rational -> MicroSeconds
MicroSeconds -> MicroSeconds
MicroSeconds -> MicroSeconds -> MicroSeconds
forall a.
Num a
-> (a -> a -> a) -> (a -> a) -> (Rational -> a) -> Fractional a
fromRational :: Rational -> MicroSeconds
$cfromRational :: Rational -> MicroSeconds
recip :: MicroSeconds -> MicroSeconds
$crecip :: MicroSeconds -> MicroSeconds
/ :: MicroSeconds -> MicroSeconds -> MicroSeconds
$c/ :: MicroSeconds -> MicroSeconds -> MicroSeconds
Fractional) via (FromSeconds MicroSeconds)

instance TimeUnit MicroSeconds where
  nanos :: NanoSeconds
nanos =
    Int64 -> NanoSeconds
NanoSeconds Int64
1000

-- |Nanoseconds.
-- This is the base unit for all conversions.
newtype NanoSeconds =
  NanoSeconds { NanoSeconds -> Int64
unNanoSeconds :: Int64 }
  deriving stock (NanoSeconds -> NanoSeconds -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NanoSeconds -> NanoSeconds -> Bool
$c/= :: NanoSeconds -> NanoSeconds -> Bool
== :: NanoSeconds -> NanoSeconds -> Bool
$c== :: NanoSeconds -> NanoSeconds -> Bool
Eq, Int -> NanoSeconds -> ShowS
[NanoSeconds] -> ShowS
NanoSeconds -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NanoSeconds] -> ShowS
$cshowList :: [NanoSeconds] -> ShowS
show :: NanoSeconds -> String
$cshow :: NanoSeconds -> String
showsPrec :: Int -> NanoSeconds -> ShowS
$cshowsPrec :: Int -> NanoSeconds -> ShowS
Show, forall x. Rep NanoSeconds x -> NanoSeconds
forall x. NanoSeconds -> Rep NanoSeconds x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NanoSeconds x -> NanoSeconds
$cfrom :: forall x. NanoSeconds -> Rep NanoSeconds x
Generic)
  deriving newtype (Integer -> NanoSeconds
NanoSeconds -> NanoSeconds
NanoSeconds -> NanoSeconds -> NanoSeconds
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> NanoSeconds
$cfromInteger :: Integer -> NanoSeconds
signum :: NanoSeconds -> NanoSeconds
$csignum :: NanoSeconds -> NanoSeconds
abs :: NanoSeconds -> NanoSeconds
$cabs :: NanoSeconds -> NanoSeconds
negate :: NanoSeconds -> NanoSeconds
$cnegate :: NanoSeconds -> NanoSeconds
* :: NanoSeconds -> NanoSeconds -> NanoSeconds
$c* :: NanoSeconds -> NanoSeconds -> NanoSeconds
- :: NanoSeconds -> NanoSeconds -> NanoSeconds
$c- :: NanoSeconds -> NanoSeconds -> NanoSeconds
+ :: NanoSeconds -> NanoSeconds -> NanoSeconds
$c+ :: NanoSeconds -> NanoSeconds -> NanoSeconds
Num, Num NanoSeconds
Ord NanoSeconds
NanoSeconds -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: NanoSeconds -> Rational
$ctoRational :: NanoSeconds -> Rational
Real, Int -> NanoSeconds
NanoSeconds -> Int
NanoSeconds -> [NanoSeconds]
NanoSeconds -> NanoSeconds
NanoSeconds -> NanoSeconds -> [NanoSeconds]
NanoSeconds -> NanoSeconds -> NanoSeconds -> [NanoSeconds]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: NanoSeconds -> NanoSeconds -> NanoSeconds -> [NanoSeconds]
$cenumFromThenTo :: NanoSeconds -> NanoSeconds -> NanoSeconds -> [NanoSeconds]
enumFromTo :: NanoSeconds -> NanoSeconds -> [NanoSeconds]
$cenumFromTo :: NanoSeconds -> NanoSeconds -> [NanoSeconds]
enumFromThen :: NanoSeconds -> NanoSeconds -> [NanoSeconds]
$cenumFromThen :: NanoSeconds -> NanoSeconds -> [NanoSeconds]
enumFrom :: NanoSeconds -> [NanoSeconds]
$cenumFrom :: NanoSeconds -> [NanoSeconds]
fromEnum :: NanoSeconds -> Int
$cfromEnum :: NanoSeconds -> Int
toEnum :: Int -> NanoSeconds
$ctoEnum :: Int -> NanoSeconds
pred :: NanoSeconds -> NanoSeconds
$cpred :: NanoSeconds -> NanoSeconds
succ :: NanoSeconds -> NanoSeconds
$csucc :: NanoSeconds -> NanoSeconds
Enum, Enum NanoSeconds
Real NanoSeconds
NanoSeconds -> Integer
NanoSeconds -> NanoSeconds -> (NanoSeconds, NanoSeconds)
NanoSeconds -> NanoSeconds -> NanoSeconds
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: NanoSeconds -> Integer
$ctoInteger :: NanoSeconds -> Integer
divMod :: NanoSeconds -> NanoSeconds -> (NanoSeconds, NanoSeconds)
$cdivMod :: NanoSeconds -> NanoSeconds -> (NanoSeconds, NanoSeconds)
quotRem :: NanoSeconds -> NanoSeconds -> (NanoSeconds, NanoSeconds)
$cquotRem :: NanoSeconds -> NanoSeconds -> (NanoSeconds, NanoSeconds)
mod :: NanoSeconds -> NanoSeconds -> NanoSeconds
$cmod :: NanoSeconds -> NanoSeconds -> NanoSeconds
div :: NanoSeconds -> NanoSeconds -> NanoSeconds
$cdiv :: NanoSeconds -> NanoSeconds -> NanoSeconds
rem :: NanoSeconds -> NanoSeconds -> NanoSeconds
$crem :: NanoSeconds -> NanoSeconds -> NanoSeconds
quot :: NanoSeconds -> NanoSeconds -> NanoSeconds
$cquot :: NanoSeconds -> NanoSeconds -> NanoSeconds
Integral, Eq NanoSeconds
NanoSeconds -> NanoSeconds -> Bool
NanoSeconds -> NanoSeconds -> Ordering
NanoSeconds -> NanoSeconds -> NanoSeconds
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: NanoSeconds -> NanoSeconds -> NanoSeconds
$cmin :: NanoSeconds -> NanoSeconds -> NanoSeconds
max :: NanoSeconds -> NanoSeconds -> NanoSeconds
$cmax :: NanoSeconds -> NanoSeconds -> NanoSeconds
>= :: NanoSeconds -> NanoSeconds -> Bool
$c>= :: NanoSeconds -> NanoSeconds -> Bool
> :: NanoSeconds -> NanoSeconds -> Bool
$c> :: NanoSeconds -> NanoSeconds -> Bool
<= :: NanoSeconds -> NanoSeconds -> Bool
$c<= :: NanoSeconds -> NanoSeconds -> Bool
< :: NanoSeconds -> NanoSeconds -> Bool
$c< :: NanoSeconds -> NanoSeconds -> Bool
compare :: NanoSeconds -> NanoSeconds -> Ordering
$ccompare :: NanoSeconds -> NanoSeconds -> Ordering
Ord, NanoSeconds
NanoSeconds -> NanoSeconds
NanoSeconds -> NanoSeconds -> NanoSeconds
forall v.
v -> (v -> v) -> (v -> v -> v) -> (v -> v -> v) -> Additive v
minus :: NanoSeconds -> NanoSeconds -> NanoSeconds
$cminus :: NanoSeconds -> NanoSeconds -> NanoSeconds
plus :: NanoSeconds -> NanoSeconds -> NanoSeconds
$cplus :: NanoSeconds -> NanoSeconds -> NanoSeconds
invert :: NanoSeconds -> NanoSeconds
$cinvert :: NanoSeconds -> NanoSeconds
zero :: NanoSeconds
$czero :: NanoSeconds
Additive)
  deriving (Num NanoSeconds
Rational -> NanoSeconds
NanoSeconds -> NanoSeconds
NanoSeconds -> NanoSeconds -> NanoSeconds
forall a.
Num a
-> (a -> a -> a) -> (a -> a) -> (Rational -> a) -> Fractional a
fromRational :: Rational -> NanoSeconds
$cfromRational :: Rational -> NanoSeconds
recip :: NanoSeconds -> NanoSeconds
$crecip :: NanoSeconds -> NanoSeconds
/ :: NanoSeconds -> NanoSeconds -> NanoSeconds
$c/ :: NanoSeconds -> NanoSeconds -> NanoSeconds
Fractional) via (FromSeconds NanoSeconds)

instance Scaling NanoSeconds Int64 where
  scale :: Int64 -> NanoSeconds -> NanoSeconds
scale Int64
s (NanoSeconds Int64
v) =
    Int64 -> NanoSeconds
NanoSeconds (forall v s. Scaling v s => s -> v -> v
scale Int64
s Int64
v)

instance TimeUnit NanoSeconds where
  nanos :: NanoSeconds
nanos =
    Int64 -> NanoSeconds
NanoSeconds Int64
1
  toNanos :: NanoSeconds -> NanoSeconds
toNanos =
    forall a. a -> a
id
  fromNanos :: NanoSeconds -> NanoSeconds
fromNanos =
    forall a. a -> a
id

divOr0 ::
  Real a =>
  Integral a =>
  a ->
  a ->
  a
divOr0 :: forall a. (Real a, Integral a) => a -> a -> a
divOr0 a
l a
r =
  forall a. a -> Maybe a -> a
fromMaybe a
0 (forall a b. (Real a, Integral b) => a -> a -> Maybe b
div' a
l a
r)
{-# inline divOr0 #-}

instance TimeUnit DiffTime where
  nanos :: NanoSeconds
nanos =
    NanoSeconds
0
  toNanos :: DiffTime -> NanoSeconds
toNanos DiffTime
dt =
    Int64 -> NanoSeconds
NanoSeconds (forall a. (Real a, Integral a) => a -> a -> a
divOr0 (forall a b. (Integral a, Num b) => a -> b
fromIntegral (DiffTime -> Integer
diffTimeToPicoseconds DiffTime
dt)) Int64
1000)
  fromNanos :: NanoSeconds -> DiffTime
fromNanos (NanoSeconds Int64
ns) =
    Integer -> DiffTime
picosecondsToDiffTime (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
ns forall a. Num a => a -> a -> a
* Integer
1000)

instance TimeUnit NominalDiffTime where
  nanos :: NanoSeconds
nanos =
    NanoSeconds
0
  toNanos :: NominalDiffTime -> NanoSeconds
toNanos NominalDiffTime
dt =
    Int64 -> NanoSeconds
NanoSeconds (forall a. (Real a, Integral a) => a -> a -> a
divOr0 (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Enum a => a -> Int
fromEnum NominalDiffTime
dt)) Int64
1000)
  fromNanos :: NanoSeconds -> NominalDiffTime
fromNanos (NanoSeconds Int64
ns) =
    forall a. Enum a => Int -> a
toEnum (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
ns) forall a. Num a => a -> a -> a
* NominalDiffTime
1000

-- |Convert between different time spans.
--
-- >>> convert (picosecondsToDiffTime 50000000) :: MicroSeconds
-- MicroSeconds {unMicroSeconds = 50}
--
-- >>> convert (MilliSeconds 5) :: MicroSeconds
-- MicroSeconds 5000
convert ::
  TimeUnit a =>
  TimeUnit b =>
  a ->
  b
convert :: forall a b. (TimeUnit a, TimeUnit b) => a -> b
convert =
  forall u. TimeUnit u => NanoSeconds -> u
fromNanos forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall u. TimeUnit u => u -> NanoSeconds
toNanos

-- |Convenience alias for 'addTimeUnit'.
type AddTimeUnit t u1 u2 =
  (TimeUnit u1, TimeUnit u2, Torsor t u2)

-- |Add a time unit to an instant.
addTimeUnit ::
   t u1 u2 .
  AddTimeUnit t u1 u2 =>
  u1 ->
  t ->
  t
addTimeUnit :: forall t u1 u2. AddTimeUnit t u1 u2 => u1 -> t -> t
addTimeUnit =
  forall p v. Torsor p v => v -> p -> p
add forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (TimeUnit a, TimeUnit b) => a -> b
convert

-- |Convert a unit into a number of seconds, keeping the subsecond part as fractional digits.
secondsFrac ::
  TimeUnit u =>
  u ->
  Double
secondsFrac :: forall u. TimeUnit u => u -> Double
secondsFrac u
u =
  forall a. a -> Maybe a -> a
fromMaybe Double
0 (forall a b. (Integral a, Num b) => a -> b
fromIntegral (NanoSeconds -> Int64
unNanoSeconds (forall a b. (TimeUnit a, TimeUnit b) => a -> b
convert u
u)) forall a. (Eq a, Fractional a) => a -> a -> Maybe a
/ Double
1e9)

json ''Years
json ''Months
json ''Weeks
json ''Days
json ''Hours
json ''Minutes
json ''Seconds
json ''MilliSeconds
json ''MicroSeconds
json ''NanoSeconds