| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Network.HTTP.Client.MultipartFormData
Description
This module handles building multipart/form-data. Example usage:
{-# LANGUAGE OverloadedStrings #-}
import Network
import Network.HTTP.Client
import Network.HTTP.Client.MultipartFormData
import Data.Text.Encoding as TE
import Control.Monad
main = void $ withManager defaultManagerSettings $ \m -> do
    req1 <- parseRequest "http://random-cat-photo.net/cat.jpg"
    res <- httpLbs req1 m
    req2 <- parseRequest "http://example.org/~friedrich/blog/addPost.hs"
    flip httpLbs m =<<
        (formDataBody [partBS "title" "Bleaurgh"
                      ,partBS "text" $ TE.encodeUtf8 "矢田矢田矢田矢田矢田"
                      ,partFileSource "file1" "/home/friedrich/Photos/MyLittlePony.jpg"
                      ,partFileRequestBody "file2" "cat.jpg" $ RequestBodyLBS $ responseBody res]
            req2)Synopsis
- data Part
- partName :: Part -> Text
- partFilename :: Part -> Maybe String
- partContentType :: Part -> Maybe MimeType
- partHeaders :: Part -> [Header]
- partGetBody :: Part -> IO RequestBody
- partBS :: Text -> ByteString -> Part
- partLBS :: Text -> ByteString -> Part
- partFile :: Text -> FilePath -> Part
- partFileSource :: Text -> FilePath -> Part
- partFileSourceChunked :: Text -> FilePath -> Part
- partFileRequestBody :: Text -> FilePath -> RequestBody -> Part
- partFileRequestBodyM :: Text -> FilePath -> IO RequestBody -> Part
- addPartHeaders :: Part -> [Header] -> Part
- formDataBody :: MonadIO m => [Part] -> Request -> m Request
- formDataBodyWithBoundary :: ByteString -> [Part] -> Request -> IO Request
- webkitBoundary :: IO ByteString
- webkitBoundaryPure :: RandomGen g => g -> (ByteString, g)
- renderParts :: ByteString -> [Part] -> IO RequestBody
- renderPart :: ByteString -> Part -> IO RequestBody
Part type
A single part of a multipart message.
partHeaders :: Part -> [Header] Source #
List of additional headers
partGetBody :: Part -> IO RequestBody Source #
Action in m which returns the body of a message.
Constructing parts
Arguments
| :: Text | Name of the corresponding <input>. | 
| -> ByteString | The body for this  | 
| -> Part | 
Make a Part whose content is a strict ByteString.
The Part does not have a file name or content type associated
 with it.
Arguments
| :: Text | Name of the corresponding <input>. | 
| -> ByteString | The body for this  | 
| -> Part | 
Make a Part whose content is a lazy ByteString.
The Part does not have a file name or content type associated
 with it.
Arguments
| :: Text | Name of the corresponding <input>. | 
| -> FilePath | The name of the local file to upload. | 
| -> Part | 
Make a Part from a file.
The entire file will reside in memory at once.  If you want
 constant memory usage, use partFileSource.
The FilePath supplied will be used as the file name of the
 Part. If you do not want to reveal this name to the server, you
 must remove it prior to uploading.
The Part does not have a content type associated with it.
partFileSourceChunked :: Text -> FilePath -> Part Source #
partFileSourceChunked will read a file and send it in chunks.
Note that not all servers support this. Only use partFileSourceChunked
 if you know the server you're sending to supports chunked request bodies.
The FilePath supplied will be used as the file name of the
 Part. If you do not want to reveal this name to the server, you
 must remove it prior to uploading.
The Part does not have a content type associated with it.
Arguments
| :: Text | Name of the corresponding <input>. | 
| -> FilePath | File name to supply to the server. | 
| -> RequestBody | Data to upload. | 
| -> Part | 
Construct a Part from form name, filepath and a RequestBody
partFileRequestBody "who_calls" "caller.json" $ RequestBodyBS "{\"caller\":\"Jason J Jason\"}"-- empty upload form partFileRequestBody "file" mempty mempty
The Part does not have a content type associated with it.
Arguments
| :: Text | Name of the corresponding <input>. | 
| -> FilePath | File name to supply to the server. | 
| -> IO RequestBody | Action that will supply data to upload. | 
| -> Part | 
Construct a Part from action returning the RequestBody
partFileRequestBodyM "cat_photo" "haskell-the-cat.jpg" $ do
    size <- fromInteger <$> withBinaryFile "haskell-the-cat.jpg" ReadMode hFileSize
    return $ RequestBodySource size $ CB.sourceFile "haskell-the-cat.jpg" $= CL.map fromByteStringThe Part does not have a content type associated with it.
Headers
Building form data
formDataBody :: MonadIO m => [Part] -> Request -> m Request Source #
Add form data to the Request.
This sets a new requestBody, adds a content-type request header and changes the method to POST.
formDataBodyWithBoundary :: ByteString -> [Part] -> Request -> IO Request Source #
Add form data with supplied boundary
Boundary
webkitBoundary :: IO ByteString Source #
Generate a boundary simillar to those generated by WebKit-based browsers.
webkitBoundaryPure :: RandomGen g => g -> (ByteString, g) Source #
Misc
Arguments
| :: ByteString | Boundary between parts. | 
| -> [Part] | |
| -> IO RequestBody | 
Combine the Parts to form multipart/form-data body
Arguments
| :: ByteString | Boundary between parts. | 
| -> Part | |
| -> IO RequestBody |