[Haskell-cafe] Browser action and new http library
bbrown
bbrown at botspiritcompany.com
Mon Nov 26 18:54:13 EST 2007
I am trying to use the HTTP library 3001 for ghc 6.8 and cant figure out how
to use a proxy to do a GET request as I am behind a proxy server. My thinking
is that I could use the setProxy method it looks like it returns a
BrowserAction? What do I do with that. Here is the current code (I havent
really used the setProxy yet).
--
-- HTTP LIBRARY version: HTTP-3001.0.2
import Data.Char (intToDigit)
import Network.HTTP
import Network.URI
import Network.Browser (defaultGETRequest)
import System.Environment (getArgs)
import System.Exit (exitFailure)
import System.IO (hPutStrLn, stderr)
main =
do
args <- getArgs
case args of
[addr] -> case parseURI addr of
Nothing -> err "Could not parse URI"
Just uri -> do
cont <- get uri
putStr cont
_ -> err "Usage: lman <url>"
err :: String -> IO a
err msg = do
hPutStrLn stderr msg
exitFailure
get :: URI -> IO String
get uri =
do
eresp <- simpleHTTP (defaultGETRequest uri)
resp <- handleErr (err . show) eresp
case rspCode resp of
(2,0,0) -> return (rspBody resp)
_ -> err (httpError resp)
where
showRspCode (a,b,c) = map intToDigit [a,b,c]
httpError resp = showRspCode (rspCode resp) ++ " " ++ rspReason resp
--
-- Handle Connection Errors
handleErr :: Monad m => (ConnError -> m a) -> Either ConnError a -> m a
handleErr h (Left e) = h e
handleErr _ (Right v) = return v
-- End of File
--
Berlin Brown
[berlin dot brown at gmail dot com]
http://botspiritcompany.com/botlist/?
More information about the Haskell-Cafe
mailing list