{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveLift #-}
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE UnboxedTuples #-}
module Temporal.Duration (
Duration,
durationSeconds,
durationNanoseconds,
mkDuration,
addDurations,
diffTimeToDuration,
nominalDiffTimeToDuration,
nanoseconds,
microseconds,
milliseconds,
seconds,
minutes,
hours,
days,
weeks,
infinity,
durationFromProto,
durationToProto,
durationToMilliseconds,
) where
import Data.Aeson
import Data.Aeson.Types (Parser)
import Data.Data
import Data.Fixed
import Data.Int (Int32, Int64)
import Data.ProtoLens (defMessage)
import qualified Data.Text as T
import Data.Time.Clock
import Language.Haskell.TH.Syntax (Lift)
import Lens.Family2 ((&), (.~), (^.))
import qualified Proto.Google.Protobuf.Duration as Duration
import qualified Proto.Google.Protobuf.Duration_Fields as Duration
import Text.Printf
data Duration = Duration
{ Duration -> Int64
durationSeconds :: {-# UNPACK #-} !Int64
, Duration -> Int32
durationNanoseconds :: {-# UNPACK #-} !Int32
}
deriving stock (Duration -> Duration -> Bool
(Duration -> Duration -> Bool)
-> (Duration -> Duration -> Bool) -> Eq Duration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Duration -> Duration -> Bool
== :: Duration -> Duration -> Bool
$c/= :: Duration -> Duration -> Bool
/= :: Duration -> Duration -> Bool
Eq, Eq Duration
Eq Duration =>
(Duration -> Duration -> Ordering)
-> (Duration -> Duration -> Bool)
-> (Duration -> Duration -> Bool)
-> (Duration -> Duration -> Bool)
-> (Duration -> Duration -> Bool)
-> (Duration -> Duration -> Duration)
-> (Duration -> Duration -> Duration)
-> Ord Duration
Duration -> Duration -> Bool
Duration -> Duration -> Ordering
Duration -> Duration -> Duration
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
$ccompare :: Duration -> Duration -> Ordering
compare :: Duration -> Duration -> Ordering
$c< :: Duration -> Duration -> Bool
< :: Duration -> Duration -> Bool
$c<= :: Duration -> Duration -> Bool
<= :: Duration -> Duration -> Bool
$c> :: Duration -> Duration -> Bool
> :: Duration -> Duration -> Bool
$c>= :: Duration -> Duration -> Bool
>= :: Duration -> Duration -> Bool
$cmax :: Duration -> Duration -> Duration
max :: Duration -> Duration -> Duration
$cmin :: Duration -> Duration -> Duration
min :: Duration -> Duration -> Duration
Ord, Int -> Duration -> ShowS
[Duration] -> ShowS
Duration -> String
(Int -> Duration -> ShowS)
-> (Duration -> String) -> ([Duration] -> ShowS) -> Show Duration
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Duration -> ShowS
showsPrec :: Int -> Duration -> ShowS
$cshow :: Duration -> String
show :: Duration -> String
$cshowList :: [Duration] -> ShowS
showList :: [Duration] -> ShowS
Show, Typeable Duration
Typeable Duration =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Duration -> c Duration)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Duration)
-> (Duration -> Constr)
-> (Duration -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Duration))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Duration))
-> ((forall b. Data b => b -> b) -> Duration -> Duration)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Duration -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Duration -> r)
-> (forall u. (forall d. Data d => d -> u) -> Duration -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Duration -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Duration -> m Duration)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Duration -> m Duration)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Duration -> m Duration)
-> Data Duration
Duration -> Constr
Duration -> DataType
(forall b. Data b => b -> b) -> Duration -> Duration
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) -> Duration -> u
forall u. (forall d. Data d => d -> u) -> Duration -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Duration -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Duration -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Duration -> m Duration
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Duration -> m Duration
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Duration
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Duration -> c Duration
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Duration)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Duration)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Duration -> c Duration
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Duration -> c Duration
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Duration
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Duration
$ctoConstr :: Duration -> Constr
toConstr :: Duration -> Constr
$cdataTypeOf :: Duration -> DataType
dataTypeOf :: Duration -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Duration)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Duration)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Duration)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Duration)
$cgmapT :: (forall b. Data b => b -> b) -> Duration -> Duration
gmapT :: (forall b. Data b => b -> b) -> Duration -> Duration
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Duration -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Duration -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Duration -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Duration -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Duration -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Duration -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Duration -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Duration -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Duration -> m Duration
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Duration -> m Duration
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Duration -> m Duration
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Duration -> m Duration
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Duration -> m Duration
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Duration -> m Duration
Data, (forall (m :: * -> *). Quote m => Duration -> m Exp)
-> (forall (m :: * -> *). Quote m => Duration -> Code m Duration)
-> Lift Duration
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => Duration -> m Exp
forall (m :: * -> *). Quote m => Duration -> Code m Duration
$clift :: forall (m :: * -> *). Quote m => Duration -> m Exp
lift :: forall (m :: * -> *). Quote m => Duration -> m Exp
$cliftTyped :: forall (m :: * -> *). Quote m => Duration -> Code m Duration
liftTyped :: forall (m :: * -> *). Quote m => Duration -> Code m Duration
Lift)
instance Semigroup Duration where
<> :: Duration -> Duration -> Duration
(<>) = Duration -> Duration -> Duration
addDurations
instance Monoid Duration where
mempty :: Duration
mempty = Int64 -> Int32 -> Duration
Duration Int64
0 Int32
0
mkDuration :: Int64 -> Int32 -> Duration
mkDuration :: Int64 -> Int32 -> Duration
mkDuration Int64
s Int32
ns = case Int64 -> Int64 -> (# Int64, Int32 #)
normalize Int64
s (Int32 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
ns) of
(# Int64
s', Int32
ns' #) -> Int64 -> Int32 -> Duration
Duration Int64
s' Int32
ns'
instance ToJSON Duration where
toJSON :: Duration -> Value
toJSON Duration {Int32
Int64
durationSeconds :: Duration -> Int64
durationNanoseconds :: Duration -> Int32
durationSeconds :: Int64
durationNanoseconds :: Int32
..} = Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String -> Int64 -> Int32 -> String
forall r. PrintfType r => String -> r
printf String
"%d.%09ds" Int64
durationSeconds Int32
durationNanoseconds
instance FromJSON Duration where
parseJSON :: Value -> Parser Duration
parseJSON = String -> (Text -> Parser Duration) -> Value -> Parser Duration
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"Duration" Text -> Parser Duration
parseDuration
parseDuration :: T.Text -> Parser Duration
parseDuration :: Text -> Parser Duration
parseDuration Text
t
| HasCallStack => Text -> Char
Text -> Char
T.last Text
t Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
's' = Duration -> Parser Duration
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Duration -> Parser Duration) -> Duration -> Parser Duration
forall a b. (a -> b) -> a -> b
$ NominalDiffTime -> Duration
nominalDiffTimeToDuration (NominalDiffTime -> Duration) -> NominalDiffTime -> Duration
forall a b. (a -> b) -> a -> b
$ Pico -> NominalDiffTime
secondsToNominalDiffTime (Pico -> NominalDiffTime) -> Pico -> NominalDiffTime
forall a b. (a -> b) -> a -> b
$ String -> Pico
forall a. Read a => String -> a
read (String -> Pico) -> String -> Pico
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack (HasCallStack => Text -> Text
Text -> Text
T.init Text
t)
| Bool
otherwise = String -> Parser Duration
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Duration must end with 's'"
addDurations :: Duration -> Duration -> Duration
addDurations :: Duration -> Duration -> Duration
addDurations (Duration Int64
s1 Int32
ns1) (Duration Int64
s2 Int32
ns2) =
let (# Int64
s, Int32
ns #) = Int64 -> Int64 -> (# Int64, Int32 #)
normalize (Int64
s1 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int64
s2) (Int32 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
ns1 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int32 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
ns2)
in Int64 -> Int32 -> Duration
Duration Int64
s Int32
ns
normalize :: Int64 -> Int64 -> (# Int64, Int32 #)
normalize :: Int64 -> Int64 -> (# Int64, Int32 #)
normalize !Int64
s !Int64
ns
| Int64
ns Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
>= Int64
1_000_000_000 = Int64 -> Int64 -> (# Int64, Int32 #)
normalize (Int64
s Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int64
1) (Int64
ns Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- Int64
1_000_000_000)
| Int64
ns Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= -Int64
1_000_000_000 = Int64 -> Int64 -> (# Int64, Int32 #)
normalize (Int64
s Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- Int64
1) (Int64
ns Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int64
1_000_000_000)
| Int64
s Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
> Int64
0 Bool -> Bool -> Bool
&& Int64
ns Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Int64
0 = Int64 -> Int64 -> (# Int64, Int32 #)
normalize (Int64
s Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- Int64
1) (Int64
ns Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int64
1_000_000_000)
| Int64
s Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Int64
0 Bool -> Bool -> Bool
&& Int64
ns Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
> Int64
0 = Int64 -> Int64 -> (# Int64, Int32 #)
normalize (Int64
s Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int64
1) (Int64
ns Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- Int64
1_000_000_000)
| Bool
otherwise = (# Int64
s, Int64 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
ns #)
diffTimeToDuration :: DiffTime -> Duration
diffTimeToDuration :: DiffTime -> Duration
diffTimeToDuration DiffTime
t =
Int64 -> Int32 -> Duration
mkDuration
(Integer -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
ds)
Int32
remainingNanosFromPicos
where
totalPicos :: Integer
totalPicos = Integer -> Integer -> Integer
forall a. Ord a => a -> a -> a
max Integer
0 (DiffTime -> Integer
diffTimeToPicoseconds DiffTime
t)
picosPerSecond :: Integer
picosPerSecond = Integer
1_000_000_000_000
(Integer
ds, Integer
remainingPicos) = Integer
totalPicos Integer -> Integer -> (Integer, Integer)
forall a. Integral a => a -> a -> (a, a)
`quotRem` Integer
picosPerSecond
remainingNanosFromPicos :: Int32
remainingNanosFromPicos = Integer -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
remainingPicos Int32 -> Int32 -> Int32
forall a. Integral a => a -> a -> a
`div` Int32
1_000
nominalDiffTimeToDuration :: NominalDiffTime -> Duration
nominalDiffTimeToDuration :: NominalDiffTime -> Duration
nominalDiffTimeToDuration NominalDiffTime
t =
Int64 -> Int32 -> Duration
mkDuration
(Integer -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
ds)
Int32
remainingNanosFromPicos
where
(MkFixed Integer
totalPicos) = Pico -> Pico -> Pico
forall a. Ord a => a -> a -> a
max Pico
0 (Pico -> Pico) -> Pico -> Pico
forall a b. (a -> b) -> a -> b
$ NominalDiffTime -> Pico
nominalDiffTimeToSeconds NominalDiffTime
t
picosPerSecond :: Integer
picosPerSecond = Integer
1_000_000_000_000
(Integer
ds, Integer
remainingPicos) = Integer
totalPicos Integer -> Integer -> (Integer, Integer)
forall a. Integral a => a -> a -> (a, a)
`quotRem` Integer
picosPerSecond
remainingNanosFromPicos :: Int32
remainingNanosFromPicos = Integer -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
remainingPicos Int32 -> Int32 -> Int32
forall a. Integral a => a -> a -> a
`div` Int32
1_000
nanoseconds :: Integer -> Duration
nanoseconds :: Integer -> Duration
nanoseconds Integer
n = Int64 -> Int32 -> Duration
mkDuration (Integer -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
secs) (Integer -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
ns)
where
(Integer
secs, Integer
ns) = Integer
n Integer -> Integer -> (Integer, Integer)
forall a. Integral a => a -> a -> (a, a)
`quotRem` Integer
1_000_000_000
microseconds :: Integer -> Duration
microseconds :: Integer -> Duration
microseconds Integer
n = Int64 -> Int32 -> Duration
mkDuration (Integer -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
secs) (Integer -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int32) -> Integer -> Int32
forall a b. (a -> b) -> a -> b
$ Integer
ns Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
1_000)
where
(Integer
secs, Integer
ns) = Integer
n Integer -> Integer -> (Integer, Integer)
forall a. Integral a => a -> a -> (a, a)
`quotRem` Integer
1_000_000
milliseconds :: Int64 -> Duration
milliseconds :: Int64 -> Duration
milliseconds Int64
n = Int64 -> Int32 -> Duration
mkDuration Int64
secs (Int32 -> Duration) -> Int32 -> Duration
forall a b. (a -> b) -> a -> b
$ Int64 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> Int32) -> Int64 -> Int32
forall a b. (a -> b) -> a -> b
$ Int64
ns Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
1_000_000
where
(Int64
secs, Int64
ns) = Int64
n Int64 -> Int64 -> (Int64, Int64)
forall a. Integral a => a -> a -> (a, a)
`quotRem` Int64
1_000
seconds :: Int64 -> Duration
seconds :: Int64 -> Duration
seconds Int64
n = Int64 -> Int32 -> Duration
Duration Int64
n Int32
0
minutes :: Int32 -> Duration
minutes :: Int32 -> Duration
minutes Int32
n = Int64 -> Int32 -> Duration
Duration (Int32 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
n Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
60) Int32
0
hours :: Int32 -> Duration
hours :: Int32 -> Duration
hours Int32
n = Int64 -> Int32 -> Duration
Duration (Int32 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
n Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
60 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
60) Int32
0
days :: Int32 -> Duration
days :: Int32 -> Duration
days Int32
n = Int64 -> Int32 -> Duration
Duration (Int32 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
n Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
60 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
60 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
24) Int32
0
weeks :: Int32 -> Duration
weeks :: Int32 -> Duration
weeks Int32
n = Int64 -> Int32 -> Duration
Duration (Int32 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
n Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
60 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
60 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
24 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
7) Int32
0
infinity :: Duration
infinity :: Duration
infinity = Int64 -> Int32 -> Duration
Duration ((Int64
2 :: Int64) Int64 -> Int64 -> Int64
forall a b. (Num a, Integral b) => a -> b -> a
^ (Int64
32 :: Int64)) Int32
0
durationFromProto :: Duration.Duration -> Duration
durationFromProto :: Duration -> Duration
durationFromProto Duration
d =
Duration
{ durationSeconds :: Int64
durationSeconds = Duration
d Duration -> FoldLike Int64 Duration Duration Int64 Int64 -> Int64
forall s a t b. s -> FoldLike a s t a b -> a
^. FoldLike Int64 Duration Duration Int64 Int64
forall (f :: * -> *) s a.
(Functor f, HasField s "seconds" a) =>
LensLike' f s a
Duration.seconds
, durationNanoseconds :: Int32
durationNanoseconds = Duration
d Duration -> FoldLike Int32 Duration Duration Int32 Int32 -> Int32
forall s a t b. s -> FoldLike a s t a b -> a
^. FoldLike Int32 Duration Duration Int32 Int32
forall (f :: * -> *) s a.
(Functor f, HasField s "nanos" a) =>
LensLike' f s a
Duration.nanos
}
durationToProto :: Duration -> Duration.Duration
durationToProto :: Duration -> Duration
durationToProto Duration
ts =
Duration
forall msg. Message msg => msg
defMessage
Duration -> (Duration -> Duration) -> Duration
forall s t. s -> (s -> t) -> t
& LensLike' f Duration Int64
forall {f :: * -> *}. Identical f => LensLike' f Duration Int64
forall (f :: * -> *) s a.
(Functor f, HasField s "seconds" a) =>
LensLike' f s a
Duration.seconds (forall {f :: * -> *}. Identical f => LensLike' f Duration Int64)
-> Int64 -> Duration -> Duration
forall s t a b. Setter s t a b -> b -> s -> t
.~ Duration -> Int64
durationSeconds Duration
ts
Duration -> (Duration -> Duration) -> Duration
forall s t. s -> (s -> t) -> t
& LensLike' f Duration Int32
forall {f :: * -> *}. Identical f => LensLike' f Duration Int32
forall (f :: * -> *) s a.
(Functor f, HasField s "nanos" a) =>
LensLike' f s a
Duration.nanos (forall {f :: * -> *}. Identical f => LensLike' f Duration Int32)
-> Int32 -> Duration -> Duration
forall s t a b. Setter s t a b -> b -> s -> t
.~ Duration -> Int32
durationNanoseconds Duration
ts
durationToMilliseconds :: Duration -> Double
durationToMilliseconds :: Duration -> Double
durationToMilliseconds (Duration Int64
secs Int32
ns) = Int64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
secs Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
1_000 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Int32 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
ns Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
1_000_000