module Network.Multipart.Header (
Headers,
HeaderName(..),
HeaderValue(..),
pHeaders,
ContentType(..),
getContentType,
parseContentType,
showContentType,
ContentTransferEncoding(..),
getContentTransferEncoding,
ContentDisposition(..),
getContentDisposition,
parseM,
caseInsensitiveEq,
caseInsensitiveCompare,
lexeme, ws1, p_token
) where
import Control.Monad
import Data.Char
import Data.List
import Data.Monoid
import Text.ParserCombinators.Parsec
type Headers = [(HeaderName, String)]
newtype HeaderName = HeaderName String deriving (Show)
instance Eq HeaderName where
HeaderName x == HeaderName y = map toLower x == map toLower y
instance Ord HeaderName where
HeaderName x `compare` HeaderName y = map toLower x `compare` map toLower y
class HeaderValue a where
parseHeaderValue :: Parser a
prettyHeaderValue :: a -> String
pHeaders :: Parser Headers
pHeaders = many pHeader
pHeader :: Parser (HeaderName, String)
pHeader =
do name <- many1 headerNameChar
_ <- char ':'
_ <- many ws1
line <- lineString
_ <- crLf
extraLines <- many extraFieldLine
return (HeaderName name, concat (line:extraLines))
extraFieldLine :: Parser String
extraFieldLine =
do sp <- ws1
line <- lineString
_ <- crLf
return (sp:line)
getHeaderValue :: (Monad m, HeaderValue a) => String -> Headers -> m a
getHeaderValue h hs = lookupM (HeaderName h) hs >>= parseM parseHeaderValue h
showParameters :: [(String,String)] -> String
showParameters = concatMap f
where f (n,v) = "; " ++ n ++ "=\"" ++ concatMap esc v ++ "\""
esc '\\' = "\\\\"
esc '"' = "\\\""
esc c | c `elem` ['\\','"'] = '\\':[c]
| otherwise = [c]
p_parameter :: Parser (String,String)
p_parameter = try $
do _ <- lexeme $ char ';'
p_name <- lexeme $ p_token
when (p_name == "q") pzero
_ <- lexeme $ char '='
let litStr = if p_name == "filename"
then buggyLiteralString
else literalString
p_value <- litStr <|> p_token
return (map toLower p_name, p_value)
data ContentType =
ContentType {
ctType :: String,
ctSubtype :: String,
ctParameters :: [(String, String)]
}
deriving (Show, Read)
instance Eq ContentType where
x == y = ctType x `caseInsensitiveEq` ctType y
&& ctSubtype x `caseInsensitiveEq` ctSubtype y
&& ctParameters x == ctParameters y
instance Ord ContentType where
x `compare` y = mconcat [ctType x `caseInsensitiveCompare` ctType y,
ctSubtype x `caseInsensitiveCompare` ctSubtype y,
ctParameters x `compare` ctParameters y]
instance HeaderValue ContentType where
parseHeaderValue =
do _ <- many ws1
c_type <- p_token
_ <- char '/'
c_subtype <- lexeme $ p_token
c_parameters <- many p_parameter
return $ ContentType (map toLower c_type) (map toLower c_subtype) c_parameters
prettyHeaderValue (ContentType x y ps) = x ++ "/" ++ y ++ showParameters ps
parseContentType :: Monad m => String -> m ContentType
parseContentType = parseM parseHeaderValue "Content-type"
showContentType :: ContentType -> String
showContentType = prettyHeaderValue
getContentType :: Monad m => Headers -> m ContentType
getContentType = getHeaderValue "content-type"
data ContentTransferEncoding =
ContentTransferEncoding String
deriving (Show, Read, Eq, Ord)
instance HeaderValue ContentTransferEncoding where
parseHeaderValue =
do _ <- many ws1
c_cte <- p_token
return $ ContentTransferEncoding (map toLower c_cte)
prettyHeaderValue (ContentTransferEncoding s) = s
getContentTransferEncoding :: Monad m => Headers -> m ContentTransferEncoding
getContentTransferEncoding = getHeaderValue "content-transfer-encoding"
data ContentDisposition =
ContentDisposition String [(String, String)]
deriving (Show, Read, Eq, Ord)
instance HeaderValue ContentDisposition where
parseHeaderValue =
do _ <- many ws1
c_cd <- p_token
c_parameters <- many p_parameter
return $ ContentDisposition (map toLower c_cd) c_parameters
prettyHeaderValue (ContentDisposition t hs) =
t ++ concat ["; " ++ n ++ "=" ++ quote v | (n,v) <- hs]
where quote x = "\"" ++ x ++ "\""
getContentDisposition :: Monad m => Headers -> m ContentDisposition
getContentDisposition = getHeaderValue "content-disposition"
parseM :: Monad m => Parser a -> SourceName -> String -> m a
parseM p n inp =
case parse p n inp of
Left e -> fail (show e)
Right x -> return x
lookupM :: (Monad m, Eq a, Show a) => a -> [(a,b)] -> m b
lookupM n = maybe (fail ("No such field: " ++ show n)) return . lookup n
caseInsensitiveEq :: String -> String -> Bool
caseInsensitiveEq x y = map toLower x == map toLower y
caseInsensitiveCompare :: String -> String -> Ordering
caseInsensitiveCompare x y = map toLower x `compare` map toLower y
ws1 :: Parser Char
ws1 = oneOf " \t"
lexeme :: Parser a -> Parser a
lexeme p = do x <- p; _ <- many ws1; return x
crLf :: Parser String
crLf = try (string "\n\r" <|> string "\r\n") <|> string "\n" <|> string "\r"
lineString :: Parser String
lineString = many (noneOf "\n\r")
literalString :: Parser String
literalString = do _ <- char '\"'
str <- many (noneOf "\"\\" <|> quoted_pair)
_ <- char '\"'
return str
buggyLiteralString :: Parser String
buggyLiteralString =
do _ <- char '\"'
str <- manyTill anyChar (try lastQuote)
return str
where lastQuote = do _ <- char '\"'
notFollowedBy (try (many (noneOf "\"") >> char '\"'))
headerNameChar :: Parser Char
headerNameChar = noneOf "\n\r:"
tspecials, tokenchar :: [Char]
tspecials = "()<>@,;:\\\"/[]?="
tokenchar = "!\"#$%&'()*+,-./0123456789:;<=>?@ABCDEFGHIJKLMNOPQRSTUVWXYZ[\\]^_`abcdefghijklmnopqrstuvwxyz{|}~" \\ tspecials
p_token :: Parser String
p_token = many1 (oneOf tokenchar)
text_chars :: [Char]
text_chars = map chr ([1..9] ++ [11,12] ++ [14..127])
p_text :: Parser Char
p_text = oneOf text_chars
quoted_pair :: Parser Char
quoted_pair = do _ <- char '\\'
p_text