]> gitweb @ CieloNegro.org - time-http.git/blobdiff - Data/Time/RFC1123.hs
RFC1123
[time-http.git] / Data / Time / RFC1123.hs
index fb7839d034bbc9dc7aaae2369170f00e59a568f8..c00bf732b64e59e2a88e7e387e9fec39833ff491 100644 (file)
@@ -1,5 +1,9 @@
 {-# LANGUAGE
-    UnicodeSyntax
+    FlexibleInstances
+  , MultiParamTypeClasses
+  , OverloadedStrings
+  , TemplateHaskell
+  , UnicodeSyntax
   #-}
 -- |This module provides functions to parse and format RFC 1123 date
 -- and time formats.
 --
 -- > year ::= 4DIGIT
 module Data.Time.RFC1123
-    ( -- * Formatting
-      toAscii
-    , toAsciiBuilder
-
-      -- * Parsing
-    , fromAscii
+    ( RFC1123
     , rfc1123DateAndTime
     )
     where
-import Data.Ascii (Ascii)
+import Control.Applicative
+import Data.Ascii (Ascii, AsciiBuilder)
 import qualified Data.Ascii as A
-import qualified Data.Attoparsec.Char8 as P
+import Data.Attoparsec.Char8
+import Data.Convertible.Base
+import Data.Monoid.Unicode
+import Data.Tagged
 import Data.Time
-import Data.Time.RFC1123.Internal
+import Data.Time.Calendar.WeekDate
+import Data.Time.HTTP.Common
+import Data.Time.RFC822
 import Prelude.Unicode
 
--- |Convert a 'ZonedTime' to RFC 1123 date and time string.
-toAscii ∷ ZonedTime → Ascii
-toAscii = A.fromAsciiBuilder ∘ toAsciiBuilder
+-- FIXME: doc
+data RFC1123
 
--- |Parse an RFC 1123 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 ← rfc1123DateAndTime
-             P.endOfInput
-             return zt
+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
+
+instance ConvertAttempt (Tagged RFC1123 Ascii) ZonedTime where
+    {-# INLINE convertAttempt #-}
+    convertAttempt = parseAttempt' rfc1123DateAndTime ∘ untag
+
+-- |Parse an RFC 1123 date and time string.
+rfc1123DateAndTime ∷ Parser ZonedTime
+rfc1123DateAndTime = dateTime
+
+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
+        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)
+
+deriveAttempts [ ([t| ZonedTime |], [t| Tagged RFC1123 Ascii        |])
+               , ([t| ZonedTime |], [t| Tagged RFC1123 AsciiBuilder |])
+               ]