[Haskell-cafe] CURL and upload a file
Evgeny Dzhurinsky
jdevelop at gmail.com
Sun Mar 27 22:07:37 CEST 2011
Hello!
I am trying to find out the way of uploading a file using HTTP
multipart/form-data.
I created simple application aimed to upload an image to imgpaste.com.
The source is below:
=========================================================
module ImgPaste.Upload where
import Control.Monad
import Network.Curl
import Data.ByteString
import Text.Regex.PCRE
import Text.Regex.PCRE.ByteString
type LocalCtx = ( ByteString, ByteString, ByteString, [ByteString] )
type UploadResult = Either UploadError ByteString
data UploadError = UploadError {
message :: String,
response :: ByteString
} deriving (Show)
extractResponse :: CurlResponse_ [(String,String)] ByteString -> ByteString
extractResponse = respBody
uploadFile :: String -> IO (ByteString)
uploadFile fileName = initialize >>= withCurlDo . (flip
uploadFileWithCurl fileName)
uploadFileWithCurl :: Curl -> String -> IO ( ByteString )
uploadFileWithCurl curl fileName = do
liftM extractResponse $ do_curl_ curl "http://imgpaste.com/"
[CurlPost True, CurlHttpPost postData, CurlVerbose True ]
where
postData = [
HttpPost "upfile"
Nothing
( ContentFile fileName )
[]
Nothing,
makeFormPost "submit" "Upload",
makeFormPost "keep" "a"
]
makeFormPost name value = HttpPost name Nothing
(ContentString value)
[]
Nothing
-- <input type="text" name="copyfield" size="31"
value="http://imgpaste.com/tmp/123456.png" />
extractUrl :: ByteString -> UploadResult
extractUrl src = match (src =~ "<input type=\"text\"
name=\"copyfield\" size=\"31\" value=\"([^\"]+?)\" />" :: LocalCtx)
where
match (_,_,_,[x]) = Right x
match _ = Left $ UploadError "Can not parse content." src
pasteImage :: String -> IO ( UploadResult )
pasteImage = liftM extractUrl . uploadFile
=========================================================
however when invoking the function: pasteImage "image.png" no data is
posted to the server. The protocol dump looks like:
=========================================================
POST / HTTP/1.1
Host: imgpaste.com
Accept: */*
Content-Length: 241
Expect: 100-continue
Content-Type: multipart/form-data;
boundary=----------------------------630d154aaf3b
=========================================================
so the request data is not sent. Can somebody please advice, what am I
doing in a wrong way?
Thank you in advance!
--
regards
Eugene Dzhurinsky
More information about the Haskell-Cafe
mailing list