module PostgreSQL.Binary.Time where
import PostgreSQL.Binary.Prelude hiding (second)
import Data.Time.Calendar.Julian
{-# INLINABLE dayToPostgresJulian #-}
dayToPostgresJulian :: Day -> Integer
dayToPostgresJulian :: Day -> Integer
dayToPostgresJulian =
(Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ (Integer
2400001 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
2451545)) (Integer -> Integer) -> (Day -> Integer) -> Day -> Integer
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Day -> Integer
toModifiedJulianDay
{-# INLINABLE postgresJulianToDay #-}
postgresJulianToDay :: Integral a => a -> Day
postgresJulianToDay :: a -> Day
postgresJulianToDay =
Integer -> Day
ModifiedJulianDay (Integer -> Day) -> (a -> Integer) -> a -> Day
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (a -> Integer) -> (a -> a) -> a -> Integer
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> a -> a
forall a. Num a => a -> a -> a
subtract (a
2400001 a -> a -> a
forall a. Num a => a -> a -> a
- a
2451545)
{-# INLINABLE microsToTimeOfDay #-}
microsToTimeOfDay :: Int64 -> TimeOfDay
microsToTimeOfDay :: Int64 -> TimeOfDay
microsToTimeOfDay =
State Int64 TimeOfDay -> Int64 -> TimeOfDay
forall s a. State s a -> s -> a
evalState (State Int64 TimeOfDay -> Int64 -> TimeOfDay)
-> State Int64 TimeOfDay -> Int64 -> TimeOfDay
forall a b. (a -> b) -> a -> b
$ do
Int64
h <- (Int64 -> (Int64, Int64)) -> StateT Int64 Identity Int64
forall (m :: * -> *) s a. Monad m => (s -> (a, s)) -> StateT s m a
state ((Int64 -> (Int64, Int64)) -> StateT Int64 Identity Int64)
-> (Int64 -> (Int64, Int64)) -> StateT Int64 Identity Int64
forall a b. (a -> b) -> a -> b
$ (Int64 -> Int64 -> (Int64, Int64))
-> Int64 -> Int64 -> (Int64, Int64)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int64 -> Int64 -> (Int64, Int64)
forall a. Integral a => a -> a -> (a, a)
divMod (Int64 -> Int64 -> (Int64, Int64))
-> Int64 -> Int64 -> (Int64, Int64)
forall a b. (a -> b) -> a -> b
$ Int64
10 Int64 -> Integer -> Int64
forall a b. (Num a, Integral b) => a -> b -> a
^ Integer
6 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
m <- (Int64 -> (Int64, Int64)) -> StateT Int64 Identity Int64
forall (m :: * -> *) s a. Monad m => (s -> (a, s)) -> StateT s m a
state ((Int64 -> (Int64, Int64)) -> StateT Int64 Identity Int64)
-> (Int64 -> (Int64, Int64)) -> StateT Int64 Identity Int64
forall a b. (a -> b) -> a -> b
$ (Int64 -> Int64 -> (Int64, Int64))
-> Int64 -> Int64 -> (Int64, Int64)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int64 -> Int64 -> (Int64, Int64)
forall a. Integral a => a -> a -> (a, a)
divMod (Int64 -> Int64 -> (Int64, Int64))
-> Int64 -> Int64 -> (Int64, Int64)
forall a b. (a -> b) -> a -> b
$ Int64
10 Int64 -> Integer -> Int64
forall a b. (Num a, Integral b) => a -> b -> a
^ Integer
6 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
60
Int64
u <- StateT Int64 Identity Int64
forall (m :: * -> *) s. Monad m => StateT s m s
get
TimeOfDay -> State Int64 TimeOfDay
forall (m :: * -> *) a. Monad m => a -> m a
return (TimeOfDay -> State Int64 TimeOfDay)
-> TimeOfDay -> State Int64 TimeOfDay
forall a b. (a -> b) -> a -> b
$
Int -> Int -> Pico -> TimeOfDay
TimeOfDay (Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
h) (Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
m) (Int64 -> Pico
microsToPico Int64
u)
{-# INLINABLE microsToUTC #-}
microsToUTC :: Int64 -> UTCTime
microsToUTC :: Int64 -> UTCTime
microsToUTC =
State Int64 UTCTime -> Int64 -> UTCTime
forall s a. State s a -> s -> a
evalState (State Int64 UTCTime -> Int64 -> UTCTime)
-> State Int64 UTCTime -> Int64 -> UTCTime
forall a b. (a -> b) -> a -> b
$ do
Int64
d <- (Int64 -> (Int64, Int64)) -> StateT Int64 Identity Int64
forall (m :: * -> *) s a. Monad m => (s -> (a, s)) -> StateT s m a
state ((Int64 -> (Int64, Int64)) -> StateT Int64 Identity Int64)
-> (Int64 -> (Int64, Int64)) -> StateT Int64 Identity Int64
forall a b. (a -> b) -> a -> b
$ (Int64 -> Int64 -> (Int64, Int64))
-> Int64 -> Int64 -> (Int64, Int64)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int64 -> Int64 -> (Int64, Int64)
forall a. Integral a => a -> a -> (a, a)
divMod (Int64 -> Int64 -> (Int64, Int64))
-> Int64 -> Int64 -> (Int64, Int64)
forall a b. (a -> b) -> a -> b
$ Int64
10Int64 -> Integer -> Int64
forall a b. (Num a, Integral b) => a -> b -> a
^Integer
6 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
u <- StateT Int64 Identity Int64
forall (m :: * -> *) s. Monad m => StateT s m s
get
UTCTime -> State Int64 UTCTime
forall (m :: * -> *) a. Monad m => a -> m a
return (UTCTime -> State Int64 UTCTime) -> UTCTime -> State Int64 UTCTime
forall a b. (a -> b) -> a -> b
$
Day -> DiffTime -> UTCTime
UTCTime (Int64 -> Day
forall a. Integral a => a -> Day
postgresJulianToDay Int64
d) (Int64 -> DiffTime
microsToDiffTime Int64
u)
{-# INLINABLE microsToPico #-}
microsToPico :: Int64 -> Pico
microsToPico :: Int64 -> Pico
microsToPico =
Integer -> Pico
forall a b. a -> b
unsafeCoerce (Integer -> Pico) -> (Int64 -> Integer) -> Int64 -> Pico
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* (Integer
10Integer -> Integer -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^Integer
6)) (Integer -> Integer) -> (Int64 -> Integer) -> Int64 -> Integer
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Int64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral :: Int64 -> Integer)
{-# INLINABLE microsToDiffTime #-}
microsToDiffTime :: Int64 -> DiffTime
microsToDiffTime :: Int64 -> DiffTime
microsToDiffTime =
(Int64 -> Pico) -> Int64 -> DiffTime
forall a b. a -> b
unsafeCoerce Int64 -> Pico
microsToPico
{-# INLINABLE microsToLocalTime #-}
microsToLocalTime :: Int64 -> LocalTime
microsToLocalTime :: Int64 -> LocalTime
microsToLocalTime =
State Int64 LocalTime -> Int64 -> LocalTime
forall s a. State s a -> s -> a
evalState (State Int64 LocalTime -> Int64 -> LocalTime)
-> State Int64 LocalTime -> Int64 -> LocalTime
forall a b. (a -> b) -> a -> b
$ do
Int64
d <- (Int64 -> (Int64, Int64)) -> StateT Int64 Identity Int64
forall (m :: * -> *) s a. Monad m => (s -> (a, s)) -> StateT s m a
state ((Int64 -> (Int64, Int64)) -> StateT Int64 Identity Int64)
-> (Int64 -> (Int64, Int64)) -> StateT Int64 Identity Int64
forall a b. (a -> b) -> a -> b
$ (Int64 -> Int64 -> (Int64, Int64))
-> Int64 -> Int64 -> (Int64, Int64)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int64 -> Int64 -> (Int64, Int64)
forall a. Integral a => a -> a -> (a, a)
divMod (Int64 -> Int64 -> (Int64, Int64))
-> Int64 -> Int64 -> (Int64, Int64)
forall a b. (a -> b) -> a -> b
$ Int64
10Int64 -> Integer -> Int64
forall a b. (Num a, Integral b) => a -> b -> a
^Integer
6 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
u <- StateT Int64 Identity Int64
forall (m :: * -> *) s. Monad m => StateT s m s
get
LocalTime -> State Int64 LocalTime
forall (m :: * -> *) a. Monad m => a -> m a
return (LocalTime -> State Int64 LocalTime)
-> LocalTime -> State Int64 LocalTime
forall a b. (a -> b) -> a -> b
$
Day -> TimeOfDay -> LocalTime
LocalTime (Int64 -> Day
forall a. Integral a => a -> Day
postgresJulianToDay Int64
d) (Int64 -> TimeOfDay
microsToTimeOfDay Int64
u)
{-# INLINABLE secsToTimeOfDay #-}
secsToTimeOfDay :: Double -> TimeOfDay
secsToTimeOfDay :: Double -> TimeOfDay
secsToTimeOfDay =
State Double TimeOfDay -> Double -> TimeOfDay
forall s a. State s a -> s -> a
evalState (State Double TimeOfDay -> Double -> TimeOfDay)
-> State Double TimeOfDay -> Double -> TimeOfDay
forall a b. (a -> b) -> a -> b
$ do
Integer
h <- (Double -> (Integer, Double)) -> StateT Double Identity Integer
forall (m :: * -> *) s a. Monad m => (s -> (a, s)) -> StateT s m a
state ((Double -> (Integer, Double)) -> StateT Double Identity Integer)
-> (Double -> (Integer, Double)) -> StateT Double Identity Integer
forall a b. (a -> b) -> a -> b
$ (Double -> Double -> (Integer, Double))
-> Double -> Double -> (Integer, Double)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Double -> Double -> (Integer, Double)
forall a b. (Real a, Integral b) => a -> a -> (b, a)
divMod' (Double -> Double -> (Integer, Double))
-> Double -> Double -> (Integer, Double)
forall a b. (a -> b) -> a -> b
$ Double
60 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
60
Integer
m <- (Double -> (Integer, Double)) -> StateT Double Identity Integer
forall (m :: * -> *) s a. Monad m => (s -> (a, s)) -> StateT s m a
state ((Double -> (Integer, Double)) -> StateT Double Identity Integer)
-> (Double -> (Integer, Double)) -> StateT Double Identity Integer
forall a b. (a -> b) -> a -> b
$ (Double -> Double -> (Integer, Double))
-> Double -> Double -> (Integer, Double)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Double -> Double -> (Integer, Double)
forall a b. (Real a, Integral b) => a -> a -> (b, a)
divMod' (Double -> Double -> (Integer, Double))
-> Double -> Double -> (Integer, Double)
forall a b. (a -> b) -> a -> b
$ Double
60
Double
s <- StateT Double Identity Double
forall (m :: * -> *) s. Monad m => StateT s m s
get
TimeOfDay -> State Double TimeOfDay
forall (m :: * -> *) a. Monad m => a -> m a
return (TimeOfDay -> State Double TimeOfDay)
-> TimeOfDay -> State Double TimeOfDay
forall a b. (a -> b) -> a -> b
$
Int -> Int -> Pico -> TimeOfDay
TimeOfDay (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
h) (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
m) (Double -> Pico
secsToPico Double
s)
{-# INLINABLE secsToUTC #-}
secsToUTC :: Double -> UTCTime
secsToUTC :: Double -> UTCTime
secsToUTC =
State Double UTCTime -> Double -> UTCTime
forall s a. State s a -> s -> a
evalState (State Double UTCTime -> Double -> UTCTime)
-> State Double UTCTime -> Double -> UTCTime
forall a b. (a -> b) -> a -> b
$ do
Integer
d <- (Double -> (Integer, Double)) -> StateT Double Identity Integer
forall (m :: * -> *) s a. Monad m => (s -> (a, s)) -> StateT s m a
state ((Double -> (Integer, Double)) -> StateT Double Identity Integer)
-> (Double -> (Integer, Double)) -> StateT Double Identity Integer
forall a b. (a -> b) -> a -> b
$ (Double -> Double -> (Integer, Double))
-> Double -> Double -> (Integer, Double)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Double -> Double -> (Integer, Double)
forall a b. (Real a, Integral b) => a -> a -> (b, a)
divMod' (Double -> Double -> (Integer, Double))
-> Double -> Double -> (Integer, Double)
forall a b. (a -> b) -> a -> b
$ Double
60 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
60 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
24
Double
s <- StateT Double Identity Double
forall (m :: * -> *) s. Monad m => StateT s m s
get
UTCTime -> State Double UTCTime
forall (m :: * -> *) a. Monad m => a -> m a
return (UTCTime -> State Double UTCTime)
-> UTCTime -> State Double UTCTime
forall a b. (a -> b) -> a -> b
$
Day -> DiffTime -> UTCTime
UTCTime (Integer -> Day
forall a. Integral a => a -> Day
postgresJulianToDay Integer
d) (Double -> DiffTime
secsToDiffTime Double
s)
{-# INLINABLE secsToLocalTime #-}
secsToLocalTime :: Double -> LocalTime
secsToLocalTime :: Double -> LocalTime
secsToLocalTime =
State Double LocalTime -> Double -> LocalTime
forall s a. State s a -> s -> a
evalState (State Double LocalTime -> Double -> LocalTime)
-> State Double LocalTime -> Double -> LocalTime
forall a b. (a -> b) -> a -> b
$ do
Integer
d <- (Double -> (Integer, Double)) -> StateT Double Identity Integer
forall (m :: * -> *) s a. Monad m => (s -> (a, s)) -> StateT s m a
state ((Double -> (Integer, Double)) -> StateT Double Identity Integer)
-> (Double -> (Integer, Double)) -> StateT Double Identity Integer
forall a b. (a -> b) -> a -> b
$ (Double -> Double -> (Integer, Double))
-> Double -> Double -> (Integer, Double)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Double -> Double -> (Integer, Double)
forall a b. (Real a, Integral b) => a -> a -> (b, a)
divMod' (Double -> Double -> (Integer, Double))
-> Double -> Double -> (Integer, Double)
forall a b. (a -> b) -> a -> b
$ Double
60 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
60 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
24
Double
s <- StateT Double Identity Double
forall (m :: * -> *) s. Monad m => StateT s m s
get
LocalTime -> State Double LocalTime
forall (m :: * -> *) a. Monad m => a -> m a
return (LocalTime -> State Double LocalTime)
-> LocalTime -> State Double LocalTime
forall a b. (a -> b) -> a -> b
$
Day -> TimeOfDay -> LocalTime
LocalTime (Integer -> Day
forall a. Integral a => a -> Day
postgresJulianToDay Integer
d) (Double -> TimeOfDay
secsToTimeOfDay Double
s)
{-# INLINABLE secsToPico #-}
secsToPico :: Double -> Pico
secsToPico :: Double -> Pico
secsToPico Double
s =
Integer -> Pico
forall a b. a -> b
unsafeCoerce (Rational -> Integer
forall a b. (RealFrac a, Integral b) => a -> b
truncate (Rational -> Integer) -> Rational -> Integer
forall a b. (a -> b) -> a -> b
$ Double -> Rational
forall a. Real a => a -> Rational
toRational Double
s Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* Rational
10 Rational -> Integer -> Rational
forall a b. (Num a, Integral b) => a -> b -> a
^ Integer
12 :: Integer)
{-# INLINABLE secsToDiffTime #-}
secsToDiffTime :: Double -> DiffTime
secsToDiffTime :: Double -> DiffTime
secsToDiffTime =
(Double -> Pico) -> Double -> DiffTime
forall a b. a -> b
unsafeCoerce Double -> Pico
secsToPico
{-# INLINABLE localTimeToMicros #-}
localTimeToMicros :: LocalTime -> Int64
localTimeToMicros :: LocalTime -> Int64
localTimeToMicros (LocalTime Day
dayX TimeOfDay
timeX) =
let d :: Integer
d = Day -> Integer
dayToPostgresJulian Day
dayX
p :: Integer
p = DiffTime -> Integer
forall a b. a -> b
unsafeCoerce (DiffTime -> Integer) -> DiffTime -> Integer
forall a b. (a -> b) -> a -> b
$ TimeOfDay -> DiffTime
timeOfDayToTime TimeOfDay
timeX
in Int64
10Int64 -> Integer -> Int64
forall a b. (Num a, Integral b) => a -> b -> a
^Integer
6 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
* Integer -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
d Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Integer -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
div Integer
p (Integer
10Integer -> Integer -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^Integer
6))
{-# INLINABLE localTimeToSecs #-}
localTimeToSecs :: LocalTime -> Double
localTimeToSecs :: LocalTime -> Double
localTimeToSecs (LocalTime Day
dayX TimeOfDay
timeX) =
let d :: Integer
d = Day -> Integer
dayToPostgresJulian Day
dayX
p :: Integer
p = DiffTime -> Integer
forall a b. a -> b
unsafeCoerce (DiffTime -> Integer) -> DiffTime -> Integer
forall a b. (a -> b) -> a -> b
$ TimeOfDay -> DiffTime
timeOfDayToTime TimeOfDay
timeX
in Double
60 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
60 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
24 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
d Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Rational -> Double
forall a. Fractional a => Rational -> a
fromRational (Integer
p Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% (Integer
10Integer -> Integer -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^Integer
12))
{-# INLINABLE utcToMicros #-}
utcToMicros :: UTCTime -> Int64
utcToMicros :: UTCTime -> Int64
utcToMicros (UTCTime Day
dayX DiffTime
diffTimeX) =
let d :: Integer
d = Day -> Integer
dayToPostgresJulian Day
dayX
p :: Integer
p = DiffTime -> Integer
forall a b. a -> b
unsafeCoerce DiffTime
diffTimeX
in Int64
10Int64 -> Integer -> Int64
forall a b. (Num a, Integral b) => a -> b -> a
^Integer
6 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
* Integer -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
d Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Integer -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
div Integer
p (Integer
10Integer -> Integer -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^Integer
6))
{-# INLINABLE utcToSecs #-}
utcToSecs :: UTCTime -> Double
utcToSecs :: UTCTime -> Double
utcToSecs (UTCTime Day
dayX DiffTime
diffTimeX) =
let d :: Integer
d = Day -> Integer
dayToPostgresJulian Day
dayX
p :: Integer
p = DiffTime -> Integer
forall a b. a -> b
unsafeCoerce DiffTime
diffTimeX
in Double
60 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
60 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
24 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
d Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Rational -> Double
forall a. Fractional a => Rational -> a
fromRational (Integer
p Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% (Integer
10Integer -> Integer -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^Integer
12))
Int64
yearMicros :: Int64 = Rational -> Int64
forall a b. (RealFrac a, Integral b) => a -> b
truncate (Rational
365.2425 Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* Int64 -> Rational
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
dayMicros :: Rational)
Int64
dayMicros :: Int64 = Int64
24 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
hourMicros
Int64
hourMicros :: Int64 = Int64
60 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
minuteMicros
Int64
minuteMicros :: Int64 = Int64
60 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
secondMicros
Int64
secondMicros :: Int64 = Int64
10 Int64 -> Integer -> Int64
forall a b. (Num a, Integral b) => a -> b -> a
^ Integer
6