Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module contains primitives and helper functions for handling
requests with Content-type: multipart/form-data
, i.e. HTML forms and file
uploads.
Typically most users will want to use handleFileUploads
, which writes
uploaded files to a temporary directory before sending them on to a handler
specified by the user.
Users who wish to handle their file uploads differently can use the
lower-level interface called handleMultipart
. That function takes
uploaded files and streams them to a consumer of the user's choosing.
Using these functions requires making "policy" decisions which Snap can't
really make for users, such as "what's the largest PDF file a user is
allowed to upload?" and "should we read form inputs into the parameters
mapping?". Policy is specified on a "global" basis (using
UploadPolicy
), and on a per-file basis (using PartUploadPolicy
, which
allows you to reject or limit the size of certain uploaded
Content-type
s).
Example usage:
{-# LANGUAGE OverloadedStrings #-} module Main where import qualified Data.ByteString.Char8 as B8 import Data.Functor ((<$>)) import Snap.Core (Snap
,route
,writeBS
) import Snap.Http.Server (quickHttpServe) import Snap.Util.FileUploads import System.Posix (FileOffset, fileSize, getFileStatus) uploadForm ::Snap
() uploadForm =writeBS
"<form enctype=\"multipart/form-data\" action=\"/do-upload\" method=\"POST\">\ \<input name=\"file\" type=\"file\" />\ \<input type=\"submit\" value=\"Send File\" />\ \</form>" getFileSize :: FilePath -> IO FileOffset getFileSize path = fileSize <$> getFileStatus path -- Upload handler that prints out the uploaded file's size. doUpload ::Snap
() doUpload = do l <-handleFileUploads
"/tmp"defaultUploadPolicy
(const $allowWithMaximumSize
(getMaximumFormInputSize
defaultUploadPolicy
)) (\pinfo mbfname -> do fsize <- either (const $ return 0) getFileSize mbfname return (partFileName
pinfo, fsize))writeBS
. B8.pack . show $ l site ::Snap
() site =route
[ ("/upload", uploadForm) , ("/do-upload", doUpload)] main :: IO () main = quickHttpServe site
Synopsis
- handleFormUploads :: MonadSnap m => UploadPolicy -> FileUploadPolicy -> (PartInfo -> InputStream ByteString -> IO a) -> m ([FormParam], [FormFile a])
- foldMultipart :: MonadSnap m => UploadPolicy -> PartFold a -> a -> m ([FormParam], a)
- type PartFold a = PartInfo -> InputStream ByteString -> a -> IO a
- type FormParam = (ByteString, ByteString)
- data FormFile a = FormFile {
- formFileName :: !ByteString
- formFileValue :: a
- storeAsLazyByteString :: InputStream ByteString -> IO ByteString
- withTemporaryStore :: MonadSnap m => FilePath -> String -> ((InputStream ByteString -> IO FilePath) -> m a) -> m a
- handleFileUploads :: MonadSnap m => FilePath -> UploadPolicy -> (PartInfo -> PartUploadPolicy) -> (PartInfo -> Either PolicyViolationException FilePath -> IO a) -> m [a]
- handleMultipart :: MonadSnap m => UploadPolicy -> PartProcessor a -> m [a]
- type PartProcessor a = PartInfo -> InputStream ByteString -> IO a
- data PartInfo
- data PartDisposition
- partFieldName :: PartInfo -> ByteString
- partFileName :: PartInfo -> Maybe ByteString
- partContentType :: PartInfo -> ByteString
- partHeaders :: PartInfo -> Headers
- partDisposition :: PartInfo -> PartDisposition
- data UploadPolicy
- defaultUploadPolicy :: UploadPolicy
- doProcessFormInputs :: UploadPolicy -> Bool
- setProcessFormInputs :: Bool -> UploadPolicy -> UploadPolicy
- getMaximumFormInputSize :: UploadPolicy -> Int64
- setMaximumFormInputSize :: Int64 -> UploadPolicy -> UploadPolicy
- getMaximumNumberOfFormInputs :: UploadPolicy -> Int
- setMaximumNumberOfFormInputs :: Int -> UploadPolicy -> UploadPolicy
- getMinimumUploadRate :: UploadPolicy -> Double
- setMinimumUploadRate :: Double -> UploadPolicy -> UploadPolicy
- getMinimumUploadSeconds :: UploadPolicy -> Int
- setMinimumUploadSeconds :: Int -> UploadPolicy -> UploadPolicy
- getUploadTimeout :: UploadPolicy -> Int
- setUploadTimeout :: Int -> UploadPolicy -> UploadPolicy
- data FileUploadPolicy
- defaultFileUploadPolicy :: FileUploadPolicy
- setMaximumFileSize :: Int64 -> FileUploadPolicy -> FileUploadPolicy
- setMaximumNumberOfFiles :: Int -> FileUploadPolicy -> FileUploadPolicy
- setSkipFilesWithoutNames :: Bool -> FileUploadPolicy -> FileUploadPolicy
- setMaximumSkippedFileSize :: Int64 -> FileUploadPolicy -> FileUploadPolicy
- data PartUploadPolicy
- disallow :: PartUploadPolicy
- allowWithMaximumSize :: Int64 -> PartUploadPolicy
- data FileUploadException
- fileUploadExceptionReason :: FileUploadException -> Text
- data BadPartException
- badPartExceptionReason :: BadPartException -> Text
- data PolicyViolationException
- policyViolationExceptionReason :: PolicyViolationException -> Text
Functions
:: MonadSnap m | |
=> UploadPolicy | general upload policy |
-> FileUploadPolicy | Upload policy for files |
-> (PartInfo -> InputStream ByteString -> IO a) | A file storage function |
-> m ([FormParam], [FormFile a]) |
Processes form data and calls provided storage function on file parts.
You can use this together with withTemporaryStore
, storeAsLazyByteString
or provide your own callback to store uploaded files.
If you need to process uploaded file mime type or file name, do it in the store callback function.
See also foldMultipart
.
Example using with small files which can safely be stored in memory.
import qualified Data.ByteString.Lazy as Lazy handleSmallFiles :: MonadSnap m => [(ByteString, ByteString, Lazy.ByteString)] handleSmallFiles = handleFormUploads uploadPolicy filePolicy store where uploadPolicy = defaultUploadPolicy filePolicy = setMaximumFileSize (64*1024) $ setMaximumNumberOfFiles 5 defaultUploadPolicy store partInfo stream = do content <- storeAsLazyByteString partInfo stream let fileName = partFileName partInfo fileMime = partContentType partInfo in (fileName, fileMime, content)
:: MonadSnap m | |
=> UploadPolicy | global upload policy |
-> PartFold a | part processor |
-> a | seed accumulator |
-> m ([FormParam], a) |
Given an upload policy and a function to consume uploaded "parts",
consume a request body uploaded with Content-type: multipart/form-data
.
If setProcessFormInputs
is True
, then parts with disposition form-data
(a form parameter) will be processed and returned as first element of
resulting pair. Parts with other disposition will be fed to PartFold
handler.
If setProcessFormInputs
is False
, then parts with any disposition will
be fed to PartFold
handler and first element of returned pair will be
empty. In this case it is important that you limit number of form inputs
and sizes of inputs in your PartFold
handler to avoid common DOS attacks.
Note: THE REQUEST MUST BE CORRECTLY ENCODED. If the request's
Content-type
is not "multipart/formdata
", this function skips
processing using pass
.
Most users will opt for the higher-level handleFileUploads
, which writes
to temporary files, rather than handleMultipart
. This function should be
chosen, however, if you need to stream uploaded files directly to your own
processing function: e.g. to a database or a remote service via RPC.
If the client's upload rate passes below the configured minimum (see
setMinimumUploadRate
and setMinimumUploadSeconds
), this function
terminates the connection. This setting is there to protect the server
against slowloris-style denial of service attacks.
Exceptions
If the given UploadPolicy
stipulates that you wish form inputs to be
processed (using setProcessFormInputs
), and a form input exceeds the
maximum allowable size or the form exceeds maximum number of inputs, this
function will throw a PolicyViolationException
.
If an uploaded part contains MIME headers longer than a fixed internal
threshold (currently 32KB), this function will throw a BadPartException
.
Since: 1.0.3.0
type PartFold a = PartInfo -> InputStream ByteString -> a -> IO a Source #
A type alias for a function that will process one of the parts of a
multipart/form-data
HTTP request body with accumulator.
type FormParam = (ByteString, ByteString) Source #
A form parameter name-value pair
Contents of form field of type file
FormFile | |
|
Instances
Eq a => Eq (FormFile a) Source # | |
Ord a => Ord (FormFile a) Source # | |
Defined in Snap.Internal.Util.FileUploads | |
Show a => Show (FormFile a) Source # | |
storeAsLazyByteString :: InputStream ByteString -> IO ByteString Source #
Stores file body in memory as Lazy ByteString.
:: MonadSnap m | |
=> FilePath | temporary directory |
-> String | file name pattern |
-> ((InputStream ByteString -> IO FilePath) -> m a) | Action taking store function |
-> m a |
Store files in a temporary directory, and clean up on function exit.
Files are safe to move until function exists.
If asynchronous exception is thrown during cleanup, temporary files may remain.
uploadsHandler = withTemporaryStore "vartmp" "upload-" $ store -> do (inputs, files) <- handleFormUploads defaultUploadpolicy defaultFileUploadPolicy (const store) saveFiles files
Backwards compatible API
:: MonadSnap m | |
=> FilePath | temporary directory |
-> UploadPolicy | general upload policy |
-> (PartInfo -> PartUploadPolicy) | per-part upload policy |
-> (PartInfo -> Either PolicyViolationException FilePath -> IO a) | user handler (see function description) |
-> m [a] |
Reads uploaded files into a temporary directory and calls a user handler to process them.
Note: THE REQUEST MUST BE CORRECTLY ENCODED. If the request's
Content-type
is not "multipart/formdata
", this function skips
processing using pass
.
Given a temporary directory, global and file-specific upload policies, and a
user handler, this function consumes a request body uploaded with
Content-type: multipart/form-data
. Each file is read into the temporary
directory, and is then passed to the user handler. After the user handler
runs (but before the Response
body is streamed to the client), the files
are deleted from disk; so if you want to retain or use the uploaded files in
the generated response, you need to move or otherwise process them.
The argument passed to the user handler is a tuple:
(PartInfo, Either PolicyViolationException FilePath)
The first half of this tuple is a PartInfo
, which contains the
information the client browser sent about the given upload part (like
filename, content-type, etc). The second half of this tuple is an Either
stipulating that either:
- the file was rejected on a policy basis because of the provided
PartUploadPolicy
handler - the file was accepted and exists at the given path.
Exceptions
If the client's upload rate passes below the configured minimum (see
setMinimumUploadRate
and setMinimumUploadSeconds
), this function
terminates the connection. This setting is there to protect the server
against slowloris-style denial of service attacks.
If the given UploadPolicy
stipulates that you wish form inputs to be
placed in the rqParams
parameter map (using setProcessFormInputs
), and
a form input exceeds the maximum allowable size, this function will throw a
PolicyViolationException
.
If an uploaded part contains MIME headers longer than a fixed internal
threshold (currently 32KB), this function will throw a BadPartException
.
:: MonadSnap m | |
=> UploadPolicy | global upload policy |
-> PartProcessor a | part processor |
-> m [a] |
A variant of foldMultipart
accumulating results into a list.
Also puts captured FormParam
s into rqPostParams and rqParams maps.
type PartProcessor a = PartInfo -> InputStream ByteString -> IO a Source #
A type alias for a function that will process one of the parts of a
multipart/form-data
HTTP request body without usinc accumulator.
Uploaded parts
PartInfo
contains information about a "part" in a request uploaded
with Content-type: multipart/form-data
.
data PartDisposition Source #
Represents the disposition type specified via the Content-Disposition
header field. See RFC 1806.
DispositionAttachment |
|
DispositionFile |
|
DispositionFormData |
|
DispositionOther ByteString | Any other value. |
Instances
Eq PartDisposition Source # | |
Defined in Snap.Internal.Util.FileUploads (==) :: PartDisposition -> PartDisposition -> Bool # (/=) :: PartDisposition -> PartDisposition -> Bool # | |
Show PartDisposition Source # | |
Defined in Snap.Internal.Util.FileUploads showsPrec :: Int -> PartDisposition -> ShowS # show :: PartDisposition -> String # showList :: [PartDisposition] -> ShowS # |
partFieldName :: PartInfo -> ByteString Source #
Field name associated with this part (i.e., the name specified with
<input name="partFieldName" ...
).
partFileName :: PartInfo -> Maybe ByteString Source #
Name of the uploaded file.
partContentType :: PartInfo -> ByteString Source #
Content type of this part.
partHeaders :: PartInfo -> Headers Source #
Remaining headers associated with this part.
partDisposition :: PartInfo -> PartDisposition Source #
Disposition type of this part. See PartDisposition
.
Policy
General upload policy
data UploadPolicy Source #
UploadPolicy
controls overall policy decisions relating to
multipart/form-data
uploads, specifically:
- whether to treat parts without filenames as form input (reading them into
the
rqParams
map) - because form input is read into memory, the maximum size of a form input read in this manner, and the maximum number of form inputs
- the minimum upload rate a client must maintain before we kill the connection; if very low-bitrate uploads were allowed then a Snap server would be vulnerable to a trivial denial-of-service using a "slowloris"-type attack
- the minimum number of seconds which must elapse before we start killing uploads for having too low an upload rate.
- the amount of time we should wait before timing out the connection whenever we receive input from the client.
defaultUploadPolicy :: UploadPolicy Source #
A reasonable set of defaults for upload policy. The default policy is:
maximum form input size
- 128kB
maximum number of form inputs
- 10
minimum upload rate
- 1kB/s
seconds before rate limiting kicks in
- 10
inactivity timeout
- 20 seconds
doProcessFormInputs :: UploadPolicy -> Bool Source #
Does this upload policy stipulate that we want to treat parts without filenames as form input?
setProcessFormInputs :: Bool -> UploadPolicy -> UploadPolicy Source #
Set the upload policy for treating parts without filenames as form input.
getMaximumFormInputSize :: UploadPolicy -> Int64 Source #
Get the maximum size of a form input which will be read into our
rqParams
map.
setMaximumFormInputSize :: Int64 -> UploadPolicy -> UploadPolicy Source #
Set the maximum size of a form input which will be read into our
rqParams
map.
getMaximumNumberOfFormInputs :: UploadPolicy -> Int Source #
Get the maximum size of a form input which will be read into our
rqParams
map.
setMaximumNumberOfFormInputs :: Int -> UploadPolicy -> UploadPolicy Source #
Set the maximum size of a form input which will be read into our
rqParams
map.
getMinimumUploadRate :: UploadPolicy -> Double Source #
Get the minimum rate (in bytes/second) a client must maintain before we kill the connection.
setMinimumUploadRate :: Double -> UploadPolicy -> UploadPolicy Source #
Set the minimum rate (in bytes/second) a client must maintain before we kill the connection.
getMinimumUploadSeconds :: UploadPolicy -> Int Source #
Get the amount of time which must elapse before we begin enforcing the upload rate minimum
setMinimumUploadSeconds :: Int -> UploadPolicy -> UploadPolicy Source #
Set the amount of time which must elapse before we begin enforcing the upload rate minimum
getUploadTimeout :: UploadPolicy -> Int Source #
Get the "upload timeout". Whenever input is received from the client, the connection timeout is set this many seconds in the future.
setUploadTimeout :: Int -> UploadPolicy -> UploadPolicy Source #
Set the upload timeout.
File upload policy
data FileUploadPolicy Source #
File upload policy, if any policy is violated then
PolicyViolationException
is thrown
defaultFileUploadPolicy :: FileUploadPolicy Source #
A default FileUploadPolicy
maximum file size
- 1MB
maximum number of files
- 10
skip files without name
- yes
maximum size of skipped file
- 0
setMaximumFileSize :: Int64 -> FileUploadPolicy -> FileUploadPolicy Source #
Maximum size of single uploaded file.
setMaximumNumberOfFiles :: Int -> FileUploadPolicy -> FileUploadPolicy Source #
Maximum number of uploaded files.
setSkipFilesWithoutNames :: Bool -> FileUploadPolicy -> FileUploadPolicy Source #
Skip files with empty file names.
If set, parts without filenames will not be fed to storage function.
HTML5 form data encoding standard states that form input fields of type
file, without value set, are encoded same way as if file with empty body,
empty file name, and type application/octet-stream
was set as value.
You most likely want to use this with zero bytes allowed to avoid storing
such fields (see setMaximumSkippedFileSize
).
By default files without names are skipped.
Since: 1.0.3.0
setMaximumSkippedFileSize :: Int64 -> FileUploadPolicy -> FileUploadPolicy Source #
Maximum size of file without name which can be skipped.
Ignored if setSkipFilesWithoutNames
is False
.
If skipped file is larger than this setting then FileUploadException
is thrown.
By default maximum file size is 0.
Since: 1.0.3.0
Per-file upload policy
data PartUploadPolicy Source #
Upload policy can be set on an "general" basis (using UploadPolicy
),
but handlers can also make policy decisions on individual files/parts
uploaded. For each part uploaded, handlers can decide:
- whether to allow the file upload at all
- the maximum size of uploaded files, if allowed
disallow :: PartUploadPolicy Source #
Disallows the file to be uploaded.
allowWithMaximumSize :: Int64 -> PartUploadPolicy Source #
Allows the file to be uploaded, with maximum size n in bytes.
Exceptions
data FileUploadException Source #
All of the exceptions defined in this package inherit from
FileUploadException
, so if you write
foo `catch` \(e :: FileUploadException) -> ...
you can catch a BadPartException
, a PolicyViolationException
, etc.
Instances
Show FileUploadException Source # | |
Defined in Snap.Internal.Util.FileUploads showsPrec :: Int -> FileUploadException -> ShowS # show :: FileUploadException -> String # showList :: [FileUploadException] -> ShowS # | |
Exception FileUploadException Source # | |
fileUploadExceptionReason :: FileUploadException -> Text Source #
Human-readable error message corresponding to the FileUploadException
.
data BadPartException Source #
Thrown when a part is invalid in some way (e.g. the headers are too large).
Instances
Show BadPartException Source # | |
Defined in Snap.Internal.Util.FileUploads showsPrec :: Int -> BadPartException -> ShowS # show :: BadPartException -> String # showList :: [BadPartException] -> ShowS # | |
Exception BadPartException Source # | |
Defined in Snap.Internal.Util.FileUploads |
badPartExceptionReason :: BadPartException -> Text Source #
Human-readable error message corresponding to the BadPartException
.
data PolicyViolationException Source #
Thrown when an UploadPolicy
or PartUploadPolicy
is violated.
Instances
policyViolationExceptionReason :: PolicyViolationException -> Text Source #
Human-readable error message corresponding to the
PolicyViolationException
.