module Happstack.Server.Internal.MessageWrap (
module Happstack.Server.Internal.MessageWrap
,defaultInputIter
) where
import Control.Concurrent.MVar (tryTakeMVar, tryPutMVar, putMVar)
import Control.Monad.Trans (MonadIO(liftIO))
import qualified Data.ByteString.Char8 as P
import qualified Data.ByteString.Lazy.Char8 as L
import qualified Data.ByteString.UTF8 as U (toString)
import Data.Int (Int64)
import Happstack.Server.Internal.Types as H
import Happstack.Server.Internal.Multipart
import Happstack.Server.Internal.RFC822Headers (parseContentType)
import Happstack.Server.SURI as SURI
queryInput :: SURI -> [(String, Input)]
queryInput uri = formDecode (case SURI.query uri of
'?':r -> r
xs -> xs)
data BodyPolicy
= BodyPolicy { inputWorker :: Int64 -> Int64 -> Int64 -> InputWorker
, maxDisk :: Int64
, maxRAM :: Int64
, maxHeader :: Int64
}
defaultBodyPolicy :: FilePath
-> Int64
-> Int64
-> Int64
-> BodyPolicy
defaultBodyPolicy tmpDir md mr mh =
BodyPolicy { inputWorker = defaultInputIter defaultFileSaver tmpDir 0 0 0
, maxDisk = md
, maxRAM = mr
, maxHeader = mh
}
bodyInput :: (MonadIO m) => BodyPolicy -> Request -> m ([(String, Input)], Maybe String)
bodyInput _ req | ((rqMethod req /= POST) && (rqMethod req /= PUT)) || (not (isDecodable ctype)) =
do _ <- liftIO $ tryPutMVar (rqInputsBody req) []
return ([], Nothing)
where
ctype :: Maybe ContentType
ctype = parseContentType . P.unpack =<< getHeader "content-type" req
isDecodable :: Maybe ContentType -> Bool
isDecodable Nothing = True
isDecodable (Just (ContentType "application" "x-www-form-urlencoded" _)) = True
isDecodable (Just (ContentType "multipart" "form-data" _ps)) = True
isDecodable (Just _) = False
bodyInput bodyPolicy req =
liftIO $
do let ctype = parseContentType . P.unpack =<< getHeader "content-type" req
mbi <- tryTakeMVar (rqInputsBody req)
case mbi of
(Just bi) ->
do putMVar (rqInputsBody req) bi
return (bi, Nothing)
Nothing ->
do rqbody <- takeRequestBody req
case rqbody of
Nothing -> return ([], Just $ "bodyInput: Request body was already consumed.")
(Just (Body bs)) ->
do r@(inputs, _err) <- decodeBody bodyPolicy ctype bs
putMVar (rqInputsBody req) inputs
return r
formDecode :: String -> [(String, Input)]
formDecode [] = []
formDecode qString =
if null pairString then rest else
(SURI.unEscapeQS name,simpleInput $ SURI.unEscapeQS val):rest
where (pairString,qString')= split (=='&') qString
(name,val)=split (=='=') pairString
rest=if null qString' then [] else formDecode qString'
formDecodeBS :: L.ByteString -> [(String, Input)]
formDecodeBS qString | L.null qString = []
formDecodeBS qString =
if L.null pairString
then rest
else (SURI.unEscapeQS (L.unpack name), simpleInput $ SURI.unEscapeQS (L.unpack $ L.drop 1 val)) : rest
where (pairString,qString') = L.break (== '&') qString
(name,val) = L.break (== '=') pairString
rest = formDecodeBS (L.drop 1 qString')
decodeBody :: BodyPolicy
-> Maybe ContentType
-> L.ByteString
-> IO ([(String,Input)], Maybe String)
decodeBody bp ctype inp
= case ctype of
Just (ContentType "application" "x-www-form-urlencoded" _) ->
return decodedUrlEncodedForm
Just (ContentType "multipart" "form-data" ps) ->
multipartDecode ((inputWorker bp) (maxDisk bp) (maxRAM bp) (maxHeader bp)) ps inp
Just ct ->
return ([], Just $ "decodeBody: unsupported content-type: " ++ show ct)
Nothing -> return decodedUrlEncodedForm
where
(upToMaxRAM,overMaxRAM) = L.splitAt (maxRAM bp) inp
decodedUrlEncodedForm = (formDecodeBS upToMaxRAM,
if L.null overMaxRAM
then Nothing
else Just ("x-www-form-urlencoded content longer than BodyPolicy.maxRAM=" ++ show (maxRAM bp) ++ " bytes"))
multipartDecode :: InputWorker
-> [(String,String)]
-> L.ByteString
-> IO ([(String,Input)], Maybe String)
multipartDecode worker ps inp =
case lookup "boundary" ps of
Just b -> multipartBody worker (L.pack b) inp
Nothing -> return ([], Just $ "boundary not found in parameters: " ++ show ps)
pathEls :: String -> [String]
pathEls = (drop 1) . map (U.toString . P.pack . SURI.unEscape) . splitList '/'
splitList :: Eq a => a -> [a] -> [[a]]
splitList _ [] = []
splitList sep list = h:splitList sep t
where (h,t)=split (==sep) list
splitListBy :: (a -> Bool) -> [a] -> [[a]]
splitListBy _ [] = []
splitListBy f list = h:splitListBy f t
where (h,t)=split f list
split :: (a -> Bool) -> [a] -> ([a], [a])
split f s = (left,right)
where
(left,right')=break f s
right = if null right' then [] else tail right'