http-client-0.3.1: An HTTP client engine, intended as a base layer for more user-friendly packages.

Safe HaskellNone

Network.HTTP.Client.MultipartFormData

Contents

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)

Synopsis

Part type

data Part Source

A single part of a multipart message.

Constructors

Part 

Fields

partName :: Text

Name of the corresponding <input>

partFilename :: Maybe String

A file name, if this is an attached file

partContentType :: Maybe MimeType

Content type

partGetBody :: IO RequestBody

Action in m which returns the body of a message.

Instances

Constructing parts

partFile :: Text -> FilePath -> PartSource

Make a Part from a file, the entire file will reside in memory at once. If you want constant memory usage use partFileSource

partFileSource :: Text -> FilePath -> PartSource

Stream Part from a file.

partFileSourceChunked :: Text -> FilePath -> PartSource

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 :: Text -> FilePath -> RequestBody -> PartSource

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 :: Text -> FilePath -> IO RequestBody -> PartSource

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 => [Part] -> Request -> m RequestSource

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 RequestSource

Add form data with supplied boundary

Boundary

webkitBoundary :: IO ByteStringSource

Generate a boundary simillar to those generated by WebKit-based browsers.

Misc

renderParts :: ByteString -> [Part] -> IO RequestBodySource

Combine the Parts to form multipart/form-data body