{-# LANGUAGE MultiParamTypeClasses, GeneralizedNewtypeDeriving, CPP, FlexibleContexts #-}
module Network.Browser
( BrowserState
, BrowserAction
, Proxy(..)
, browse
, request
, getBrowserState
, withBrowserState
, setAllowRedirects
, getAllowRedirects
, setMaxRedirects
, getMaxRedirects
, Authority(..)
, getAuthorities
, setAuthorities
, addAuthority
, Challenge(..)
, Qop(..)
, Algorithm(..)
, getAuthorityGen
, setAuthorityGen
, setAllowBasicAuth
, getAllowBasicAuth
, setMaxErrorRetries
, getMaxErrorRetries
, setMaxPoolSize
, getMaxPoolSize
, setMaxAuthAttempts
, getMaxAuthAttempts
, setCookieFilter
, getCookieFilter
, defaultCookieFilter
, userCookieFilter
, Cookie(..)
, getCookies
, setCookies
, addCookie
, setErrHandler
, setOutHandler
, setEventHandler
, BrowserEvent(..)
, BrowserEventType(..)
, RequestID
, setProxy
, getProxy
, setCheckForProxy
, getCheckForProxy
, setDebugLog
, getUserAgent
, setUserAgent
, out
, err
, ioAction
, defaultGETRequest
, defaultGETRequest_
, formToRequest
, uriDefaultTo
, Form(..)
, FormVar
) where
import Network.URI
( URI(..)
, URIAuth(..)
, parseURI, parseURIReference, relativeTo
)
import Network.StreamDebugger (debugByteStream)
import Network.HTTP hiding ( sendHTTP_notify )
import Network.HTTP.HandleStream ( sendHTTP_notify )
import Network.HTTP.Auth
import Network.HTTP.Cookie
import Network.HTTP.Proxy
import Network.Stream ( ConnError(..), Result )
import Network.BufferType
import Data.Char (toLower)
import Data.List (isPrefixOf)
import Data.Maybe (fromMaybe, listToMaybe, catMaybes )
import Control.Applicative (Applicative (..), (<$>))
#ifdef MTL1
import Control.Monad (filterM, forM_, when, ap)
#else
import Control.Monad (filterM, forM_, when)
#endif
import Control.Monad.State (StateT (..), MonadIO (..), modify, gets, withStateT, evalStateT, MonadState (..))
import qualified System.IO
( hSetBuffering, hPutStr, stdout, stdin, hGetChar
, BufferMode(NoBuffering, LineBuffering)
)
import Data.Time.Clock ( UTCTime, getCurrentTime )
defaultCookieFilter :: URI -> Cookie -> IO Bool
defaultCookieFilter _url _cky = return True
userCookieFilter :: URI -> Cookie -> IO Bool
userCookieFilter url cky = do
do putStrLn ("Set-Cookie received when requesting: " ++ show url)
case ckComment cky of
Nothing -> return ()
Just x -> putStrLn ("Cookie Comment:\n" ++ x)
let pth = maybe "" ('/':) (ckPath cky)
putStrLn ("Domain/Path: " ++ ckDomain cky ++ pth)
putStrLn (ckName cky ++ '=' : ckValue cky)
System.IO.hSetBuffering System.IO.stdout System.IO.NoBuffering
System.IO.hSetBuffering System.IO.stdin System.IO.NoBuffering
System.IO.hPutStr System.IO.stdout "Accept [y/n]? "
x <- System.IO.hGetChar System.IO.stdin
System.IO.hSetBuffering System.IO.stdin System.IO.LineBuffering
System.IO.hSetBuffering System.IO.stdout System.IO.LineBuffering
return (toLower x == 'y')
addCookie :: Cookie -> BrowserAction t ()
addCookie c = modify (\b -> b{bsCookies = c : filter (/=c) (bsCookies b) })
setCookies :: [Cookie] -> BrowserAction t ()
setCookies cs = modify (\b -> b { bsCookies=cs })
getCookies :: BrowserAction t [Cookie]
getCookies = gets bsCookies
getCookiesFor :: String -> String -> BrowserAction t [Cookie]
getCookiesFor dom path =
do cks <- getCookies
return (filter cookiematch cks)
where
cookiematch :: Cookie -> Bool
cookiematch = cookieMatch (dom,path)
setCookieFilter :: (URI -> Cookie -> IO Bool) -> BrowserAction t ()
setCookieFilter f = modify (\b -> b { bsCookieFilter=f })
getCookieFilter :: BrowserAction t (URI -> Cookie -> IO Bool)
getCookieFilter = gets bsCookieFilter
getAuthFor :: String -> String -> BrowserAction t [Authority]
getAuthFor dom pth = getAuthorities >>= return . (filter match)
where
match :: Authority -> Bool
match au@AuthBasic{} = matchURI (auSite au)
match au@AuthDigest{} = or (map matchURI (auDomain au))
matchURI :: URI -> Bool
matchURI s = (uriToAuthorityString s == dom) && (uriPath s `isPrefixOf` pth)
getAuthorities :: BrowserAction t [Authority]
getAuthorities = gets bsAuthorities
setAuthorities :: [Authority] -> BrowserAction t ()
setAuthorities as = modify (\b -> b { bsAuthorities=as })
addAuthority :: Authority -> BrowserAction t ()
addAuthority a = modify (\b -> b { bsAuthorities=a:bsAuthorities b })
getAuthorityGen :: BrowserAction t (URI -> String -> IO (Maybe (String,String)))
getAuthorityGen = gets bsAuthorityGen
setAuthorityGen :: (URI -> String -> IO (Maybe (String,String))) -> BrowserAction t ()
setAuthorityGen f = modify (\b -> b { bsAuthorityGen=f })
setAllowBasicAuth :: Bool -> BrowserAction t ()
setAllowBasicAuth ba = modify (\b -> b { bsAllowBasicAuth=ba })
getAllowBasicAuth :: BrowserAction t Bool
getAllowBasicAuth = gets bsAllowBasicAuth
setMaxAuthAttempts :: Maybe Int -> BrowserAction t ()
setMaxAuthAttempts mb
| fromMaybe 0 mb < 0 = return ()
| otherwise = modify (\ b -> b{bsMaxAuthAttempts=mb})
getMaxAuthAttempts :: BrowserAction t (Maybe Int)
getMaxAuthAttempts = gets bsMaxAuthAttempts
setMaxErrorRetries :: Maybe Int -> BrowserAction t ()
setMaxErrorRetries mb
| fromMaybe 0 mb < 0 = return ()
| otherwise = modify (\ b -> b{bsMaxErrorRetries=mb})
getMaxErrorRetries :: BrowserAction t (Maybe Int)
getMaxErrorRetries = gets bsMaxErrorRetries
pickChallenge :: Bool -> [Challenge] -> Maybe Challenge
pickChallenge allowBasic []
| allowBasic = Just (ChalBasic "/")
pickChallenge _ ls = listToMaybe ls
anticipateChallenge :: Request ty -> BrowserAction t (Maybe Authority)
anticipateChallenge rq =
let uri = rqURI rq in
do { authlist <- getAuthFor (uriAuthToString $ reqURIAuth rq) (uriPath uri)
; return (listToMaybe authlist)
}
challengeToAuthority :: URI -> Challenge -> BrowserAction t (Maybe Authority)
challengeToAuthority uri ch
| not (answerable ch) = return Nothing
| otherwise = do
prompt <- getAuthorityGen
userdetails <- liftIO $ prompt uri (chRealm ch)
case userdetails of
Nothing -> return Nothing
Just (u,p) -> return (Just $ buildAuth ch u p)
where
answerable :: Challenge -> Bool
answerable ChalBasic{} = True
answerable chall = (chAlgorithm chall) == Just AlgMD5
buildAuth :: Challenge -> String -> String -> Authority
buildAuth (ChalBasic r) u p =
AuthBasic { auSite=uri
, auRealm=r
, auUsername=u
, auPassword=p
}
buildAuth (ChalDigest r d n o _stale a q) u p =
AuthDigest { auRealm=r
, auUsername=u
, auPassword=p
, auDomain=d
, auNonce=n
, auOpaque=o
, auAlgorithm=a
, auQop=q
}
data BrowserState connection
= BS { bsErr, bsOut :: String -> IO ()
, bsCookies :: [Cookie]
, bsCookieFilter :: URI -> Cookie -> IO Bool
, bsAuthorityGen :: URI -> String -> IO (Maybe (String,String))
, bsAuthorities :: [Authority]
, bsAllowRedirects :: Bool
, bsAllowBasicAuth :: Bool
, bsMaxRedirects :: Maybe Int
, bsMaxErrorRetries :: Maybe Int
, bsMaxAuthAttempts :: Maybe Int
, bsMaxPoolSize :: Maybe Int
, bsConnectionPool :: [connection]
, bsCheckProxy :: Bool
, bsProxy :: Proxy
, bsDebug :: Maybe String
, bsEvent :: Maybe (BrowserEvent -> BrowserAction connection ())
, bsRequestID :: RequestID
, bsUserAgent :: Maybe String
}
instance Show (BrowserState t) where
show bs = "BrowserState { "
++ shows (bsCookies bs) ("\n"
++ "AllowRedirects: " ++ shows (bsAllowRedirects bs) "} ")
newtype BrowserAction conn a
= BA { unBA :: StateT (BrowserState conn) IO a }
#ifdef MTL1
deriving (Functor, Monad, MonadIO, MonadState (BrowserState conn))
instance Applicative (BrowserAction conn) where
pure = return
(<*>) = ap
#else
deriving (Functor, Applicative, Monad, MonadIO, MonadState (BrowserState conn))
#endif
runBA :: BrowserState conn -> BrowserAction conn a -> IO a
runBA bs = flip evalStateT bs . unBA
browse :: BrowserAction conn a -> IO a
browse = runBA defaultBrowserState
defaultBrowserState :: BrowserState t
defaultBrowserState = res
where
res = BS
{ bsErr = putStrLn
, bsOut = putStrLn
, bsCookies = []
, bsCookieFilter = defaultCookieFilter
, bsAuthorityGen = \ _uri _realm -> do
bsErr res "No action for prompting/generating user+password credentials provided (use: setAuthorityGen); returning Nothing"
return Nothing
, bsAuthorities = []
, bsAllowRedirects = True
, bsAllowBasicAuth = False
, bsMaxRedirects = Nothing
, bsMaxErrorRetries = Nothing
, bsMaxAuthAttempts = Nothing
, bsMaxPoolSize = Nothing
, bsConnectionPool = []
, bsCheckProxy = defaultAutoProxyDetect
, bsProxy = noProxy
, bsDebug = Nothing
, bsEvent = Nothing
, bsRequestID = 0
, bsUserAgent = Nothing
}
{-# DEPRECATED getBrowserState "Use Control.Monad.State.get instead." #-}
getBrowserState :: BrowserAction t (BrowserState t)
getBrowserState = get
withBrowserState :: BrowserState t -> BrowserAction t a -> BrowserAction t a
withBrowserState bs = BA . withStateT (const bs) . unBA
nextRequest :: BrowserAction t a -> BrowserAction t a
nextRequest act = do
let updReqID st =
let
rid = succ (bsRequestID st)
in
rid `seq` st{bsRequestID=rid}
modify updReqID
act
{-# DEPRECATED ioAction "Use Control.Monad.Trans.liftIO instead." #-}
ioAction :: IO a -> BrowserAction t a
ioAction = liftIO
setErrHandler :: (String -> IO ()) -> BrowserAction t ()
setErrHandler h = modify (\b -> b { bsErr=h })
setOutHandler :: (String -> IO ()) -> BrowserAction t ()
setOutHandler h = modify (\b -> b { bsOut=h })
out, err :: String -> BrowserAction t ()
out s = do { f <- gets bsOut ; liftIO $ f s }
err s = do { f <- gets bsErr ; liftIO $ f s }
setAllowRedirects :: Bool -> BrowserAction t ()
setAllowRedirects bl = modify (\b -> b {bsAllowRedirects=bl})
getAllowRedirects :: BrowserAction t Bool
getAllowRedirects = gets bsAllowRedirects
setMaxRedirects :: Maybe Int -> BrowserAction t ()
setMaxRedirects c
| fromMaybe 0 c < 0 = return ()
| otherwise = modify (\b -> b{bsMaxRedirects=c})
getMaxRedirects :: BrowserAction t (Maybe Int)
getMaxRedirects = gets bsMaxRedirects
setMaxPoolSize :: Maybe Int -> BrowserAction t ()
setMaxPoolSize c = modify (\b -> b{bsMaxPoolSize=c})
getMaxPoolSize :: BrowserAction t (Maybe Int)
getMaxPoolSize = gets bsMaxPoolSize
setProxy :: Proxy -> BrowserAction t ()
setProxy p =
modify (\b -> b {bsProxy = p, bsCheckProxy=False})
getProxy :: BrowserAction t Proxy
getProxy = do
p <- gets bsProxy
case p of
Proxy{} -> return p
NoProxy{} -> do
flg <- gets bsCheckProxy
if not flg
then return p
else do
np <- liftIO $ fetchProxy True
setProxy np
return np
setCheckForProxy :: Bool -> BrowserAction t ()
setCheckForProxy flg = modify (\ b -> b{bsCheckProxy=flg})
getCheckForProxy :: BrowserAction t Bool
getCheckForProxy = gets bsCheckProxy
setDebugLog :: Maybe String -> BrowserAction t ()
setDebugLog v = modify (\b -> b {bsDebug=v})
setUserAgent :: String -> BrowserAction t ()
setUserAgent ua = modify (\b -> b{bsUserAgent=Just ua})
getUserAgent :: BrowserAction t String
getUserAgent = do
n <- gets bsUserAgent
return (maybe defaultUserAgent id n)
data RequestState
= RequestState
{ reqDenies :: Int
, reqRedirects :: Int
, reqRetries :: Int
, reqStopOnDeny :: Bool
}
type RequestID = Int
nullRequestState :: RequestState
nullRequestState = RequestState
{ reqDenies = 0
, reqRedirects = 0
, reqRetries = 0
, reqStopOnDeny = True
}
data BrowserEvent
= BrowserEvent
{ browserTimestamp :: UTCTime
, browserRequestID :: RequestID
, browserRequestURI :: String
, browserEventType :: BrowserEventType
}
data BrowserEventType
= OpenConnection
| ReuseConnection
| RequestSent
| ResponseEnd ResponseData
| ResponseFinish
setEventHandler :: Maybe (BrowserEvent -> BrowserAction ty ()) -> BrowserAction ty ()
setEventHandler mbH = modify (\b -> b { bsEvent=mbH})
buildBrowserEvent :: BrowserEventType -> String -> RequestID -> IO BrowserEvent
buildBrowserEvent bt uri reqID = do
ct <- getCurrentTime
return BrowserEvent
{ browserTimestamp = ct
, browserRequestID = reqID
, browserRequestURI = uri
, browserEventType = bt
}
reportEvent :: BrowserEventType -> String -> BrowserAction t ()
reportEvent bt uri = do
st <- get
case bsEvent st of
Nothing -> return ()
Just evH -> do
evt <- liftIO $ buildBrowserEvent bt uri (bsRequestID st)
evH evt
defaultMaxRetries :: Int
defaultMaxRetries = 4
defaultMaxErrorRetries :: Int
defaultMaxErrorRetries = 4
defaultMaxAuthAttempts :: Int
defaultMaxAuthAttempts = 2
defaultAutoProxyDetect :: Bool
defaultAutoProxyDetect = False
request :: HStream ty
=> Request ty
-> BrowserAction (HandleStream ty) (URI,Response ty)
request req = nextRequest $ do
res <- request' nullVal initialState req
reportEvent ResponseFinish (show (rqURI req))
case res of
Right r -> return r
Left e -> do
let errStr = ("Network.Browser.request: Error raised " ++ show e)
err errStr
fail errStr
where
initialState = nullRequestState
nullVal = buf_empty bufferOps
request' :: HStream ty
=> ty
-> RequestState
-> Request ty
-> BrowserAction (HandleStream ty) (Result (URI,Response ty))
request' nullVal rqState rq = do
let uri = rqURI rq
failHTTPS uri
let uria = reqURIAuth rq
cookies <- getCookiesFor (uriAuthToString uria) (uriPath uri)
when (not $ null cookies)
(out $ "Adding cookies to request. Cookie names: " ++ unwords (map ckName cookies))
rq' <-
if not (reqStopOnDeny rqState)
then return rq
else do
auth <- anticipateChallenge rq
case auth of
Nothing -> return rq
Just x -> return (insertHeader HdrAuthorization (withAuthority x rq) rq)
let rq'' = if not $ null cookies then insertHeaders [cookiesToHeader cookies] rq' else rq'
p <- getProxy
def_ua <- gets bsUserAgent
let defaultOpts =
case p of
NoProxy -> defaultNormalizeRequestOptions{normUserAgent=def_ua}
Proxy _ ath ->
defaultNormalizeRequestOptions
{ normForProxy = True
, normUserAgent = def_ua
, normCustoms =
maybe []
(\ authS -> [\ _ r -> insertHeader HdrProxyAuthorization (withAuthority authS r) r])
ath
}
let final_req = normalizeRequest defaultOpts rq''
out ("Sending:\n" ++ show final_req)
e_rsp <-
case p of
NoProxy -> dorequest (reqURIAuth rq'') final_req
Proxy str _ath -> do
let notURI
| null pt || null hst =
URIAuth{ uriUserInfo = ""
, uriRegName = str
, uriPort = ""
}
| otherwise =
URIAuth{ uriUserInfo = ""
, uriRegName = hst
, uriPort = pt
}
where (hst, pt) = span (':'/=) str
let proxyURIAuth =
maybe notURI
(\parsed -> maybe notURI id (uriAuthority parsed))
(parseURI str)
out $ "proxy uri host: " ++ uriRegName proxyURIAuth ++ ", port: " ++ uriPort proxyURIAuth
dorequest proxyURIAuth final_req
mbMx <- getMaxErrorRetries
case e_rsp of
Left v
| (reqRetries rqState < fromMaybe defaultMaxErrorRetries mbMx) &&
(v == ErrorReset || v == ErrorClosed) -> do
modify (\b -> b { bsConnectionPool=[] })
request' nullVal rqState{reqRetries=succ (reqRetries rqState)} rq
| otherwise ->
return (Left v)
Right rsp -> do
out ("Received:\n" ++ show rsp)
handleCookies uri (uriAuthToString $ reqURIAuth rq)
(retrieveHeaders HdrSetCookie rsp)
handleConnectionClose (reqURIAuth rq) (retrieveHeaders HdrConnection rsp)
mbMxAuths <- getMaxAuthAttempts
case rspCode rsp of
(4,0,1)
| reqDenies rqState > fromMaybe defaultMaxAuthAttempts mbMxAuths -> do
out "401 - credentials again refused; exceeded retry count (2)"
return (Right (uri,rsp))
| otherwise -> do
out "401 - credentials not supplied or refused; retrying.."
let hdrs = retrieveHeaders HdrWWWAuthenticate rsp
flg <- getAllowBasicAuth
case pickChallenge flg (catMaybes $ map (headerToChallenge uri) hdrs) of
Nothing -> do
out "no challenge"
return (Right (uri,rsp))
Just x -> do
au <- challengeToAuthority uri x
case au of
Nothing -> do
out "no auth"
return (Right (uri,rsp))
Just au' -> do
out "Retrying request with new credentials"
request' nullVal
rqState{ reqDenies = succ(reqDenies rqState)
, reqStopOnDeny = False
}
(insertHeader HdrAuthorization (withAuthority au' rq) rq)
(4,0,7)
| reqDenies rqState > fromMaybe defaultMaxAuthAttempts mbMxAuths -> do
out "407 - proxy authentication required; max deny count exceeeded (2)"
return (Right (uri,rsp))
| otherwise -> do
out "407 - proxy authentication required"
let hdrs = retrieveHeaders HdrProxyAuthenticate rsp
flg <- getAllowBasicAuth
case pickChallenge flg (catMaybes $ map (headerToChallenge uri) hdrs) of
Nothing -> return (Right (uri,rsp))
Just x -> do
au <- challengeToAuthority uri x
case au of
Nothing -> return (Right (uri,rsp))
Just au' -> do
pxy <- gets bsProxy
case pxy of
NoProxy -> do
err "Proxy authentication required without proxy!"
return (Right (uri,rsp))
Proxy px _ -> do
out "Retrying with proxy authentication"
setProxy (Proxy px (Just au'))
request' nullVal
rqState{ reqDenies = succ(reqDenies rqState)
, reqStopOnDeny = False
}
rq
(3,0,x) | x `elem` [2,3,1,7] -> do
out ("30" ++ show x ++ " - redirect")
allow_redirs <- allowRedirect rqState
case allow_redirs of
False -> return (Right (uri,rsp))
_ -> do
case retrieveHeaders HdrLocation rsp of
[] -> do
err "No Location: header in redirect response"
return (Right (uri,rsp))
(Header _ u:_) ->
case parseURIReference u of
Nothing -> do
err ("Parse of Location: header in a redirect response failed: " ++ u)
return (Right (uri,rsp))
Just newURI
| (not (supportedScheme newURI_abs)) -> do
err ("Unable to handle redirect, unsupported scheme: " ++ show newURI_abs)
return (Right (uri, rsp))
| otherwise -> do
out ("Redirecting to " ++ show newURI_abs ++ " ...")
let toGet = x `elem` [2,3]
method = if toGet then GET else rqMethod rq
rq1 = rq { rqMethod=method, rqURI=newURI_abs }
rq2 = if toGet then (replaceHeader HdrContentLength "0") (rq1 {rqBody = nullVal}) else rq1
request' nullVal
rqState{ reqDenies = 0
, reqRedirects = succ(reqRedirects rqState)
, reqStopOnDeny = True
}
rq2
where
newURI_abs = uriDefaultTo newURI uri
(3,0,5) ->
case retrieveHeaders HdrLocation rsp of
[] -> do
err "No Location header in proxy redirect response."
return (Right (uri,rsp))
(Header _ u:_) ->
case parseURIReference u of
Nothing -> do
err ("Parse of Location header in a proxy redirect response failed: " ++ u)
return (Right (uri,rsp))
Just newuri -> do
out ("Retrying with proxy " ++ show newuri ++ "...")
setProxy (Proxy (uriToAuthorityString newuri) Nothing)
request' nullVal rqState{ reqDenies = 0
, reqRedirects = 0
, reqRetries = succ (reqRetries rqState)
, reqStopOnDeny = True
}
rq
_ -> return (Right (uri,rsp))
dorequest :: (HStream ty)
=> URIAuth
-> Request ty
-> BrowserAction (HandleStream ty)
(Result (Response ty))
dorequest hst rqst = do
pool <- gets bsConnectionPool
let uPort = uriAuthPort Nothing hst
conn <- liftIO $ filterM (\c -> c `isTCPConnectedTo` EndPoint (uriRegName hst) uPort) pool
rsp <-
case conn of
[] -> do
out ("Creating new connection to " ++ uriAuthToString hst)
reportEvent OpenConnection (show (rqURI rqst))
c <- liftIO $ openStream (uriRegName hst) uPort
updateConnectionPool c
dorequest2 c rqst
(c:_) -> do
out ("Recovering connection to " ++ uriAuthToString hst)
reportEvent ReuseConnection (show (rqURI rqst))
dorequest2 c rqst
case rsp of
Right (Response a b c _) ->
reportEvent (ResponseEnd (a,b,c)) (show (rqURI rqst)) ; _ -> return ()
return rsp
where
dorequest2 c r = do
dbg <- gets bsDebug
st <- get
let
onSendComplete =
maybe (return ())
(\evh -> do
x <- buildBrowserEvent RequestSent (show (rqURI r)) (bsRequestID st)
runBA st (evh x)
return ())
(bsEvent st)
liftIO $
maybe (sendHTTP_notify c r onSendComplete)
(\ f -> do
c' <- debugByteStream (f++'-': uriAuthToString hst) c
sendHTTP_notify c' r onSendComplete)
dbg
updateConnectionPool :: HStream hTy
=> HandleStream hTy
-> BrowserAction (HandleStream hTy) ()
updateConnectionPool c = do
pool <- gets bsConnectionPool
let len_pool = length pool
maxPoolSize <- fromMaybe defaultMaxPoolSize <$> gets bsMaxPoolSize
when (len_pool > maxPoolSize)
(liftIO $ close (last pool))
let pool'
| len_pool > maxPoolSize = init pool
| otherwise = pool
when (maxPoolSize > 0) $ modify (\b -> b { bsConnectionPool=c:pool' })
return ()
defaultMaxPoolSize :: Int
defaultMaxPoolSize = 5
cleanConnectionPool :: HStream hTy
=> URIAuth -> BrowserAction (HandleStream hTy) ()
cleanConnectionPool uri = do
let ep = EndPoint (uriRegName uri) (uriAuthPort Nothing uri)
pool <- gets bsConnectionPool
bad <- liftIO $ mapM (\c -> c `isTCPConnectedTo` ep) pool
let tmp = zip bad pool
newpool = map snd $ filter (not . fst) tmp
toclose = map snd $ filter fst tmp
liftIO $ forM_ toclose close
modify (\b -> b { bsConnectionPool = newpool })
handleCookies :: URI -> String -> [Header] -> BrowserAction t ()
handleCookies _ _ [] = return ()
handleCookies uri dom cookieHeaders = do
when (not $ null errs)
(err $ unlines ("Errors parsing these cookie values: ":errs))
when (not $ null newCookies)
(out $ foldl (\x y -> x ++ "\n " ++ show y) "Cookies received:" newCookies)
filterfn <- getCookieFilter
newCookies' <- liftIO (filterM (filterfn uri) newCookies)
when (not $ null newCookies')
(out $ "Accepting cookies with names: " ++ unwords (map ckName newCookies'))
mapM_ addCookie newCookies'
where
(errs, newCookies) = processCookieHeaders dom cookieHeaders
handleConnectionClose :: HStream hTy
=> URIAuth -> [Header]
-> BrowserAction (HandleStream hTy) ()
handleConnectionClose _ [] = return ()
handleConnectionClose uri headers = do
let doClose = any (== "close") $ map headerToConnType headers
when doClose $ cleanConnectionPool uri
where headerToConnType (Header _ t) = map toLower t
allowRedirect :: RequestState -> BrowserAction t Bool
allowRedirect rqState = do
rd <- getAllowRedirects
mbMxRetries <- getMaxRedirects
return (rd && (reqRedirects rqState <= fromMaybe defaultMaxRetries mbMxRetries))
supportedScheme :: URI -> Bool
supportedScheme u = uriScheme u == "http:"
uriDefaultTo :: URI -> URI -> URI
#if MIN_VERSION_network(2,4,0)
uriDefaultTo a b = a `relativeTo` b
#else
uriDefaultTo a b = maybe a id (a `relativeTo` b)
#endif
type FormVar = (String,String)
data Form = Form RequestMethod URI [FormVar]
formToRequest :: Form -> Request_String
formToRequest (Form m u vs) =
let enc = urlEncodeVars vs
in case m of
GET -> Request { rqMethod=GET
, rqHeaders=[ Header HdrContentLength "0" ]
, rqBody=""
, rqURI=u { uriQuery= '?' : enc }
}
POST -> Request { rqMethod=POST
, rqHeaders=[ Header HdrContentType "application/x-www-form-urlencoded",
Header HdrContentLength (show $ length enc) ]
, rqBody=enc
, rqURI=u
}
_ -> error ("unexpected request: " ++ show m)