{-# LANGUAGE OverloadedStrings #-}
module Network.Multipart
(
MultiPart(..), BodyPart(..)
, parseMultipartBody, hGetMultipartBody
, showMultipartBody
, Headers , HeaderName(..)
, ContentType(..), ContentTransferEncoding(..)
, ContentDisposition(..)
, parseContentType
, getContentType
, getContentTransferEncoding
, getContentDisposition
) where
import Control.Monad
import Data.List (intersperse)
import Data.Maybe
import System.IO (Handle)
import Network.Multipart.Header
import qualified Data.ByteString.Lazy.Char8 as BS
import Data.ByteString.Lazy.Char8 (ByteString)
import Data.ByteString.Lazy.Search (breakOn)
data MultiPart = MultiPart [BodyPart]
deriving (Show, Eq, Ord)
data BodyPart = BodyPart Headers ByteString
deriving (Show, Eq, Ord)
parseMultipartBody :: String
-> ByteString -> MultiPart
parseMultipartBody b =
MultiPart . mapMaybe parseBodyPart . splitParts (BS.pack b)
hGetMultipartBody :: String
-> Handle
-> IO MultiPart
hGetMultipartBody b = liftM (parseMultipartBody b) . BS.hGetContents
parseBodyPart :: ByteString -> Maybe BodyPart
parseBodyPart s = do
let (hdr,bdy) = splitAtEmptyLine s
hs <- parseM pHeaders "<input>" (BS.unpack hdr)
return $ BodyPart hs bdy
showMultipartBody :: String -> MultiPart -> ByteString
showMultipartBody b (MultiPart bs) =
unlinesCRLF $ foldr (\x xs -> d:showBodyPart x:xs) [c,BS.empty] bs
where d = BS.pack ("--" ++ b)
c = BS.pack ("--" ++ b ++ "--")
showBodyPart :: BodyPart -> ByteString
showBodyPart (BodyPart hs c) =
unlinesCRLF $ [BS.pack (n++": "++v) | (HeaderName n,v) <- hs] ++ [BS.empty,c]
splitParts :: ByteString
-> ByteString
-> [ByteString]
splitParts b = spl . dropPreamble b
where
spl x = case splitAtBoundary b x of
Nothing -> []
Just (s1,d,s2) | isClose b d -> [s1]
| otherwise -> s1:spl s2
dropPreamble :: ByteString
-> ByteString
-> ByteString
dropPreamble b s = case splitAtBoundary b s of
Nothing -> BS.empty
Just (_,_,v) -> v
splitAtBoundary :: ByteString
-> ByteString
-> Maybe (ByteString,ByteString,ByteString)
splitAtBoundary b s =
let b' = BS.append "--" b
bcrlf = BS.append "\r\n" b'
prefix = if BS.isPrefixOf b' s then b'
else bcrlf
(before, t) = breakOn (BS.toStrict prefix) s
in case BS.stripPrefix prefix t of
Nothing -> Nothing
Just t' ->
let after = case BS.stripPrefix "\r\n" t' of
Nothing -> t'
Just t'' -> t''
in Just (before, prefix, after)
isClose :: ByteString
-> ByteString
-> Bool
isClose b s = BS.isPrefixOf (BS.append "--" (BS.append b "--")) s
crlf :: ByteString
crlf = BS.pack "\r\n"
unlinesCRLF :: [ByteString] -> ByteString
unlinesCRLF = BS.concat . intersperse crlf
splitAtEmptyLine :: ByteString -> (ByteString, ByteString)
splitAtEmptyLine s =
let blank = "\r\n\r\n"
(before, after) = breakOn (BS.toStrict blank) s
in case BS.stripPrefix blank after of
Nothing -> (before, after)
Just after' -> (BS.append before "\r\n", after')