{-# LANGUAGE
    UnicodeSyntax
  #-}
-- |This module provides functions to parse and format RFC 822 date
-- and time formats.
--
-- The syntax is as follows:
--
-- > date-time   ::= [ day-of-week ", " ] date SP time SP zone
-- > day-of-week ::= "Mon" | "Tue" | "Wed" | "Thu"
-- >               | "Fri" | "Sat" | "Sun"
-- > date        ::= day SP month SP year
-- > day         ::= 2DIGIT
-- > year        ::= 2DIGIT             ; Yes, only 2 digits.
-- > month       ::= "Jan" | "Feb" | "Mar" | "Apr"
-- >               | "May" | "Jun" | "Jul" | "Aug"
-- >               | "Sep" | "Oct" | "Nov" | "Dec"
-- > time        ::= hour ":" minute [ ":" second ]
-- > hour        ::= 2DIGIT
-- > minute      ::= 2DIGIT
-- > second      ::= 2DIGIT
-- > zone        ::= "UT"  | "GMT"      ; Universal Time
-- >               | "EST" | "EDT"      ; Eastern : -5 / -4
-- >               | "CST" | "CDT"      ; Central : -6 / -5
-- >               | "MST" | "MDT"      ; Mountain: -7 / -6
-- >               | "PST" | "PDT"      ; Pacific : -8 / -7
-- >               | "Z"                ; UT
-- >               | "A"                ;  -1
-- >               | "M"                ; -12
-- >               | "N"                ;  +1
-- >               | "Y"                ; +12
-- >               | ("+" | "-") 4DIGIT ; Local diff: HHMM
module Data.Time.RFC822
    ( -- * Formatting
      toAscii
    , toAsciiBuilder

      -- * Parsing
    , fromAscii
    , rfc822DateAndTime
    )
    where
import Data.Ascii (Ascii)
import qualified Data.Ascii as A
import qualified Data.Attoparsec.Char8 as P
import Data.Time
import Data.Time.RFC822.Internal
import Prelude.Unicode

-- |Convert a 'ZonedTime' to RFC 822 date and time string.
toAscii  ZonedTime  Ascii
toAscii = A.fromAsciiBuilder  toAsciiBuilder

-- |Parse an RFC 822 date and time string. When the string can't be
-- parsed, it returns @'Left' err@.
fromAscii  Ascii  Either String ZonedTime
fromAscii = P.parseOnly p  A.toByteString
    where
      p = do zt  rfc822DateAndTime
             P.endOfInput
             return zt