{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 708
{-# LANGUAGE PatternSynonyms #-}
#endif
module Data.Thyme.Clock (
UTCTime
, utctDay, utctDayTime
, _utctDay, _utctDayTime
#if __GLASGOW_HASKELL__ >= 708
, pattern UTCTime
#endif
, mkUTCTime
, utcTime
, UTCView (..), _utcvDay, _utcvDayTime
, NominalDiffTime
, getCurrentTime
, DiffTime
, TimeDiff (..)
, toSeconds, fromSeconds
, toSeconds', fromSeconds'
, picoseconds
, UniversalTime
#if __GLASGOW_HASKELL__ >= 708
, pattern UniversalTime
#endif
, modJulianDate
, getModJulianDate
, mkModJulianDate
, secondsToDiffTime
, picosecondsToDiffTime
, unUTCTime
, addUTCTime
, diffUTCTime
, toMicroseconds
, fromMicroseconds
) where
import Prelude
import Control.Lens
import Data.AffineSpace
import Data.Int
import Data.Ratio ((%))
import Data.Thyme.Clock.Internal
import Data.Thyme.Clock.POSIX
getCurrentTime :: IO UTCTime
getCurrentTime :: IO UTCTime
getCurrentTime = (POSIXTime -> UTCTime) -> IO POSIXTime -> IO UTCTime
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview UTCTime UTCTime POSIXTime POSIXTime -> POSIXTime -> UTCTime
forall s t a b. AReview s t a b -> b -> t
review AReview UTCTime UTCTime POSIXTime POSIXTime
Iso' UTCTime POSIXTime
posixTime) IO POSIXTime
getPOSIXTime
{-# INLINE picoseconds #-}
picoseconds :: (TimeDiff t) => Iso' t Integer
picoseconds :: forall t. TimeDiff t => Iso' t Integer
picoseconds = Overloaded p f t t Int64 Int64
forall t. TimeDiff t => Iso' t Int64
Iso' t Int64
microseconds Overloaded p f t t Int64 Int64
-> (p Integer (f Integer) -> p Int64 (f Int64))
-> p Integer (f Integer)
-> p t (f t)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int64 -> Integer)
-> (Integer -> Int64) -> Iso Int64 Int64 Integer Integer
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
(*) Integer
1000000 (Integer -> Integer) -> (Int64 -> Integer) -> Int64 -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Integer
forall a. Integral a => a -> Integer
toInteger) (\ Integer
ps -> Rational -> Int64
forall b. Integral b => Rational -> b
forall a b. (RealFrac a, Integral b) => a -> b
round (Integer
ps Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
1000000))
{-# INLINE getModJulianDate #-}
getModJulianDate :: UniversalTime -> Rational
getModJulianDate :: UniversalTime -> Rational
getModJulianDate = Getting Rational UniversalTime Rational
-> UniversalTime -> Rational
forall a s. Getting a s a -> s -> a
view Getting Rational UniversalTime Rational
Iso' UniversalTime Rational
modJulianDate
{-# INLINE mkModJulianDate #-}
mkModJulianDate :: Rational -> UniversalTime
mkModJulianDate :: Rational -> UniversalTime
mkModJulianDate = AReview UniversalTime UniversalTime Rational Rational
-> Rational -> UniversalTime
forall s t a b. AReview s t a b -> b -> t
review AReview UniversalTime UniversalTime Rational Rational
Iso' UniversalTime Rational
modJulianDate
{-# INLINE secondsToDiffTime #-}
secondsToDiffTime :: Int64 -> DiffTime
secondsToDiffTime :: Int64 -> DiffTime
secondsToDiffTime = Int64 -> DiffTime
forall n t. (Real n, TimeDiff t) => n -> t
fromSeconds
{-# INLINE picosecondsToDiffTime #-}
picosecondsToDiffTime :: Integer -> DiffTime
picosecondsToDiffTime :: Integer -> DiffTime
picosecondsToDiffTime = AReview DiffTime DiffTime Integer Integer -> Integer -> DiffTime
forall s t a b. AReview s t a b -> b -> t
review AReview DiffTime DiffTime Integer Integer
forall t. TimeDiff t => Iso' t Integer
Iso' DiffTime Integer
picoseconds
{-# INLINE unUTCTime #-}
unUTCTime :: UTCTime -> UTCView
unUTCTime :: UTCTime -> UTCView
unUTCTime = Getting UTCView UTCTime UTCView -> UTCTime -> UTCView
forall a s. Getting a s a -> s -> a
view Getting UTCView UTCTime UTCView
Iso' UTCTime UTCView
utcTime
{-# INLINE addUTCTime #-}
addUTCTime :: NominalDiffTime -> UTCTime -> UTCTime
addUTCTime :: POSIXTime -> UTCTime -> UTCTime
addUTCTime = (UTCTime -> POSIXTime -> UTCTime)
-> POSIXTime -> UTCTime -> UTCTime
forall a b c. (a -> b -> c) -> b -> a -> c
flip UTCTime -> Diff UTCTime -> UTCTime
UTCTime -> POSIXTime -> UTCTime
forall p. AffineSpace p => p -> Diff p -> p
(.+^)
{-# INLINE diffUTCTime #-}
diffUTCTime :: UTCTime -> UTCTime -> NominalDiffTime
diffUTCTime :: UTCTime -> UTCTime -> POSIXTime
diffUTCTime = UTCTime -> UTCTime -> Diff UTCTime
UTCTime -> UTCTime -> POSIXTime
forall p. AffineSpace p => p -> p -> Diff p
(.-.)
{-# INLINE toMicroseconds #-}
toMicroseconds :: (TimeDiff t) => t -> Int64
toMicroseconds :: forall t. TimeDiff t => t -> Int64
toMicroseconds = Getting Int64 t Int64 -> t -> Int64
forall a s. Getting a s a -> s -> a
view Getting Int64 t Int64
forall t. TimeDiff t => Iso' t Int64
Iso' t Int64
microseconds
{-# INLINE fromMicroseconds #-}
fromMicroseconds :: (TimeDiff t) => Int64 -> t
fromMicroseconds :: forall t. TimeDiff t => Int64 -> t
fromMicroseconds = AReview t t Int64 Int64 -> Int64 -> t
forall s t a b. AReview s t a b -> b -> t
review AReview t t Int64 Int64
forall t. TimeDiff t => Iso' t Int64
Iso' t Int64
microseconds