module Network.HTTP.Client.Request
( parseUrl
, parseUrlThrow
, parseRequest
, parseRequest_
, defaultRequest
, setUriRelative
, getUri
, setUri
, browserDecompress
, alwaysDecompress
, addProxy
, applyBasicAuth
, applyBasicProxyAuth
, urlEncodedBody
, needsGunzip
, requestBuilder
, setRequestIgnoreStatus
, setQueryString
#if MIN_VERSION_http_types(0,12,1)
, setQueryStringPartialEscape
#endif
, streamFile
, observedStreamFile
, extractBasicAuthInfo
) where
import Data.Int (Int64)
import Data.Maybe (fromMaybe, isJust, isNothing)
import Data.Monoid (mempty, mappend, (<>))
import Data.String (IsString(..))
import Data.Char (toLower)
import Control.Applicative as A ((<$>))
import Control.Monad (unless, guard)
import Numeric (showHex)
import Blaze.ByteString.Builder (Builder, fromByteString, fromLazyByteString, toByteStringIO, flush)
import Blaze.ByteString.Builder.Char8 (fromChar, fromShow)
import qualified Data.ByteString as S
import qualified Data.ByteString.Char8 as S8
import qualified Data.ByteString.Lazy as L
import Data.ByteString.Lazy.Internal (defaultChunkSize)
import qualified Network.HTTP.Types as W
import Network.URI (URI (..), URIAuth (..), parseURI, relativeTo, escapeURIString, unEscapeString, isAllowedInURI)
import Control.Exception (throw, throwIO, IOException)
import qualified Control.Exception as E
import qualified Data.CaseInsensitive as CI
import qualified Data.ByteArray.Encoding as BAE
import Network.HTTP.Client.Body
import Network.HTTP.Client.Types
import Network.HTTP.Client.Util
import Control.Monad.Catch (MonadThrow, throwM)
import System.IO (withBinaryFile, hTell, hFileSize, Handle, IOMode (ReadMode))
import Control.Monad (liftM)
parseUrl :: MonadThrow m => String -> m Request
parseUrl = parseUrlThrow
parseUrlThrow :: MonadThrow m => String -> m Request
parseUrlThrow =
liftM yesThrow . parseRequest
where
yesThrow req = req
{ checkResponse = \_req res ->
let W.Status sci _ = responseStatus res in
if 200 <= sci && sci < 300
then return ()
else do
chunk <- brReadSome (responseBody res) 1024
let res' = fmap (const ()) res
throwHttp $ StatusCodeException res' (L.toStrict chunk)
}
parseRequest :: MonadThrow m => String -> m Request
parseRequest s' =
case parseURI (encode s) of
Just uri -> liftM setMethod (setUri defaultRequest uri)
Nothing -> throwM $ InvalidUrlException s "Invalid URL"
where
encode = escapeURIString isAllowedInURI
(mmethod, s) =
case break (== ' ') s' of
(x, ' ':y) | all (\c -> 'A' <= c && c <= 'Z') x -> (Just x, y)
_ -> (Nothing, s')
setMethod req =
case mmethod of
Nothing -> req
Just m -> req { method = S8.pack m }
parseRequest_ :: String -> Request
parseRequest_ = either throw id . parseRequest
setUriRelative :: MonadThrow m => Request -> URI -> m Request
setUriRelative req uri = setUri req $ uri `relativeTo` getUri req
getUri :: Request -> URI
getUri req = URI
{ uriScheme = if secure req
then "https:"
else "http:"
, uriAuthority = Just URIAuth
{ uriUserInfo = ""
, uriRegName = S8.unpack $ host req
, uriPort = ':' : show (port req)
}
, uriPath = S8.unpack $ path req
, uriQuery =
case S8.uncons $ queryString req of
Just (c, _) | c /= '?' -> '?' : (S8.unpack $ queryString req)
_ -> S8.unpack $ queryString req
, uriFragment = ""
}
applyAnyUriBasedAuth :: URI -> Request -> Request
applyAnyUriBasedAuth uri req =
case extractBasicAuthInfo uri of
Just auth -> uncurry applyBasicAuth auth req
Nothing -> req
extractBasicAuthInfo :: URI -> Maybe (S8.ByteString, S8.ByteString)
extractBasicAuthInfo uri = do
userInfo <- uriUserInfo A.<$> uriAuthority uri
guard (':' `elem` userInfo)
let (username, ':':password) = break (==':') . takeWhile (/='@') $ userInfo
return (toLiteral username, toLiteral password)
where
toLiteral = S8.pack . unEscapeString
setUri :: MonadThrow m => Request -> URI -> m Request
setUri req uri = do
sec <- parseScheme uri
auth <- maybe (failUri "URL must be absolute") return $ uriAuthority uri
port' <- parsePort sec auth
return $ applyAnyUriBasedAuth uri req
{ host = S8.pack $ uriRegName auth
, port = port'
, secure = sec
, path = S8.pack $
if null $ uriPath uri
then "/"
else uriPath uri
, queryString = S8.pack $ uriQuery uri
}
where
failUri :: MonadThrow m => String -> m a
failUri = throwM . InvalidUrlException (show uri)
parseScheme URI{uriScheme = scheme} =
case map toLower scheme of
"http:" -> return False
"https:" -> return True
_ -> failUri "Invalid scheme"
parsePort sec URIAuth{uriPort = portStr} =
case portStr of
':':rest -> maybe
(failUri "Invalid port")
return
(readDec rest)
_ -> case sec of
False -> return 80
True -> return 443
defaultRequest :: Request
defaultRequest = Request
{ host = "localhost"
, port = 80
, secure = False
, requestHeaders = []
, path = "/"
, queryString = S8.empty
, requestBody = RequestBodyLBS L.empty
, method = "GET"
, proxy = Nothing
, hostAddress = Nothing
, rawBody = False
, decompress = browserDecompress
, redirectCount = 10
, checkResponse = \_ _ -> return ()
, responseTimeout = ResponseTimeoutDefault
, cookieJar = Just Data.Monoid.mempty
, requestVersion = W.http11
, onRequestBodyException = \se ->
case E.fromException se of
Just (_ :: IOException) -> return ()
Nothing -> throwIO se
, requestManagerOverride = Nothing
}
instance IsString Request where
fromString = parseRequest_
alwaysDecompress :: S.ByteString -> Bool
alwaysDecompress = const True
browserDecompress :: S.ByteString -> Bool
browserDecompress = (/= "application/x-tar")
buildBasicAuth ::
S8.ByteString
-> S8.ByteString
-> S8.ByteString
buildBasicAuth user passwd =
S8.append "Basic " (BAE.convertToBase BAE.Base64 (S8.concat [ user, ":", passwd ]))
applyBasicAuth :: S.ByteString -> S.ByteString -> Request -> Request
applyBasicAuth user passwd req =
req { requestHeaders = authHeader : requestHeaders req }
where
authHeader = (CI.mk "Authorization", buildBasicAuth user passwd)
addProxy :: S.ByteString -> Int -> Request -> Request
addProxy hst prt req =
req { proxy = Just $ Proxy hst prt }
applyBasicProxyAuth :: S.ByteString -> S.ByteString -> Request -> Request
applyBasicProxyAuth user passwd req =
req { requestHeaders = authHeader : requestHeaders req }
where
authHeader = (CI.mk "Proxy-Authorization", buildBasicAuth user passwd)
urlEncodedBody :: [(S.ByteString, S.ByteString)] -> Request -> Request
urlEncodedBody headers req = req
{ requestBody = RequestBodyLBS body
, method = "POST"
, requestHeaders =
(ct, "application/x-www-form-urlencoded")
: filter (\(x, _) -> x /= ct) (requestHeaders req)
}
where
ct = "Content-Type"
body = L.fromChunks . return $ W.renderSimpleQuery False headers
needsGunzip :: Request
-> [W.Header]
-> Bool
needsGunzip req hs' =
not (rawBody req)
&& ("content-encoding", "gzip") `elem` hs'
&& decompress req (fromMaybe "" $ lookup "content-type" hs')
requestBuilder :: Request -> Connection -> IO (Maybe (IO ()))
requestBuilder req Connection {..} = do
(contentLength, sendNow, sendLater) <- toTriple (requestBody req)
if expectContinue
then flushHeaders contentLength >> return (Just (checkBadSend sendLater))
else sendNow >> return Nothing
where
expectContinue = Just "100-continue" == lookup "Expect" (requestHeaders req)
checkBadSend f = f `E.catch` onRequestBodyException req
writeBuilder = toByteStringIO connectionWrite
writeHeadersWith contentLength = writeBuilder . (builder contentLength `Data.Monoid.mappend`)
flushHeaders contentLength = writeHeadersWith contentLength flush
toTriple (RequestBodyLBS lbs) = do
let body = fromLazyByteString lbs
len = Just $ L.length lbs
now = checkBadSend $ writeHeadersWith len body
later = writeBuilder body
return (len, now, later)
toTriple (RequestBodyBS bs) = do
let body = fromByteString bs
len = Just $ fromIntegral $ S.length bs
now = checkBadSend $ writeHeadersWith len body
later = writeBuilder body
return (len, now, later)
toTriple (RequestBodyBuilder len body) = do
let now = checkBadSend $ writeHeadersWith (Just len) body
later = writeBuilder body
return (Just len, now, later)
toTriple (RequestBodyStream len stream) = do
let body = writeStream (Just . fromIntegral $ len) stream
now = flushHeaders (Just len) >> checkBadSend body
return (Just len, now, body)
toTriple (RequestBodyStreamChunked stream) = do
let body = writeStream Nothing stream
now = flushHeaders Nothing >> checkBadSend body
return (Nothing, now, body)
toTriple (RequestBodyIO mbody) = mbody >>= toTriple
writeStream mlen withStream =
withStream (loop 0)
where
loop !n stream = do
bs <- stream
if S.null bs
then case mlen of
Nothing -> connectionWrite "0\r\n\r\n"
Just len -> unless (len == n) $ throwHttp $ WrongRequestBodyStreamSize (fromIntegral len) (fromIntegral n)
else do
connectionWrite $
if (isNothing mlen)
then S.concat
[ S8.pack $ showHex (S.length bs) "\r\n"
, bs
, "\r\n"
]
else bs
loop (n + (S.length bs)) stream
hh
| port req == 80 && not (secure req) = host req
| port req == 443 && secure req = host req
| otherwise = host req <> S8.pack (':' : show (port req))
requestProtocol
| secure req = fromByteString "https://"
| otherwise = fromByteString "http://"
requestHostname
| isJust (proxy req) && not (secure req)
= requestProtocol <> fromByteString hh
| otherwise = mempty
contentLengthHeader (Just contentLength') =
if method req `elem` ["GET", "HEAD"] && contentLength' == 0
then id
else (:) ("Content-Length", S8.pack $ show contentLength')
contentLengthHeader Nothing = (:) ("Transfer-Encoding", "chunked")
acceptEncodingHeader =
case lookup "Accept-Encoding" $ requestHeaders req of
Nothing -> (("Accept-Encoding", "gzip"):)
Just "" -> filter (\(k, _) -> k /= "Accept-Encoding")
Just _ -> id
hostHeader x =
case lookup "Host" x of
Nothing -> ("Host", hh) : x
Just{} -> x
headerPairs :: Maybe Int64 -> W.RequestHeaders
headerPairs contentLength
= hostHeader
$ acceptEncodingHeader
$ contentLengthHeader contentLength
$ requestHeaders req
builder :: Maybe Int64 -> Builder
builder contentLength =
fromByteString (method req)
<> fromByteString " "
<> requestHostname
<> (case S8.uncons $ path req of
Just ('/', _) -> fromByteString $ path req
_ -> fromChar '/' <> fromByteString (path req))
<> (case S8.uncons $ queryString req of
Nothing -> mempty
Just ('?', _) -> fromByteString $ queryString req
_ -> fromChar '?' <> fromByteString (queryString req))
<> (case requestVersion req of
W.HttpVersion 1 1 -> fromByteString " HTTP/1.1\r\n"
W.HttpVersion 1 0 -> fromByteString " HTTP/1.0\r\n"
version ->
fromChar ' ' <>
fromShow version <>
fromByteString "\r\n")
<> foldr
(\a b -> headerPairToBuilder a <> b)
(fromByteString "\r\n")
(headerPairs contentLength)
headerPairToBuilder (k, v) =
fromByteString (CI.original k)
<> fromByteString ": "
<> fromByteString v
<> fromByteString "\r\n"
setRequestIgnoreStatus :: Request -> Request
setRequestIgnoreStatus req = req { checkResponse = \_ _ -> return () }
setQueryString :: [(S.ByteString, Maybe S.ByteString)] -> Request -> Request
setQueryString qs req = req { queryString = W.renderQuery True qs }
#if MIN_VERSION_http_types(0,12,1)
setQueryStringPartialEscape :: [(S.ByteString, [W.EscapeItem])] -> Request -> Request
setQueryStringPartialEscape qs req = req { queryString = W.renderQueryPartialEscape True qs }
#endif
streamFile :: FilePath -> IO RequestBody
streamFile = observedStreamFile (\_ -> return ())
observedStreamFile :: (StreamFileStatus -> IO ()) -> FilePath -> IO RequestBody
observedStreamFile obs path = do
size <- fromIntegral <$> withBinaryFile path ReadMode hFileSize
let filePopper :: Handle -> Popper
filePopper h = do
bs <- S.hGetSome h defaultChunkSize
currentPosition <- fromIntegral <$> hTell h
obs $ StreamFileStatus
{ fileSize = size
, readSoFar = currentPosition
, thisChunkSize = S.length bs
}
return bs
givesFilePopper :: GivesPopper ()
givesFilePopper k = withBinaryFile path ReadMode $ \h -> do
k (filePopper h)
return $ RequestBodyStream size givesFilePopper