{-# LANGUAGE
    OverloadedStrings
  , UnicodeSyntax
  #-}
-- |Internal functions for "Data.Time.RFC822".
module Data.Time.RFC822.Internal
    ( rfc822DateAndTime
    , rfc822time
    , showRFC822TimeZone
    , toAsciiBuilder
    )
    where
import Control.Applicative
import Data.Ascii (AsciiBuilder)
import qualified Data.Ascii as A
import Data.Attoparsec.Char8
import Data.Monoid.Unicode
import Data.Time
import Data.Time.Calendar.WeekDate
import Data.Time.HTTP.Common
import Prelude.Unicode

-- |Parse an RFC 822 date and time string.
rfc822DateAndTime  Parser ZonedTime
rfc822DateAndTime = dateTime

dateTime  Parser ZonedTime
dateTime = do weekDay  optionMaybe $
                        do w  shortWeekDayNameP
                           _  string ", "
                           return w
              gregDay  date
              case weekDay of
                Nothing
                    -> return ()
                Just givenWD
                    -> assertWeekDayIsGood givenWD gregDay
              (tod, timeZone)  rfc822time
              let lt = LocalTime gregDay tod
                  zt = ZonedTime lt timeZone
              return zt

date  Parser Day
date = do day    read2
          _      char ' '
          month  shortMonthNameP
          _      char ' '
          year   (+ 1900) <$> read2
          _      char ' '
          assertGregorianDateIsGood year month day

-- |Parse the time and time zone of an RFC 822 date and time string.
rfc822time  Parser (TimeOfDay, TimeZone)
rfc822time = do tod  hms
                _    char ' '
                tz   zone
                return (tod, tz)

hms  Parser TimeOfDay
hms = do hour    read2
         minute  char ':' *> read2
         second  option 0 (char ':' *> read2)
         assertTimeOfDayIsGood hour minute second

zone  Parser TimeZone
zone = choice [ string "UT"  *> return (TimeZone 0 False "UT" )
              , string "GMT" *> return (TimeZone 0 False "GMT")
              , char 'E'
                *> choice [ string "ST" *> return (TimeZone ((-5) * 60) False "EST")
                          , string "DT" *> return (TimeZone ((-4) * 60) True  "EDT")
                          ]
              , char 'C'
                *> choice [ string "ST" *> return (TimeZone ((-6) * 60) False "CST")
                          , string "DT" *> return (TimeZone ((-5) * 60) True  "CDT")
                          ]
              , char 'M'
                *> choice [ string "ST" *> return (TimeZone ((-7) * 60) False "MST")
                          , string "DT" *> return (TimeZone ((-6) * 60) True  "MDT")
                          , return (TimeZone ((-12) * 60) False "M")
                          ]
              , char 'P'
                *> choice [ string "ST" *> return (TimeZone ((-8) * 60) False "PST")
                          , string "DT" *> return (TimeZone ((-7) * 60) True  "PDT")
                          ]
              , char 'Z' *> return (TimeZone 0           False "Z")
              , char 'A' *> return (TimeZone ((-1) * 60) False "A")
              , char 'N' *> return (TimeZone (  1  * 60) False "N")
              , char 'Y' *> return (TimeZone ( 12  * 60) False "Y")
              , read4digitsTZ
              ]

-- |No need to explain.
showRFC822TimeZone  TimeZone  AsciiBuilder
showRFC822TimeZone tz
    | timeZoneMinutes tz  0 = A.toAsciiBuilder "GMT"
    | otherwise              = show4digitsTZ tz

-- |Convert a 'ZonedTime' to RFC 822 date and time string.
toAsciiBuilder  ZonedTime  AsciiBuilder
toAsciiBuilder zonedTime
    = let localTime          = zonedTimeToLocalTime zonedTime
          timeZone           = zonedTimeZone 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 " "
         show2 (year `mod` 100)
         A.toAsciiBuilder " "
         show2 (todHour timeOfDay)
         A.toAsciiBuilder ":"
         show2 (todMin timeOfDay)
         A.toAsciiBuilder ":"
         show2 (floor (todSec timeOfDay)  Int)
         A.toAsciiBuilder " "
         showRFC822TimeZone timeZone