[Haskell-cafe] Network.Curl curiosity

Michael Orlitzky michael at orlitzky.com
Fri Jun 29 04:32:00 CEST 2012


I've been fighting with this silly bug: I have two functions using curl
(Network.Curl) for logging in via POST and downloading pages via GET.
They do the usual boring stuff; cookies go in a text file whose path is
passed in to both functions. They work great individually.

But, I'm calling them sequentially:

  cj <- make_cookie_jar
  li_result <- log_in cj username password
  html <- get_page (Just cj) my_article

The symptom that I noticed was that the call to get_page wasn't using
the cookies. I looked in the cookie file -- they're all there. And when
I call get_page from ghci (with the same cookie file), it works.

It turns out that between the calls to log_in and get_page, the cookie
file is empty. The stupidest possible solution that works is,

  cj <- make_cookie_jar
  li_result <- log_in cj username password

  putStrLn "Waiting one second..."
  thread_sleep 1

  html <- get_page (Just cj) my_article

And this program is not at all time sensitive, so that actually works
for me. But now I'm curious. Does anyone have an idea what sort of
sorcery is going on?

Here's the rest of log_in if it's useful.



log_in :: FilePath -> String -> String -> IO Bool
log_in cookie_jar username password =
  withCurlDo $ do
    -- Create a curl instance.
    curl <- initialize

    -- Perform the request, and get back a CurlResponse object.
    -- The cast is needed to specify how we would like our headers
    -- and body returned (Strings).
    resp <- do_curl_ curl login_url curl_opts :: IO CurlResponse

    -- Pull out the response code as a CurlCode.
    let code = respCurlCode resp

    case code of
      CurlOK -> return True
      error_code -> do
        hPutStrLn stderr ("HTTP Error: " ++ (show error_code))
        -- If an error occurred, we want to dump as much information as
        -- possible. If this becomes a problem, we can use respGetInfo
        -- to query the response object for more information
        return False
  where
    post_submit :: String
    post_submit = submit_field ++ "=Log+In"

    post_username :: String
    post_username = username_field ++ "=" ++ username

    post_password :: String
    post_password = password_field ++ "=" ++ password

    post_data :: [String]
    post_data = [post_username, post_password, post_submit]

    post_opts :: [CurlOption]
    post_opts =
      [ CurlCookieSession True,
        CurlCookieJar cookie_jar,
        CurlPost True,
        CurlPostFields post_data ]

    curl_opts :: [CurlOption]
    curl_opts = default_curl_opts ++ post_opts


default_curl_opts :: [CurlOption]
default_curl_opts =
  [ -- The Global cache is not thread-friendly.
    CurlDNSUseGlobalCache False,

    -- And we don't want to use a DNS cache anyway.
    CurlDNSCacheTimeout 0,

    -- Follow redirects.
    CurlFollowLocation True,

    -- Give it a little time...
    CurlTimeout 45,

    -- For debugging.
    CurlVerbose True ]



More information about the Haskell-Cafe mailing list