servant-multipart-0.12.1: multipart/form-data (e.g file upload) support for servant
Safe HaskellNone
LanguageHaskell2010

Servant.Multipart

Description

multipart/form-data server-side support for servant. See servant-multipart-api for the API definitions.

Synopsis

Documentation

type MultipartForm tag a = MultipartForm' ('[] :: [Type]) tag a #

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 :: [Type]) tag a #

MultipartForm which can be modified with Lenient.

Instances

Instances details
(HasForeignType lang ftype a, HasForeign lang ftype api) => HasForeign (lang :: Type) ftype (MultipartForm t a :> api) Source # 
Instance details

Defined in Servant.Multipart

Associated Types

type Foreign ftype (MultipartForm t a :> api) #

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) 
Instance details

Defined in Servant.Multipart.API

Associated Types

type MkLink (MultipartForm tag a :> sub) a #

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 ToMultipartSample for your MultipartForm type to be able to use this HasDocs instance.

Instance details

Defined in Servant.Multipart

Methods

docsFor :: Proxy (MultipartForm tag a :> api) -> (Endpoint, Action) -> DocOptions -> API #

(FromMultipart tag a, MultipartBackend tag, LookupContext config (MultipartOptions tag), LookupContext config ErrorFormatters, SBoolI (FoldLenient mods), HasServer sublayout config) => HasServer (MultipartForm' mods tag a :> sublayout :: Type) config Source #

Upon seeing MultipartForm a :> ... in an API type,

Instance details

Defined in Servant.Multipart

Associated Types

type ServerT (MultipartForm' mods tag a :> sublayout) m #

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 Foreign ftype (MultipartForm t a :> api) Source # 
Instance details

Defined in Servant.Multipart

type Foreign ftype (MultipartForm t a :> api) = Foreign ftype api
type MkLink (MultipartForm tag a :> sub :: Type) r 
Instance details

Defined in Servant.Multipart.API

type MkLink (MultipartForm tag a :> sub :: Type) r = MkLink sub r
type ServerT (MultipartForm' mods tag a :> sublayout :: Type) m Source # 
Instance details

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 #

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 

Fields

Instances

Instances details
FromMultipart tag (MultipartData tag) 
Instance details

Defined in Servant.Multipart.API

ToMultipart tag (MultipartData tag) 
Instance details

Defined in Servant.Multipart.API

class FromMultipart tag a where #

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 #

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

Instances details
FromMultipart tag (MultipartData tag) 
Instance details

Defined in Servant.Multipart.API

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.

defaultMultipartOptions :: MultipartBackend tag => Proxy tag -> MultipartOptions tag Source #

Default configuration for multipart handling.

Uses defaultParseRequestBodyOptions and defaultBackendOptions respectively.

data Tmp #

Tag for data stored as a temporary file

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).

data Mem #

Tag for data stored in memory

Instances

Instances details
MultipartBackend Mem Source # 
Instance details

Defined in Servant.Multipart

Associated Types

type MultipartBackendOptions Mem Source #

type MultipartResult Mem 
Instance details

Defined in Servant.Multipart.API

type MultipartBackendOptions Mem Source # 
Instance details

Defined in Servant.Multipart

defaultTmpBackendOptions :: TmpBackendOptions Source #

Default options for the temporary file backend: getTemporaryDirectory and "servant-multipart.buf"

data Input #

Representation for a textual input (any <input> type but file).

<input name="foo" value="bar" /> would appear as Input "foo" "bar".

Constructors

Input 

Fields

Instances

Instances details
Eq Input 
Instance details

Defined in Servant.Multipart.API

Methods

(==) :: Input -> Input -> Bool #

(/=) :: Input -> Input -> Bool #

Show Input 
Instance details

Defined in Servant.Multipart.API

Methods

showsPrec :: Int -> Input -> ShowS #

show :: Input -> String #

showList :: [Input] -> ShowS #

data FileData tag #

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

  • fdInputName :: Text

    name attribute of the corresponding HTML <input>

  • fdFileName :: Text

    name of the file on the client's disk

  • fdFileCType :: Text

    MIME type for the file

  • fdPayload :: MultipartResult tag

    path to the temporary file that has the content of the user's original file. Only valid during the execution of your handler as it gets removed right after, which means you really want to move or copy it in your handler.

Instances

Instances details
Eq (MultipartResult tag) => Eq (FileData tag) 
Instance details

Defined in Servant.Multipart.API

Methods

(==) :: FileData tag -> FileData tag -> Bool #

(/=) :: FileData tag -> FileData tag -> Bool #

Show (MultipartResult tag) => Show (FileData tag) 
Instance details

Defined in Servant.Multipart.API

Methods

showsPrec :: Int -> FileData tag -> ShowS #

show :: FileData tag -> String #

showList :: [FileData tag] -> ShowS #

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"
            ]
        )
      ]

Orphan instances

(HasForeignType lang ftype a, HasForeign lang ftype api) => HasForeign (lang :: Type) ftype (MultipartForm t a :> api) Source # 
Instance details

Associated Types

type Foreign ftype (MultipartForm t a :> api) #

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy (MultipartForm t a :> api) -> Req ftype -> Foreign ftype (MultipartForm t a :> api) #

(HasDocs api, ToMultipartSample tag a) => HasDocs (MultipartForm tag a :> api :: Type) Source #

Declare an instance of ToMultipartSample for your MultipartForm type to be able to use this HasDocs instance.

Instance details

Methods

docsFor :: Proxy (MultipartForm tag a :> api) -> (Endpoint, Action) -> DocOptions -> API #

(FromMultipart tag a, MultipartBackend tag, LookupContext config (MultipartOptions tag), LookupContext config ErrorFormatters, SBoolI (FoldLenient mods), HasServer sublayout config) => HasServer (MultipartForm' mods tag a :> sublayout :: Type) config Source #

Upon seeing MultipartForm a :> ... in an API type,

Instance details

Associated Types

type ServerT (MultipartForm' mods tag a :> sublayout) m #

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 #