]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/ETag.hs
Examples now compile.
[Lucu.git] / Network / HTTP / Lucu / ETag.hs
index acc496fa2113ef6a0848e570dffd56c453566f4b..f7ef8387c7044d02acc1451a7fa0e140c3197c60 100644 (file)
@@ -2,12 +2,10 @@
     OverloadedStrings
   , UnicodeSyntax
   #-}
-{-# OPTIONS_HADDOCK prune #-}
-
 -- |Manipulation of entity tags.
 module Network.HTTP.Lucu.ETag
     ( ETag(..)
-
+    , parseETag
     , printETag
 
     , strongETag
@@ -16,14 +14,15 @@ module Network.HTTP.Lucu.ETag
     , eTagListP
     )
     where
+import Control.Applicative
 import Control.Monad
-import Control.Monad.Unicode
-import Data.Ascii (Ascii)
+import Data.Ascii (Ascii, AsciiBuilder)
 import qualified Data.Ascii as A
 import Data.Attoparsec.Char8
 import Data.Monoid.Unicode
 import Network.HTTP.Lucu.Parser.Http hiding (token)
 import Network.HTTP.Lucu.Utils
+import Prelude.Unicode
 
 -- |An entity tag is made of a weakness flag and a opaque string.
 data ETag = ETag {
@@ -35,34 +34,53 @@ data ETag = ETag {
     , etagToken  ∷ !Ascii
     } deriving (Eq, Show)
 
--- |Convert an 'ETag' to 'Ascii'.
-printETag ∷ ETag → Ascii
+-- |Convert an 'ETag' to 'AsciiBuilder'.
+printETag ∷ ETag → AsciiBuilder
+{-# INLINEABLE printETag #-}
 printETag et
-    = A.fromAsciiBuilder $
-      ( ( if etagIsWeak et then
-              A.toAsciiBuilder "W/"
-          else
-              (∅)
-        )
-        ⊕
-        quoteStr (etagToken et) )
+    = ( if etagIsWeak et then
+            A.toAsciiBuilder "W/"
+        else
+            (∅)
+      )
+      ⊕
+      quoteStr (etagToken et)
+
+-- |Parse 'Etag' from an 'Ascii'. This functions throws an exception
+-- for parse error.
+parseETag ∷ Ascii → ETag
+{-# INLINEABLE parseETag #-}
+parseETag str
+    = case parseOnly p $ A.toByteString str of
+        Right et → et
+        Left err → error ("unparsable ETag: " ⧺ A.toString str ⧺ ": " ⧺ err)
+    where
+      p ∷ Parser ETag
+      {-# INLINE p #-}
+      p = do et ← eTagP
+             endOfInput
+             return et
 
 -- |This is equivalent to @'ETag' 'Prelude.False'@. If you want to
 -- generate an ETag from a file, try using
 -- 'Network.HTTP.Lucu.StaticFile.generateETagFromFile'.
 strongETag ∷ Ascii → ETag
+{-# INLINE strongETag #-}
 strongETag = ETag False
 
 -- |This is equivalent to @'ETag' 'Prelude.True'@.
 weakETag ∷ Ascii → ETag
+{-# INLINE weakETag #-}
 weakETag = ETag True
 
 eTagP ∷ Parser ETag
-eTagP = do isWeak ← option False (string "W/" ≫ return True)
+{-# INLINEABLE eTagP #-}
+eTagP = do isWeak ← option False (string "W/" *> return True)
            str    ← quotedStr
            return $ ETag isWeak str
 
 eTagListP ∷ Parser [ETag]
+{-# INLINEABLE eTagListP #-}
 eTagListP = do xs ← listOf eTagP
                when (null xs) $
                    fail "empty list of ETags"