{-# LANGUAGE CPP #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ViewPatterns #-}
#if HLINT
#include "cabal_macros.h"
#endif
module Data.Thyme.Time.Core
( module Data.Thyme
, module Data.Thyme.Time.Core
) where
import Prelude
import Control.Lens
import Data.AffineSpace
import Data.Fixed
import Data.Ratio
import Data.Thyme
import Data.Thyme.Clock.TAI
import qualified Data.Time.Calendar as T
import qualified Data.Time.Clock as T
import qualified Data.Time.Clock.TAI as T
import qualified Data.Time.LocalTime as T
import Data.Thyme.TrueName
class Thyme time thyme | thyme -> time where
thyme :: Iso' time thyme
instance Thyme T.Day Day where
{-# INLINE thyme #-}
thyme :: Iso' Day Day
thyme = (Day -> Day) -> (Day -> Day) -> Iso' Day Day
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(Int -> Day
ModifiedJulianDay (Int -> Day) -> (Day -> Int) -> Day -> Day
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Integer -> Int) -> (Day -> Integer) -> Day -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Day -> Integer
T.toModifiedJulianDay)
(Integer -> Day
T.ModifiedJulianDay (Integer -> Day) -> (Day -> Integer) -> Day -> Day
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Integer
forall a. Integral a => a -> Integer
toInteger (Int -> Integer) -> (Day -> Int) -> Day -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Day -> Int
toModifiedJulianDay)
instance Thyme T.UniversalTime UniversalTime where
{-# INLINE thyme #-}
thyme :: Iso' UniversalTime UniversalTime
thyme = (UniversalTime -> Rational)
-> (Rational -> UniversalTime)
-> Iso UniversalTime UniversalTime Rational Rational
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso UniversalTime -> Rational
T.getModJulianDate Rational -> UniversalTime
T.ModJulianDate Overloaded p f UniversalTime UniversalTime Rational Rational
-> (p UniversalTime (f UniversalTime) -> p Rational (f Rational))
-> p UniversalTime (f UniversalTime)
-> p UniversalTime (f UniversalTime)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnIso UniversalTime UniversalTime Rational Rational
-> Iso Rational Rational UniversalTime UniversalTime
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso UniversalTime UniversalTime Rational Rational
Iso' UniversalTime Rational
modJulianDate
instance Thyme T.DiffTime DiffTime where
{-# INLINE thyme #-}
thyme :: Iso' DiffTime DiffTime
thyme = Overloaded p f DiffTime DiffTime Pico Pico
dt Overloaded p f DiffTime DiffTime Pico Pico
-> (p DiffTime (f DiffTime) -> p Pico (f Pico))
-> p DiffTime (f DiffTime)
-> p DiffTime (f DiffTime)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Overloaded p f Pico Pico Integer Integer
forall {a} {a}. Overloaded p f (Fixed a) (Fixed a) Integer Integer
fixed Overloaded p f Pico Pico Integer Integer
-> (p DiffTime (f DiffTime) -> p Integer (f Integer))
-> p DiffTime (f DiffTime)
-> p Pico (f Pico)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnIso DiffTime DiffTime Integer Integer
-> Iso Integer Integer DiffTime DiffTime
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso DiffTime DiffTime Integer Integer
forall t. TimeDiff t => Iso' t Integer
Iso' DiffTime Integer
picoseconds where
dt :: Overloaded p f DiffTime DiffTime Pico Pico
dt = (DiffTime -> Pico)
-> (Pico -> DiffTime) -> Iso DiffTime DiffTime Pico Pico
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso (\ DiffTime
[truename| ''T.DiffTime MkDiffTime | ps |] -> Pico
ps )
Pico -> DiffTime
[truename| ''T.DiffTime MkDiffTime |]
#if MIN_VERSION_base(4,7,0)
fixed :: Overloaded p f (Fixed a) (Fixed a) Integer Integer
fixed = (Fixed a -> Integer)
-> (Integer -> Fixed a) -> Iso (Fixed a) (Fixed a) Integer Integer
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso (\ (MkFixed Integer
n) -> Integer
n ) Integer -> Fixed a
forall k (a :: k). Integer -> Fixed a
MkFixed
#else
fixed = iso (\ [truename| ''Fixed MkFixed | n |] -> n )
[truename| ''Fixed MkFixed |]
#endif
instance Thyme T.NominalDiffTime NominalDiffTime where
{-# INLINE thyme #-}
thyme :: Iso' NominalDiffTime NominalDiffTime
thyme = Overloaded p f NominalDiffTime NominalDiffTime Pico Pico
ndt Overloaded p f NominalDiffTime NominalDiffTime Pico Pico
-> (p NominalDiffTime (f NominalDiffTime) -> p Pico (f Pico))
-> p NominalDiffTime (f NominalDiffTime)
-> p NominalDiffTime (f NominalDiffTime)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Overloaded p f Pico Pico Integer Integer
forall {a} {a}. Overloaded p f (Fixed a) (Fixed a) Integer Integer
fixed Overloaded p f Pico Pico Integer Integer
-> (p NominalDiffTime (f NominalDiffTime) -> p Integer (f Integer))
-> p NominalDiffTime (f NominalDiffTime)
-> p Pico (f Pico)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnIso NominalDiffTime NominalDiffTime Integer Integer
-> Iso Integer Integer NominalDiffTime NominalDiffTime
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso NominalDiffTime NominalDiffTime Integer Integer
forall t. TimeDiff t => Iso' t Integer
Iso' NominalDiffTime Integer
picoseconds where
ndt :: Overloaded p f NominalDiffTime NominalDiffTime Pico Pico
ndt = (NominalDiffTime -> Pico)
-> (Pico -> NominalDiffTime)
-> Iso NominalDiffTime NominalDiffTime Pico Pico
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso (\ NominalDiffTime
[truename| ''T.NominalDiffTime MkNominalDiffTime | ps |] -> Pico
ps )
Pico -> NominalDiffTime
[truename| ''T.NominalDiffTime MkNominalDiffTime |]
#if MIN_VERSION_base(4,7,0)
fixed :: Overloaded p f (Fixed a) (Fixed a) Integer Integer
fixed = (Fixed a -> Integer)
-> (Integer -> Fixed a) -> Iso (Fixed a) (Fixed a) Integer Integer
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso (\ (MkFixed Integer
n) -> Integer
n ) Integer -> Fixed a
forall k (a :: k). Integer -> Fixed a
MkFixed
#else
fixed = iso (\ [truename| ''Fixed MkFixed | n |] -> n )
[truename| ''Fixed MkFixed |]
#endif
instance Thyme T.UTCTime UTCView where
{-# INLINE thyme #-}
thyme :: Iso' UTCTime UTCView
thyme = (UTCTime -> UTCView)
-> (UTCView -> UTCTime) -> Iso' UTCTime UTCView
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\ (T.UTCTime Day
d DiffTime
t) -> Day -> DiffTime -> UTCView
UTCView (Day
d Day -> Getting Day Day Day -> Day
forall s a. s -> Getting a s a -> a
^. Getting Day Day Day
forall time thyme. Thyme time thyme => Iso' time thyme
Iso' Day Day
thyme) (DiffTime
t DiffTime -> Getting DiffTime DiffTime DiffTime -> DiffTime
forall s a. s -> Getting a s a -> a
^. Getting DiffTime DiffTime DiffTime
forall time thyme. Thyme time thyme => Iso' time thyme
Iso' DiffTime DiffTime
thyme))
(\ (UTCView Day
d DiffTime
t) -> Day -> DiffTime -> UTCTime
T.UTCTime (Overloaded Reviewed Identity Day Day Day Day
forall time thyme. Thyme time thyme => Iso' time thyme
Iso' Day Day
thyme Overloaded Reviewed Identity Day Day Day Day -> Day -> Day
forall s t a b. AReview s t a b -> b -> t
# Day
d) (Overloaded Reviewed Identity DiffTime DiffTime DiffTime DiffTime
forall time thyme. Thyme time thyme => Iso' time thyme
Iso' DiffTime DiffTime
thyme Overloaded Reviewed Identity DiffTime DiffTime DiffTime DiffTime
-> DiffTime -> DiffTime
forall s t a b. AReview s t a b -> b -> t
# DiffTime
t))
instance Thyme T.UTCTime UTCTime where
{-# INLINE thyme #-}
thyme :: Iso' UTCTime UTCTime
thyme = Overloaded p f UTCTime UTCTime UTCView UTCView
forall time thyme. Thyme time thyme => Iso' time thyme
Iso' UTCTime UTCView
thyme Overloaded p f UTCTime UTCTime UTCView UTCView
-> (p UTCTime (f UTCTime) -> p UTCView (f UTCView))
-> p UTCTime (f UTCTime)
-> p UTCTime (f UTCTime)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnIso UTCTime UTCTime UTCView UTCView
-> Iso UTCView UTCView UTCTime UTCTime
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso UTCTime UTCTime UTCView UTCView
Iso' UTCTime UTCView
utcTime
instance Thyme T.AbsoluteTime AbsoluteTime where
{-# INLINE thyme #-}
thyme :: Iso' AbsoluteTime AbsoluteTime
thyme = (AbsoluteTime -> DiffTime)
-> (DiffTime -> AbsoluteTime)
-> Iso AbsoluteTime AbsoluteTime DiffTime DiffTime
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso (AbsoluteTime -> AbsoluteTime -> DiffTime
`T.diffAbsoluteTime` AbsoluteTime
T.taiEpoch)
(DiffTime -> AbsoluteTime -> AbsoluteTime
`T.addAbsoluteTime` AbsoluteTime
T.taiEpoch)
Overloaded p f AbsoluteTime AbsoluteTime DiffTime DiffTime
-> (p AbsoluteTime (f AbsoluteTime) -> p DiffTime (f DiffTime))
-> p AbsoluteTime (f AbsoluteTime)
-> p AbsoluteTime (f AbsoluteTime)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Overloaded p f DiffTime DiffTime DiffTime DiffTime
forall time thyme. Thyme time thyme => Iso' time thyme
Iso' DiffTime DiffTime
thyme Overloaded p f DiffTime DiffTime DiffTime DiffTime
-> (p AbsoluteTime (f AbsoluteTime) -> p DiffTime (f DiffTime))
-> p AbsoluteTime (f AbsoluteTime)
-> p DiffTime (f DiffTime)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DiffTime -> AbsoluteTime)
-> (AbsoluteTime -> DiffTime)
-> Iso DiffTime DiffTime AbsoluteTime AbsoluteTime
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso (AbsoluteTime
taiEpoch AbsoluteTime -> Diff AbsoluteTime -> AbsoluteTime
forall p. AffineSpace p => p -> Diff p -> p
.+^) (AbsoluteTime -> AbsoluteTime -> Diff AbsoluteTime
forall p. AffineSpace p => p -> p -> Diff p
.-. AbsoluteTime
taiEpoch)
instance Thyme T.TimeZone TimeZone where
{-# INLINE thyme #-}
thyme :: Iso' TimeZone TimeZone
thyme = (TimeZone -> TimeZone)
-> (TimeZone -> TimeZone) -> Iso' TimeZone TimeZone
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso (\ T.TimeZone {Bool
Int
String
timeZoneMinutes :: Int
timeZoneSummerOnly :: Bool
timeZoneName :: String
timeZoneMinutes :: TimeZone -> Int
timeZoneSummerOnly :: TimeZone -> Bool
timeZoneName :: TimeZone -> String
..} -> TimeZone {Bool
Int
String
timeZoneMinutes :: Int
timeZoneSummerOnly :: Bool
timeZoneName :: String
timeZoneMinutes :: Int
timeZoneSummerOnly :: Bool
timeZoneName :: String
..})
(\ TimeZone {Bool
Int
String
timeZoneMinutes :: TimeZone -> Int
timeZoneSummerOnly :: TimeZone -> Bool
timeZoneName :: TimeZone -> String
timeZoneMinutes :: Int
timeZoneSummerOnly :: Bool
timeZoneName :: String
..} -> T.TimeZone {Bool
Int
String
timeZoneMinutes :: Int
timeZoneSummerOnly :: Bool
timeZoneName :: String
timeZoneMinutes :: Int
timeZoneSummerOnly :: Bool
timeZoneName :: String
..})
instance Thyme T.TimeOfDay TimeOfDay where
{-# INLINE thyme #-}
thyme :: Iso' TimeOfDay TimeOfDay
thyme = (TimeOfDay -> TimeOfDay)
-> (TimeOfDay -> TimeOfDay) -> Iso' TimeOfDay TimeOfDay
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso ( \ (T.TimeOfDay Int
h Int
m Pico
s) -> Int -> Int -> DiffTime -> TimeOfDay
TimeOfDay Int
h Int
m (DiffTime -> TimeOfDay) -> DiffTime -> TimeOfDay
forall a b. (a -> b) -> a -> b
$
Overloaded Reviewed Identity DiffTime DiffTime Int64 Int64
forall t. TimeDiff t => Iso' t Int64
Iso' DiffTime Int64
microseconds Overloaded Reviewed Identity DiffTime DiffTime Int64 Int64
-> Int64 -> DiffTime
forall s t a b. AReview s t a b -> b -> t
# Pico -> Int64
forall b. Integral b => Pico -> b
forall a b. (RealFrac a, Integral b) => a -> b
round (Pico
s Pico -> Pico -> Pico
forall a. Num a => a -> a -> a
* Pico
1000000) )
( \ (TimeOfDay Int
h Int
m DiffTime
s) -> Int -> Int -> Pico -> TimeOfDay
T.TimeOfDay Int
h Int
m (Pico -> TimeOfDay) -> (Rational -> Pico) -> Rational -> TimeOfDay
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rational -> Pico
forall a. Fractional a => Rational -> a
fromRational (Rational -> TimeOfDay) -> Rational -> TimeOfDay
forall a b. (a -> b) -> a -> b
$
Int64 -> Integer
forall a. Integral a => a -> Integer
toInteger (DiffTime
s DiffTime -> Getting Int64 DiffTime Int64 -> Int64
forall s a. s -> Getting a s a -> a
^. Getting Int64 DiffTime Int64
forall t. TimeDiff t => Iso' t Int64
Iso' DiffTime Int64
microseconds) Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
1000000 )
instance Thyme T.LocalTime LocalTime where
{-# INLINE thyme #-}
thyme :: Iso' LocalTime LocalTime
thyme = (LocalTime -> LocalTime)
-> (LocalTime -> LocalTime) -> Iso' LocalTime LocalTime
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\ (T.LocalTime Day
d TimeOfDay
t) -> Day -> TimeOfDay -> LocalTime
LocalTime (Day
d Day -> Getting Day Day Day -> Day
forall s a. s -> Getting a s a -> a
^. Getting Day Day Day
forall time thyme. Thyme time thyme => Iso' time thyme
Iso' Day Day
thyme) (TimeOfDay
t TimeOfDay -> Getting TimeOfDay TimeOfDay TimeOfDay -> TimeOfDay
forall s a. s -> Getting a s a -> a
^. Getting TimeOfDay TimeOfDay TimeOfDay
forall time thyme. Thyme time thyme => Iso' time thyme
Iso' TimeOfDay TimeOfDay
thyme))
(\ (LocalTime Day
d TimeOfDay
t) -> Day -> TimeOfDay -> LocalTime
T.LocalTime (Overloaded Reviewed Identity Day Day Day Day
forall time thyme. Thyme time thyme => Iso' time thyme
Iso' Day Day
thyme Overloaded Reviewed Identity Day Day Day Day -> Day -> Day
forall s t a b. AReview s t a b -> b -> t
# Day
d) (Overloaded
Reviewed Identity TimeOfDay TimeOfDay TimeOfDay TimeOfDay
forall time thyme. Thyme time thyme => Iso' time thyme
Iso' TimeOfDay TimeOfDay
thyme Overloaded
Reviewed Identity TimeOfDay TimeOfDay TimeOfDay TimeOfDay
-> TimeOfDay -> TimeOfDay
forall s t a b. AReview s t a b -> b -> t
# TimeOfDay
t))
instance Thyme T.ZonedTime ZonedTime where
{-# INLINE thyme #-}
thyme :: Iso' ZonedTime ZonedTime
thyme = (ZonedTime -> ZonedTime)
-> (ZonedTime -> ZonedTime) -> Iso' ZonedTime ZonedTime
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\ (T.ZonedTime LocalTime
t TimeZone
z) -> LocalTime -> TimeZone -> ZonedTime
ZonedTime (LocalTime
t LocalTime -> Getting LocalTime LocalTime LocalTime -> LocalTime
forall s a. s -> Getting a s a -> a
^. Getting LocalTime LocalTime LocalTime
forall time thyme. Thyme time thyme => Iso' time thyme
Iso' LocalTime LocalTime
thyme) (TimeZone
z TimeZone -> Getting TimeZone TimeZone TimeZone -> TimeZone
forall s a. s -> Getting a s a -> a
^. Getting TimeZone TimeZone TimeZone
forall time thyme. Thyme time thyme => Iso' time thyme
Iso' TimeZone TimeZone
thyme))
(\ (ZonedTime LocalTime
t TimeZone
z) -> LocalTime -> TimeZone -> ZonedTime
T.ZonedTime (Overloaded
Reviewed Identity LocalTime LocalTime LocalTime LocalTime
forall time thyme. Thyme time thyme => Iso' time thyme
Iso' LocalTime LocalTime
thyme Overloaded
Reviewed Identity LocalTime LocalTime LocalTime LocalTime
-> LocalTime -> LocalTime
forall s t a b. AReview s t a b -> b -> t
# LocalTime
t) (Overloaded Reviewed Identity TimeZone TimeZone TimeZone TimeZone
forall time thyme. Thyme time thyme => Iso' time thyme
Iso' TimeZone TimeZone
thyme Overloaded Reviewed Identity TimeZone TimeZone TimeZone TimeZone
-> TimeZone -> TimeZone
forall s t a b. AReview s t a b -> b -> t
# TimeZone
z))
{-# INLINE toThyme #-}
toThyme :: (Thyme time thyme) => time -> thyme
toThyme :: forall time thyme. Thyme time thyme => time -> thyme
toThyme = Getting thyme time thyme -> time -> thyme
forall a s. Getting a s a -> s -> a
view Getting thyme time thyme
forall time thyme. Thyme time thyme => Iso' time thyme
Iso' time thyme
thyme
{-# INLINE fromThyme #-}
fromThyme :: (Thyme time thyme) => thyme -> time
fromThyme :: forall time thyme. Thyme time thyme => thyme -> time
fromThyme = AReview time time thyme thyme -> thyme -> time
forall s t a b. AReview s t a b -> b -> t
review AReview time time thyme thyme
forall time thyme. Thyme time thyme => Iso' time thyme
Iso' time thyme
thyme