OverloadedStrings
, UnicodeSyntax
#-}
+-- |Internal functions for "Data.Time.Asctime".
module Data.Time.Asctime.Internal
( asctime
, toAsciiBuilder
+{-# LANGUAGE
+ UnicodeSyntax
+ #-}
-- |This module provides functions to parse and format HTTP\/1.1 date
-- and time formats.
--
-- > | "May" | "Jun" | "Jul" | "Aug"
-- > | "Sep" | "Oct" | "Nov" | "Dec"
module Data.Time.HTTP
- ( format
- , parse
+ ( -- * Formatting
+ toAscii
+ , toAsciiBuilder
+
+ -- * Parsing
+ , fromAscii
+ , httpDateAndTime
)
where
-import qualified Data.Time.RFC1123 as RFC1123
+import Data.Ascii (Ascii)
+import qualified Data.Ascii as A
+import qualified Data.Attoparsec.Char8 as P
import Data.Time
import Data.Time.HTTP.Internal
+import Prelude.Unicode
--- |Format an 'UTCTime' in RFC 1123 date and time.
-format :: UTCTime -> String
-format utcTime
- = let timeZone = TimeZone 0 False "GMT"
- zonedTime = utcToZonedTime timeZone utcTime
- in
- RFC1123.format zonedTime
+-- |Convert a 'UTCTime' to RFC 1123 date and time string.
+toAscii ∷ UTCTime → Ascii
+toAscii = A.fromAsciiBuilder ∘ toAsciiBuilder
-- |Parse a date and time string in any of RFC 822, RFC 1123, RFC 850
-- and ANSI C's asctime() formats. When the string can't be parsed, it
--- returns 'Nothing'.
+-- returns @'Left' err@.
--
-- This function is even more permissive than what HTTP\/1.1
-- specifies. That is, it accepts 2-digit years in RFC 822, omitted
-- separator symbols in RFC 850, omitted sec fields, and non-GMT time
-- zones. I believe this behavior will not cause a problem but you
-- should know this.
-parse :: String -> Maybe UTCTime
-parse src = case P.parse p "" src of
- Right ut -> Just ut
- Left _ -> Nothing
+fromAscii ∷ Ascii → Either String UTCTime
+fromAscii = P.parseOnly p ∘ A.toByteString
where
- p = do zt <- rfc2616DateAndTime
- _ <- P.eof
+ p = do zt ← httpDateAndTime
+ P.endOfInput
return zt
-{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE
+ UnicodeSyntax
+ #-}
+-- |Internal functions for "Data.Time.HTTP".
module Data.Time.HTTP.Internal
- ( rfc2616DateAndTime
+ ( httpDateAndTime
+ , toAsciiBuilder
)
where
-import Control.Monad
+import Control.Applicative
+import Data.Ascii (AsciiBuilder)
+import Data.Attoparsec.Char8
import Data.Time
-import Data.Time.RFC1123.Internal
-import Data.Time.RFC733.Internal
-import Data.Time.Asctime.Internal
+import qualified Data.Time.RFC1123.Internal as RFC1123
+import qualified Data.Time.RFC733.Internal as RFC733
+import qualified Data.Time.Asctime.Internal as Asctime
+import Prelude.Unicode
--- |This is a parsec parser for date and time formats allowed in
--- HTTP\/1.1 (RFC 2616).
-rfc2616DateAndTime :: Stream s m Char => ParsecT s u m UTCTime
-rfc2616DateAndTime
- = choice [ liftM zonedTimeToUTC $ try rfc1123DateAndTime
- , liftM zonedTimeToUTC $ try rfc733DateAndTime
- , liftM (localTimeToUTC utc) asctime
+-- |Parse a date and time string in any formats allowed by HTTP\/1.1
+-- (RFC 2616).
+httpDateAndTime ∷ Parser UTCTime
+httpDateAndTime
+ = choice [ zonedTimeToUTC <$> try RFC1123.rfc1123DateAndTime
+ , zonedTimeToUTC <$> try RFC733.rfc733DateAndTime
+ , localTimeToUTC utc <$> Asctime.asctime
]
+
+-- |Convert a 'UTCTime' to RFC 1123 date and time string.
+toAsciiBuilder ∷ UTCTime → AsciiBuilder
+toAsciiBuilder = RFC1123.toAsciiBuilder ∘ ut2zt
+ where
+ ut2zt ∷ UTCTime → ZonedTime
+ ut2zt = utcToZonedTime gmt
+
+ gmt ∷ TimeZone
+ gmt = TimeZone 0 False "GMT"
OverloadedStrings
, UnicodeSyntax
#-}
+-- |Internal functions for "Data.Time.RFC1123".
module Data.Time.RFC1123.Internal
( rfc1123DateAndTime
, toAsciiBuilder
OverloadedStrings
, UnicodeSyntax
#-}
+-- |Internal functions for "Data.Time.RFC733".
module Data.Time.RFC733.Internal
( rfc733DateAndTime
)