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

-- |Parse RFC 733 date and time strings.
rfc733DateAndTime  Parser ZonedTime
rfc733DateAndTime = dateTime

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

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

time  Parser (TimeOfDay, TimeZone)
time = do tod  hms
          _    char '-' <|> char ' '
          tz   zone
          return (tod, tz)

hms  Parser TimeOfDay
hms = do hour    read2
         _       optional (char ':')
         minute  read2
         second  option 0 $
                  do _  optional (char ':')
                     read2
         assertTimeOfDayIsGood hour minute second

zone  Parser TimeZone
zone = choice [ string "GMT" *> return (TimeZone 0 False "GMT")
              , char 'N'
                *> choice [ string "ST" *> return (TimeZone ((-3) * 60 - 30) False "NST")
                          , return (TimeZone (1 * 60) False "N")
                          ]
              , char 'A'
                *> choice [ string "ST" *> return (TimeZone ((-4) * 60) False "AST")
                          , string "DT" *> return (TimeZone ((-3) * 60) False "AST")
                          , return (TimeZone ((-1) * 60) False "A")
                          ]
              , 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 'Y'
                *> choice [ string "ST" *> return (TimeZone ((-9) * 60) False "YST")
                          , string "DT" *> return (TimeZone ((-8) * 60) True  "YDT")
                          , return (TimeZone ( 12  * 60) False "Y")
                          ]
              , char 'H'
                *> choice [ string "ST" *> return (TimeZone ((-10) * 60) False "HST")
                          , string "DT" *> return (TimeZone (( -9) * 60) True  "HDT")
                          ]
              , char 'B'
                *> choice [ string "ST" *> return (TimeZone ((-11) * 60) False "BST")
                          , string "DT" *> return (TimeZone ((-10) * 60) True  "BDT")
                          ]
              , char 'Z' *> return (TimeZone 0 False "Z")
              , read4digitsTZ
              ]

-- |Convert a 'ZonedTime' to RFC 733 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
        longWeekDayName 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 " "
         showRFC822TimeZone timeZone