module Network.Multipart
(
MultiPart(..), BodyPart(..)
, parseMultipartBody, hGetMultipartBody
, showMultipartBody
, Headers , HeaderName(..)
, ContentType(..), ContentTransferEncoding(..)
, ContentDisposition(..)
, parseContentType
, getContentType
, getContentTransferEncoding
, getContentDisposition
) where
import Control.Monad
import Data.Int (Int64)
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)
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 | BS.null s = BS.empty
| isBoundary b s = dropLine s
| otherwise = dropPreamble b (dropLine s)
splitAtBoundary :: ByteString
-> ByteString
-> Maybe (ByteString,ByteString,ByteString)
splitAtBoundary b s = spl 0
where
spl i = case findCRLF (BS.drop i s) of
Nothing -> Nothing
Just (j,l) | isBoundary b s2 -> Just (s1,d,s3)
| otherwise -> spl (i+j+l)
where
s1 = BS.take (i+j) s
s2 = BS.drop (i+j+l) s
(d,s3) = splitAtCRLF s2
isBoundary :: ByteString
-> ByteString
-> Bool
isBoundary b s = startsWithDashes s && b `BS.isPrefixOf` BS.drop 2 s
isClose :: ByteString
-> ByteString
-> Bool
isClose b s = startsWithDashes (BS.drop (2+BS.length b) s)
startsWithDashes :: ByteString -> Bool
startsWithDashes s = BS.pack "--" `BS.isPrefixOf` s
crlf :: ByteString
crlf = BS.pack "\r\n"
unlinesCRLF :: [ByteString] -> ByteString
unlinesCRLF = BS.concat . intersperse crlf
dropLine :: ByteString -> ByteString
dropLine s = snd (splitAtCRLF s)
splitAtEmptyLine :: ByteString -> (ByteString, ByteString)
splitAtEmptyLine s | startsWithCRLF s = (BS.empty, dropCRLF s)
| otherwise = spl 0
where
spl i = case findCRLF (BS.drop i s) of
Nothing -> (s, BS.empty)
Just (j,l) | startsWithCRLF s2 -> (s1, dropCRLF s2)
| otherwise -> spl (i+j+l)
where (s1,s2) = BS.splitAt (i+j+l) s
splitAtCRLF :: ByteString
-> (ByteString,ByteString)
splitAtCRLF s = case findCRLF s of
Nothing -> (s,BS.empty)
Just (i,l) -> (s1, BS.drop l s2)
where (s1,s2) = BS.splitAt i s
findCRLF :: ByteString
-> Maybe (Int64,Int64)
findCRLF s =
case findCRorLF s of
Nothing -> Nothing
Just j | BS.null (BS.drop (j+1) s) -> Just (j,1)
Just j -> case (BS.index s j, BS.index s (j+1)) of
('\n','\r') -> Just (j,2)
('\r','\n') -> Just (j,2)
_ -> Just (j,1)
findCRorLF :: ByteString -> Maybe Int64
findCRorLF s = BS.findIndex (\c -> c == '\n' || c == '\r') s
startsWithCRLF :: ByteString -> Bool
startsWithCRLF s = not (BS.null s) && (c == '\n' || c == '\r')
where c = BS.index s 0
dropCRLF :: ByteString -> ByteString
dropCRLF s | BS.null s = BS.empty
| BS.null (BS.drop 1 s) = BS.empty
| c0 == '\n' && c1 == '\r' = BS.drop 2 s
| c0 == '\r' && c1 == '\n' = BS.drop 2 s
| otherwise = BS.drop 1 s
where c0 = BS.index s 0
c1 = BS.index s 1