module Network.Wai.Middleware.RequestSizeLimit
(
requestSizeLimitMiddleware
, defaultRequestSizeLimitSettings
, RequestSizeLimitSettings
, setMaxLengthForRequest
, setOnLengthExceeded
) where
import Network.Wai
import Network.Wai.Request
import qualified Data.ByteString.Lazy as BSL
import Data.Word (Word64)
import Network.HTTP.Types.Status (requestEntityTooLarge413)
import qualified Data.ByteString.Lazy.Char8 as LS8
import Control.Exception (try, catch)
import Data.Monoid ((<>))
import Network.Wai.Middleware.RequestSizeLimit.Internal (RequestSizeLimitSettings(..), setMaxLengthForRequest, setOnLengthExceeded)
defaultRequestSizeLimitSettings :: RequestSizeLimitSettings
defaultRequestSizeLimitSettings = RequestSizeLimitSettings
{ maxLengthForRequest = \_req -> pure $ Just $ 2 * 1024 * 1024
, onLengthExceeded = \maxLen _app req sendResponse -> sendResponse (tooLargeResponse maxLen (requestBodyLength req))
}
requestSizeLimitMiddleware :: RequestSizeLimitSettings -> Middleware
requestSizeLimitMiddleware settings app req sendResponse = do
maybeMaxLen <- (maxLengthForRequest settings) req
case maybeMaxLen of
Nothing -> app req sendResponse
Just maxLen -> do
eitherSizeExceptionOrNewReq <- try (requestSizeCheck maxLen req)
case eitherSizeExceptionOrNewReq of
Left (RequestSizeException _maxLen) -> handleLengthExceeded maxLen
Right newReq -> app newReq sendResponse `catch` \(RequestSizeException _maxLen) -> handleLengthExceeded maxLen
where
handleLengthExceeded maxLen = (onLengthExceeded settings) maxLen app req sendResponse
tooLargeResponse :: Word64 -> RequestBodyLength -> Response
tooLargeResponse maxLen bodyLen = responseLBS
requestEntityTooLarge413
[("Content-Type", "text/plain")]
(BSL.concat
[ "Request body too large to be processed. The maximum size is "
, (LS8.pack (show maxLen))
, " bytes; your request body was "
, case bodyLen of
KnownLength knownLen -> (LS8.pack (show knownLen)) <> " bytes."
ChunkedBody -> "split into chunks, whose total size is unknown, but exceeded the limit."
, " . If you're the developer of this site, you can configure the maximum length with `requestSizeLimitMiddleware`."
])