
Hi Micheal,
You cannot use curlGetString to POST since it always uses GET.
Here is a code snippet which I use. Although I don't use basic auth,
you can add another opt to use it.
{-# LANGUAGE ScopedTypeVariables #-}
import Control.Exception (IOException, handle)
import Control.Monad (liftM)
import qualified Data.ByteString as BSS
import qualified Data.ByteString.Lazy as BS
import qualified Data.ByteString.Lazy.Char8 as BS8
import Data.IORef
import qualified Network.Curl as Curl
import Network.URI (URI)
post :: URI -> BS.ByteString -> String -> IO (Maybe BS.ByteString)
post uri body contentType = handleIOException (const $ return Nothing)
$ Curl.withCurlDo $ do
bodyRef <- newIORef []
h <- Curl.initialize
mapM_ (Curl.setopt h) $ [Curl.CurlURL $ show uri,
Curl.CurlNoBody False,
Curl.CurlFollowLocation False,
Curl.CurlMaxRedirs 0,
Curl.CurlAutoReferer False,
Curl.CurlUserAgent "Mozilla/5.0",
Curl.CurlNoSignal True,
-- Curl.CurlVerbose True,
Curl.CurlPostFields [BS8.unpack body],
Curl.CurlHttpHeaders ["Content-Type:
" ++ contentType],
Curl.CurlWriteFunction $ bodyFunction bodyRef]
code <- Curl.perform h
if code /= Curl.CurlOK
then return Nothing
else liftM (Just . BS.fromChunks . reverse) $ readIORef bodyRef
bodyFunction :: IORef [BSS.ByteString] -> Curl.WriteFunction
bodyFunction r = Curl.gatherOutput_ $ \s -> do
bs <- BSS.packCStringLen s
modifyIORef r (bs:)
handleIOException :: (IOException -> IO a) -> IO a -> IO a
handleIOException handler action = handle (\(e :: IOException) ->
handler e) action
--
Satoshi Nakamura
I've tried 3 different HTTP libraries for this project: Network.HTTP (which doesn't support SSL), Network.Curl, and http-enumerator. This project requires SSL, HTTP Basic Auth and Post. Network.HTTP does not support SSL and http-enumerator does not support HTTP basic authentication. The maintainer said he'd welcome a patch to it but I don't really have the time or skill at this stage to implement something like that. So I'm stuck with trying to coerce curl into doing what I need it to do. Hopefully someone on this list has been able to successfully POST a string body with Network.Curl
On Wed, May 11, 2011 at 6:07 PM, Erik de Castro Lopo
wrote: Bryce Verdier wrote:
I would be interested in this as well. I'm trying to use Network.Curl for a personal project, also using a method_post, and am not able to get a response. Though I know it's connecting.
I _think_ that I need to use CurlWriteFunction, but I'm still new to Haskell & not sure how to work with that option.
I tried a number of times to do things with Network.Curl and found it to be a painful and frustrating experience. The API is highly irregular and often remains too close to the underlying C API.
More recently I've been using the http-enumerator package which is conceptually a little more complicated but works really, really well. It does both HTTP and HTTPS, GET and POST. It currently doesn't work via a proxy, but the http-enumerator author has said he will take patches and I'm working on it.
Cheers, Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Michael Xavier http://www.michaelxavier.net
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners