[Haskell-cafe] CURL and threads

Eugene Dzhurinsky bofh at redwerk.com
Wed Feb 17 12:34:07 EST 2010


Hello, all!

Can somebody please explain, what is the best way of using CURL with several
threads? I wrote simple client, which tries to authenticate against HTTP
server. With running this client, it starts to eat memory insanely (and I know
this code is far, far away of even being close to be called good one )

=========================================================================================
module NTLMTest where

import System.IO
import Network.Curl
import Control.Concurrent
import Control.Concurrent.Chan

type ResponseState = Either Bool String

type RespChannel = Chan ResponseState

delay = 500 * 1000

isResponseOk :: String -> CurlResponse -> ResponseState
isResponseOk username response = case respCurlCode response of
                            CurlOK  -> Left True
                            _       -> Right $ username ++ " => " ++ respStatusLine response ++ " :: " ++ (show . respStatus $ response)
                        

checkAuthResponse :: RespChannel -> String -> String -> String -> IO ()
checkAuthResponse state user passwd url = do 
                                    response <- curlGetResponse_ url [CurlHttpAuth [HttpAuthAny], CurlUserPwd $ user ++ ":" ++ passwd]
                                    writeChan state $ isResponseOk user response
                                    threadDelay $ delay

runHTTPThread :: RespChannel -> (String,String) -> IO ()
runHTTPThread state (user,passwd) = checkAuthResponse state user passwd url
        

url = "http://localhost:8082/"
credentials = map (\i -> ("user" ++ show i,"123456")) [1..21]

main = withCurlDo $ do
    chan <- newChan :: IO (RespChannel)
    mapM_ ( \cred -> forkIO $ runHTTPThread chan cred ) credentials
    dumpChannel chan $ length credentials
    main
    where
        dumpChannel :: RespChannel -> Int -> IO ()
        dumpChannel _chan n | n == 0    = return ()
                            | otherwise = do    state <- readChan _chan
                                                case state of
                                                    (Left _) -> return () --putStrLn "OK"
                                                    (Right err) -> putStrLn err
                                                dumpChannel _chan $ n-1

=========================================================================================

If I get rid of forkIO - it stops at 40-50 megabytes and don't raise memory
usage anymore.

Also, I noticed that (either because of buffering, or may be something else)
results are appearing on console much slower than if I simply use "wget" with
looping in shell script. JMeter also reports awesome speed, so server can
authenticate tens of concurrent users per second (thus it's not server or
connection bandwidth issue).

Hopefully, someone could help me in overcoming my ignorance :)

-- 
Eugene N Dzhurinsky
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 196 bytes
Desc: not available
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20100217/83f58ee9/attachment.bin


More information about the Haskell-Cafe mailing list