]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/ETag.hs
Code clean-up using convertible-text
[Lucu.git] / Network / HTTP / Lucu / ETag.hs
index b8191a353fd86dd05c325b3d99d872d5a34e3e9b..3ebfc1d91b35b3f7e676571d0ed981a813b67dbf 100644 (file)
@@ -1,15 +1,15 @@
 {-# LANGUAGE
     DeriveDataTypeable
+  , FlexibleInstances
+  , MultiParamTypeClasses
   , OverloadedStrings
   , RecordWildCards
   , TemplateHaskell
   , UnicodeSyntax
   #-}
--- |Entity tags
+-- |An internal module for entity tags.
 module Network.HTTP.Lucu.ETag
     ( ETag(..)
-    , parseETag
-    , printETag
 
     , strongETag
     , weakETag
@@ -20,20 +20,22 @@ module Network.HTTP.Lucu.ETag
 import Control.Applicative
 import Control.Monad
 import Data.Ascii (Ascii, AsciiBuilder)
-import qualified Data.Ascii as A
 import Data.Attoparsec.Char8
+import Data.Convertible.Base
+import Data.Convertible.Instances.Ascii ()
+import Data.Convertible.Utils
 import Data.Data
 import Data.Monoid.Unicode
 import Language.Haskell.TH.Syntax
-import Network.HTTP.Lucu.Parser
+import Network.HTTP.Lucu.OrphanInstances ()
 import Network.HTTP.Lucu.Parser.Http hiding (token)
 import Network.HTTP.Lucu.Utils
 import Prelude.Unicode
 
 -- |An entity tag consists of a weakness flag and an opaque string.
 data ETag = ETag {
-      -- |The weakness flag. Weak tags looks like W\/\"blahblah\" and
-      -- strong tags are like \"blahblah\". See:
+      -- |The weakness flag. Weak tags looks like @W\/\"blahblah\"@
+      -- and strong tags are like @\"blahblah\"@. See:
       -- <http://www.w3.org/Protocols/rfc2616/rfc2616-sec13.html#sec13.3.3>
       etagIsWeak ∷ !Bool
       -- |An opaque string. Only characters from 0x20 (sp) to 0x7e (~)
@@ -45,30 +47,28 @@ instance Lift ETag where
     lift (ETag {..})
         = [| ETag {
                etagIsWeak = $(lift etagIsWeak)
-             , etagToken  = $(liftAscii etagToken)
+             , etagToken  = $(lift etagToken )
              }
            |]
 
--- |Convert an 'ETag' to an 'AsciiBuilder'.
-printETag ∷ ETag → AsciiBuilder
-{-# INLINEABLE printETag #-}
-printETag et
-    = ( if etagIsWeak et then
-            A.toAsciiBuilder "W/"
-        else
-            (∅)
-      )
-      ⊕
-      quoteStr (etagToken et)
+instance ConvertSuccess ETag Ascii where
+    {-# INLINE convertSuccess #-}
+    convertSuccess = convertSuccessVia ((⊥) ∷ AsciiBuilder)
 
--- |Parse 'Etag' from an 'Ascii'. This functions throws an exception
--- for parse error.
-parseETag ∷ Ascii → ETag
-{-# INLINEABLE parseETag #-}
-parseETag str
-    = case parseOnly (finishOff eTag) $ A.toByteString str of
-        Right et → et
-        Left err → error ("unparsable ETag: " ⧺ A.toString str ⧺ ": " ⧺ err)
+instance ConvertSuccess ETag AsciiBuilder where
+    {-# INLINE convertSuccess #-}
+    convertSuccess (ETag {..})
+        = ( if etagIsWeak then
+                cs ("W/" ∷ Ascii)
+            else
+                (∅)
+          )
+          ⊕
+          quoteStr etagToken
+
+deriveAttempts [ ([t| ETag |], [t| Ascii        |])
+               , ([t| ETag |], [t| AsciiBuilder |])
+               ]
 
 -- |This is equivalent to @'ETag' 'False'@. If you want to generate an
 -- ETag from a file, try using