{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_HADDOCK hide #-}
#include "thyme.h"
module Data.Thyme.Clock.Internal where
import Prelude
import Control.DeepSeq
import Control.Lens
import Data.AdditiveGroup
import Data.AffineSpace
import Data.Basis
import Data.Data
import Data.Int
import Data.Ix
import Data.Thyme.Internal.Micro
import Data.Thyme.Calendar.Internal
#if __GLASGOW_HASKELL__ == 704
import qualified Data.Vector.Generic
import qualified Data.Vector.Generic.Mutable
#endif
import Data.Vector.Unboxed.Deriving
import Data.VectorSpace
import GHC.Generics (Generic)
import System.Random
import Test.QuickCheck
#if !SHOW_INTERNAL
import Control.Monad
import Text.ParserCombinators.ReadPrec (lift)
import Text.ParserCombinators.ReadP (char)
import Text.Read (readPrec)
#endif
class (HasBasis t, Basis t ~ (), Scalar t ~ Rational) => TimeDiff t where
microseconds :: Iso' t Int64
{-# INLINE toSeconds #-}
toSeconds :: (TimeDiff t, Fractional n) => t -> n
toSeconds :: t -> n
toSeconds = (n -> n -> n
forall a. Num a => a -> a -> a
* n -> n
forall a. Fractional a => a -> a
recip 1000000) (n -> n) -> (t -> n) -> t -> n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> n
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> n) -> (t -> Int64) -> t -> n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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
microseconds
{-# INLINE[0] fromSeconds #-}
fromSeconds :: (Real n, TimeDiff t) => n -> t
fromSeconds :: n -> t
fromSeconds = Rational -> t
forall t. TimeDiff t => Rational -> t
fromSeconds' (Rational -> t) -> (n -> Rational) -> n -> t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. n -> Rational
forall a. Real a => a -> Rational
toRational
{-# INLINE toSeconds' #-}
toSeconds' :: (TimeDiff t) => t -> Rational
toSeconds' :: t -> Rational
toSeconds' = (t -> Basis t -> Scalar t
forall v. HasBasis v => v -> Basis v -> Scalar v
`decompose'` ())
{-# INLINE fromSeconds' #-}
fromSeconds' :: (TimeDiff t) => Rational -> t
fromSeconds' :: Rational -> t
fromSeconds' = (Scalar t -> t -> t
forall v. VectorSpace v => Scalar v -> v -> v
*^ Basis t -> t
forall v. HasBasis v => Basis v -> v
basisValue ())
{-# INLINE picoseconds #-}
picoseconds :: (TimeDiff t) => Iso' t Integer
picoseconds :: Iso' t Integer
picoseconds = Overloaded p f t t Int64 Int64
forall t. TimeDiff t => 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
(*) 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)
(\ ps :: Integer
ps -> Integer -> Int64
forall a. Num a => Integer -> a
fromInteger (Integer -> Int64) -> Integer -> Int64
forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
quot (Integer
ps Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer -> Integer
forall a. Num a => a -> a
signum Integer
ps Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* 500000) 1000000)
{-# INLINE fromSecondsRealFrac #-}
fromSecondsRealFrac :: (RealFrac n, TimeDiff t) => n -> n -> t
fromSecondsRealFrac :: n -> n -> t
fromSecondsRealFrac _ = 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
microseconds (Int64 -> t) -> (n -> Int64) -> n -> t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. n -> Int64
forall a b. (RealFrac a, Integral b) => a -> b
round (n -> Int64) -> (n -> n) -> n -> Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. n -> n -> n
forall a. Num a => a -> a -> a
(*) 1000000
{-# INLINE fromSecondsIntegral #-}
fromSecondsIntegral :: (Integral n, TimeDiff t) => n -> n -> t
fromSecondsIntegral :: n -> n -> t
fromSecondsIntegral _ = 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
microseconds (Int64 -> t) -> (n -> Int64) -> n -> t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
(*) 1000000 (Int64 -> Int64) -> (n -> Int64) -> n -> Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. n -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# RULES
"fromSeconds/Float" [~0] fromSeconds = fromSecondsRealFrac (0 :: Float)
"fromSeconds/Double" [~0] fromSeconds = fromSecondsRealFrac (0 :: Double)
"fromSeconds/Int" [~0] fromSeconds = fromSecondsIntegral (0 :: Int)
"fromSeconds/Int64" [~0] fromSeconds = fromSecondsIntegral (0 :: Int64)
"fromSeconds/Integer" [~0] fromSeconds = fromSecondsIntegral (0 :: Integer)
#-}
newtype DiffTime = DiffTime Micro deriving (INSTANCES_MICRO, AdditiveGroup)
derivingUnbox "DiffTime" [t| DiffTime -> Micro |]
[| \ (DiffTime a) -> a |] [| DiffTime |]
#if SHOW_INTERNAL
deriving instance Show DiffTime
deriving instance Read DiffTime
#else
instance Show DiffTime where
{-# INLINEABLE showsPrec #-}
showsPrec :: Int -> DiffTime -> ShowS
showsPrec p :: Int
p (DiffTime a :: Micro
a) = Int -> Micro -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
p Micro
a ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:) 's'
instance Read DiffTime where
{-# INLINEABLE readPrec #-}
readPrec :: ReadPrec DiffTime
readPrec = (Micro -> Char -> DiffTime) -> ReadPrec (Micro -> Char -> DiffTime)
forall (m :: * -> *) a. Monad m => a -> m a
return (DiffTime -> Char -> DiffTime
forall a b. a -> b -> a
const (DiffTime -> Char -> DiffTime)
-> (Micro -> DiffTime) -> Micro -> Char -> DiffTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Micro -> DiffTime
DiffTime) ReadPrec (Micro -> Char -> DiffTime)
-> ReadPrec Micro -> ReadPrec (Char -> DiffTime)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` ReadPrec Micro
forall a. Read a => ReadPrec a
readPrec ReadPrec (Char -> DiffTime) -> ReadPrec Char -> ReadPrec DiffTime
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` ReadP Char -> ReadPrec Char
forall a. ReadP a -> ReadPrec a
lift (Char -> ReadP Char
char 's')
#endif
instance VectorSpace DiffTime where
type Scalar DiffTime = Rational
{-# INLINE (*^) #-}
*^ :: Scalar DiffTime -> DiffTime -> DiffTime
(*^) = \ s :: Scalar DiffTime
s (DiffTime t :: Micro
t) -> Micro -> DiffTime
DiffTime (Scalar Micro
Scalar DiffTime
s Scalar Micro -> Micro -> Micro
forall v. VectorSpace v => Scalar v -> v -> v
*^ Micro
t)
instance HasBasis DiffTime where
type Basis DiffTime = ()
{-# INLINE basisValue #-}
basisValue :: Basis DiffTime -> DiffTime
basisValue = \ _ -> Micro -> DiffTime
DiffTime (Basis Micro -> Micro
forall v. HasBasis v => Basis v -> v
basisValue ())
{-# INLINE decompose #-}
decompose :: DiffTime -> [(Basis DiffTime, Scalar DiffTime)]
decompose = \ (DiffTime a :: Micro
a) -> Micro -> [(Basis Micro, Scalar Micro)]
forall v. HasBasis v => v -> [(Basis v, Scalar v)]
decompose Micro
a
{-# INLINE decompose' #-}
decompose' :: DiffTime -> Basis DiffTime -> Scalar DiffTime
decompose' = \ (DiffTime a :: Micro
a) -> Micro -> Basis Micro -> Scalar Micro
forall v. HasBasis v => v -> Basis v -> Scalar v
decompose' Micro
a
instance TimeDiff DiffTime where
{-# INLINE microseconds #-}
microseconds :: Overloaded p f DiffTime DiffTime Int64 Int64
microseconds = (DiffTime -> Int64) -> (Int64 -> DiffTime) -> Iso' DiffTime Int64
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso (\ (DiffTime (Micro u :: Int64
u)) -> Int64
u) (Micro -> DiffTime
DiffTime (Micro -> DiffTime) -> (Int64 -> Micro) -> Int64 -> DiffTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Micro
Micro)
newtype NominalDiffTime = NominalDiffTime Micro deriving (INSTANCES_MICRO, AdditiveGroup)
derivingUnbox "NominalDiffTime" [t| NominalDiffTime -> Micro |]
[| \ (NominalDiffTime a) -> a |] [| NominalDiffTime |]
#if SHOW_INTERNAL
deriving instance Show NominalDiffTime
deriving instance Read NominalDiffTime
#else
instance Show NominalDiffTime where
{-# INLINEABLE showsPrec #-}
showsPrec :: Int -> NominalDiffTime -> ShowS
showsPrec p :: Int
p (NominalDiffTime a :: Micro
a) rest :: String
rest = Int -> Micro -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
p Micro
a ('s' Char -> ShowS
forall a. a -> [a] -> [a]
: String
rest)
instance Read NominalDiffTime where
{-# INLINEABLE readPrec #-}
readPrec :: ReadPrec NominalDiffTime
readPrec = (Micro -> Char -> NominalDiffTime)
-> ReadPrec (Micro -> Char -> NominalDiffTime)
forall (m :: * -> *) a. Monad m => a -> m a
return (NominalDiffTime -> Char -> NominalDiffTime
forall a b. a -> b -> a
const (NominalDiffTime -> Char -> NominalDiffTime)
-> (Micro -> NominalDiffTime) -> Micro -> Char -> NominalDiffTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Micro -> NominalDiffTime
NominalDiffTime) ReadPrec (Micro -> Char -> NominalDiffTime)
-> ReadPrec Micro -> ReadPrec (Char -> NominalDiffTime)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` ReadPrec Micro
forall a. Read a => ReadPrec a
readPrec ReadPrec (Char -> NominalDiffTime)
-> ReadPrec Char -> ReadPrec NominalDiffTime
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` ReadP Char -> ReadPrec Char
forall a. ReadP a -> ReadPrec a
lift (Char -> ReadP Char
char 's')
#endif
instance VectorSpace NominalDiffTime where
type Scalar NominalDiffTime = Rational
{-# INLINE (*^) #-}
*^ :: Scalar NominalDiffTime -> NominalDiffTime -> NominalDiffTime
(*^) = \ s :: Scalar NominalDiffTime
s (NominalDiffTime t :: Micro
t) -> Micro -> NominalDiffTime
NominalDiffTime (Scalar Micro
Scalar NominalDiffTime
s Scalar Micro -> Micro -> Micro
forall v. VectorSpace v => Scalar v -> v -> v
*^ Micro
t)
instance HasBasis NominalDiffTime where
type Basis NominalDiffTime = ()
{-# INLINE basisValue #-}
basisValue :: Basis NominalDiffTime -> NominalDiffTime
basisValue = \ _ -> Micro -> NominalDiffTime
NominalDiffTime (Basis Micro -> Micro
forall v. HasBasis v => Basis v -> v
basisValue ())
{-# INLINE decompose #-}
decompose :: NominalDiffTime
-> [(Basis NominalDiffTime, Scalar NominalDiffTime)]
decompose = \ (NominalDiffTime a :: Micro
a) -> Micro -> [(Basis Micro, Scalar Micro)]
forall v. HasBasis v => v -> [(Basis v, Scalar v)]
decompose Micro
a
{-# INLINE decompose' #-}
decompose' :: NominalDiffTime -> Basis NominalDiffTime -> Scalar NominalDiffTime
decompose' = \ (NominalDiffTime a :: Micro
a) -> Micro -> Basis Micro -> Scalar Micro
forall v. HasBasis v => v -> Basis v -> Scalar v
decompose' Micro
a
instance TimeDiff NominalDiffTime where
{-# INLINE microseconds #-}
microseconds :: Overloaded p f NominalDiffTime NominalDiffTime Int64 Int64
microseconds = (NominalDiffTime -> Int64)
-> (Int64 -> NominalDiffTime) -> Iso' NominalDiffTime Int64
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso (\ (NominalDiffTime (Micro u :: Int64
u)) -> Int64
u) (Micro -> NominalDiffTime
NominalDiffTime (Micro -> NominalDiffTime)
-> (Int64 -> Micro) -> Int64 -> NominalDiffTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Micro
Micro)
{-# INLINE posixDayLength #-}
posixDayLength :: NominalDiffTime
posixDayLength :: NominalDiffTime
posixDayLength = Overloaded
Reviewed Identity NominalDiffTime NominalDiffTime Int64 Int64
forall t. TimeDiff t => Iso' t Int64
microseconds Overloaded
Reviewed Identity NominalDiffTime NominalDiffTime Int64 Int64
-> Int64 -> NominalDiffTime
forall s t a b. AReview s t a b -> b -> t
# 86400000000
newtype UniversalTime = UniversalRep NominalDiffTime deriving (INSTANCES_MICRO)
derivingUnbox "UniversalTime" [t| UniversalTime -> NominalDiffTime |]
[| \ (UniversalRep a) -> a |] [| UniversalRep |]
{-# INLINE modJulianDate #-}
modJulianDate :: Iso' UniversalTime Rational
modJulianDate :: Overloaded p f UniversalTime UniversalTime Rational Rational
modJulianDate = (UniversalTime -> Rational)
-> (Rational -> UniversalTime)
-> Iso UniversalTime UniversalTime Rational Rational
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\ (UniversalRep t :: NominalDiffTime
t) -> NominalDiffTime -> Rational
forall t n. (TimeDiff t, Fractional n) => t -> n
toSeconds NominalDiffTime
t Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/ NominalDiffTime -> Rational
forall t n. (TimeDiff t, Fractional n) => t -> n
toSeconds NominalDiffTime
posixDayLength)
(NominalDiffTime -> UniversalTime
UniversalRep (NominalDiffTime -> UniversalTime)
-> (Rational -> NominalDiffTime) -> Rational -> UniversalTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Scalar NominalDiffTime -> NominalDiffTime -> NominalDiffTime
forall v. VectorSpace v => Scalar v -> v -> v
*^ NominalDiffTime
posixDayLength))
newtype UTCTime = UTCRep NominalDiffTime deriving (INSTANCES_MICRO)
derivingUnbox "UTCTime" [t| UTCTime -> NominalDiffTime |]
[| \ (UTCRep a) -> a |] [| UTCRep |]
data UTCView = UTCTime
{ UTCView -> Day
utctDay :: {-# UNPACK #-}!Day
, UTCView -> DiffTime
utctDayTime :: {-# UNPACK #-}!DiffTime
} deriving (INSTANCES_USUAL, Show)
derivingUnbox "UTCView" [t| UTCView -> (Day, DiffTime) |]
[| \ UTCTime {..} -> (utctDay, utctDayTime) |]
[| \ (utctDay, utctDayTime) -> UTCTime {..} |]
instance NFData UTCView
_utctDay :: Lens' UTCTime Day
_utctDay :: Overloaded (->) f UTCTime UTCTime Day Day
_utctDay = Overloaded (->) f UTCTime UTCTime UTCView UTCView
Iso' UTCTime UTCView
utcTime Overloaded (->) f UTCTime UTCTime UTCView UTCView
-> ((Day -> f Day) -> UTCView -> f UTCView)
-> Overloaded (->) f UTCTime UTCTime Day Day
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UTCView -> Day)
-> (UTCView -> Day -> UTCView) -> Lens UTCView UTCView Day Day
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens UTCView -> Day
utctDay (\ (UTCTime _ t :: DiffTime
t) d :: Day
d -> Day -> DiffTime -> UTCView
UTCTime Day
d DiffTime
t)
_utctDayTime :: Lens' UTCTime DiffTime
_utctDayTime :: Overloaded (->) f UTCTime UTCTime DiffTime DiffTime
_utctDayTime = Overloaded (->) f UTCTime UTCTime UTCView UTCView
Iso' UTCTime UTCView
utcTime Overloaded (->) f UTCTime UTCTime UTCView UTCView
-> ((DiffTime -> f DiffTime) -> UTCView -> f UTCView)
-> Overloaded (->) f UTCTime UTCTime DiffTime DiffTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UTCView -> DiffTime)
-> (UTCView -> DiffTime -> UTCView)
-> Lens UTCView UTCView DiffTime DiffTime
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens UTCView -> DiffTime
utctDayTime (\ (UTCTime d :: Day
d _) t :: DiffTime
t -> Day -> DiffTime -> UTCView
UTCTime Day
d DiffTime
t)
instance AffineSpace UTCTime where
type Diff UTCTime = NominalDiffTime
{-# INLINE (.-.) #-}
.-. :: UTCTime -> UTCTime -> Diff UTCTime
(.-.) = \ (UTCRep a :: NominalDiffTime
a) (UTCRep b :: NominalDiffTime
b) -> NominalDiffTime
a NominalDiffTime -> NominalDiffTime -> NominalDiffTime
forall v. AdditiveGroup v => v -> v -> v
^-^ NominalDiffTime
b
{-# INLINE (.+^) #-}
.+^ :: UTCTime -> Diff UTCTime -> UTCTime
(.+^) = \ (UTCRep a :: NominalDiffTime
a) d :: Diff UTCTime
d -> NominalDiffTime -> UTCTime
UTCRep (NominalDiffTime
a NominalDiffTime -> NominalDiffTime -> NominalDiffTime
forall v. AdditiveGroup v => v -> v -> v
^+^ Diff UTCTime
NominalDiffTime
d)
{-# INLINE utcTime #-}
utcTime :: Iso' UTCTime UTCView
utcTime :: Overloaded p f UTCTime UTCTime UTCView UTCView
utcTime = (UTCTime -> UTCView)
-> (UTCView -> UTCTime) -> Iso' UTCTime UTCView
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso UTCTime -> UTCView
toView UTCView -> UTCTime
fromView where
NominalDiffTime posixDay :: Micro
posixDay@(Micro uPosixDay :: Int64
uPosixDay) = NominalDiffTime
posixDayLength
{-# INLINE toView #-}
toView :: UTCTime -> UTCView
toView :: UTCTime -> UTCView
toView (UTCRep (NominalDiffTime a :: Micro
a)) = Day -> DiffTime -> UTCView
UTCTime
(Int -> Day
ModifiedJulianDay Int
mjd) (Micro -> DiffTime
DiffTime Micro
dt) where
(Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Int
mjd, dt :: Micro
dt) = Micro -> Micro -> (Int64, Micro)
microDivMod Micro
a Micro
posixDay
{-# INLINE fromView #-}
fromView :: UTCView -> UTCTime
fromView :: UTCView -> UTCTime
fromView (UTCTime (ModifiedJulianDay mjd :: Int
mjd) (DiffTime dt :: Micro
dt)) = NominalDiffTime -> UTCTime
UTCRep NominalDiffTime
a where
a :: NominalDiffTime
a = Micro -> NominalDiffTime
NominalDiffTime (Int64 -> Micro
Micro (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
mjd Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
uPosixDay) Micro -> Micro -> Micro
forall v. AdditiveGroup v => v -> v -> v
^+^ Micro
dt)