Get responsecode(Int) from simpleHTTP's Response

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 Jacques

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.

You can replace all the multiplication with
concatMap show [x,y,z]
On Oct 16, 2012 7:34 PM, "Michael Orlitzky"
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.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

This is great works perfectly !
I'm so new at haskell its scary !
One last question i dont *understand* one line ( just the right side )
let (x,y,z) = rspCode response
1) If i look at the documentation: Sorry for HTML. I see the constructors
of Response and below it rspCode,rspReason,rspHeaders etc Are
those parters or functions ?
2) I see the new version has a getResponseCode functions like
getResponseBody with the signature:
getResponseCode :: Result (Response a) -> IO ResponseCode
getResponseCode (Left err) = fail (show err)
getResponseCode (Right r) = return (rspCode r)
What does this mean in the signature *Result (Response a)*
Thanks again
Jacques
Constructors
Response
rspCode ::ResponseCodehttp://hackage.haskell.org/packages/archive/HTTP/4000.0.7/doc/html/Network-H...
rspReason :: Stringhttp://hackage.haskell.org/packages/archive/base/4.2.0.2/doc/html/Data-Char....
rspHeaders :: [Headerhttp://hackage.haskell.org/packages/archive/HTTP/4000.0.7/doc/html/Network-H...
]rspBody :: a
On Wed, Oct 17, 2012 at 1:32 AM, Michael Orlitzky
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.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On 10/17/2012 02:51 AM, Jacques du Rand wrote:
This is great works perfectly ! I'm so new at haskell its scary !
One last question i dont *understand* one line ( just the right side )
let (x,y,z) = rspCode response
1) If i look at the documentation: Sorry for HTML. I see the constructors of Response and below it rspCode,rspReason,rspHeaders etc Are those parters or functions ?
They're functions that you can think of as the names of attributes of a Response object (if you're coming from object-oriented programming). There's a little magic going on under the hood, so you might want to check out e.g., http://learnyouahaskell.com/making-our-own-types-and-typeclasses In particular the "Record Syntax" section. Papering over the details, in an OO language, you might do something like, response.rspCode to get the code out of a Response object. In Haskell, we just use a function to do it. So, rspCode response calls the rspCode function on 'response'. If you check the API docs,
http://hackage.haskell.org/packages/archive/HTTP/4000.0.7/doc/html/Network-H... you should see that rspCode takes a Response object and returns a ResponseCode. But ResponseCode is just a synonym for (Int,Int,Int): type ResponseCode = (Int, Int, Int) Therefore, rspCode takes a Response, and gives you back three Ints in an ordered triplet.
2) I see the new version has a getResponseCode functions like getResponseBody with the signature: getResponseCode :: Result (Response a) -> IO ResponseCode getResponseCode (Left err) = fail (show err) getResponseCode (Right r) = return (rspCode r)
What does this mean in the signature *Result (Response a)*
The Result type is really just a wrapper around Either. Either usually takes two parameters, but Result fixes one of them to be ConnError: type Result a = Either ConnError a So Result still takes one parameter. The parameter in this case is (Response a). For a more concrete example, think of a data type where you've got a box and you can put stuff in it. data Box a = Box a The 'a' parameter means that we can put different types of stuff in the box. For example, foo :: Box Int foo = Box 3 bar :: Box String bar = Box "Hello" If this makes sense to you, then (Result (Response a)) is doing exactly the same thing as (Box Int) or (Box String), only with slightly more complicated types.

Michael
That's a fantastic explanation !
I appreciate the time taken and depth of it !
Best Regards
Jacques
On Wed, Oct 17, 2012 at 1:52 PM, Michael Orlitzky
On 10/17/2012 02:51 AM, Jacques du Rand wrote:
This is great works perfectly ! I'm so new at haskell its scary !
One last question i dont *understand* one line ( just the right side )
let (x,y,z) = rspCode response
1) If i look at the documentation: Sorry for HTML. I see the constructors of Response and below it rspCode,rspReason,rspHeaders etc Are those parters or functions ?
They're functions that you can think of as the names of attributes of a Response object (if you're coming from object-oriented programming). There's a little magic going on under the hood, so you might want to check out e.g.,
http://learnyouahaskell.com/making-our-own-types-and-typeclasses
In particular the "Record Syntax" section. Papering over the details, in an OO language, you might do something like,
response.rspCode
to get the code out of a Response object. In Haskell, we just use a function to do it. So,
rspCode response
calls the rspCode function on 'response'. If you check the API docs,
http://hackage.haskell.org/packages/archive/HTTP/4000.0.7/doc/html/Network-H...
you should see that rspCode takes a Response object and returns a ResponseCode. But ResponseCode is just a synonym for (Int,Int,Int):
type ResponseCode = (Int, Int, Int)
Therefore, rspCode takes a Response, and gives you back three Ints in an ordered triplet.
2) I see the new version has a getResponseCode functions like getResponseBody with the signature: getResponseCode :: Result (Response a) -> IO ResponseCode getResponseCode (Left err) = fail (show err) getResponseCode (Right r) = return (rspCode r)
What does this mean in the signature *Result (Response a)*
The Result type is really just a wrapper around Either. Either usually takes two parameters, but Result fixes one of them to be ConnError:
type Result a = Either ConnError a
So Result still takes one parameter. The parameter in this case is (Response a).
For a more concrete example, think of a data type where you've got a box and you can put stuff in it.
data Box a = Box a
The 'a' parameter means that we can put different types of stuff in the box. For example,
foo :: Box Int foo = Box 3
bar :: Box String bar = Box "Hello"
If this makes sense to you, then (Result (Response a)) is doing exactly the same thing as (Box Int) or (Box String), only with slightly more complicated types.
participants (3)
-
Jacques du Rand
-
Michael Orlitzky
-
Tom Murphy