]> gitweb @ CieloNegro.org - time-http.git/blobdiff - Data/Time/RFC1123.hs
RFC1123
[time-http.git] / Data / Time / RFC1123.hs
index abb0a6d53e882eee4e70aaf27e3ea928a1cbce92..c00bf732b64e59e2a88e7e387e9fec39833ff491 100644 (file)
+{-# LANGUAGE
+    FlexibleInstances
+  , MultiParamTypeClasses
+  , OverloadedStrings
+  , TemplateHaskell
+  , UnicodeSyntax
+  #-}
+-- |This module provides functions to parse and format RFC 1123 date
+-- and time formats.
+--
+-- The format is basically same as RFC 822, but the syntax for @date@
+-- is changed from:
+--
+-- > year ::= 2DIGIT
+--
+-- to:
+--
+-- > year ::= 4DIGIT
 module Data.Time.RFC1123
-    ( format
-    , parse
+    ( RFC1123
+    , rfc1123DateAndTime
     )
     where
-
-import qualified Text.Parsec as P
-
+import Control.Applicative
+import Data.Ascii (Ascii, AsciiBuilder)
+import qualified Data.Ascii as A
+import Data.Attoparsec.Char8
+import Data.Convertible.Base
+import Data.Monoid.Unicode
+import Data.Tagged
 import Data.Time
 import Data.Time.Calendar.WeekDate
 import Data.Time.HTTP.Common
-import Data.Time.RFC1123.Parsec
+import Data.Time.RFC822
+import Prelude.Unicode
+
+-- FIXME: doc
+data RFC1123
+
+instance ConvertSuccess ZonedTime (Tagged RFC1123 Ascii) where
+    {-# INLINE convertSuccess #-}
+    convertSuccess = (A.fromAsciiBuilder <$>) ∘ cs
+
+instance ConvertSuccess ZonedTime (Tagged RFC1123 AsciiBuilder) where
+    {-# INLINE convertSuccess #-}
+    convertSuccess = Tagged ∘ toAsciiBuilder
 
-{-
-         The syntax for the date is hereby changed to:
+instance ConvertAttempt (Tagged RFC1123 Ascii) ZonedTime where
+    {-# INLINE convertAttempt #-}
+    convertAttempt = parseAttempt' rfc1123DateAndTime ∘ untag
 
-            date = 1*2DIGIT month 2*4DIGIT
--}
+-- |Parse an RFC 1123 date and time string.
+rfc1123DateAndTime ∷ Parser ZonedTime
+rfc1123DateAndTime = dateTime
 
-format :: ZonedTime -> String
-format zonedTime
+dateTime ∷ Parser ZonedTime
+dateTime = do weekDay ← optionMaybe $
+                         do w ← shortWeekDayNameP
+                            _ ← string ", "
+                            return w
+              gregDay ← date
+              case weekDay of
+                Nothing
+                    → return ()
+                Just givenWD
+                    → assertWeekDayIsGood givenWD gregDay
+              (tod, timeZone) ← rfc822Time
+              let lt = LocalTime gregDay tod
+                  zt = ZonedTime lt timeZone
+              return zt
+
+date ∷ Parser Day
+date = do day   ← read2
+          _     ← char ' '
+          month ← shortMonthNameP
+          _     ← char ' '
+          year  ← read4
+          _     ← char ' '
+          assertGregorianDateIsGood year month day
+
+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
-        concat [ shortWeekDayName week
-               , ", "
-               , show2 day
-               , " "
-               , shortMonthName month
-               , " "
-               , show4 year
-               , " "
-               , show2 (todHour timeOfDay)
-               , ":"
-               , show2 (todMin timeOfDay)
-               , ":"
-               , show2 (floor (todSec timeOfDay))
-               , " "
-               , show4digitsTZ timeZone
-               ]
+        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 " "
+        ⊕ untag (cs timeZone ∷ Tagged RFC822 AsciiBuilder)
 
-parse :: String -> Maybe ZonedTime
-parse src = case P.parse p "" src of
-              Right zt -> Just zt
-              Left  _  -> Nothing
-    where
-      p = do zt <- rfc1123DateAndTime
-             _  <- P.eof
-             return zt
+deriveAttempts [ ([t| ZonedTime |], [t| Tagged RFC1123 Ascii        |])
+               , ([t| ZonedTime |], [t| Tagged RFC1123 AsciiBuilder |])
+               ]