{-# LANGUAGE Trustworthy #-}

module Data.Time.Clock.Internal.DiffTime
    (
    -- * Absolute intervals
      DiffTime
    , secondsToDiffTime
    , picosecondsToDiffTime
    , diffTimeToPicoseconds
    ) where

import Control.DeepSeq
import Data.Data
import Data.Fixed
import Text.ParserCombinators.ReadP
import Text.ParserCombinators.ReadPrec
import GHC.Read

-- | This is a length of time, as measured by a clock.
-- Conversion functions such as 'fromInteger' and 'realToFrac' will treat it as seconds.
-- For example, @(0.010 :: DiffTime)@ corresponds to 10 milliseconds.
--
-- It has a precision of one picosecond (= 10^-12 s). Enumeration functions will treat it as picoseconds.
newtype DiffTime =
    MkDiffTime Pico
    deriving (DiffTime -> DiffTime -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DiffTime -> DiffTime -> Bool
$c/= :: DiffTime -> DiffTime -> Bool
== :: DiffTime -> DiffTime -> Bool
$c== :: DiffTime -> DiffTime -> Bool
Eq, Eq DiffTime
DiffTime -> DiffTime -> Bool
DiffTime -> DiffTime -> Ordering
DiffTime -> DiffTime -> DiffTime
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 :: DiffTime -> DiffTime -> DiffTime
$cmin :: DiffTime -> DiffTime -> DiffTime
max :: DiffTime -> DiffTime -> DiffTime
$cmax :: DiffTime -> DiffTime -> DiffTime
>= :: DiffTime -> DiffTime -> Bool
$c>= :: DiffTime -> DiffTime -> Bool
> :: DiffTime -> DiffTime -> Bool
$c> :: DiffTime -> DiffTime -> Bool
<= :: DiffTime -> DiffTime -> Bool
$c<= :: DiffTime -> DiffTime -> Bool
< :: DiffTime -> DiffTime -> Bool
$c< :: DiffTime -> DiffTime -> Bool
compare :: DiffTime -> DiffTime -> Ordering
$ccompare :: DiffTime -> DiffTime -> Ordering
Ord, Typeable DiffTime
DiffTime -> DataType
DiffTime -> Constr
(forall b. Data b => b -> b) -> DiffTime -> DiffTime
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> DiffTime -> u
forall u. (forall d. Data d => d -> u) -> DiffTime -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DiffTime -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DiffTime -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DiffTime -> m DiffTime
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DiffTime -> m DiffTime
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DiffTime
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DiffTime -> c DiffTime
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DiffTime)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DiffTime)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DiffTime -> m DiffTime
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DiffTime -> m DiffTime
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DiffTime -> m DiffTime
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DiffTime -> m DiffTime
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DiffTime -> m DiffTime
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DiffTime -> m DiffTime
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> DiffTime -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> DiffTime -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> DiffTime -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> DiffTime -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DiffTime -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DiffTime -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DiffTime -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DiffTime -> r
gmapT :: (forall b. Data b => b -> b) -> DiffTime -> DiffTime
$cgmapT :: (forall b. Data b => b -> b) -> DiffTime -> DiffTime
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DiffTime)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DiffTime)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DiffTime)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DiffTime)
dataTypeOf :: DiffTime -> DataType
$cdataTypeOf :: DiffTime -> DataType
toConstr :: DiffTime -> Constr
$ctoConstr :: DiffTime -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DiffTime
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DiffTime
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DiffTime -> c DiffTime
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DiffTime -> c DiffTime
Data, Typeable)

instance NFData DiffTime where
    rnf :: DiffTime -> ()
rnf (MkDiffTime Pico
t) = forall a. NFData a => a -> ()
rnf Pico
t

instance Enum DiffTime where
    succ :: DiffTime -> DiffTime
succ (MkDiffTime Pico
a) = Pico -> DiffTime
MkDiffTime (forall a. Enum a => a -> a
succ Pico
a)
    pred :: DiffTime -> DiffTime
pred (MkDiffTime Pico
a) = Pico -> DiffTime
MkDiffTime (forall a. Enum a => a -> a
pred Pico
a)
    toEnum :: Int -> DiffTime
toEnum = Pico -> DiffTime
MkDiffTime forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => Int -> a
toEnum
    fromEnum :: DiffTime -> Int
fromEnum (MkDiffTime Pico
a) = forall a. Enum a => a -> Int
fromEnum Pico
a
    enumFrom :: DiffTime -> [DiffTime]
enumFrom (MkDiffTime Pico
a) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Pico -> DiffTime
MkDiffTime (forall a. Enum a => a -> [a]
enumFrom Pico
a)
    enumFromThen :: DiffTime -> DiffTime -> [DiffTime]
enumFromThen (MkDiffTime Pico
a) (MkDiffTime Pico
b) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Pico -> DiffTime
MkDiffTime (forall a. Enum a => a -> a -> [a]
enumFromThen Pico
a Pico
b)
    enumFromTo :: DiffTime -> DiffTime -> [DiffTime]
enumFromTo (MkDiffTime Pico
a) (MkDiffTime Pico
b) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Pico -> DiffTime
MkDiffTime (forall a. Enum a => a -> a -> [a]
enumFromTo Pico
a Pico
b)
    enumFromThenTo :: DiffTime -> DiffTime -> DiffTime -> [DiffTime]
enumFromThenTo (MkDiffTime Pico
a) (MkDiffTime Pico
b) (MkDiffTime Pico
c) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Pico -> DiffTime
MkDiffTime (forall a. Enum a => a -> a -> a -> [a]
enumFromThenTo Pico
a Pico
b Pico
c)

instance Show DiffTime where
    show :: DiffTime -> String
show (MkDiffTime Pico
t) = (forall {k} (a :: k). HasResolution a => Bool -> Fixed a -> String
showFixed Bool
True Pico
t) forall a. [a] -> [a] -> [a]
++ String
"s"

instance Read DiffTime where
    readPrec :: ReadPrec DiffTime
readPrec = do
        Pico
t <- forall a. Read a => ReadPrec a
readPrec
        Char
_ <- forall a. ReadP a -> ReadPrec a
lift forall a b. (a -> b) -> a -> b
$ Char -> ReadP Char
char Char
's'
        forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Pico -> DiffTime
MkDiffTime Pico
t

instance Num DiffTime where
    (MkDiffTime Pico
a) + :: DiffTime -> DiffTime -> DiffTime
+ (MkDiffTime Pico
b) = Pico -> DiffTime
MkDiffTime (Pico
a forall a. Num a => a -> a -> a
+ Pico
b)
    (MkDiffTime Pico
a) - :: DiffTime -> DiffTime -> DiffTime
- (MkDiffTime Pico
b) = Pico -> DiffTime
MkDiffTime (Pico
a forall a. Num a => a -> a -> a
- Pico
b)
    (MkDiffTime Pico
a) * :: DiffTime -> DiffTime -> DiffTime
* (MkDiffTime Pico
b) = Pico -> DiffTime
MkDiffTime (Pico
a forall a. Num a => a -> a -> a
* Pico
b)
    negate :: DiffTime -> DiffTime
negate (MkDiffTime Pico
a) = Pico -> DiffTime
MkDiffTime (forall a. Num a => a -> a
negate Pico
a)
    abs :: DiffTime -> DiffTime
abs (MkDiffTime Pico
a) = Pico -> DiffTime
MkDiffTime (forall a. Num a => a -> a
abs Pico
a)
    signum :: DiffTime -> DiffTime
signum (MkDiffTime Pico
a) = Pico -> DiffTime
MkDiffTime (forall a. Num a => a -> a
signum Pico
a)
    fromInteger :: Integer -> DiffTime
fromInteger Integer
i = Pico -> DiffTime
MkDiffTime (forall a. Num a => Integer -> a
fromInteger Integer
i)

instance Real DiffTime where
    toRational :: DiffTime -> Rational
toRational (MkDiffTime Pico
a) = forall a. Real a => a -> Rational
toRational Pico
a

instance Fractional DiffTime where
    (MkDiffTime Pico
a) / :: DiffTime -> DiffTime -> DiffTime
/ (MkDiffTime Pico
b) = Pico -> DiffTime
MkDiffTime (Pico
a forall a. Fractional a => a -> a -> a
/ Pico
b)
    recip :: DiffTime -> DiffTime
recip (MkDiffTime Pico
a) = Pico -> DiffTime
MkDiffTime (forall a. Fractional a => a -> a
recip Pico
a)
    fromRational :: Rational -> DiffTime
fromRational Rational
r = Pico -> DiffTime
MkDiffTime (forall a. Fractional a => Rational -> a
fromRational Rational
r)

instance RealFrac DiffTime where
    properFraction :: forall b. Integral b => DiffTime -> (b, DiffTime)
properFraction (MkDiffTime Pico
a) = let
        (b
b', Pico
a') = forall a b. (RealFrac a, Integral b) => a -> (b, a)
properFraction Pico
a
        in (b
b', Pico -> DiffTime
MkDiffTime Pico
a')
    truncate :: forall b. Integral b => DiffTime -> b
truncate (MkDiffTime Pico
a) = forall a b. (RealFrac a, Integral b) => a -> b
truncate Pico
a
    round :: forall b. Integral b => DiffTime -> b
round (MkDiffTime Pico
a) = forall a b. (RealFrac a, Integral b) => a -> b
round Pico
a
    ceiling :: forall b. Integral b => DiffTime -> b
ceiling (MkDiffTime Pico
a) = forall a b. (RealFrac a, Integral b) => a -> b
ceiling Pico
a
    floor :: forall b. Integral b => DiffTime -> b
floor (MkDiffTime Pico
a) = forall a b. (RealFrac a, Integral b) => a -> b
floor Pico
a

-- | Create a 'DiffTime' which represents an integral number of seconds.
secondsToDiffTime :: Integer -> DiffTime
secondsToDiffTime :: Integer -> DiffTime
secondsToDiffTime = forall a. Num a => Integer -> a
fromInteger

-- | Create a 'DiffTime' from a number of picoseconds.
picosecondsToDiffTime :: Integer -> DiffTime
picosecondsToDiffTime :: Integer -> DiffTime
picosecondsToDiffTime Integer
x = Pico -> DiffTime
MkDiffTime (forall k (a :: k). Integer -> Fixed a
MkFixed Integer
x)

-- | Get the number of picoseconds in a 'DiffTime'.
diffTimeToPicoseconds :: DiffTime -> Integer
diffTimeToPicoseconds :: DiffTime -> Integer
diffTimeToPicoseconds (MkDiffTime (MkFixed Integer
x)) = Integer
x

{-# RULES
"realToFrac/DiffTime->Pico" realToFrac = \ (MkDiffTime ps) -> ps
"realToFrac/Pico->DiffTime" realToFrac = MkDiffTime
 #-}