{-# LANGUAGE
    FlexibleInstances
  , MultiParamTypeClasses
  , OverloadedStrings
  , TemplateHaskell
  , TypeSynonymInstances
  , UnicodeSyntax
  #-}
-- |This module provides functions to parse and format RFC 1123 date
-- and time strings (<http://tools.ietf.org/html/rfc1123#page-55>).
--
-- The format is basically the same as RFC 822, but the syntax for
-- @date@ is changed from:
--
-- > year ::= 2DIGIT
--
-- to:
--
-- > year ::= 4DIGIT
module Data.Time.Format.RFC1123
    ( RFC1123
    )
    where
import Control.Applicative
import Control.Applicative.Unicode
import Data.Ascii (Ascii, AsciiBuilder)
import qualified Data.Ascii as A
import Data.Attoparsec.Char8
import Data.Convertible.Base
import Data.Default
import Data.Monoid.Unicode
import Data.Tagged
import Data.Time
import Data.Time.Calendar.WeekDate
import Data.Time.Format.HTTP.Common
import Data.Time.Format.RFC822
import Prelude.Unicode

-- |The phantom type for conversions between RFC 1123 date and time
-- strings and 'ZonedTime'.
--
-- >>> convertSuccess (Tagged (ZonedTime (LocalTime (ModifiedJulianDay 49662) (TimeOfDay 8 49 37)) utc) :: Tagged RFC1123 ZonedTime)
-- "Sun, 06 Nov 1994 08:49:37 GMT"
data RFC1123

instance ConvertSuccess (Tagged RFC1123 ZonedTime) Ascii where
    {-# INLINE convertSuccess #-}
    convertSuccess = A.fromAsciiBuilder  cs

instance ConvertSuccess (Tagged RFC1123 ZonedTime) AsciiBuilder where
    {-# INLINE convertSuccess #-}
    convertSuccess = toAsciiBuilder

instance ConvertAttempt Ascii (Tagged RFC1123 ZonedTime) where
    {-# INLINE convertAttempt #-}
    convertAttempt = parseAttempt' def

-- |Parse an RFC 1123 date and time string.
instance Default (Parser (Tagged RFC1123 ZonedTime)) where
    def = do weekDay  optionMaybe $
                       do w  shortWeekDayNameP
                          string ", " *> pure w
             gregDay  date
             case weekDay of
               Nothing
                    return ()
               Just givenWD
                    assertWeekDayIsGood givenWD gregDay
             tod  def
             tz   char ' ' *> def
             let lt = LocalTime gregDay <$> tod
                 zt = ZonedTime <$> lt  tz
             pure $ retag' zt
        where
          retag'  Tagged RFC822 α  Tagged τ α
          retag' = retag

date  Parser Day
date = do day    read2
          _      char ' '
          month  shortMonthNameP
          _      char ' '
          year   read4
          _      char ' '
          assertGregorianDateIsGood year month day

toAsciiBuilder  Tagged RFC1123 ZonedTime  AsciiBuilder
toAsciiBuilder zonedTime
    = let localTime          = zonedTimeToLocalTime $ untag zonedTime
          timeZone           = zonedTimeZone <$> retag' zonedTime
          (year, month, day) = toGregorian (localDay localTime)
          (_, _, week)       = toWeekDate  (localDay localTime)
          timeOfDay          = localTimeOfDay localTime
      in
        shortWeekDayName week
         A.toAsciiBuilder ", "
         show2 day
         A.toAsciiBuilder " "
         shortMonthName month
         A.toAsciiBuilder " "
         show4 year
         A.toAsciiBuilder " "
         show2 (todHour timeOfDay)
         A.toAsciiBuilder ":"
         show2 (todMin timeOfDay)
         A.toAsciiBuilder ":"
         show2 (floor (todSec timeOfDay)  Int)
         A.toAsciiBuilder " "
         cs timeZone
    where
      retag'  Tagged τ α  Tagged RFC822 α
      retag' = retag

deriveAttempts [ ([t| Tagged RFC1123 ZonedTime |], [t| Ascii        |])
               , ([t| Tagged RFC1123 ZonedTime |], [t| AsciiBuilder |])
               ]