{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
#include "thyme.h"
#if HLINT
#include "cabal_macros.h"
#endif
module Data.Thyme.LocalTime
( Hour, Minute
, module Data.Thyme.LocalTime
) where
import Prelude hiding ((.))
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative
#endif
import Control.Arrow
import Control.Category hiding (id)
import Control.DeepSeq
import Control.Lens
import Control.Monad
import Data.AffineSpace
import Data.Bits
import Data.Data
import Data.Hashable
import Data.Int
import Data.Thyme.Internal.Micro
import Data.Thyme.Calendar
import Data.Thyme.Calendar.Internal
import Data.Thyme.Clock
import Data.Thyme.Clock.Internal
import Data.Thyme.Format.Internal
import qualified Data.Time as T
#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 hiding ((.&.))
type Hours = Int
type Minutes = Int
data TimeZone = TimeZone
{ TimeZone -> Int
timeZoneMinutes :: {-# UNPACK #-}!Minutes
, TimeZone -> Bool
timeZoneSummerOnly :: !Bool
, TimeZone -> String
timeZoneName :: String
} deriving (INSTANCES_USUAL)
LENS(TimeZone,timeZoneMinutes,Minutes)
LENS(TimeZone,timeZoneSummerOnly,Bool)
LENS(TimeZone,timeZoneName,String)
instance Hashable TimeZone
instance NFData TimeZone
#if SHOW_INTERNAL
deriving instance Show TimeZone
#else
instance Show TimeZone where
show :: TimeZone -> String
show tz :: TimeZone
tz@TimeZone {Bool
Int
String
timeZoneMinutes :: TimeZone -> Int
timeZoneSummerOnly :: TimeZone -> Bool
timeZoneName :: TimeZone -> String
timeZoneMinutes :: Int
timeZoneSummerOnly :: Bool
timeZoneName :: String
..} = if String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
timeZoneName
then TimeZone -> String
timeZoneOffsetString TimeZone
tz else String
timeZoneName
#endif
instance Bounded TimeZone where
minBound :: TimeZone
minBound = Int -> Bool -> String -> TimeZone
TimeZone (-Int
12 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
60) Bool
forall a. Bounded a => a
minBound String
"AAAA"
maxBound :: TimeZone
maxBound = Int -> Bool -> String -> TimeZone
TimeZone (Int
13 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
60) Bool
forall a. Bounded a => a
maxBound String
"ZZZZ"
instance Random TimeZone where
randomR :: forall g. RandomGen g => (TimeZone, TimeZone) -> g -> (TimeZone, g)
randomR (TimeZone
l, TimeZone
u) g
g0 = (Int -> Bool -> String -> TimeZone
TimeZone Int
minutes Bool
summer String
name, g
g3) where
(Int
minutes, g
g1) = (Int, Int) -> g -> (Int, g)
forall g. RandomGen g => (Int, Int) -> g -> (Int, g)
forall a g. (Random a, RandomGen g) => (a, a) -> g -> (a, g)
randomR (TimeZone -> Int
timeZoneMinutes TimeZone
l, TimeZone -> Int
timeZoneMinutes TimeZone
u) g
g0
(Bool
summer, g
g2) = (Bool, Bool) -> g -> (Bool, g)
forall g. RandomGen g => (Bool, Bool) -> g -> (Bool, g)
forall a g. (Random a, RandomGen g) => (a, a) -> g -> (a, g)
randomR (TimeZone -> Bool
timeZoneSummerOnly TimeZone
l, TimeZone -> Bool
timeZoneSummerOnly TimeZone
u) g
g1
(String
name, g
g3) = ((Char, Char) -> (String, g) -> (String, g))
-> (String, g) -> [(Char, Char)] -> (String, g)
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (Char, Char) -> (String, g) -> (String, g)
forall {a} {g}.
(Random a, RandomGen g) =>
(a, a) -> ([a], g) -> ([a], g)
randChar ([], g
g2) ([(Char, Char)] -> (String, g))
-> ([(Char, Char)] -> [(Char, Char)])
-> [(Char, Char)]
-> (String, g)
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> [(Char, Char)] -> [(Char, Char)]
forall a. Int -> [a] -> [a]
take Int
4 ([(Char, Char)] -> (String, g)) -> [(Char, Char)] -> (String, g)
forall a b. (a -> b) -> a -> b
$ String -> String -> [(Char, Char)]
forall a b. [a] -> [b] -> [(a, b)]
zip
(TimeZone -> String
timeZoneName TimeZone
l String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"AAAA") (TimeZone -> String
timeZoneName TimeZone
u String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"ZZZZ")
randChar :: (a, a) -> ([a], g) -> ([a], g)
randChar (a, a)
nR ([a]
ns, g
g) = (a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
ns) (a -> [a]) -> (a, g) -> ([a], g)
forall b c d. (b -> c) -> (b, d) -> (c, d)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
`first` (a, a) -> g -> (a, g)
forall g. RandomGen g => (a, a) -> g -> (a, g)
forall a g. (Random a, RandomGen g) => (a, a) -> g -> (a, g)
randomR (a, a)
nR g
g
random :: forall g. RandomGen g => g -> (TimeZone, g)
random = (TimeZone, TimeZone) -> g -> (TimeZone, g)
forall g. RandomGen g => (TimeZone, TimeZone) -> g -> (TimeZone, g)
forall a g. (Random a, RandomGen g) => (a, a) -> g -> (a, g)
randomR (TimeZone
forall a. Bounded a => a
minBound, TimeZone
forall a. Bounded a => a
maxBound)
instance Arbitrary TimeZone where
arbitrary :: Gen TimeZone
arbitrary = (TimeZone, TimeZone) -> Gen TimeZone
forall a. Random a => (a, a) -> Gen a
choose (TimeZone
forall a. Bounded a => a
minBound, TimeZone
forall a. Bounded a => a
maxBound)
shrink :: TimeZone -> [TimeZone]
shrink tz :: TimeZone
tz@TimeZone {Bool
Int
String
timeZoneMinutes :: TimeZone -> Int
timeZoneSummerOnly :: TimeZone -> Bool
timeZoneName :: TimeZone -> String
timeZoneMinutes :: Int
timeZoneSummerOnly :: Bool
timeZoneName :: String
..}
= [ TimeZone
tz {timeZoneSummerOnly = s} | Bool
s <- Bool -> [Bool]
forall a. Arbitrary a => a -> [a]
shrink Bool
timeZoneSummerOnly ]
[TimeZone] -> [TimeZone] -> [TimeZone]
forall a. [a] -> [a] -> [a]
++ [ TimeZone
tz {timeZoneMinutes = m} | Int
m <- Int -> [Int]
forall a. Arbitrary a => a -> [a]
shrink Int
timeZoneMinutes ]
[TimeZone] -> [TimeZone] -> [TimeZone]
forall a. [a] -> [a] -> [a]
++ [ TimeZone
tz {timeZoneName = n} | String
n <- String -> [String]
forall a. Arbitrary a => a -> [a]
shrink String
timeZoneName ]
instance CoArbitrary TimeZone where
coarbitrary :: forall b. TimeZone -> Gen b -> Gen b
coarbitrary (TimeZone Int
m Bool
s String
n)
= Int -> Gen b -> Gen b
forall b. Int -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary Int
m (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Bool -> Gen b -> Gen b
forall b. Bool -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary Bool
s (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> Gen b -> Gen b
forall b. String -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary String
n
{-# INLINEABLE timeZoneOffsetString #-}
timeZoneOffsetString :: TimeZone -> String
timeZoneOffsetString :: TimeZone -> String
timeZoneOffsetString TimeZone {Bool
Int
String
timeZoneMinutes :: TimeZone -> Int
timeZoneSummerOnly :: TimeZone -> Bool
timeZoneName :: TimeZone -> String
timeZoneMinutes :: Int
timeZoneSummerOnly :: Bool
timeZoneName :: String
..} = Char
sign Char -> ShowS
forall a. a -> [a] -> [a]
: (Int -> ShowS
shows02 Int
h ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> ShowS
shows02 Int
m) String
"" where
(Int
h, Int
m) = Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
divMod Int
offset Int
60
(Char
sign, Int
offset) = if Int
timeZoneMinutes Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0
then (Char
'-', Int -> Int
forall a. Num a => a -> a
negate Int
timeZoneMinutes) else (Char
'+', Int
timeZoneMinutes)
{-# INLINEABLE timeZoneOffsetStringColon #-}
timeZoneOffsetStringColon :: TimeZone -> String
timeZoneOffsetStringColon :: TimeZone -> String
timeZoneOffsetStringColon TimeZone {Bool
Int
String
timeZoneMinutes :: TimeZone -> Int
timeZoneSummerOnly :: TimeZone -> Bool
timeZoneName :: TimeZone -> String
timeZoneMinutes :: Int
timeZoneSummerOnly :: Bool
timeZoneName :: String
..} =
Char
sign Char -> ShowS
forall a. a -> [a] -> [a]
: (Int -> ShowS
shows02 Int
h ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (:) Char
':' ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> ShowS
shows02 Int
m) String
"" where
(Int
h, Int
m) = Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
divMod Int
offset Int
60
(Char
sign, Int
offset) = if Int
timeZoneMinutes Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0
then (Char
'-', Int -> Int
forall a. Num a => a -> a
negate Int
timeZoneMinutes) else (Char
'+', Int
timeZoneMinutes)
minutesToTimeZone :: Minutes -> TimeZone
minutesToTimeZone :: Int -> TimeZone
minutesToTimeZone Int
m = Int -> Bool -> String -> TimeZone
TimeZone Int
m Bool
False String
""
hoursToTimeZone :: Hours -> TimeZone
hoursToTimeZone :: Int -> TimeZone
hoursToTimeZone Int
i = Int -> TimeZone
minutesToTimeZone (Int
60 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
i)
utc :: TimeZone
utc :: TimeZone
utc = Int -> Bool -> String -> TimeZone
TimeZone Int
0 Bool
False String
"UTC"
{-# INLINEABLE getTimeZone #-}
getTimeZone :: UTCTime -> IO TimeZone
getTimeZone :: UTCTime -> IO TimeZone
getTimeZone UTCTime
t = TimeZone -> TimeZone
thyme (TimeZone -> TimeZone) -> IO TimeZone -> IO TimeZone
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` UTCTime -> IO TimeZone
T.getTimeZone (Day -> DiffTime -> UTCTime
T.UTCTime Day
day (DiffTime -> UTCTime) -> DiffTime -> UTCTime
forall a b. (a -> b) -> a -> b
$ DiffTime -> DiffTime
forall t n. (TimeDiff t, Fractional n) => t -> n
toSeconds DiffTime
dt) where
day :: Day
day = Integer -> Day
T.ModifiedJulianDay (Int -> Integer
forall a. Integral a => a -> Integer
toInteger Int
mjd)
UTCView (ModifiedJulianDay Int
mjd) DiffTime
dt = UTCTime
t UTCTime -> Getting UTCView UTCTime UTCView -> UTCView
forall s a. s -> Getting a s a -> a
^. Getting UTCView UTCTime UTCView
Iso' UTCTime UTCView
utcTime
thyme :: TimeZone -> TimeZone
thyme 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
..}
{-# INLINE getCurrentTimeZone #-}
getCurrentTimeZone :: IO TimeZone
getCurrentTimeZone :: IO TimeZone
getCurrentTimeZone = IO UTCTime
getCurrentTime IO UTCTime -> (UTCTime -> IO TimeZone) -> IO TimeZone
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= UTCTime -> IO TimeZone
getTimeZone
data TimeOfDay = TimeOfDay
{ TimeOfDay -> Int
todHour :: {-# UNPACK #-}!Hour
, TimeOfDay -> Int
todMin :: {-# UNPACK #-}!Minute
, TimeOfDay -> DiffTime
todSec :: {-# UNPACK #-}!DiffTime
} deriving (INSTANCES_USUAL)
LENS(TimeOfDay,todHour,Hour)
LENS(TimeOfDay,todMin,Minute)
LENS(TimeOfDay,todSec,DiffTime)
derivingUnbox "TimeOfDay" [t| TimeOfDay -> Int64 |]
[| \ TimeOfDay {..} -> fromIntegral (todHour .|. shiftL todMin 8)
.|. shiftL (todSec ^. microseconds) 16 |]
[| \ n -> TimeOfDay (fromIntegral $ n .&. 0xff)
(fromIntegral $ shiftR n 8 .&. 0xff) (microseconds # shiftR n 16) |]
instance Hashable TimeOfDay
instance NFData TimeOfDay
#if SHOW_INTERNAL
deriving instance Show TimeOfDay
#else
instance Show TimeOfDay where
showsPrec :: Int -> TimeOfDay -> ShowS
showsPrec Int
_ (TimeOfDay Int
h Int
m (DiffTime Micro
s))
= Int -> ShowS
shows02 Int
h ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (:) Char
':' ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> ShowS
shows02 Int
m ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (:) Char
':'
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> ShowS
shows02 (Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
si) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ShowS
frac where
(Int64
si, Micro Int64
su) = Micro -> Micro -> (Int64, Micro)
microQuotRem Micro
s (Int64 -> Micro
Micro Int64
1000000)
frac :: ShowS
frac = if Int64
su Int64 -> Int64 -> Bool
forall a. Eq a => a -> a -> Bool
== Int64
0 then ShowS
forall a. a -> a
id else (:) Char
'.' ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int64 -> ShowS
fills06 Int64
su ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int64 -> ShowS
drops0 Int64
su
#endif
instance Bounded TimeOfDay where
minBound :: TimeOfDay
minBound = Int -> Int -> DiffTime -> TimeOfDay
TimeOfDay Int
0 Int
0 DiffTime
forall v. AdditiveGroup v => v
zeroV
maxBound :: TimeOfDay
maxBound = Int -> Int -> DiffTime -> TimeOfDay
TimeOfDay Int
23 Int
59 (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
# Int64
60999999)
instance Random TimeOfDay where
randomR :: forall g.
RandomGen g =>
(TimeOfDay, TimeOfDay) -> g -> (TimeOfDay, g)
randomR = Iso' DiffTime TimeOfDay
-> (TimeOfDay, TimeOfDay) -> g -> (TimeOfDay, g)
forall s g a.
(Random s, RandomGen g) =>
Iso' s a -> (a, a) -> g -> (a, g)
randomIsoR Overloaded p f DiffTime DiffTime TimeOfDay TimeOfDay
Iso' DiffTime TimeOfDay
timeOfDay
random :: forall g. RandomGen g => g -> (TimeOfDay, g)
random = (DiffTime -> TimeOfDay) -> (DiffTime, g) -> (TimeOfDay, g)
forall b c d. (b -> c) -> (b, d) -> (c, d)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first (DiffTime -> Getting TimeOfDay DiffTime TimeOfDay -> TimeOfDay
forall s a. s -> Getting a s a -> a
^. Getting TimeOfDay DiffTime TimeOfDay
Iso' DiffTime TimeOfDay
timeOfDay) ((DiffTime, g) -> (TimeOfDay, g))
-> (g -> (DiffTime, g)) -> g -> (TimeOfDay, g)
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. g -> (DiffTime, g)
forall g. RandomGen g => g -> (DiffTime, g)
forall a g. (Random a, RandomGen g) => g -> (a, g)
random
instance Arbitrary TimeOfDay where
arbitrary :: Gen TimeOfDay
arbitrary = do
Int
h <- (Int, Int) -> Gen Int
forall a. Random a => (a, a) -> Gen a
choose (Int
0, Int
23)
Int
m <- (Int, Int) -> Gen Int
forall a. Random a => (a, a) -> Gen a
choose (Int
0, Int
59)
let DiffTime Micro
ml = Int -> Int -> DiffTime
minuteLength Int
h Int
m
Int -> Int -> DiffTime -> TimeOfDay
TimeOfDay Int
h Int
m (DiffTime -> TimeOfDay)
-> (Micro -> DiffTime) -> Micro -> TimeOfDay
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Micro -> DiffTime
DiffTime (Micro -> TimeOfDay) -> Gen Micro -> Gen TimeOfDay
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Micro, Micro) -> Gen Micro
forall a. Random a => (a, a) -> Gen a
choose (Micro
forall v. AdditiveGroup v => v
zeroV, Micro -> Micro
forall a. Enum a => a -> a
pred Micro
ml)
shrink :: TimeOfDay -> [TimeOfDay]
shrink TimeOfDay
tod = Getting TimeOfDay DiffTime TimeOfDay -> DiffTime -> TimeOfDay
forall a s. Getting a s a -> s -> a
view Getting TimeOfDay DiffTime TimeOfDay
Iso' DiffTime TimeOfDay
timeOfDay (DiffTime -> TimeOfDay)
-> (DiffTime -> DiffTime) -> DiffTime -> TimeOfDay
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. DiffTime -> DiffTime -> DiffTime
forall v. AdditiveGroup v => v -> v -> v
(^+^) DiffTime
noon
(DiffTime -> TimeOfDay) -> [DiffTime] -> [TimeOfDay]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DiffTime -> [DiffTime]
forall a. Arbitrary a => a -> [a]
shrink (Overloaded Reviewed Identity DiffTime DiffTime TimeOfDay TimeOfDay
Iso' DiffTime TimeOfDay
timeOfDay Overloaded Reviewed Identity DiffTime DiffTime TimeOfDay TimeOfDay
-> TimeOfDay -> DiffTime
forall s t a b. AReview s t a b -> b -> t
# TimeOfDay
tod DiffTime -> DiffTime -> DiffTime
forall v. AdditiveGroup v => v -> v -> v
^-^ DiffTime
noon) where
noon :: DiffTime
noon = Overloaded Reviewed Identity DiffTime DiffTime TimeOfDay TimeOfDay
Iso' DiffTime TimeOfDay
timeOfDay Overloaded Reviewed Identity DiffTime DiffTime TimeOfDay TimeOfDay
-> TimeOfDay -> DiffTime
forall s t a b. AReview s t a b -> b -> t
# TimeOfDay
midday
instance CoArbitrary TimeOfDay where
coarbitrary :: forall b. TimeOfDay -> Gen b -> Gen b
coarbitrary (TimeOfDay Int
h Int
m DiffTime
s)
= Int -> Gen b -> Gen b
forall b. Int -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary Int
h (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> Gen b -> Gen b
forall b. Int -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary Int
m (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. DiffTime -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. DiffTime -> Gen b -> Gen b
coarbitrary DiffTime
s
{-# INLINE minuteLength #-}
minuteLength :: Hour -> Minute -> DiffTime
minuteLength :: Int -> Int -> DiffTime
minuteLength Int
23 Int
59 = Rational -> DiffTime
forall t. TimeDiff t => Rational -> t
fromSeconds' Rational
61
minuteLength Int
_ Int
_ = Rational -> DiffTime
forall t. TimeDiff t => Rational -> t
fromSeconds' Rational
60
midnight :: TimeOfDay
midnight :: TimeOfDay
midnight = Int -> Int -> DiffTime -> TimeOfDay
TimeOfDay Int
0 Int
0 DiffTime
forall v. AdditiveGroup v => v
zeroV
midday :: TimeOfDay
midday :: TimeOfDay
midday = Int -> Int -> DiffTime -> TimeOfDay
TimeOfDay Int
12 Int
0 DiffTime
forall v. AdditiveGroup v => v
zeroV
{-# INLINE makeTimeOfDayValid #-}
makeTimeOfDayValid :: Hour -> Minute -> DiffTime -> Maybe TimeOfDay
makeTimeOfDayValid :: Int -> Int -> DiffTime -> Maybe TimeOfDay
makeTimeOfDayValid Int
h Int
m DiffTime
s = Int -> Int -> DiffTime -> TimeOfDay
TimeOfDay Int
h Int
m DiffTime
s
TimeOfDay -> Maybe () -> Maybe TimeOfDay
forall a b. a -> Maybe b -> Maybe a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Int
0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
h Bool -> Bool -> Bool
&& Int
h Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
23 Bool -> Bool -> Bool
&& Int
0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
m Bool -> Bool -> Bool
&& Int
m Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
59)
Maybe TimeOfDay -> Maybe () -> Maybe TimeOfDay
forall a b. Maybe a -> Maybe b -> Maybe a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (DiffTime
forall v. AdditiveGroup v => v
zeroV DiffTime -> DiffTime -> Bool
forall a. Ord a => a -> a -> Bool
<= DiffTime
s Bool -> Bool -> Bool
&& DiffTime
s DiffTime -> DiffTime -> Bool
forall a. Ord a => a -> a -> Bool
< Int -> Int -> DiffTime
minuteLength Int
h Int
m)
{-# INLINE timeOfDay #-}
timeOfDay :: Iso' DiffTime TimeOfDay
timeOfDay :: Iso' DiffTime TimeOfDay
timeOfDay = (DiffTime -> TimeOfDay)
-> (TimeOfDay -> DiffTime) -> Iso' DiffTime TimeOfDay
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso DiffTime -> TimeOfDay
fromDiff TimeOfDay -> DiffTime
toDiff where
{-# INLINEABLE fromDiff #-}
fromDiff :: DiffTime -> TimeOfDay
fromDiff :: DiffTime -> TimeOfDay
fromDiff (DiffTime Micro
t) = Int -> Int -> DiffTime -> 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) (Micro -> DiffTime
DiffTime Micro
s) where
(Int64
h, Micro
ms) = Micro -> Micro -> (Int64, Micro)
microQuotRem Micro
t (Int64 -> Micro
Micro Int64
3600000000)
(Int64
m, Micro
s) = Micro -> Micro -> (Int64, Micro)
microQuotRem Micro
ms (Int64 -> Micro
Micro Int64
60000000)
{-# INLINEABLE toDiff #-}
toDiff :: TimeOfDay -> DiffTime
toDiff :: TimeOfDay -> DiffTime
toDiff (TimeOfDay Int
h Int
m DiffTime
s) = DiffTime
s
DiffTime -> DiffTime -> DiffTime
forall v. AdditiveGroup v => v -> v -> v
^+^ Int -> Rational
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
m Scalar DiffTime -> DiffTime -> DiffTime
forall v. VectorSpace v => Scalar v -> v -> v
*^ Micro -> DiffTime
DiffTime (Int64 -> Micro
Micro Int64
60000000)
DiffTime -> DiffTime -> DiffTime
forall v. AdditiveGroup v => v -> v -> v
^+^ Int -> Rational
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
h Scalar DiffTime -> DiffTime -> DiffTime
forall v. VectorSpace v => Scalar v -> v -> v
*^ Micro -> DiffTime
DiffTime (Int64 -> Micro
Micro Int64
3600000000)
{-# INLINE addMinutes #-}
addMinutes :: Minutes -> TimeOfDay -> (Days, TimeOfDay)
addMinutes :: Int -> TimeOfDay -> (Int, TimeOfDay)
addMinutes Int
dm (TimeOfDay Int
h Int
m DiffTime
s) = (Int
dd, Int -> Int -> DiffTime -> TimeOfDay
TimeOfDay Int
h' Int
m' DiffTime
s) where
(Int
dd, Int
h') = Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
divMod (Int
h Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
dh) Int
24
(Int
dh, Int
m') = Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
divMod (Int
m Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
dm) Int
60
{-# INLINE dayFraction #-}
dayFraction :: Iso' TimeOfDay Rational
dayFraction :: Iso' TimeOfDay Rational
dayFraction = AnIso DiffTime DiffTime TimeOfDay TimeOfDay
-> Iso TimeOfDay TimeOfDay DiffTime DiffTime
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso DiffTime DiffTime TimeOfDay TimeOfDay
Iso' DiffTime TimeOfDay
timeOfDay Overloaded p f TimeOfDay TimeOfDay DiffTime DiffTime
-> (p Rational (f Rational) -> p DiffTime (f DiffTime))
-> p Rational (f Rational)
-> p TimeOfDay (f TimeOfDay)
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (DiffTime -> Rational)
-> (Rational -> DiffTime)
-> Iso DiffTime DiffTime Rational Rational
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso DiffTime -> Rational
toRatio Rational -> DiffTime
fromRatio where
{-# INLINEABLE toRatio #-}
toRatio :: DiffTime -> Rational
toRatio :: DiffTime -> Rational
toRatio DiffTime
t = DiffTime -> Rational
forall t n. (TimeDiff t, Fractional n) => t -> n
toSeconds DiffTime
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
{-# INLINEABLE fromRatio #-}
fromRatio :: Rational -> DiffTime
fromRatio :: Rational -> DiffTime
fromRatio ((Scalar NominalDiffTime -> NominalDiffTime -> NominalDiffTime
forall v. VectorSpace v => Scalar v -> v -> v
*^ NominalDiffTime
posixDayLength) -> NominalDiffTime Micro
r) = Micro -> DiffTime
DiffTime Micro
r
data LocalTime = LocalTime
{ LocalTime -> Day
localDay :: {-# UNPACK #-}!Day
, LocalTime -> TimeOfDay
localTimeOfDay :: {-# UNPACK #-}!TimeOfDay
} deriving (INSTANCES_USUAL)
LENS(LocalTime,localDay,Day)
LENS(LocalTime,localTimeOfDay,TimeOfDay)
derivingUnbox "LocalTime" [t| LocalTime -> (Day, TimeOfDay) |]
[| \ LocalTime {..} -> (localDay, localTimeOfDay) |]
[| \ (localDay, localTimeOfDay) -> LocalTime {..} |]
instance Hashable LocalTime
instance NFData LocalTime
#if SHOW_INTERNAL
deriving instance Show LocalTime
#else
instance Show LocalTime where
showsPrec :: Int -> LocalTime -> ShowS
showsPrec Int
p (LocalTime Day
d TimeOfDay
t) = Int -> Day -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
p Day
d ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (:) Char
' ' ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> TimeOfDay -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
p TimeOfDay
t
#endif
instance Bounded LocalTime where
minBound :: LocalTime
minBound = UTCTime
forall a. Bounded a => a
minBound UTCTime -> Getting LocalTime UTCTime LocalTime -> LocalTime
forall s a. s -> Getting a s a -> a
^. TimeZone -> Iso' UTCTime LocalTime
utcLocalTime TimeZone
forall a. Bounded a => a
maxBound
maxBound :: LocalTime
maxBound = UTCTime
forall a. Bounded a => a
maxBound UTCTime -> Getting LocalTime UTCTime LocalTime -> LocalTime
forall s a. s -> Getting a s a -> a
^. TimeZone -> Iso' UTCTime LocalTime
utcLocalTime TimeZone
forall a. Bounded a => a
minBound
instance Random LocalTime where
randomR :: forall g.
RandomGen g =>
(LocalTime, LocalTime) -> g -> (LocalTime, g)
randomR = Iso' UTCTime LocalTime
-> (LocalTime, LocalTime) -> g -> (LocalTime, g)
forall s g a.
(Random s, RandomGen g) =>
Iso' s a -> (a, a) -> g -> (a, g)
randomIsoR (TimeZone -> Iso' UTCTime LocalTime
utcLocalTime TimeZone
utc)
random :: forall g. RandomGen g => g -> (LocalTime, g)
random = (LocalTime, LocalTime) -> g -> (LocalTime, g)
forall g.
RandomGen g =>
(LocalTime, LocalTime) -> g -> (LocalTime, g)
forall a g. (Random a, RandomGen g) => (a, a) -> g -> (a, g)
randomR (LocalTime
forall a. Bounded a => a
minBound, LocalTime
forall a. Bounded a => a
maxBound)
instance Arbitrary LocalTime where
arbitrary :: Gen LocalTime
arbitrary = (LocalTime, LocalTime) -> Gen LocalTime
forall a. Random a => (a, a) -> Gen a
choose (LocalTime
forall a. Bounded a => a
minBound, LocalTime
forall a. Bounded a => a
maxBound)
shrink :: LocalTime -> [LocalTime]
shrink lt :: LocalTime
lt@LocalTime {Day
TimeOfDay
localDay :: LocalTime -> Day
localTimeOfDay :: LocalTime -> TimeOfDay
localDay :: Day
localTimeOfDay :: TimeOfDay
..}
= [ LocalTime
lt {localDay = d} | Day
d <- Day -> [Day]
forall a. Arbitrary a => a -> [a]
shrink Day
localDay ]
[LocalTime] -> [LocalTime] -> [LocalTime]
forall a. [a] -> [a] -> [a]
++ [ LocalTime
lt {localTimeOfDay = d} | TimeOfDay
d <- TimeOfDay -> [TimeOfDay]
forall a. Arbitrary a => a -> [a]
shrink TimeOfDay
localTimeOfDay ]
instance CoArbitrary LocalTime where
coarbitrary :: forall b. LocalTime -> Gen b -> Gen b
coarbitrary (LocalTime Day
d TimeOfDay
t) = Day -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. Day -> Gen b -> Gen b
coarbitrary Day
d (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. TimeOfDay -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. TimeOfDay -> Gen b -> Gen b
coarbitrary TimeOfDay
t
{-# INLINE utcLocalTime #-}
utcLocalTime :: TimeZone -> Iso' UTCTime LocalTime
utcLocalTime :: TimeZone -> Iso' UTCTime LocalTime
utcLocalTime TimeZone {Bool
Int
String
timeZoneMinutes :: TimeZone -> Int
timeZoneSummerOnly :: TimeZone -> Bool
timeZoneName :: TimeZone -> String
timeZoneMinutes :: Int
timeZoneSummerOnly :: Bool
timeZoneName :: String
..} = Overloaded p f UTCTime UTCTime UTCView UTCView
Iso' UTCTime UTCView
utcTime Overloaded p f UTCTime UTCTime UTCView UTCView
-> (p LocalTime (f LocalTime) -> p UTCView (f UTCView))
-> p LocalTime (f LocalTime)
-> p UTCTime (f UTCTime)
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (UTCView -> LocalTime)
-> (LocalTime -> UTCView)
-> Iso UTCView UTCView LocalTime LocalTime
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso UTCView -> LocalTime
localise LocalTime -> UTCView
globalise where
{-# INLINEABLE localise #-}
localise :: UTCView -> LocalTime
localise :: UTCView -> LocalTime
localise (UTCView Day
day DiffTime
dt) = Day -> TimeOfDay -> LocalTime
LocalTime (Day
day Day -> Diff Day -> Day
forall p. AffineSpace p => p -> Diff p -> p
.+^ Int
Diff Day
dd) TimeOfDay
tod where
(Int
dd, TimeOfDay
tod) = Int -> TimeOfDay -> (Int, TimeOfDay)
addMinutes Int
timeZoneMinutes (DiffTime
dt DiffTime -> Getting TimeOfDay DiffTime TimeOfDay -> TimeOfDay
forall s a. s -> Getting a s a -> a
^. Getting TimeOfDay DiffTime TimeOfDay
Iso' DiffTime TimeOfDay
timeOfDay)
{-# INLINEABLE globalise #-}
globalise :: LocalTime -> UTCView
globalise :: LocalTime -> UTCView
globalise (LocalTime Day
day TimeOfDay
tod) = Day -> DiffTime -> UTCView
UTCView (Day
day Day -> Diff Day -> Day
forall p. AffineSpace p => p -> Diff p -> p
.+^ Int
Diff Day
dd)
(Overloaded Reviewed Identity DiffTime DiffTime TimeOfDay TimeOfDay
Iso' DiffTime TimeOfDay
timeOfDay Overloaded Reviewed Identity DiffTime DiffTime TimeOfDay TimeOfDay
-> TimeOfDay -> DiffTime
forall s t a b. AReview s t a b -> b -> t
# TimeOfDay
utcToD) where
(Int
dd, TimeOfDay
utcToD) = Int -> TimeOfDay -> (Int, TimeOfDay)
addMinutes (Int -> Int
forall a. Num a => a -> a
negate Int
timeZoneMinutes) TimeOfDay
tod
{-# INLINE ut1LocalTime #-}
ut1LocalTime :: Rational -> Iso' UniversalTime LocalTime
ut1LocalTime :: Rational -> Iso' UniversalTime LocalTime
ut1LocalTime Rational
long = (UniversalTime -> LocalTime)
-> (LocalTime -> UniversalTime) -> Iso' UniversalTime LocalTime
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso UniversalTime -> LocalTime
localise LocalTime -> UniversalTime
globalise where
NominalDiffTime posixDay :: Micro
posixDay@(Micro Int64
usDay) = NominalDiffTime
posixDayLength
{-# INLINEABLE localise #-}
localise :: UniversalTime -> LocalTime
localise :: UniversalTime -> LocalTime
localise (UniversalRep (NominalDiffTime Micro
t)) = Day -> TimeOfDay -> LocalTime
LocalTime
(Int -> Day
ModifiedJulianDay (Int -> Day) -> Int -> Day
forall a b. (a -> b) -> a -> b
$ Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
day)
(Micro -> DiffTime
DiffTime Micro
dt DiffTime -> Getting TimeOfDay DiffTime TimeOfDay -> TimeOfDay
forall s a. s -> Getting a s a -> a
^. Getting TimeOfDay DiffTime TimeOfDay
Iso' DiffTime TimeOfDay
timeOfDay) where
(Int64
day, Micro
dt) = Micro -> Micro -> (Int64, Micro)
microDivMod (Micro
t Micro -> Micro -> Micro
forall v. AdditiveGroup v => v -> v -> v
^+^ (Rational
long Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/ Rational
360) Scalar Micro -> Micro -> Micro
forall v. VectorSpace v => Scalar v -> v -> v
*^ Micro
posixDay) Micro
posixDay
{-# INLINEABLE globalise #-}
globalise :: LocalTime -> UniversalTime
globalise :: LocalTime -> UniversalTime
globalise (LocalTime Day
day TimeOfDay
tod) = NominalDiffTime -> UniversalTime
UniversalRep (NominalDiffTime -> UniversalTime)
-> (Micro -> NominalDiffTime) -> Micro -> UniversalTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Micro -> NominalDiffTime
NominalDiffTime (Micro -> UniversalTime) -> Micro -> UniversalTime
forall a b. (a -> b) -> a -> b
$
Int64 -> Micro
Micro (Int64
mjd Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
usDay) Micro -> Micro -> Micro
forall v. AdditiveGroup v => v -> v -> v
^+^ Micro
dt Micro -> Micro -> Micro
forall v. AdditiveGroup v => v -> v -> v
^-^ (Rational
long Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/ Rational
360) Scalar Micro -> Micro -> Micro
forall v. VectorSpace v => Scalar v -> v -> v
*^ Micro
posixDay where
ModifiedJulianDay (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Int64
mjd) = Day
day
DiffTime Micro
dt = Overloaded Reviewed Identity DiffTime DiffTime TimeOfDay TimeOfDay
Iso' DiffTime TimeOfDay
timeOfDay Overloaded Reviewed Identity DiffTime DiffTime TimeOfDay TimeOfDay
-> TimeOfDay -> DiffTime
forall s t a b. AReview s t a b -> b -> t
# TimeOfDay
tod
data ZonedTime = ZonedTime
{ ZonedTime -> LocalTime
zonedTimeToLocalTime :: {-# UNPACK #-}!LocalTime
, ZonedTime -> TimeZone
zonedTimeZone :: !TimeZone
} deriving (INSTANCES_USUAL)
LENS(ZonedTime,zonedTimeToLocalTime,LocalTime)
LENS(ZonedTime,zonedTimeZone,TimeZone)
instance Hashable ZonedTime
instance NFData ZonedTime where
rnf :: ZonedTime -> ()
rnf ZonedTime {TimeZone
LocalTime
zonedTimeToLocalTime :: ZonedTime -> LocalTime
zonedTimeZone :: ZonedTime -> TimeZone
zonedTimeToLocalTime :: LocalTime
zonedTimeZone :: TimeZone
..} = TimeZone -> ()
forall a. NFData a => a -> ()
rnf TimeZone
zonedTimeZone
instance Bounded ZonedTime where
minBound :: ZonedTime
minBound = LocalTime -> TimeZone -> ZonedTime
ZonedTime LocalTime
forall a. Bounded a => a
minBound TimeZone
forall a. Bounded a => a
maxBound
maxBound :: ZonedTime
maxBound = LocalTime -> TimeZone -> ZonedTime
ZonedTime LocalTime
forall a. Bounded a => a
maxBound TimeZone
forall a. Bounded a => a
minBound
instance Random ZonedTime where
randomR :: forall g.
RandomGen g =>
(ZonedTime, ZonedTime) -> g -> (ZonedTime, g)
randomR (ZonedTime
l, ZonedTime
u) g
g0 = (Getting ZonedTime (TimeZone, UTCTime) ZonedTime
-> (TimeZone, UTCTime) -> ZonedTime
forall a s. Getting a s a -> s -> a
view Getting ZonedTime (TimeZone, UTCTime) ZonedTime
Iso' (TimeZone, UTCTime) ZonedTime
zonedTime ((TimeZone, UTCTime) -> ZonedTime)
-> (UTCTime -> (TimeZone, UTCTime)) -> UTCTime -> ZonedTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (,) TimeZone
tz)
(UTCTime -> ZonedTime) -> (UTCTime, g) -> (ZonedTime, g)
forall b c d. (b -> c) -> (b, d) -> (c, d)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
`first` (UTCTime, UTCTime) -> g -> (UTCTime, g)
forall g. RandomGen g => (UTCTime, UTCTime) -> g -> (UTCTime, g)
forall a g. (Random a, RandomGen g) => (a, a) -> g -> (a, g)
randomR (UTCTime
l', UTCTime
u') g
g1 where
(TimeZone
tz, g
g1) = g -> (TimeZone, g)
forall g. RandomGen g => g -> (TimeZone, g)
forall a g. (Random a, RandomGen g) => g -> (a, g)
random g
g0
l' :: UTCTime
l' = (TimeZone, UTCTime) -> UTCTime
forall a b. (a, b) -> b
snd ((TimeZone, UTCTime) -> UTCTime) -> (TimeZone, UTCTime) -> UTCTime
forall a b. (a -> b) -> a -> b
$ Overloaded
Reviewed
Identity
(TimeZone, UTCTime)
(TimeZone, UTCTime)
ZonedTime
ZonedTime
Iso' (TimeZone, UTCTime) ZonedTime
zonedTime Overloaded
Reviewed
Identity
(TimeZone, UTCTime)
(TimeZone, UTCTime)
ZonedTime
ZonedTime
-> ZonedTime -> (TimeZone, UTCTime)
forall s t a b. AReview s t a b -> b -> t
# ZonedTime
l
u' :: UTCTime
u' = (TimeZone, UTCTime) -> UTCTime
forall a b. (a, b) -> b
snd ((TimeZone, UTCTime) -> UTCTime) -> (TimeZone, UTCTime) -> UTCTime
forall a b. (a -> b) -> a -> b
$ Overloaded
Reviewed
Identity
(TimeZone, UTCTime)
(TimeZone, UTCTime)
ZonedTime
ZonedTime
Iso' (TimeZone, UTCTime) ZonedTime
zonedTime Overloaded
Reviewed
Identity
(TimeZone, UTCTime)
(TimeZone, UTCTime)
ZonedTime
ZonedTime
-> ZonedTime -> (TimeZone, UTCTime)
forall s t a b. AReview s t a b -> b -> t
# ZonedTime
u
random :: forall g. RandomGen g => g -> (ZonedTime, g)
random = (ZonedTime, ZonedTime) -> g -> (ZonedTime, g)
forall g.
RandomGen g =>
(ZonedTime, ZonedTime) -> g -> (ZonedTime, g)
forall a g. (Random a, RandomGen g) => (a, a) -> g -> (a, g)
randomR (ZonedTime
forall a. Bounded a => a
minBound, ZonedTime
forall a. Bounded a => a
maxBound)
instance Arbitrary ZonedTime where
arbitrary :: Gen ZonedTime
arbitrary = (ZonedTime, ZonedTime) -> Gen ZonedTime
forall a. Random a => (a, a) -> Gen a
choose (ZonedTime
forall a. Bounded a => a
minBound, ZonedTime
forall a. Bounded a => a
maxBound)
shrink :: ZonedTime -> [ZonedTime]
shrink zt :: ZonedTime
zt@ZonedTime {TimeZone
LocalTime
zonedTimeToLocalTime :: ZonedTime -> LocalTime
zonedTimeZone :: ZonedTime -> TimeZone
zonedTimeToLocalTime :: LocalTime
zonedTimeZone :: TimeZone
..}
= [ ZonedTime
zt {zonedTimeToLocalTime = lt} | LocalTime
lt <- LocalTime -> [LocalTime]
forall a. Arbitrary a => a -> [a]
shrink LocalTime
zonedTimeToLocalTime ]
[ZonedTime] -> [ZonedTime] -> [ZonedTime]
forall a. [a] -> [a] -> [a]
++ [ ZonedTime
zt {zonedTimeZone = tz} | TimeZone
tz <- TimeZone -> [TimeZone]
forall a. Arbitrary a => a -> [a]
shrink TimeZone
zonedTimeZone ]
instance CoArbitrary ZonedTime where
coarbitrary :: forall b. ZonedTime -> Gen b -> Gen b
coarbitrary (ZonedTime LocalTime
lt TimeZone
tz) = LocalTime -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. LocalTime -> Gen b -> Gen b
coarbitrary LocalTime
lt (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. TimeZone -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. TimeZone -> Gen b -> Gen b
coarbitrary TimeZone
tz
{-# INLINE zonedTime #-}
zonedTime :: Iso' (TimeZone, UTCTime) ZonedTime
zonedTime :: Iso' (TimeZone, UTCTime) ZonedTime
zonedTime = ((TimeZone, UTCTime) -> ZonedTime)
-> (ZonedTime -> (TimeZone, UTCTime))
-> Iso' (TimeZone, UTCTime) ZonedTime
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso (TimeZone, UTCTime) -> ZonedTime
toZoned ZonedTime -> (TimeZone, UTCTime)
fromZoned where
{-# INLINE toZoned #-}
toZoned :: (TimeZone, UTCTime) -> ZonedTime
toZoned :: (TimeZone, UTCTime) -> ZonedTime
toZoned (TimeZone
tz, UTCTime
time) = LocalTime -> TimeZone -> ZonedTime
ZonedTime (UTCTime
time UTCTime -> Getting LocalTime UTCTime LocalTime -> LocalTime
forall s a. s -> Getting a s a -> a
^. TimeZone -> Iso' UTCTime LocalTime
utcLocalTime TimeZone
tz) TimeZone
tz
{-# INLINE fromZoned #-}
fromZoned :: ZonedTime -> (TimeZone, UTCTime)
fromZoned :: ZonedTime -> (TimeZone, UTCTime)
fromZoned (ZonedTime LocalTime
lt TimeZone
tz) = (TimeZone
tz, TimeZone -> Iso' UTCTime LocalTime
utcLocalTime TimeZone
tz Overloaded Reviewed Identity UTCTime UTCTime LocalTime LocalTime
-> LocalTime -> UTCTime
forall s t a b. AReview s t a b -> b -> t
# LocalTime
lt)
#if SHOW_INTERNAL
deriving instance Show ZonedTime
instance Show UTCTime where
showsPrec p = showsPrec p . view utcTime
#else
instance Show ZonedTime where
showsPrec :: Int -> ZonedTime -> ShowS
showsPrec Int
p (ZonedTime LocalTime
lt TimeZone
tz) = Int -> LocalTime -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
p LocalTime
lt ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (:) Char
' ' ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> TimeZone -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
p TimeZone
tz
instance Show UTCTime where
showsPrec :: Int -> UTCTime -> ShowS
showsPrec Int
p = Int -> ZonedTime -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
p (ZonedTime -> ShowS) -> (UTCTime -> ZonedTime) -> UTCTime -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Getting ZonedTime (TimeZone, UTCTime) ZonedTime
-> (TimeZone, UTCTime) -> ZonedTime
forall a s. Getting a s a -> s -> a
view Getting ZonedTime (TimeZone, UTCTime) ZonedTime
Iso' (TimeZone, UTCTime) ZonedTime
zonedTime ((TimeZone, UTCTime) -> ZonedTime)
-> (UTCTime -> (TimeZone, UTCTime)) -> UTCTime -> ZonedTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (,) TimeZone
utc
#endif
{-# INLINE getZonedTime #-}
getZonedTime :: IO ZonedTime
getZonedTime :: IO ZonedTime
getZonedTime = UTCTime -> IO ZonedTime
utcToLocalZonedTime (UTCTime -> IO ZonedTime) -> IO UTCTime -> IO ZonedTime
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO UTCTime
getCurrentTime
{-# INLINEABLE utcToLocalZonedTime #-}
utcToLocalZonedTime :: UTCTime -> IO ZonedTime
utcToLocalZonedTime :: UTCTime -> IO ZonedTime
utcToLocalZonedTime UTCTime
time = do
TimeZone
tz <- UTCTime -> IO TimeZone
getTimeZone UTCTime
time
ZonedTime -> IO ZonedTime
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (ZonedTime -> IO ZonedTime) -> ZonedTime -> IO ZonedTime
forall a b. (a -> b) -> a -> b
$ (TimeZone
tz, UTCTime
time) (TimeZone, UTCTime)
-> Getting ZonedTime (TimeZone, UTCTime) ZonedTime -> ZonedTime
forall s a. s -> Getting a s a -> a
^. Getting ZonedTime (TimeZone, UTCTime) ZonedTime
Iso' (TimeZone, UTCTime) ZonedTime
zonedTime
{-# INLINE utcToLocalTimeOfDay #-}
utcToLocalTimeOfDay :: TimeZone -> TimeOfDay -> (Days, TimeOfDay)
utcToLocalTimeOfDay :: TimeZone -> TimeOfDay -> (Int, TimeOfDay)
utcToLocalTimeOfDay = Int -> TimeOfDay -> (Int, TimeOfDay)
addMinutes (Int -> TimeOfDay -> (Int, TimeOfDay))
-> (TimeZone -> Int) -> TimeZone -> TimeOfDay -> (Int, TimeOfDay)
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. TimeZone -> Int
timeZoneMinutes
{-# INLINE localToUTCTimeOfDay #-}
localToUTCTimeOfDay :: TimeZone -> TimeOfDay -> (Days, TimeOfDay)
localToUTCTimeOfDay :: TimeZone -> TimeOfDay -> (Int, TimeOfDay)
localToUTCTimeOfDay = Int -> TimeOfDay -> (Int, TimeOfDay)
addMinutes (Int -> TimeOfDay -> (Int, TimeOfDay))
-> (TimeZone -> Int) -> TimeZone -> TimeOfDay -> (Int, TimeOfDay)
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> Int
forall a. Num a => a -> a
negate (Int -> Int) -> (TimeZone -> Int) -> TimeZone -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. TimeZone -> Int
timeZoneMinutes
{-# INLINE timeToTimeOfDay #-}
timeToTimeOfDay :: DiffTime -> TimeOfDay
timeToTimeOfDay :: DiffTime -> TimeOfDay
timeToTimeOfDay = Getting TimeOfDay DiffTime TimeOfDay -> DiffTime -> TimeOfDay
forall a s. Getting a s a -> s -> a
view Getting TimeOfDay DiffTime TimeOfDay
Iso' DiffTime TimeOfDay
timeOfDay
{-# INLINE timeOfDayToTime #-}
timeOfDayToTime :: TimeOfDay -> DiffTime
timeOfDayToTime :: TimeOfDay -> DiffTime
timeOfDayToTime = Overloaded Reviewed Identity DiffTime DiffTime TimeOfDay TimeOfDay
-> TimeOfDay -> DiffTime
forall s t a b. AReview s t a b -> b -> t
review Overloaded Reviewed Identity DiffTime DiffTime TimeOfDay TimeOfDay
Iso' DiffTime TimeOfDay
timeOfDay
{-# INLINE dayFractionToTimeOfDay #-}
dayFractionToTimeOfDay :: Rational -> TimeOfDay
dayFractionToTimeOfDay :: Rational -> TimeOfDay
dayFractionToTimeOfDay = AReview TimeOfDay TimeOfDay Rational Rational
-> Rational -> TimeOfDay
forall s t a b. AReview s t a b -> b -> t
review AReview TimeOfDay TimeOfDay Rational Rational
Iso' TimeOfDay Rational
dayFraction
{-# INLINE timeOfDayToDayFraction #-}
timeOfDayToDayFraction :: TimeOfDay -> Rational
timeOfDayToDayFraction :: TimeOfDay -> Rational
timeOfDayToDayFraction = Getting Rational TimeOfDay Rational -> TimeOfDay -> Rational
forall a s. Getting a s a -> s -> a
view Getting Rational TimeOfDay Rational
Iso' TimeOfDay Rational
dayFraction
{-# INLINE utcToLocalTime #-}
utcToLocalTime :: TimeZone -> UTCTime -> LocalTime
utcToLocalTime :: TimeZone -> UTCTime -> LocalTime
utcToLocalTime TimeZone
tz = Getting LocalTime UTCTime LocalTime -> UTCTime -> LocalTime
forall a s. Getting a s a -> s -> a
view (TimeZone -> Iso' UTCTime LocalTime
utcLocalTime TimeZone
tz)
{-# INLINE localTimeToUTC #-}
localTimeToUTC :: TimeZone -> LocalTime -> UTCTime
localTimeToUTC :: TimeZone -> LocalTime -> UTCTime
localTimeToUTC TimeZone
tz = Overloaded Reviewed Identity UTCTime UTCTime LocalTime LocalTime
-> LocalTime -> UTCTime
forall s t a b. AReview s t a b -> b -> t
review (TimeZone -> Iso' UTCTime LocalTime
utcLocalTime TimeZone
tz)
{-# INLINE ut1ToLocalTime #-}
ut1ToLocalTime :: Rational -> UniversalTime -> LocalTime
ut1ToLocalTime :: Rational -> UniversalTime -> LocalTime
ut1ToLocalTime Rational
l = Getting LocalTime UniversalTime LocalTime
-> UniversalTime -> LocalTime
forall a s. Getting a s a -> s -> a
view (Rational -> Iso' UniversalTime LocalTime
ut1LocalTime Rational
l)
{-# INLINE localTimeToUT1 #-}
localTimeToUT1 :: Rational -> LocalTime -> UniversalTime
localTimeToUT1 :: Rational -> LocalTime -> UniversalTime
localTimeToUT1 Rational
l = AReview UniversalTime UniversalTime LocalTime LocalTime
-> LocalTime -> UniversalTime
forall s t a b. AReview s t a b -> b -> t
review (Rational -> Iso' UniversalTime LocalTime
ut1LocalTime Rational
l)
{-# INLINE utcToZonedTime #-}
utcToZonedTime :: TimeZone -> UTCTime -> ZonedTime
utcToZonedTime :: TimeZone -> UTCTime -> ZonedTime
utcToZonedTime TimeZone
z UTCTime
t = Getting ZonedTime (TimeZone, UTCTime) ZonedTime
-> (TimeZone, UTCTime) -> ZonedTime
forall a s. Getting a s a -> s -> a
view Getting ZonedTime (TimeZone, UTCTime) ZonedTime
Iso' (TimeZone, UTCTime) ZonedTime
zonedTime (TimeZone
z, UTCTime
t)
{-# INLINE zonedTimeToUTC #-}
zonedTimeToUTC :: ZonedTime -> UTCTime
zonedTimeToUTC :: ZonedTime -> UTCTime
zonedTimeToUTC = (TimeZone, UTCTime) -> UTCTime
forall a b. (a, b) -> b
snd ((TimeZone, UTCTime) -> UTCTime)
-> (ZonedTime -> (TimeZone, UTCTime)) -> ZonedTime -> UTCTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Overloaded
Reviewed
Identity
(TimeZone, UTCTime)
(TimeZone, UTCTime)
ZonedTime
ZonedTime
-> ZonedTime -> (TimeZone, UTCTime)
forall s t a b. AReview s t a b -> b -> t
review Overloaded
Reviewed
Identity
(TimeZone, UTCTime)
(TimeZone, UTCTime)
ZonedTime
ZonedTime
Iso' (TimeZone, UTCTime) ZonedTime
zonedTime