]> gitweb @ CieloNegro.org - time-http.git/blobdiff - Data/Time/RFC822/Internal.hs
RFC822.Internal
[time-http.git] / Data / Time / RFC822 / Internal.hs
index 607cf88c0277ee2cb0750c9b7c61a8eac10a37b5..4fd701ae29e8b7244ca6bcfa3ed76d14314e5365 100644 (file)
@@ -1,25 +1,53 @@
 {-# LANGUAGE
-    OverloadedStrings
+    FlexibleInstances
+  , MultiParamTypeClasses
+  , OverloadedStrings
+  , TemplateHaskell
   , UnicodeSyntax
   #-}
--- |Internal functions for "Data.Time.RFC822".
 module Data.Time.RFC822.Internal
-    ( rfc822DateAndTime
-    , rfc822time
-    , showRFC822TimeZone
-    , toAsciiBuilder
+    ( RFC822
+    , rfc822DateAndTime
+    , rfc822Time
     )
     where
 import Control.Applicative
-import Data.Ascii (AsciiBuilder)
+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
 rfc822DateAndTime = dateTime
@@ -35,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
@@ -49,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)
@@ -89,13 +116,6 @@ zone = choice [ string "UT"  *> return (TimeZone 0 False "UT" )
               , read4digitsTZ
               ]
 
--- |No need to explain.
-showRFC822TimeZone ∷ TimeZone → AsciiBuilder
-showRFC822TimeZone tz
-    | timeZoneMinutes tz ≡ 0 = A.toAsciiBuilder "GMT"
-    | otherwise              = show4digitsTZ tz
-
--- |Convert a 'ZonedTime' to RFC 822 date and time string.
 toAsciiBuilder ∷ ZonedTime → AsciiBuilder
 toAsciiBuilder zonedTime
     = let localTime          = zonedTimeToLocalTime zonedTime
@@ -118,4 +138,10 @@ toAsciiBuilder zonedTime
         ⊕ A.toAsciiBuilder ":"
         ⊕ show2 (floor (todSec timeOfDay) ∷ Int)
         ⊕ A.toAsciiBuilder " "
-        ⊕ showRFC822TimeZone timeZone
+        ⊕ 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 |])
+               ]