#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.Micro
import Data.Thyme.Calendar.Internal
import Data.VectorSpace
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
toSeconds :: (TimeDiff t, Fractional n) => t -> n
toSeconds = (* recip 1000000) . fromIntegral . view microseconds
fromSeconds :: (Real n, TimeDiff t) => n -> t
fromSeconds = fromSeconds' . toRational
toSeconds' :: (TimeDiff t) => t -> Rational
toSeconds' = (`decompose'` ())
fromSeconds' :: (TimeDiff t) => Rational -> t
fromSeconds' = (*^ basisValue ())
fromSecondsRealFrac :: (RealFrac n, TimeDiff t) => n -> n -> t
fromSecondsRealFrac _ = review microseconds . round . (*) 1000000
fromSecondsIntegral :: (Integral n, TimeDiff t) => n -> n -> t
fromSecondsIntegral _ = review microseconds . (*) 1000000 . fromIntegral
newtype DiffTime = DiffTime Micro deriving (INSTANCES_MICRO, AdditiveGroup)
#if SHOW_INTERNAL
deriving instance Show DiffTime
deriving instance Read DiffTime
#else
instance Show DiffTime where
showsPrec p (DiffTime a) = showsPrec p a . (:) 's'
instance Read DiffTime where
readPrec = return (const . DiffTime) `ap` readPrec `ap` lift (char 's')
#endif
instance VectorSpace DiffTime where
type Scalar DiffTime = Rational
s *^ DiffTime t = DiffTime (s *^ t)
instance HasBasis DiffTime where
type Basis DiffTime = ()
basisValue () = DiffTime (basisValue ())
decompose (DiffTime a) = decompose a
decompose' (DiffTime a) = decompose' a
instance TimeDiff DiffTime where
microseconds = iso (\ (DiffTime (Micro u)) -> u) (DiffTime . Micro)
newtype NominalDiffTime = NominalDiffTime Micro deriving (INSTANCES_MICRO, AdditiveGroup)
#if SHOW_INTERNAL
deriving instance Show NominalDiffTime
deriving instance Read NominalDiffTime
#else
instance Show NominalDiffTime where
showsPrec p (NominalDiffTime a) rest = showsPrec p a ('s' : rest)
instance Read NominalDiffTime where
readPrec = return (const . NominalDiffTime) `ap` readPrec `ap` lift (char 's')
#endif
instance VectorSpace NominalDiffTime where
type Scalar NominalDiffTime = Rational
s *^ NominalDiffTime t = NominalDiffTime (s *^ t)
instance HasBasis NominalDiffTime where
type Basis NominalDiffTime = ()
basisValue () = NominalDiffTime (basisValue ())
decompose (NominalDiffTime a) = decompose a
decompose' (NominalDiffTime a) = decompose' a
instance TimeDiff NominalDiffTime where
microseconds = iso (\ (NominalDiffTime (Micro u)) -> u) (NominalDiffTime . Micro)
posixDayLength :: NominalDiffTime
posixDayLength = microseconds # 86400000000
newtype UniversalTime = UniversalRep NominalDiffTime deriving (INSTANCES_MICRO)
modJulianDate :: Iso' UniversalTime Rational
modJulianDate = iso
(\ (UniversalRep t) -> toSeconds t / toSeconds posixDayLength)
(UniversalRep . (*^ posixDayLength))
newtype UTCTime = UTCRep NominalDiffTime deriving (INSTANCES_MICRO)
data UTCView = UTCTime
{ utctDay :: !Day
, utctDayTime :: !DiffTime
} deriving (INSTANCES_USUAL, Show)
instance NFData UTCView
_utctDay :: Lens' UTCTime Day
_utctDay = utcTime . lens utctDay (\ (UTCTime _ t) d -> UTCTime d t)
_utctDayTime :: Lens' UTCTime DiffTime
_utctDayTime = utcTime . lens utctDayTime (\ (UTCTime d _) t -> UTCTime d t)
instance AffineSpace UTCTime where
type Diff UTCTime = NominalDiffTime
UTCRep a .-. UTCRep b = a ^-^ b
UTCRep a .+^ d = UTCRep (a ^+^ d)
utcTime :: Iso' UTCTime UTCView
utcTime = iso toView fromView where
NominalDiffTime posixDay@(Micro uPosixDay) = posixDayLength
toView :: UTCTime -> UTCView
toView (UTCRep (NominalDiffTime a)) = UTCTime
(ModifiedJulianDay mjd) (DiffTime dt) where
(fromIntegral -> mjd, dt) = microDivMod a posixDay
fromView :: UTCView -> UTCTime
fromView (UTCTime (ModifiedJulianDay mjd) (DiffTime dt)) = UTCRep a where
a = NominalDiffTime (Micro (fromIntegral mjd * uPosixDay) ^+^ dt)