module Network.HTTP.Client.Core
( withResponse
, httpLbs
, httpNoBody
, httpRaw
, httpRaw'
, getModifiedRequestManager
, responseOpen
, responseClose
, httpRedirect
, httpRedirect'
) where
import Network.HTTP.Types
import Network.HTTP.Client.Manager
import Network.HTTP.Client.Types
import Network.HTTP.Client.Body
import Network.HTTP.Client.Request
import Network.HTTP.Client.Response
import Network.HTTP.Client.Cookies
import Data.Maybe (fromMaybe, isJust)
import Data.Time
import Control.Exception
import qualified Data.ByteString.Lazy as L
import Data.Monoid
import Control.Monad (void)
import System.Timeout (timeout)
import Data.KeyedPool
withResponse :: Request
-> Manager
-> (Response BodyReader -> IO a)
-> IO a
withResponse req man f = bracket (responseOpen req man) responseClose f
httpLbs :: Request -> Manager -> IO (Response L.ByteString)
httpLbs req man = withResponse req man $ \res -> do
bss <- brConsume $ responseBody res
return res { responseBody = L.fromChunks bss }
httpNoBody :: Request -> Manager -> IO (Response ())
httpNoBody req man = withResponse req man $ return . void
httpRaw
:: Request
-> Manager
-> IO (Response BodyReader)
httpRaw = fmap (fmap snd) . httpRaw'
httpRaw'
:: Request
-> Manager
-> IO (Request, Response BodyReader)
httpRaw' req0 m = do
let req' = mSetProxy m req0
(req, cookie_jar') <- case cookieJar req' of
Just cj -> do
now <- getCurrentTime
return $ insertCookiesIntoRequest req' (evictExpiredCookies cj now) now
Nothing -> return (req', Data.Monoid.mempty)
(timeout', mconn) <- getConnectionWrapper
(responseTimeout' req)
(getConn req m)
ex <- try $ do
cont <- requestBuilder (dropProxyAuthSecure req) (managedResource mconn)
getResponse timeout' req mconn cont
case ex of
Left e | managedReused mconn && mRetryableException m e -> do
managedRelease mconn DontReuse
httpRaw' req m
Left e -> throwIO e
Right res -> case cookieJar req' of
Just _ -> do
now' <- getCurrentTime
let (cookie_jar, _) = updateCookieJar res req now' cookie_jar'
return (req, res {responseCookieJar = cookie_jar})
Nothing -> return (req, res)
where
getConnectionWrapper mtimeout f =
case mtimeout of
Nothing -> fmap ((,) Nothing) f
Just timeout' -> do
before <- getCurrentTime
mres <- timeout timeout' f
case mres of
Nothing -> throwHttp ConnectionTimeout
Just res -> do
now <- getCurrentTime
let timeSpentMicro = diffUTCTime now before * 1000000
remainingTime = round $ fromIntegral timeout' timeSpentMicro
if remainingTime <= 0
then throwHttp ConnectionTimeout
else return (Just remainingTime, res)
responseTimeout' req =
case responseTimeout req of
ResponseTimeoutDefault ->
case mResponseTimeout m of
ResponseTimeoutDefault -> Just 30000000
ResponseTimeoutNone -> Nothing
ResponseTimeoutMicro u -> Just u
ResponseTimeoutNone -> Nothing
ResponseTimeoutMicro u -> Just u
getModifiedRequestManager :: Manager -> Request -> IO (Manager, Request)
getModifiedRequestManager manager0 req0 = do
let manager = fromMaybe manager0 (requestManagerOverride req0)
req <- mModifyRequest manager req0
return (manager, req)
responseOpen :: Request -> Manager -> IO (Response BodyReader)
responseOpen inputReq manager' = do
(manager, req0) <- getModifiedRequestManager manager' inputReq
wrapExc req0 $ mWrapException manager req0 $ do
(req, res) <- go manager (redirectCount req0) req0
checkResponse req req res
mModifyResponse manager res
{ responseBody = wrapExc req0 (responseBody res)
}
where
wrapExc :: Request -> IO a -> IO a
wrapExc req0 = handle $ throwIO . toHttpException req0
go manager0 count req' = httpRedirect'
count
(\req -> do
(manager, modReq) <- getModifiedRequestManager manager0 req
(req'', res) <- httpRaw' modReq manager
let mreq = if redirectCount modReq == 0
then Nothing
else getRedirectedRequest req'' (responseHeaders res) (responseCookieJar res) (statusCode (responseStatus res))
return (res, fromMaybe req'' mreq, isJust mreq))
req'
httpRedirect
:: Int
-> (Request -> IO (Response BodyReader, Maybe Request))
-> Request
-> IO (Response BodyReader)
httpRedirect count0 http0 req0 = fmap snd $ httpRedirect' count0 http' req0
where
http' req' = do
(res, mbReq) <- http0 req'
return (res, fromMaybe req0 mbReq, isJust mbReq)
httpRedirect'
:: Int
-> (Request -> IO (Response BodyReader, Request, Bool))
-> Request
-> IO (Request, Response BodyReader)
httpRedirect' count0 http' req0 = go count0 req0 []
where
go count _ ress | count < 0 = throwHttp $ TooManyRedirects ress
go count req' ress = do
(res, req, isRedirect) <- http' req'
if isRedirect then do
let maxFlush = 1024
lbs <- brReadSome (responseBody res) maxFlush
`Control.Exception.catch` \se ->
case () of
()
| Just ConnectionClosed <-
fmap unHttpExceptionContentWrapper
(fromException se) -> return L.empty
| Just (HttpExceptionRequest _ ConnectionClosed) <-
fromException se -> return L.empty
_ -> throwIO se
responseClose res
go (count 1) req (res { responseBody = lbs }:ress)
else
return (req, res)
responseClose :: Response a -> IO ()
responseClose = runResponseClose . responseClose'