| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Servant.Multipart
Contents
Description
multipart/form-data support for servant.
This is mostly useful for adding file upload support to
an API. See haddocks of MultipartForm for an introduction.
Synopsis
- type MultipartForm tag a = MultipartForm' '[] tag a
- data MultipartForm' (mods :: [*]) tag a
- data MultipartData tag = MultipartData {}
- class FromMultipart tag a where
- fromMultipart :: MultipartData tag -> Either String a
- lookupInput :: Text -> MultipartData tag -> Either String Text
- lookupFile :: Text -> MultipartData tag -> Either String (FileData tag)
- data MultipartOptions tag = MultipartOptions {}
- defaultMultipartOptions :: MultipartBackend tag => Proxy tag -> MultipartOptions tag
- class MultipartBackend tag where
- type MultipartResult tag :: *
- type MultipartBackendOptions tag :: *
- backend :: Proxy tag -> MultipartBackendOptions tag -> InternalState -> ignored1 -> ignored2 -> IO ByteString -> IO (MultipartResult tag)
- loadFile :: Proxy tag -> MultipartResult tag -> SourceIO ByteString
- defaultBackendOptions :: Proxy tag -> MultipartBackendOptions tag
- data Tmp
- data TmpBackendOptions = TmpBackendOptions {
- getTmpDir :: IO FilePath
- filenamePat :: String
- data Mem
- defaultTmpBackendOptions :: TmpBackendOptions
- data Input = Input {}
- data FileData tag = FileData {
- fdInputName :: Text
- fdFileName :: Text
- fdFileCType :: Text
- fdPayload :: MultipartResult tag
- genBoundary :: IO ByteString
- class ToMultipart tag a where
- toMultipart :: a -> MultipartData tag
- multipartToBody :: forall tag. MultipartBackend tag => ByteString -> MultipartData tag -> RequestBody
- class ToMultipartSample tag a where
- toMultipartSamples :: Proxy a -> [(Text, MultipartData tag)]
Documentation
type MultipartForm tag a = MultipartForm' '[] tag a Source #
Combinator for specifying a multipart/form-data request
body, typically (but not always) issued from an HTML <form>.
multipart/form-data can't be made into an ordinary content
type for now in servant because it doesn't just decode the
request body from some format but also performs IO in the case
of writing the uploaded files to disk, e.g in /tmp, which is
not compatible with servant's vision of a content type as things
stand now. This also means that MultipartForm can't be used in
conjunction with ReqBody in an endpoint.
The tag type parameter instructs the function to handle data
either as data to be saved to temporary storage (Tmp) or saved to
memory (Mem).
The a type parameter represents the Haskell type to which
you are going to decode the multipart data to, where the
multipart data consists in all the usual form inputs along
with the files sent along through <input type="file">
fields in the form.
One option provided out of the box by this library is to decode
to MultipartData.
Example:
type API = MultipartForm Tmp (MultipartData Tmp) :> Post '[PlainText] String
api :: Proxy API
api = Proxy
server :: MultipartData Tmp -> Handler String
server multipartData = return str
where str = "The form was submitted with "
++ show nInputs ++ " textual inputs and "
++ show nFiles ++ " files."
nInputs = length (inputs multipartData)
nFiles = length (files multipartData)
You can alternatively provide a FromMultipart instance
for some type of yours, allowing you to regroup data
into a structured form and potentially selecting
a subset of the entire form data that was submitted.
Example, where we only look extract one input, username, and one file, where the corresponding input field's name attribute was set to pic:
data User = User { username :: Text, pic :: FilePath }
instance FromMultipart Tmp User where
fromMultipart multipartData =
User <$> lookupInput "username" multipartData
<*> fmap fdPayload (lookupFile "pic" multipartData)
type API = MultipartForm Tmp User :> Post '[PlainText] String
server :: User -> Handler String
server usr = return str
where str = username usr ++ "'s profile picture"
++ " got temporarily uploaded to "
++ pic usr ++ " and will be removed from there "
++ " after this handler has run."
Note that the behavior of this combinator is configurable,
by using serveWith from servant-server instead of serve,
which takes an additional Context argument. It simply is an
heterogeneous list where you can for example store
a value of type MultipartOptions that has the configuration that
you want, which would then get picked up by servant-multipart.
Important: as mentionned in the example above, the file paths point to temporary files which get removed after your handler has run, if they are still there. It is therefore recommended to move or copy them somewhere in your handler code if you need to keep the content around.
data MultipartForm' (mods :: [*]) tag a Source #
MultipartForm which can be modified with Lenient.
Instances
| (ToMultipart tag a, HasClient m api, MultipartBackend tag) => HasClient m (MultipartForm' mods tag a :> api) Source # | Upon seeing |
Defined in Servant.Multipart Associated Types type Client m (MultipartForm' mods tag a :> api) :: Type # Methods clientWithRoute :: Proxy m -> Proxy (MultipartForm' mods tag a :> api) -> Request -> Client m (MultipartForm' mods tag a :> api) # hoistClientMonad :: Proxy m -> Proxy (MultipartForm' mods tag a :> api) -> (forall x. mon x -> mon' x) -> Client mon (MultipartForm' mods tag a :> api) -> Client mon' (MultipartForm' mods tag a :> api) # | |
| (HasForeignType lang ftype a, HasForeign lang ftype api) => HasForeign (lang :: Type) ftype (MultipartForm t a :> api) Source # | |
Defined in Servant.Multipart Associated Types type Foreign ftype (MultipartForm t a :> api) :: Type # Methods foreignFor :: Proxy lang -> Proxy ftype -> Proxy (MultipartForm t a :> api) -> Req ftype -> Foreign ftype (MultipartForm t a :> api) # | |
| HasLink sub => HasLink (MultipartForm tag a :> sub :: Type) Source # | |
Defined in Servant.Multipart Associated Types type MkLink (MultipartForm tag a :> sub) a :: Type # Methods toLink :: (Link -> a0) -> Proxy (MultipartForm tag a :> sub) -> Link -> MkLink (MultipartForm tag a :> sub) a0 # | |
| (HasDocs api, ToMultipartSample tag a) => HasDocs (MultipartForm tag a :> api :: Type) Source # | Declare an instance of |
Defined in Servant.Multipart Methods docsFor :: Proxy (MultipartForm tag a :> api) -> (Endpoint, Action) -> DocOptions -> API # | |
| (FromMultipart tag a, MultipartBackend tag, LookupContext config (MultipartOptions tag), SBoolI (FoldLenient mods), HasServer sublayout config) => HasServer (MultipartForm' mods tag a :> sublayout :: Type) config Source # | Upon seeing |
Defined in Servant.Multipart Associated Types type ServerT (MultipartForm' mods tag a :> sublayout) m :: Type # Methods route :: Proxy (MultipartForm' mods tag a :> sublayout) -> Context config -> Delayed env (Server (MultipartForm' mods tag a :> sublayout)) -> Router env # hoistServerWithContext :: Proxy (MultipartForm' mods tag a :> sublayout) -> Proxy config -> (forall x. m x -> n x) -> ServerT (MultipartForm' mods tag a :> sublayout) m -> ServerT (MultipartForm' mods tag a :> sublayout) n # | |
| type Client m (MultipartForm' mods tag a :> api) Source # | |
Defined in Servant.Multipart | |
| type Foreign ftype (MultipartForm t a :> api) Source # | |
Defined in Servant.Multipart | |
| type MkLink (MultipartForm tag a :> sub :: Type) r Source # | |
Defined in Servant.Multipart | |
| type ServerT (MultipartForm' mods tag a :> sublayout :: Type) m Source # | |
Defined in Servant.Multipart type ServerT (MultipartForm' mods tag a :> sublayout :: Type) m = If (FoldLenient mods) (Either String a) a -> ServerT sublayout m | |
data MultipartData tag Source #
What servant gets out of a multipart/form-data form submission.
The type parameter tag tells if MultipartData is stored as a
temporary file or stored in memory. tag is type of either Mem
or Tmp.
The inputs field contains a list of textual Inputs, where
each input for which a value is provided gets to be in this list,
represented by the input name and the input value. See haddocks for
Input.
The files field contains a list of files that were sent along with the
other inputs in the form. Each file is represented by a value of type
FileData which among other things contains the path to the temporary file
(to be removed when your handler is done running) with a given uploaded
file's content. See haddocks for FileData.
Constructors
| MultipartData | |
Instances
| ToMultipart tag (MultipartData tag) Source # | |
Defined in Servant.Multipart Methods toMultipart :: MultipartData tag -> MultipartData tag Source # | |
| FromMultipart tag (MultipartData tag) Source # | |
Defined in Servant.Multipart Methods fromMultipart :: MultipartData tag -> Either String (MultipartData tag) Source # | |
class FromMultipart tag a where Source #
MultipartData is the type representing
multipart/form-data form inputs. Sometimes
you may instead want to work with a more structured type
of yours that potentially selects only a fraction of
the data that was submitted, or just reshapes it to make
it easier to work with. The FromMultipart class is exactly
what allows you to tell servant how to turn "raw" multipart
data into a value of your nicer type.
data User = User { username :: Text, pic :: FilePath }
instance FromMultipart Tmp User where
fromMultipart form =
User <$> lookupInput "username" (inputs form)
<*> fmap fdPayload (lookupFile "pic" $ files form)
Methods
fromMultipart :: MultipartData tag -> Either String a Source #
Given a value of type MultipartData, which consists
in a list of textual inputs and another list for
files, try to extract a value of type a. When
extraction fails, servant errors out with status code 400.
Instances
| FromMultipart tag (MultipartData tag) Source # | |
Defined in Servant.Multipart Methods fromMultipart :: MultipartData tag -> Either String (MultipartData tag) Source # | |
lookupInput :: Text -> MultipartData tag -> Either String Text Source #
Lookup a textual input with the given name attribute.
lookupFile :: Text -> MultipartData tag -> Either String (FileData tag) Source #
Lookup a file input with the given name attribute.
data MultipartOptions tag Source #
Global options for configuring how the server should handle multipart data.
generalOptions lets you specify mostly multipart parsing
related options, such as the maximum file size, while
backendOptions lets you configure aspects specific to the chosen
backend. Note: there isn't anything to tweak in a memory
backend (Mem). Maximum file size etc. options are in
ParseRequestBodyOptions.
See haddocks for ParseRequestBodyOptions and
TmpBackendOptions respectively for more information on
what you can tweak.
Constructors
| MultipartOptions | |
Fields | |
defaultMultipartOptions :: MultipartBackend tag => Proxy tag -> MultipartOptions tag Source #
Default configuration for multipart handling.
Uses defaultParseRequestBodyOptions and
defaultBackendOptions respectively.
class MultipartBackend tag where Source #
Associated Types
type MultipartResult tag :: * Source #
type MultipartBackendOptions tag :: * Source #
Methods
backend :: Proxy tag -> MultipartBackendOptions tag -> InternalState -> ignored1 -> ignored2 -> IO ByteString -> IO (MultipartResult tag) Source #
loadFile :: Proxy tag -> MultipartResult tag -> SourceIO ByteString Source #
defaultBackendOptions :: Proxy tag -> MultipartBackendOptions tag Source #
Instances
| MultipartBackend Mem Source # | |
Defined in Servant.Multipart Associated Types type MultipartResult Mem :: Type Source # type MultipartBackendOptions Mem :: Type Source # Methods backend :: Proxy Mem -> MultipartBackendOptions Mem -> InternalState -> ignored1 -> ignored2 -> IO ByteString -> IO (MultipartResult Mem) Source # loadFile :: Proxy Mem -> MultipartResult Mem -> SourceIO ByteString Source # defaultBackendOptions :: Proxy Mem -> MultipartBackendOptions Mem Source # | |
| MultipartBackend Tmp Source # | |
Defined in Servant.Multipart Associated Types type MultipartResult Tmp :: Type Source # type MultipartBackendOptions Tmp :: Type Source # Methods backend :: Proxy Tmp -> MultipartBackendOptions Tmp -> InternalState -> ignored1 -> ignored2 -> IO ByteString -> IO (MultipartResult Tmp) Source # loadFile :: Proxy Tmp -> MultipartResult Tmp -> SourceIO ByteString Source # defaultBackendOptions :: Proxy Tmp -> MultipartBackendOptions Tmp Source # | |
Tag for data stored as a temporary file
Instances
| MultipartBackend Tmp Source # | |
Defined in Servant.Multipart Associated Types type MultipartResult Tmp :: Type Source # type MultipartBackendOptions Tmp :: Type Source # Methods backend :: Proxy Tmp -> MultipartBackendOptions Tmp -> InternalState -> ignored1 -> ignored2 -> IO ByteString -> IO (MultipartResult Tmp) Source # loadFile :: Proxy Tmp -> MultipartResult Tmp -> SourceIO ByteString Source # defaultBackendOptions :: Proxy Tmp -> MultipartBackendOptions Tmp Source # | |
| type MultipartResult Tmp Source # | |
Defined in Servant.Multipart | |
| type MultipartBackendOptions Tmp Source # | |
Defined in Servant.Multipart | |
data TmpBackendOptions Source #
Configuration for the temporary file based backend.
You can configure the way servant-multipart gets its hands
on a temporary directory (defaults to getTemporaryDirectory)
as well as the filename pattern used for generating the temporary files
(defaults to calling them servant-multipartXXX.buf, where XXX is some
random number).
Constructors
| TmpBackendOptions | |
Fields
| |
Tag for data stored in memory
Instances
| MultipartBackend Mem Source # | |
Defined in Servant.Multipart Associated Types type MultipartResult Mem :: Type Source # type MultipartBackendOptions Mem :: Type Source # Methods backend :: Proxy Mem -> MultipartBackendOptions Mem -> InternalState -> ignored1 -> ignored2 -> IO ByteString -> IO (MultipartResult Mem) Source # loadFile :: Proxy Mem -> MultipartResult Mem -> SourceIO ByteString Source # defaultBackendOptions :: Proxy Mem -> MultipartBackendOptions Mem Source # | |
| type MultipartResult Mem Source # | |
Defined in Servant.Multipart | |
| type MultipartBackendOptions Mem Source # | |
Defined in Servant.Multipart | |
defaultTmpBackendOptions :: TmpBackendOptions Source #
Default options for the temporary file backend:
getTemporaryDirectory and "servant-multipart.buf"
Representation for a textual input (any <input> type but file).
<input name="foo" value="bar" /> would appear as .Input "foo" "bar"
Constructors
| Input | |
Representation for an uploaded file, usually resulting from
picking a local file for an HTML input that looks like
<input type="file" name="somefile" />.
Constructors
| FileData | |
Fields
| |
servant-client
genBoundary :: IO ByteString Source #
Generates a boundary to be used to separate parts of the multipart.
Requires IO because it is randomized.
class ToMultipart tag a where Source #
Allows you to tell servant how to turn a more structured type
into a MultipartData, which is what is actually sent by the
client.
data User = User { username :: Text, pic :: FilePath }
instance toMultipart Tmp User where
toMultipart user = MultipartData [Input "username" $ username user]
[FileData "pic"
(pic user)
"image/png"
(pic user)
]
Methods
toMultipart :: a -> MultipartData tag Source #
Given a value of type a, convert it to a
MultipartData.
Instances
| ToMultipart tag (MultipartData tag) Source # | |
Defined in Servant.Multipart Methods toMultipart :: MultipartData tag -> MultipartData tag Source # | |
multipartToBody :: forall tag. MultipartBackend tag => ByteString -> MultipartData tag -> RequestBody Source #
Given a bytestring for the boundary, turns a MultipartData into
a RequestBody
servant-docs
class ToMultipartSample tag a where Source #
The ToMultipartSample class allows you to create sample MultipartData
inputs for your type for use with Servant.Docs. This is used by the
HasDocs instance for MultipartForm.
Given the example User type and FromMultipart instance above, here is a
corresponding ToMultipartSample instance:
data User = User { username :: Text, pic :: FilePath }
instance ToMultipartSample Tmp User where
toMultipartSamples proxy =
[ ( "sample 1"
, MultipartData
[ Input "username" "Elvis Presley" ]
[ FileData
"pic"
"playing_guitar.jpeg"
"image/jpeg"
"tmpservant-multipart000.buf"
]
)
]
Methods
toMultipartSamples :: Proxy a -> [(Text, MultipartData tag)] Source #