| Safe Haskell | None |
|---|
Network.HTTP.Conduit.MultipartFormData
Description
This module handles building multipart/form-data. Example usage:
{-# LANGUAGE OverloadedStrings #-}
import Network
import Network.HTTP.Conduit
import Network.HTTP.Conduit.MultipartFormData
import Data.Text.Encoding as TE
import Control.Monad
main = withSocketsDo $ withManager $ \m -> do
req1 <- parseUrl "http://random-cat-photo.net/cat.jpg"
res <- httpLbs req1 m
req2 <- parseUrl "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)
- data Part m m' = Part {
- partName :: Text
- partFilename :: Maybe String
- partContentType :: Maybe MimeType
- partGetBody :: m (RequestBody m')
- partBS :: (Monad m, Monad m') => Text -> ByteString -> Part m m'
- partLBS :: (Monad m, Monad m') => Text -> ByteString -> Part m m'
- partFile :: (MonadIO m, Monad m') => Text -> FilePath -> Part m m'
- partFileSource :: (MonadIO m, MonadResource m') => Text -> FilePath -> Part m m'
- partFileSourceChunked :: (Monad m, MonadResource m') => Text -> FilePath -> Part m m'
- partFileRequestBody :: (Monad m, Monad m') => Text -> FilePath -> RequestBody m' -> Part m m'
- partFileRequestBodyM :: Monad m' => Text -> FilePath -> m (RequestBody m') -> Part m m'
- formDataBody :: (MonadIO m, Monad m') => [Part m m'] -> Request m' -> m (Request m')
- formDataBodyPure :: Monad m => ByteString -> [Part Identity m] -> Request m -> Request m
- formDataBodyWithBoundary :: (Monad m, Monad m') => ByteString -> [Part m m'] -> Request m' -> m (Request m')
- webkitBoundary :: IO ByteString
- webkitBoundaryPure :: RandomGen g => g -> (ByteString, g)
- renderParts :: (Monad m, Monad m') => ByteString -> [Part m m'] -> m (RequestBody m')
- renderPart :: (Monad m, Monad m') => ByteString -> Part m m' -> m (RequestBody m')
Part type
A single part of a multipart message.
Constructors
| Part | |
Fields
| |
Constructing parts
partFile :: (MonadIO m, Monad m') => Text -> FilePath -> Part m m'Source
Make a Part from a file, the entire file will reside in memory at once.
If you want constant memory usage use partFileSource
partFileSource :: (MonadIO m, MonadResource m') => Text -> FilePath -> Part m m'Source
Stream Part from a file.
partFileSourceChunked :: (Monad m, MonadResource m') => Text -> FilePath -> Part m m'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.
partFileRequestBody :: (Monad m, Monad m') => Text -> FilePath -> RequestBody m' -> Part m m'Source
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
partFileRequestBodyM :: Monad m' => Text -> FilePath -> m (RequestBody m') -> Part m m'Source
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 fromByteString
Building form data
formDataBody :: (MonadIO m, Monad m') => [Part m m'] -> Request m' -> m (Request m')Source
Add form data to the Request.
This sets a new requestBody, adds a content-type request header and changes the method to POST.
formDataBodyPure :: Monad m => ByteString -> [Part Identity m] -> Request m -> Request mSource
Add form data to request without doing any IO. Your form data should only
contain pure parts (partBS, partLBS, partFileRequestBody). You'll have
to supply your own boundary (for example one generated by webkitBoundary)
formDataBodyWithBoundary :: (Monad m, Monad m') => ByteString -> [Part m m'] -> Request m' -> m (Request m')Source
Add form data with supplied boundary
Boundary
webkitBoundary :: IO ByteStringSource
Generate a boundary simillar to those generated by WebKit-based browsers.
webkitBoundaryPure :: RandomGen g => g -> (ByteString, g)Source
Misc
renderParts :: (Monad m, Monad m') => ByteString -> [Part m m'] -> m (RequestBody m')Source
Combine the Parts to form multipart/form-data body
renderPart :: (Monad m, Monad m') => ByteString -> Part m m' -> m (RequestBody m')Source