-----------------------------------------------------------------------------
-- |
-- Module      :  Data.HodaTime.OffsetDateTime
-- Copyright   :  (C) 2016 Jason Johnson
-- License     :  BSD-style (see the file LICENSE)
-- Maintainer  :  Jason Johnson <jason.johnson.081@gmail.com>
-- Stability   :  experimental
-- Portability :  TBD
--
-- An 'OffsetDateTime' is a date and time combined with an offset from UTC time.  'OffsetDateTime' is the form that HTTP uses to deal with dates and times.
----------------------------------------------------------------------------
module Data.HodaTime.OffsetDateTime
(
  -- * Types
   OffsetDateTime
  -- * Constructors
  ,fromInstantWithOffset
  ,fromCalendarDateTimeWithOffset
  -- * Math
  -- * Conversion
)
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)

-- | A 'CalendarDateTime' with a UTC offset.  This is the format used by e.g. HTTP.  This type has a fixed 'TimeZone' with the name "UTC(+/-)offset".  If the offset is
-- empty, the name of the 'TimeZone' will be UTC
newtype OffsetDateTime cal = OffsetDateTime (ZonedDateTime cal)
  deriving (OffsetDateTime cal -> OffsetDateTime cal -> Bool
(OffsetDateTime cal -> OffsetDateTime cal -> Bool)
-> (OffsetDateTime cal -> OffsetDateTime cal -> Bool)
-> Eq (OffsetDateTime cal)
forall cal. OffsetDateTime cal -> OffsetDateTime cal -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall cal. OffsetDateTime cal -> OffsetDateTime cal -> Bool
== :: OffsetDateTime cal -> OffsetDateTime cal -> Bool
$c/= :: forall cal. OffsetDateTime cal -> OffsetDateTime cal -> Bool
/= :: OffsetDateTime cal -> OffsetDateTime cal -> Bool
Eq, Int -> OffsetDateTime cal -> ShowS
[OffsetDateTime cal] -> ShowS
OffsetDateTime cal -> String
(Int -> OffsetDateTime cal -> ShowS)
-> (OffsetDateTime cal -> String)
-> ([OffsetDateTime cal] -> ShowS)
-> Show (OffsetDateTime cal)
forall cal. Int -> OffsetDateTime cal -> ShowS
forall cal. [OffsetDateTime cal] -> ShowS
forall cal. OffsetDateTime cal -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall cal. Int -> OffsetDateTime cal -> ShowS
showsPrec :: Int -> OffsetDateTime cal -> ShowS
$cshow :: forall cal. OffsetDateTime cal -> String
show :: OffsetDateTime cal -> String
$cshowList :: forall cal. [OffsetDateTime cal] -> ShowS
showList :: [OffsetDateTime cal] -> ShowS
Show)    -- TODO: Remove Show

-- | Create an 'OffsetDateTime' from an 'Instant' and an 'Offset'.
fromInstantWithOffset :: IsCalendarDateTime cal => Instant -> Offset -> OffsetDateTime cal
fromInstantWithOffset :: forall cal.
IsCalendarDateTime cal =>
Instant -> Offset -> OffsetDateTime cal
fromInstantWithOffset Instant
inst Offset
offset = ZonedDateTime cal -> OffsetDateTime cal
forall cal. ZonedDateTime cal -> OffsetDateTime cal
OffsetDateTime (ZonedDateTime cal -> OffsetDateTime cal)
-> ZonedDateTime cal -> OffsetDateTime cal
forall a b. (a -> b) -> a -> b
$ CalendarDateTime cal
-> TimeZone -> TransitionInfo -> ZonedDateTime cal
forall cal.
CalendarDateTime cal
-> TimeZone -> TransitionInfo -> ZonedDateTime cal
ZonedDateTime CalendarDateTime cal
cdt TimeZone
tz TransitionInfo
tInfo
  where
    (TimeZone
tz, TransitionInfo
tInfo) = Offset -> (TimeZone, TransitionInfo)
makeFixedTimeZone Offset
offset
    cdt :: CalendarDateTime cal
cdt = Instant -> CalendarDateTime cal
forall cal.
IsCalendarDateTime cal =>
Instant -> CalendarDateTime cal
fromAdjustedInstant (Instant -> CalendarDateTime cal)
-> (Instant -> Instant) -> Instant -> CalendarDateTime cal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Offset -> Instant -> Instant
adjustInstant Offset
offset (Instant -> CalendarDateTime cal)
-> Instant -> CalendarDateTime cal
forall a b. (a -> b) -> a -> b
$ Instant
inst

-- | Create an 'OffsetDateTime' from a 'CalendarDateTime' and an 'Offset'.
fromCalendarDateTimeWithOffset :: CalendarDateTime cal -> Offset -> OffsetDateTime cal
fromCalendarDateTimeWithOffset :: forall cal. CalendarDateTime cal -> Offset -> OffsetDateTime cal
fromCalendarDateTimeWithOffset CalendarDateTime cal
cdt Offset
offset = ZonedDateTime cal -> OffsetDateTime cal
forall cal. ZonedDateTime cal -> OffsetDateTime cal
OffsetDateTime (ZonedDateTime cal -> OffsetDateTime cal)
-> ZonedDateTime cal -> OffsetDateTime cal
forall a b. (a -> b) -> a -> b
$ CalendarDateTime cal
-> TimeZone -> TransitionInfo -> ZonedDateTime cal
forall cal.
CalendarDateTime cal
-> TimeZone -> TransitionInfo -> ZonedDateTime cal
ZonedDateTime CalendarDateTime cal
cdt TimeZone
tz TransitionInfo
tInfo
  where
    (TimeZone
tz, TransitionInfo
tInfo) = Offset -> (TimeZone, TransitionInfo)
makeFixedTimeZone Offset
offset

-- helper functions

makeFixedTimeZone :: Offset -> (TimeZone, TransitionInfo)
makeFixedTimeZone :: Offset -> (TimeZone, TransitionInfo)
makeFixedTimeZone Offset
offset = (TZIdentifier
-> UtcTransitionsMap -> CalDateTransitionsMap -> TimeZone
TimeZone (String -> TZIdentifier
Zone String
tzName) UtcTransitionsMap
utcM CalDateTransitionsMap
calDateM, TransitionInfo
tInfo)
  where
    tzName :: String
tzName = Offset -> String
toStringRep Offset
offset
    (UtcTransitionsMap
utcM, CalDateTransitionsMap
calDateM, TransitionInfo
tInfo) = String
-> Offset
-> (UtcTransitionsMap, CalDateTransitionsMap, TransitionInfo)
fixedOffsetZone String
tzName Offset
offset