module Data.HodaTime.OffsetDateTime
(
OffsetDateTime
,fromInstantWithOffset
,fromCalendarDateTimeWithOffset
)
where
import Data.HodaTime.Offset.Internal
import Data.HodaTime.Instant.Internal (Instant)
import Data.HodaTime.CalendarDateTime.Internal (CalendarDateTime, IsCalendarDateTime(..))
import Data.HodaTime.ZonedDateTime.Internal (ZonedDateTime(..))
import Data.HodaTime.TimeZone.Internal (TimeZone(..), TZIdentifier(..), TransitionInfo, fixedOffsetZone)
newtype OffsetDateTime cal = OffsetDateTime (ZonedDateTime cal)
deriving (Eq, Show)
fromInstantWithOffset :: IsCalendarDateTime cal => Instant -> Offset -> OffsetDateTime cal
fromInstantWithOffset inst offset = OffsetDateTime $ ZonedDateTime cdt tz tInfo
where
(tz, tInfo) = makeFixedTimeZone offset
cdt = fromAdjustedInstant . adjustInstant offset $ inst
fromCalendarDateTimeWithOffset :: CalendarDateTime cal -> Offset -> OffsetDateTime cal
fromCalendarDateTimeWithOffset cdt offset = OffsetDateTime $ ZonedDateTime cdt tz tInfo
where
(tz, tInfo) = makeFixedTimeZone offset
makeFixedTimeZone :: Offset -> (TimeZone, TransitionInfo)
makeFixedTimeZone offset = (TimeZone (Zone tzName) utcM calDateM, tInfo)
where
tzName = toStringRep offset
(utcM, calDateM, tInfo) = fixedOffsetZone tzName offset