]> gitweb @ CieloNegro.org - time-http.git/blobdiff - Data/Time/RFC822/Internal.hs
RFC822.Internal
[time-http.git] / Data / Time / RFC822 / Internal.hs
index 297120a40c51fdede753bd57e9a5770881b99d4a..4fd701ae29e8b7244ca6bcfa3ed76d14314e5365 100644 (file)
@@ -1,16 +1,52 @@
 {-# LANGUAGE
-    OverloadedStrings
+    FlexibleInstances
+  , MultiParamTypeClasses
+  , OverloadedStrings
+  , TemplateHaskell
   , UnicodeSyntax
   #-}
 module Data.Time.RFC822.Internal
-    ( rfc822DateAndTime
-    , rfc822time
+    ( RFC822
+    , rfc822DateAndTime
+    , rfc822Time
     )
     where
 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 Prelude.Unicode
+
+-- |FIXME: docs
+data RFC822
+
+instance ConvertSuccess ZonedTime (Tagged RFC822 Ascii) where
+    {-# INLINE convertSuccess #-}
+    convertSuccess = (A.fromAsciiBuilder <$>) ∘ cs
+
+instance ConvertSuccess ZonedTime (Tagged RFC822 AsciiBuilder) where
+    {-# INLINE convertSuccess #-}
+    convertSuccess = Tagged ∘ toAsciiBuilder
+
+instance ConvertSuccess TimeZone (Tagged RFC822 Ascii) where
+    {-# INLINE convertSuccess #-}
+    convertSuccess = (A.fromAsciiBuilder <$>) ∘ cs
+
+instance ConvertSuccess TimeZone (Tagged RFC822 AsciiBuilder) where
+    {-# INLINE convertSuccess #-}
+    convertSuccess tz
+        | timeZoneMinutes tz ≡ 0 = Tagged $ A.toAsciiBuilder "GMT"
+        | otherwise              = Tagged $ show4digitsTZ tz
+
+instance ConvertAttempt (Tagged RFC822 Ascii) ZonedTime where
+    {-# INLINE convertAttempt #-}
+    convertAttempt = parseAttempt' rfc822DateAndTime ∘ untag
 
 -- |Parse an RFC 822 date and time string.
 rfc822DateAndTime ∷ Parser ZonedTime
@@ -27,7 +63,7 @@ dateTime = do weekDay ← optionMaybe $
                     -> return ()
                 Just givenWD
                     -> assertWeekDayIsGood givenWD gregDay
-              (tod, timeZone) ← rfc822time
+              (tod, timeZone) ← rfc822Time
               let lt = LocalTime gregDay tod
                   zt = ZonedTime lt timeZone
               return zt
@@ -41,9 +77,8 @@ date = do day   ← read2
           _     ← char ' '
           assertGregorianDateIsGood year month day
 
--- |Parse the time and time zone of an RFC 822 date and time string.
-rfc822time ∷ Parser (TimeOfDay, TimeZone)
-rfc822time = do tod ← hms
+rfc822Time ∷ Parser (TimeOfDay, TimeZone)
+rfc822Time = do tod ← hms
                 _   ← char ' '
                 tz  ← zone
                 return (tod, tz)
@@ -80,3 +115,33 @@ zone = choice [ string "UT"  *> return (TimeZone 0 False "UT" )
               , char 'Y' *> return (TimeZone ( 12  * 60) False "Y")
               , read4digitsTZ
               ]
+
+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 " "
+        ⊕ show2 (year `mod` 100)
+        ⊕ 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 RFC822 Ascii        |])
+               , ([t| ZonedTime |], [t| Tagged RFC822 AsciiBuilder |])
+               , ([t| TimeZone  |], [t| Tagged RFC822 Ascii        |])
+               , ([t| TimeZone  |], [t| Tagged RFC822 AsciiBuilder |])
+               ]