+{-# LANGUAGE
+ UnicodeSyntax
+ #-}
-- |This module provides functions to parse and format RFC 733 date
-- and time formats.
--
-- > | "Y" ; +12
-- > | ("+" | "-") 4DIGIT ; Local diff: HHMM
module Data.Time.RFC733
- ( format
- , parse
+ ( -- * Formatting
+ toAscii
+ , toAsciiBuilder
+
+ -- * Parsing
+ , fromAscii
+ , rfc733DateAndTime
)
where
+import Data.Ascii (Ascii)
+import qualified Data.Ascii as A
+import qualified Data.Attoparsec.Char8 as P
import Data.Time
-import Data.Time.Calendar.WeekDate
-import Data.Time.HTTP.Common
import Data.Time.RFC733.Internal
+import Prelude.Unicode
--- |Format a 'ZonedTime' in RFC 733.
-format :: ZonedTime -> String
-format zonedTime
- = let localTime = zonedTimeToLocalTime zonedTime
- timeZone = zonedTimeZone zonedTime
- (year, month, day) = toGregorian (localDay localTime)
- (_, _, week) = toWeekDate (localDay localTime)
- timeOfDay = localTimeOfDay localTime
- in
- concat [ longWeekDayName week
- , ", "
- , show2 day
- , "-"
- , shortMonthName month
- , "-"
- , show4 year
- , " "
- , show2 (todHour timeOfDay)
- , ":"
- , show2 (todMin timeOfDay)
- , ":"
- , show2 (floor (todSec timeOfDay))
- , "-"
- , show4digitsTZ timeZone
- ]
+-- |Convert a 'ZonedTime' to RFC 733 date and time string.
+toAscii ∷ ZonedTime → Ascii
+toAscii = A.fromAsciiBuilder ∘ toAsciiBuilder
-- |Parse an RFC 733 date and time string. When the string can't be
--- parsed, it returns 'Nothing'.
-parse :: String -> Maybe ZonedTime
-parse src = case P.parse p "" src of
- Right zt -> Just zt
- Left _ -> Nothing
+-- parsed, it returns @'Left' err@.
+fromAscii ∷ Ascii → Either String ZonedTime
+fromAscii = P.parseOnly p ∘ A.toByteString
where
- p = do zt <- rfc733DateAndTime
- _ <- P.eof
+ p = do zt ← rfc733DateAndTime
+ P.endOfInput
return zt
-- |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
-- |Parse RFC 733 date and time strings.
, 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 "-"
+ ⊕ show4digitsTZ timeZone