{-# LANGUAGE
- UnboxedTuples
+ OverloadedStrings
, UnicodeSyntax
#-}
{-# OPTIONS_HADDOCK prune #-}
, mimeTypeListP
)
where
+import Control.Applicative
import Data.Ascii (Ascii, CIAscii)
import qualified Data.Ascii as A
-import qualified Data.ByteString.Lazy as B
+import Data.Attoparsec.Char8 as P
+import qualified Data.ByteString.Char8 as C8
+import Data.Monoid.Unicode
import Network.HTTP.Lucu.Parser.Http
import Network.HTTP.Lucu.Utils
import Prelude hiding (min)
+import Prelude.Unicode
-- |@'MIMEType' \"major\" \"minor\" [(\"name\", \"value\")]@
-- represents \"major\/minor; name=value\".
data MIMEType = MIMEType {
- mtMajor :: !CIAscii
- , mtMinor :: !CIAscii
- , mtParams :: ![ (CIAscii, Ascii) ]
+ mtMajor ∷ !CIAscii
+ , mtMinor ∷ !CIAscii
+ , mtParams ∷ ![ (CIAscii, Ascii) ]
} deriving (Eq, Show)
-- |Convert a 'MIMEType' to 'Ascii'.
printMIMEType ∷ MIMEType → Ascii
printMIMEType (MIMEType maj min params)
= A.fromAsciiBuilder $
- ( A.toAsciiBuilder maj ⊕
+ ( A.toAsciiBuilder (A.fromCIAscii maj) ⊕
A.toAsciiBuilder "/" ⊕
- A.toAsciiBuilder min ⊕
+ A.toAsciiBuilder (A.fromCIAscii min) ⊕
if null params then
(∅)
else
printPair (name, value)
= A.toAsciiBuilder (A.fromCIAscii name) ⊕
A.toAsciiBuilder "=" ⊕
- if any ((¬) ∘ isToken) value then
+ if C8.any ((¬) ∘ isToken) (A.toByteString value) then
quoteStr value
else
A.toAsciiBuilder value
--- |Parse 'MIMEType' from a 'Prelude.String'. This function throws an
+-- |Parse 'MIMEType' from an 'Ascii'. This function throws an
-- exception for parse error.
-parseMIMEType :: String -> MIMEType
-parseMIMEType str = case parseStr mimeTypeP str of
- (# Success t, r #) -> if B.null r
- then t
- else error ("unparsable MIME Type: " ++ str)
- (# _ , _ #) -> error ("unparsable MIME Type: " ++ str)
+parseMIMEType ∷ Ascii → MIMEType
+parseMIMEType str
+ = let p = do t ← mimeTypeP
+ endOfInput
+ return t
+ bs = A.toByteString str
+ in
+ case parseOnly p bs of
+ Right t → t
+ Left err → error ("unparsable MIME Type: " ⧺ C8.unpack bs ⧺ ": " ⧺ err)
-
-mimeTypeP :: Parser MIMEType
-mimeTypeP = allowEOF $!
- do maj <- token
- _ <- char '/'
- min <- token
- params <- many paramP
+mimeTypeP ∷ Parser MIMEType
+mimeTypeP = try $
+ do maj ← A.toCIAscii <$> token
+ _ ← char '/'
+ min ← A.toCIAscii <$> token
+ params ← P.many paramP
return $ MIMEType maj min params
where
- paramP :: Parser (String, String)
- paramP = do _ <- many lws
- _ <- char ';'
- _ <- many lws
- name <- token
- _ <- char '='
- value <- token <|> quotedStr
+ paramP ∷ Parser (CIAscii, Ascii)
+ paramP = try $
+ do skipMany lws
+ _ ← char ';'
+ skipMany lws
+ name ← A.toCIAscii <$> token
+ _ ← char '='
+ value ← token <|> quotedStr
return (name, value)
-mimeTypeListP :: Parser [MIMEType]
-mimeTypeListP = allowEOF $! listOf mimeTypeP
+mimeTypeListP ∷ Parser [MIMEType]
+mimeTypeListP = listOf mimeTypeP
-- |> joinWith ":" ["ab", "c", "def"]
-- > ==> "ab:c:def"
-joinWith ∷ Ascii → [Ascii] → AsciiBuilder
+joinWith ∷ Ascii → [AsciiBuilder] → AsciiBuilder
{-# INLINEABLE joinWith #-}
joinWith sep = flip go (∅)
where
- go ∷ [Ascii] → A.AsciiBuilder → A.AsciiBuilder
+ go ∷ [AsciiBuilder] → AsciiBuilder → AsciiBuilder
{-# INLINE go #-}
go [] ab = ab
- go (x:[]) ab = ab ⊕ A.toAsciiBuilder x
- go (x:xs) ab = go xs ( ab ⊕
- A.toAsciiBuilder sep ⊕
- A.toAsciiBuilder x )
+ go (x:[]) ab = ab ⊕ x
+ go (x:xs) ab = go xs (ab ⊕ A.toAsciiBuilder sep ⊕ x)
-- |> quoteStr "abc"
-- > ==> "\"abc\""