[Haskell-beginners] Get responsecode(Int) from simpleHTTP's Response

Michael Orlitzky michael at orlitzky.com
Wed Oct 17 01:32:57 CEST 2012


On 10/16/2012 03:10 PM, Jacques du Rand wrote:
> HI all
> I'm trying to write a function that gives me the HTTP code in Int
> 
> --This is broken
> getStatusCode::Response->String
> getStatusCode (Response _,x1,_,_) = x1
> 
> --this work the download  trying to get http status code as well
> download_file fname url= do
> let clean_uri = check_url url
> putStrLn ("Downloading " ++ url ++ "...")
> rsp <- simpleHTTP (defaultGETRequest_ clean_uri) 
> --problamatic function next line
>                                                         print
> (getStatusCode rsp)
> file_buffer <- getResponseBody(rsp)
> B.writeFile fname file_buffer
> Best Regards


There are two reasons this isn't working...

The first is that simpleHTTP doesn't return a Response object. I'm
guessing from your variable name that you're expecting one. In fact, it
returns *either* an error *or* a Response object, so the first thing you
have to do before you deal with the response is check for an error.

The second problem is that the response code (within a Response object)
is not an integer -- it's an ordered pair of three integers (x,y,z). The
reason stated in the docs is so that it's easy to tell whether or not
you've got an OK/Error code on your hands.

This is the simplest thing I could come up with that does what you want.

  module Main
  where

  import Network.HTTP

  main :: IO ()
  main = do
    let req = getRequest "http://michael.orlitzky.com/"
    result <- simpleHTTP req
    case result of
      Left err -> do
        putStrLn "Error!"
      Right response -> do
        let (x,y,z) = rspCode response
        let hundreds = 100*x
        let tens = 10*y
        let ones = z
        let code = hundreds + tens + ones
        putStrLn $ "Response code: " ++ (show code)

    return ()


You could of course factor out the part that multiplies the (x,y,z) by
(100,10,1) into a function.



More information about the Beginners mailing list