+{-# LANGUAGE
+ UnicodeSyntax
+ #-}
-- |This module provides functions for ANSI C's asctime() format.
--
-- ANSI C's asctime() format looks like:
-- As you can see, it has no time zone info. "Data.Time.HTTP" will
-- treat it as UTC.
module Data.Time.Asctime
- ( format
- , parse
+ ( -- * Formatting
+ toAscii
+ , toAsciiBuilder
+
+ -- * Parsing
+ , fromAscii
+ , asctime
)
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.Asctime.Internal
+import Prelude.Unicode
--- |Format a 'LocalTime' in the ANSI C's asctime() way.
-format :: LocalTime -> String
-format localTime
- = let (year, month, day) = toGregorian (localDay localTime)
- (_, _, week) = toWeekDate (localDay localTime)
- timeOfDay = localTimeOfDay localTime
- in
- concat [ shortWeekDayName week
- , ", "
- , shortMonthName month
- , " "
- , show2 day
- , " "
- , show2 (todHour timeOfDay)
- , ":"
- , show2 (todMin timeOfDay)
- , ":"
- , show2 (floor (todSec timeOfDay))
- , " "
- , show4 year
- ]
+-- |Convert a 'LocalTime' to ANSI C's @asctime()@ string.
+toAscii ∷ LocalTime → Ascii
+toAscii = A.fromAsciiBuilder ∘ toAsciiBuilder
--- |Parse an ANSI C's asctime() format to 'LocalTime'. When the string
--- can't be parsed, it returns 'Nothing'.
-parse :: String -> Maybe LocalTime
-parse src = case P.parse p "" src of
- Right zt -> Just zt
- Left _ -> Nothing
+-- |Parse an ANSI C's @asctime()@ string. When the string can't be
+-- parsed, it returns @'Left' err@.
+fromAscii ∷ Ascii → Either String LocalTime
+fromAscii = P.parseOnly p ∘ A.toByteString
where
- p = do zt <- asctime
- _ <- P.eof
+ p = do zt ← asctime
+ P.endOfInput
return zt
-{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE
+ OverloadedStrings
+ , UnicodeSyntax
+ #-}
module Data.Time.Asctime.Internal
( asctime
+ , toAsciiBuilder
)
where
-import Control.Monad
-import Data.Fixed
+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
--- |This is a parsec parser for ANSI C's asctime() format.
-asctime :: Stream s m Char => ParsecT s u m LocalTime
-asctime = do weekDay <- shortWeekDayNameP
- _ <- string ", "
- month <- shortMonthNameP
- _ <- char ' '
- day <- read2
- _ <- char ' '
- hour <- read2
- _ <- char ':'
- minute <- read2
- _ <- char ':'
- second <- read2
- _ <- char ' '
- year <- read4
+-- |Parse an ANSI C's @asctime()@ string.
+asctime ∷ Parser LocalTime
+asctime = do weekDay ← shortWeekDayNameP
+ _ ← string ", "
+ month ← shortMonthNameP
+ _ ← char ' '
+ day ← read2
+ _ ← char ' '
+ hour ← read2
+ _ ← char ':'
+ minute ← read2
+ _ ← char ':'
+ second ← read2
+ _ ← char ' '
+ year ← read4
- gregDay <- assertGregorianDateIsGood year month day
- _ <- assertWeekDayIsGood weekDay gregDay
- tod <- assertTimeOfDayIsGood hour minute second
+ gregDay ← assertGregorianDateIsGood year month day
+ _ ← assertWeekDayIsGood weekDay gregDay
+ tod ← assertTimeOfDayIsGood hour minute second
return (LocalTime gregDay tod)
+
+-- |Convert a 'LocalTime' to ANSI C's @asctime()@ string.
+toAsciiBuilder ∷ LocalTime → AsciiBuilder
+toAsciiBuilder localTime
+ = let (year, month, day) = toGregorian (localDay localTime)
+ (_, _, week) = toWeekDate (localDay localTime)
+ timeOfDay = localTimeOfDay localTime
+ in
+ shortWeekDayName week
+ ⊕ A.toAsciiBuilder "⊕ "
+ ⊕ shortMonthName month
+ ⊕ A.toAsciiBuilder " "
+ ⊕ show2 day
+ ⊕ A.toAsciiBuilder " "
+ ⊕ show2 (todHour timeOfDay)
+ ⊕ A.toAsciiBuilder ":"
+ ⊕ show2 (todMin timeOfDay)
+ ⊕ A.toAsciiBuilder ":"
+ ⊕ show2 (floor (todSec timeOfDay) ∷ Int)
+ ⊕ A.toAsciiBuilder " "
+ ⊕ show4 year
+
+{-# LANGUAGE
+ UnicodeSyntax
+ #-}
-- |This module provides functions to parse and format RFC 1123 date
-- and time formats.
--
--
-- > year ::= 4DIGIT
module Data.Time.RFC1123
- ( format
- , parse
+ ( -- * Formatting
+ toAscii
+ , toAsciiBuilder
+
+ -- * Parsing
+ , fromAscii
+ , rfc1123DateAndTime
)
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.RFC822 (showRFC822TimeZone)
import Data.Time.RFC1123.Internal
+import Prelude.Unicode
--- |Format a 'ZonedTime' in RFC 1123.
-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 [ shortWeekDayName week
- , ", "
- , show2 day
- , " "
- , shortMonthName month
- , " "
- , show4 year
- , " "
- , show2 (todHour timeOfDay)
- , ":"
- , show2 (todMin timeOfDay)
- , ":"
- , show2 (floor (todSec timeOfDay))
- , " "
- , showRFC822TimeZone timeZone
- ]
+-- |Convert a 'ZonedTime' to RFC 1123 date and time string.
+toAscii ∷ ZonedTime → Ascii
+toAscii = A.fromAsciiBuilder ∘ toAsciiBuilder
-- |Parse an RFC 1123 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 <- rfc1123DateAndTime
- _ <- P.eof
+ p = do zt ← rfc1123DateAndTime
+ P.endOfInput
return zt
-{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE
+ OverloadedStrings
+ , UnicodeSyntax
+ #-}
module Data.Time.RFC1123.Internal
( rfc1123DateAndTime
+ , toAsciiBuilder
)
where
-import Control.Monad
+import Data.Ascii (AsciiBuilder)
+import qualified Data.Ascii as A
import Data.Attoparsec.Char8
-import Data.Fixed
+import Data.Monoid.Unicode
import Data.Time
import Data.Time.Calendar.WeekDate
import Data.Time.HTTP.Common
-import Data.Time.RFC822.Internal
+import Data.Time.RFC822.Internal hiding (toAsciiBuilder)
-- |Parse an RFC 1123 date and time string.
-rfc1123DateAndTime :: Parser ZonedTime
+rfc1123DateAndTime ∷ Parser ZonedTime
rfc1123DateAndTime = dateTime
-dateTime :: Parser ZonedTime
-dateTime = do weekDay <- optionMaybe $
- do w <- shortWeekDayNameP
- _ <- string ", "
+dateTime ∷ Parser ZonedTime
+dateTime = do weekDay ← optionMaybe $
+ do w ← shortWeekDayNameP
+ _ ← string ", "
return w
- gregDay <- date
+ gregDay ← date
case weekDay of
Nothing
- -> return () -- No day in week exists.
+ → return ()
Just givenWD
- -> assertWeekDayIsGood givenWD gregDay
- (tod, timeZone) <- rfc822time
+ → assertWeekDayIsGood givenWD gregDay
+ (tod, timeZone) ← rfc822time
let lt = LocalTime gregDay tod
zt = ZonedTime lt timeZone
return zt
-date :: Stream s m Char => ParsecT s u m Day
-date = do day <- read2
- _ <- char ' '
- month <- shortMonthNameP
- _ <- char ' '
- year <- read4
- _ <- char ' '
+date ∷ Parser Day
+date = do day ← read2
+ _ ← char ' '
+ month ← shortMonthNameP
+ _ ← char ' '
+ year ← read4
+ _ ← char ' '
assertGregorianDateIsGood year month day
+
+-- |Convert a 'ZonedTime' to RFC 1123 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 " "
+ ⊕ show4 year
+ ⊕ A.toAsciiBuilder " "
+ ⊕ show2 (todHour timeOfDay)
+ ⊕ A.toAsciiBuilder ":"
+ ⊕ show2 (todMin timeOfDay)
+ ⊕ A.toAsciiBuilder ":"
+ ⊕ show2 (floor (todSec timeOfDay) ∷ Int)
+ ⊕ A.toAsciiBuilder " "
+ ⊕ showRFC822TimeZone timeZone