module Data.HodaTime.ZonedDateTime
(
ZonedDateTime
,fromCalendarDateTimeLeniently
,fromCalendarDateTimeStrictly
,fromInstant
,toCalendarDateTime
,toCalendarDate
,toLocalTime
,inDst
,zoneAbbreviation
,year
,month
,day
,hour
,minute
,second
,nanosecond
,fromCalendarDateTimeAll
,resolve
,DateTimeDoesNotExistException
,DateTimeAmbiguousException
)
where
import Data.HodaTime.ZonedDateTime.Internal
import Data.HodaTime.CalendarDateTime.Internal (CalendarDateTime(..), CalendarDate(..), IsCalendarDateTime(..), IsCalendar(..), LocalTime)
import qualified Data.HodaTime.LocalTime.Internal as LT(second)
import Data.HodaTime.Offset.Internal (Offset(..))
import Data.HodaTime.TimeZone.Internal (TimeZone, TransitionInfo(..), calDateTransitionsFor, aroundCalDateTransition)
import Control.Exception (Exception)
import Control.Monad.Catch (MonadThrow, throwM)
import Data.Typeable (Typeable)
data DateTimeDoesNotExistException = DateTimeDoesNotExistException
deriving (Typeable, Int -> DateTimeDoesNotExistException -> ShowS
[DateTimeDoesNotExistException] -> ShowS
DateTimeDoesNotExistException -> String
(Int -> DateTimeDoesNotExistException -> ShowS)
-> (DateTimeDoesNotExistException -> String)
-> ([DateTimeDoesNotExistException] -> ShowS)
-> Show DateTimeDoesNotExistException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DateTimeDoesNotExistException -> ShowS
showsPrec :: Int -> DateTimeDoesNotExistException -> ShowS
$cshow :: DateTimeDoesNotExistException -> String
show :: DateTimeDoesNotExistException -> String
$cshowList :: [DateTimeDoesNotExistException] -> ShowS
showList :: [DateTimeDoesNotExistException] -> ShowS
Show)
instance Exception DateTimeDoesNotExistException
data DateTimeAmbiguousException = DateTimeAmbiguousException
deriving (Typeable, Int -> DateTimeAmbiguousException -> ShowS
[DateTimeAmbiguousException] -> ShowS
DateTimeAmbiguousException -> String
(Int -> DateTimeAmbiguousException -> ShowS)
-> (DateTimeAmbiguousException -> String)
-> ([DateTimeAmbiguousException] -> ShowS)
-> Show DateTimeAmbiguousException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DateTimeAmbiguousException -> ShowS
showsPrec :: Int -> DateTimeAmbiguousException -> ShowS
$cshow :: DateTimeAmbiguousException -> String
show :: DateTimeAmbiguousException -> String
$cshowList :: [DateTimeAmbiguousException] -> ShowS
showList :: [DateTimeAmbiguousException] -> ShowS
Show)
instance Exception DateTimeAmbiguousException
fromCalendarDateTimeLeniently :: (IsCalendar cal, IsCalendarDateTime cal) => CalendarDateTime cal -> TimeZone -> ZonedDateTime cal
fromCalendarDateTimeLeniently :: forall cal.
(IsCalendar cal, IsCalendarDateTime cal) =>
CalendarDateTime cal -> TimeZone -> ZonedDateTime cal
fromCalendarDateTimeLeniently = (ZonedDateTime cal -> ZonedDateTime cal -> ZonedDateTime cal)
-> (ZonedDateTime cal -> ZonedDateTime cal -> ZonedDateTime cal)
-> CalendarDateTime cal
-> TimeZone
-> ZonedDateTime cal
forall cal.
IsCalendarDateTime cal =>
(ZonedDateTime cal -> ZonedDateTime cal -> ZonedDateTime cal)
-> (ZonedDateTime cal -> ZonedDateTime cal -> ZonedDateTime cal)
-> CalendarDateTime cal
-> TimeZone
-> ZonedDateTime cal
resolve ZonedDateTime cal -> ZonedDateTime cal -> ZonedDateTime cal
forall {p} {p}. p -> p -> p
ambiguous ZonedDateTime cal -> ZonedDateTime cal -> ZonedDateTime cal
forall {cal} {cal}.
IsCalendar cal =>
ZonedDateTime cal -> ZonedDateTime cal -> ZonedDateTime cal
skipped
where
ambiguous :: p -> p -> p
ambiguous p
zdt p
_ = p
zdt
skipped :: ZonedDateTime cal -> ZonedDateTime cal -> ZonedDateTime cal
skipped (ZonedDateTime CalendarDateTime cal
_ TimeZone
_ (TransitionInfo (Offset Int
bOff) Bool
_ String
_)) (ZonedDateTime CalendarDateTime cal
cdt TimeZone
tz ti :: TransitionInfo
ti@(TransitionInfo (Offset Int
aOff) Bool
_ String
_)) = CalendarDateTime cal
-> TimeZone -> TransitionInfo -> ZonedDateTime cal
forall cal.
CalendarDateTime cal
-> TimeZone -> TransitionInfo -> ZonedDateTime cal
ZonedDateTime CalendarDateTime cal
cdt' TimeZone
tz TransitionInfo
ti
where
cdt' :: CalendarDateTime cal
cdt' = (Int -> Int)
-> ((Int -> [Int])
-> CalendarDateTime cal -> [CalendarDateTime cal])
-> CalendarDateTime cal
-> CalendarDateTime cal
forall {a} {b} {a} {c}.
(a -> b) -> ((a -> [b]) -> a -> [c]) -> a -> c
modify (\Int
s -> Int
s Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
aOff Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
bOff) (Int -> [Int]) -> CalendarDateTime cal -> [CalendarDateTime cal]
forall lt (f :: * -> *).
(HasLocalTime lt, Functor f) =>
(Int -> f Int) -> lt -> f lt
forall (f :: * -> *).
Functor f =>
(Int -> f Int) -> CalendarDateTime cal -> f (CalendarDateTime cal)
LT.second CalendarDateTime cal
cdt
modify :: (a -> b) -> ((a -> [b]) -> a -> [c]) -> a -> c
modify a -> b
f (a -> [b]) -> a -> [c]
l = [c] -> c
forall a. HasCallStack => [a] -> a
head ([c] -> c) -> (a -> [c]) -> a -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> [b]) -> a -> [c]
l ((b -> [b] -> [b]
forall a. a -> [a] -> [a]
:[]) (b -> [b]) -> (a -> b) -> a -> [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f)
fromCalendarDateTimeStrictly :: (MonadThrow m, IsCalendarDateTime cal) => CalendarDateTime cal -> TimeZone -> m (ZonedDateTime cal)
fromCalendarDateTimeStrictly :: forall (m :: * -> *) cal.
(MonadThrow m, IsCalendarDateTime cal) =>
CalendarDateTime cal -> TimeZone -> m (ZonedDateTime cal)
fromCalendarDateTimeStrictly CalendarDateTime cal
cdt = [ZonedDateTime cal] -> m (ZonedDateTime cal)
forall {m :: * -> *} {a}. MonadThrow m => [a] -> m a
go ([ZonedDateTime cal] -> m (ZonedDateTime cal))
-> (TimeZone -> [ZonedDateTime cal])
-> TimeZone
-> m (ZonedDateTime cal)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CalendarDateTime cal -> TimeZone -> [ZonedDateTime cal]
forall cal.
IsCalendarDateTime cal =>
CalendarDateTime cal -> TimeZone -> [ZonedDateTime cal]
fromCalendarDateTimeAll CalendarDateTime cal
cdt
where
go :: [a] -> m a
go [] = DateTimeDoesNotExistException -> m a
forall e a. (HasCallStack, Exception e) => e -> m a
forall (m :: * -> *) e a.
(MonadThrow m, HasCallStack, Exception e) =>
e -> m a
throwM (DateTimeDoesNotExistException -> m a)
-> DateTimeDoesNotExistException -> m a
forall a b. (a -> b) -> a -> b
$ DateTimeDoesNotExistException
DateTimeDoesNotExistException
go [a
zdt] = a -> m a
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
zdt
go [a]
_ = DateTimeAmbiguousException -> m a
forall e a. (HasCallStack, Exception e) => e -> m a
forall (m :: * -> *) e a.
(MonadThrow m, HasCallStack, Exception e) =>
e -> m a
throwM (DateTimeAmbiguousException -> m a)
-> DateTimeAmbiguousException -> m a
forall a b. (a -> b) -> a -> b
$ DateTimeAmbiguousException
DateTimeAmbiguousException
fromCalendarDateTimeAll :: IsCalendarDateTime cal => CalendarDateTime cal -> TimeZone -> [ZonedDateTime cal]
fromCalendarDateTimeAll :: forall cal.
IsCalendarDateTime cal =>
CalendarDateTime cal -> TimeZone -> [ZonedDateTime cal]
fromCalendarDateTimeAll CalendarDateTime cal
cdt TimeZone
tz = [ZonedDateTime cal]
zdts
where
instant :: Instant
instant = CalendarDateTime cal -> Instant
forall cal.
IsCalendarDateTime cal =>
CalendarDateTime cal -> Instant
toUnadjustedInstant CalendarDateTime cal
cdt
zdts :: [ZonedDateTime cal]
zdts = (TransitionInfo -> ZonedDateTime cal)
-> [TransitionInfo] -> [ZonedDateTime cal]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TransitionInfo -> ZonedDateTime cal
mkZdt ([TransitionInfo] -> [ZonedDateTime cal])
-> (TimeZone -> [TransitionInfo])
-> TimeZone
-> [ZonedDateTime cal]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Instant -> TimeZone -> [TransitionInfo]
calDateTransitionsFor Instant
instant (TimeZone -> [ZonedDateTime cal])
-> TimeZone -> [ZonedDateTime cal]
forall a b. (a -> b) -> a -> b
$ TimeZone
tz
mkZdt :: TransitionInfo -> ZonedDateTime cal
mkZdt = CalendarDateTime cal
-> TimeZone -> TransitionInfo -> ZonedDateTime cal
forall cal.
CalendarDateTime cal
-> TimeZone -> TransitionInfo -> ZonedDateTime cal
ZonedDateTime CalendarDateTime cal
cdt TimeZone
tz
resolve ::
IsCalendarDateTime cal =>
(ZonedDateTime cal -> ZonedDateTime cal -> ZonedDateTime cal) ->
(ZonedDateTime cal -> ZonedDateTime cal -> ZonedDateTime cal) ->
CalendarDateTime cal ->
TimeZone ->
ZonedDateTime cal
resolve :: forall cal.
IsCalendarDateTime cal =>
(ZonedDateTime cal -> ZonedDateTime cal -> ZonedDateTime cal)
-> (ZonedDateTime cal -> ZonedDateTime cal -> ZonedDateTime cal)
-> CalendarDateTime cal
-> TimeZone
-> ZonedDateTime cal
resolve ZonedDateTime cal -> ZonedDateTime cal -> ZonedDateTime cal
ambiguous ZonedDateTime cal -> ZonedDateTime cal -> ZonedDateTime cal
skipped CalendarDateTime cal
cdt TimeZone
tz = [ZonedDateTime cal] -> ZonedDateTime cal
go ([ZonedDateTime cal] -> ZonedDateTime cal)
-> (TimeZone -> [ZonedDateTime cal])
-> TimeZone
-> ZonedDateTime cal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TransitionInfo -> ZonedDateTime cal)
-> [TransitionInfo] -> [ZonedDateTime cal]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TransitionInfo -> ZonedDateTime cal
mkZdt ([TransitionInfo] -> [ZonedDateTime cal])
-> (TimeZone -> [TransitionInfo])
-> TimeZone
-> [ZonedDateTime cal]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Instant -> TimeZone -> [TransitionInfo]
calDateTransitionsFor Instant
instant (TimeZone -> ZonedDateTime cal) -> TimeZone -> ZonedDateTime cal
forall a b. (a -> b) -> a -> b
$ TimeZone
tz
where
instant :: Instant
instant = CalendarDateTime cal -> Instant
forall cal.
IsCalendarDateTime cal =>
CalendarDateTime cal -> Instant
toUnadjustedInstant CalendarDateTime cal
cdt
(TransitionInfo
before, TransitionInfo
after) = Instant -> TimeZone -> (TransitionInfo, TransitionInfo)
aroundCalDateTransition Instant
instant (TimeZone -> (TransitionInfo, TransitionInfo))
-> TimeZone -> (TransitionInfo, TransitionInfo)
forall a b. (a -> b) -> a -> b
$ TimeZone
tz
mkZdt :: TransitionInfo -> ZonedDateTime cal
mkZdt = CalendarDateTime cal
-> TimeZone -> TransitionInfo -> ZonedDateTime cal
forall cal.
CalendarDateTime cal
-> TimeZone -> TransitionInfo -> ZonedDateTime cal
ZonedDateTime CalendarDateTime cal
cdt TimeZone
tz
go :: [ZonedDateTime cal] -> ZonedDateTime cal
go [] = ZonedDateTime cal -> ZonedDateTime cal -> ZonedDateTime cal
skipped (TransitionInfo -> ZonedDateTime cal
mkZdt TransitionInfo
before) (TransitionInfo -> ZonedDateTime cal
mkZdt TransitionInfo
after)
go [ZonedDateTime cal
zdt] = ZonedDateTime cal
zdt
go (ZonedDateTime cal
zdt1:ZonedDateTime cal
zdt2:[]) = ZonedDateTime cal -> ZonedDateTime cal -> ZonedDateTime cal
ambiguous ZonedDateTime cal
zdt1 ZonedDateTime cal
zdt2
go [ZonedDateTime cal]
_ = String -> ZonedDateTime cal
forall a. HasCallStack => String -> a
error String
"misconfiguration: more than 2 dates returns from calDateTransitionsFor"
toCalendarDateTime :: ZonedDateTime cal -> CalendarDateTime cal
toCalendarDateTime :: forall cal. ZonedDateTime cal -> CalendarDateTime cal
toCalendarDateTime (ZonedDateTime CalendarDateTime cal
cdt TimeZone
_ TransitionInfo
_) = CalendarDateTime cal
cdt
toCalendarDate :: ZonedDateTime cal -> CalendarDate cal
toCalendarDate :: forall cal. ZonedDateTime cal -> CalendarDate cal
toCalendarDate (ZonedDateTime (CalendarDateTime CalendarDate cal
cd LocalTime
_) TimeZone
_ TransitionInfo
_) = CalendarDate cal
cd
toLocalTime :: ZonedDateTime cal -> LocalTime
toLocalTime :: forall cal. ZonedDateTime cal -> LocalTime
toLocalTime (ZonedDateTime (CalendarDateTime CalendarDate cal
_ LocalTime
lt) TimeZone
_ TransitionInfo
_) = LocalTime
lt
inDst :: ZonedDateTime cal -> Bool
inDst :: forall cal. ZonedDateTime cal -> Bool
inDst (ZonedDateTime CalendarDateTime cal
_ TimeZone
_ (TransitionInfo Offset
_ Bool
isInDst String
_)) = Bool
isInDst
zoneAbbreviation :: ZonedDateTime cal -> String
zoneAbbreviation :: forall cal. ZonedDateTime cal -> String
zoneAbbreviation (ZonedDateTime CalendarDateTime cal
_ TimeZone
_ (TransitionInfo Offset
_ Bool
_ String
abbr)) = String
abbr