Safe Haskell | None |
---|
Network.HTTP.Conduit
Contents
Description
This module contains everything you need to initiate HTTP connections. If
you want a simple interface based on URLs, you can use simpleHttp
. If you
want raw power, http
is the underlying workhorse of this package. Some
examples:
-- Just download an HTML document and print it. import Network.HTTP.Conduit import qualified Data.ByteString.Lazy as L main = simpleHttp "http://www.haskell.org/" >>= L.putStr
This example uses interleaved IO to write the response body to a file in constant memory space.
import Data.Conduit.Binary (sinkFile) import Network.HTTP.Conduit import qualified Data.Conduit as C main :: IO () main = do request <- parseUrl "http://google.com/" withManager $ \manager -> do response <- http request manager responseBody response C.$$+- sinkFile "google.html"
The following headers are automatically set by this module, and should not
be added to requestHeaders
:
- Cookie
- Content-Length
- Transfer-Encoding
Note: In previous versions, the Host header would be set by this module in
all cases. Starting from 1.6.1, if a Host header is present in
requestHeaders
, it will be used in place of the header this module would
have generated. This can be useful for calling a server which utilizes
virtual hosting.
Use cookieJar
If you want to supply cookies with your request:
{-# LANGUAGE OverloadedStrings #-} import Network.HTTP.Conduit import Network import Data.Time.Clock import Data.Time.Calendar import qualified Control.Exception as E past :: UTCTime past = UTCTime (ModifiedJulianDay 56200) (secondsToDiffTime 0) future :: UTCTime future = UTCTime (ModifiedJulianDay 562000) (secondsToDiffTime 0) cookie :: Cookie cookie = Cookie { cookie_name = "password_hash" , cookie_value = "abf472c35f8297fbcabf2911230001234fd2" , cookie_expiry_time = future , cookie_domain = "example.com" , cookie_path = "/" , cookie_creation_time = past , cookie_last_access_time = past , cookie_persistent = False , cookie_host_only = False , cookie_secure_only = False , cookie_http_only = False } main = withSocketsDo $ do request' <- parseUrl "http://example.com/secret-page" let request = request' { cookieJar = Just $ createCookieJar [cookie] } E.catch (withManager $ httpLbs request) (\(StatusCodeException s _ _) -> if statusCode==403 then putStrLn "login failed" else return ())
Any network code on Windows requires some initialization, and the network library provides withSocketsDo to perform it. Therefore, proper usage of this library will always involve calling that function at some point. The best approach is to simply call them at the beginning of your main function, such as:
import Network.HTTP.Conduit import qualified Data.ByteString.Lazy as L import Network (withSocketsDo) main = withSocketsDo $ simpleHttp "http://www.haskell.org/" >>= L.putStr Cookies are implemented according to RFC 6265.
Note that by default, the functions in this package will throw exceptions
for non-2xx status codes. If you would like to avoid this, you should use
checkStatus
, e.g.:
import Data.Conduit.Binary (sinkFile) import Network.HTTP.Conduit import qualified Data.Conduit as C import Network main :: IO () main = withSocketsDo $ do request' <- parseUrl "http://www.yesodweb.com/does-not-exist" let request = request' { checkStatus = \_ _ _ -> Nothing } res <- withManager $ httpLbs request print res
By default, when connecting to websites using HTTPS, functions in this
package will throw an exception if the TLS certificate doesn't validate. To
continue the HTTPS transaction even if the TLS cerficate validation fails,
you should use mkManagerSetttings
as follows:
import Network.Connection (TLSSettings (..)) import Network.HTTP.Conduit main :: IO () main = do request <- parseUrl "https://github.com/" let settings = mkManagerSettings (TLSSettingsSimple True False False) Nothing res <- withManagerSettings settings $ httpLbs request print res
- simpleHttp :: MonadIO m => String -> m ByteString
- httpLbs :: MonadIO m => Request -> Manager -> m (Response ByteString)
- http :: MonadResource m => Request -> Manager -> m (Response (ResumableSource m ByteString))
- data Proxy = Proxy {
- proxyHost :: !ByteString
- proxyPort :: !Int
- data RequestBody
- = RequestBodyLBS !ByteString
- | RequestBodyBS !ByteString
- | RequestBodyBuilder !Int64 !Builder
- | RequestBodyStream !Int64 !(GivesPopper ())
- | RequestBodyStreamChunked !(GivesPopper ())
- data Request
- method :: Request -> Method
- secure :: Request -> Bool
- host :: Request -> ByteString
- port :: Request -> Int
- path :: Request -> ByteString
- queryString :: Request -> ByteString
- requestHeaders :: Request -> RequestHeaders
- requestBody :: Request -> RequestBody
- proxy :: Request -> Maybe Proxy
- hostAddress :: Request -> Maybe HostAddress
- rawBody :: Request -> Bool
- decompress :: Request -> ByteString -> Bool
- redirectCount :: Request -> Int
- checkStatus :: Request -> Status -> ResponseHeaders -> CookieJar -> Maybe SomeException
- responseTimeout :: Request -> Maybe Int
- cookieJar :: Request -> Maybe CookieJar
- getConnectionWrapper :: Request -> Maybe Int -> HttpException -> IO (ConnRelease, Connection, ManagedConn) -> IO (Maybe Int, (ConnRelease, Connection, ManagedConn))
- requestBodySource :: Int64 -> Source (ResourceT IO) ByteString -> RequestBody
- requestBodySourceChunked :: Source (ResourceT IO) ByteString -> RequestBody
- requestBodySourceIO :: Int64 -> Source IO ByteString -> RequestBody
- requestBodySourceChunkedIO :: Source IO ByteString -> RequestBody
- data Response body
- responseStatus :: Response body -> Status
- responseVersion :: Response body -> HttpVersion
- responseHeaders :: Response body -> ResponseHeaders
- responseBody :: Response body -> body
- responseCookieJar :: Response body -> CookieJar
- data Manager
- newManager :: ManagerSettings -> IO Manager
- closeManager :: Manager -> IO ()
- withManager :: (MonadIO m, MonadBaseControl IO m) => (Manager -> ResourceT m a) -> m a
- withManagerSettings :: (MonadIO m, MonadBaseControl IO m) => ManagerSettings -> (Manager -> ResourceT m a) -> m a
- data ManagerSettings
- conduitManagerSettings :: ManagerSettings
- mkManagerSettings :: TLSSettings -> Maybe SockSettings -> ManagerSettings
- managerConnCount :: ManagerSettings -> Int
- managerResponseTimeout :: ManagerSettings -> Maybe Int
- managerTlsConnection :: ManagerSettings -> IO (Maybe HostAddress -> String -> Int -> IO Connection)
- data Cookie = Cookie {}
- data CookieJar
- createCookieJar :: [Cookie] -> CookieJar
- destroyCookieJar :: CookieJar -> [Cookie]
- parseUrl :: Failure HttpException m => String -> m Request
- applyBasicAuth :: ByteString -> ByteString -> Request -> Request
- addProxy :: ByteString -> Int -> Request -> Request
- lbsResponse :: Monad m => Response (ResumableSource m ByteString) -> m (Response ByteString)
- getRedirectedRequest :: Request -> ResponseHeaders -> CookieJar -> Int -> Maybe Request
- alwaysDecompress :: ByteString -> Bool
- browserDecompress :: ByteString -> Bool
- urlEncodedBody :: [(ByteString, ByteString)] -> Request -> Request
- data HttpException
- = StatusCodeException Status ResponseHeaders CookieJar
- | InvalidUrlException String String
- | TooManyRedirects [Response ByteString]
- | UnparseableRedirect (Response ByteString)
- | TooManyRetries
- | HttpParserException String
- | HandshakeFailed
- | OverlongHeaders
- | ResponseTimeout
- | FailedConnectionException String Int
- | ExpectedBlankAfter100Continue
- | InvalidStatusLine ByteString
- | InvalidHeader ByteString
- | InternalIOException IOException
- | ProxyConnectException ByteString Int (Either ByteString HttpException)
- | NoResponseDataReceived
- | TlsException SomeException
- | TlsNotSupported
- | ResponseBodyTooShort Word64 Word64
- | InvalidChunkHeaders
- | IncompleteHeaders
- | InvalidDestinationHost ByteString
Perform a request
simpleHttp :: MonadIO m => String -> m ByteStringSource
Download the specified URL, following any redirects, and return the response body.
This function will throwIO
an HttpException
for any
response with a non-2xx status code (besides 3xx redirects up
to a limit of 10 redirects). It uses parseUrl
to parse the
input. This function essentially wraps httpLbs
.
Note: Even though this function returns a lazy bytestring, it
does not utilize lazy I/O, and therefore the entire response
body will live in memory. If you want constant memory usage,
you'll need to use the conduit
package and http
directly.
Note: This function creates a new Manager
. It should be avoided
in production code.
httpLbs :: MonadIO m => Request -> Manager -> m (Response ByteString)Source
Download the specified Request
, returning the results as a Response
.
This is a simplified version of http
for the common case where you simply
want the response data as a simple datatype. If you want more power, such as
interleaved actions on the response body during download, you'll need to use
http
directly. This function is defined as:
httpLbs =lbsResponse
<=<http
Even though the Response
contains a lazy bytestring, this
function does not utilize lazy I/O, and therefore the entire
response body will live in memory. If you want constant memory
usage, you'll need to use conduit
packages's
Source
returned by http
.
Note: Unlike previous versions, this function will perform redirects, as
specified by the redirectCount
setting.
http :: MonadResource m => Request -> Manager -> m (Response (ResumableSource m ByteString))
Datatypes
data RequestBody
Constructors
RequestBodyLBS !ByteString | |
RequestBodyBS !ByteString | |
RequestBodyBuilder !Int64 !Builder | |
RequestBodyStream !Int64 !(GivesPopper ()) | |
RequestBodyStreamChunked !(GivesPopper ()) |
Instances
Request
host :: Request -> ByteString
path :: Request -> ByteString
queryString :: Request -> ByteString
requestBody :: Request -> RequestBody
hostAddress :: Request -> Maybe HostAddress
decompress :: Request -> ByteString -> Bool
redirectCount :: Request -> Int
checkStatus :: Request -> Status -> ResponseHeaders -> CookieJar -> Maybe SomeException
responseTimeout :: Request -> Maybe Int
getConnectionWrapper :: Request -> Maybe Int -> HttpException -> IO (ConnRelease, Connection, ManagedConn) -> IO (Maybe Int, (ConnRelease, Connection, ManagedConn))
Request body
requestBodySource :: Int64 -> Source (ResourceT IO) ByteString -> RequestBody
requestBodySourceIO :: Int64 -> Source IO ByteString -> RequestBody
Response
data Response body
responseStatus :: Response body -> Status
responseVersion :: Response body -> HttpVersion
responseHeaders :: Response body -> ResponseHeaders
responseBody :: Response body -> body
responseCookieJar :: Response body -> CookieJar
Manager
data Manager
newManager :: ManagerSettings -> IO Manager
closeManager :: Manager -> IO ()
withManager :: (MonadIO m, MonadBaseControl IO m) => (Manager -> ResourceT m a) -> m aSource
withManagerSettings :: (MonadIO m, MonadBaseControl IO m) => ManagerSettings -> (Manager -> ResourceT m a) -> m aSource
Settings
data ManagerSettings
mkManagerSettings :: TLSSettings -> Maybe SockSettings -> ManagerSettings
managerTlsConnection :: ManagerSettings -> IO (Maybe HostAddress -> String -> Int -> IO Connection)
Cookies
data Cookie
Constructors
data CookieJar
createCookieJar :: [Cookie] -> CookieJar
destroyCookieJar :: CookieJar -> [Cookie]
Utility functions
parseUrl :: Failure HttpException m => String -> m Request
applyBasicAuth :: ByteString -> ByteString -> Request -> Request
addProxy :: ByteString -> Int -> Request -> Request
lbsResponse :: Monad m => Response (ResumableSource m ByteString) -> m (Response ByteString)Source
getRedirectedRequest :: Request -> ResponseHeaders -> CookieJar -> Int -> Maybe Request
Decompression predicates
alwaysDecompress :: ByteString -> Bool
browserDecompress :: ByteString -> Bool
Request bodies
Network.HTTP.Conduit.MultipartFormData provides an API for building form-data request bodies.
urlEncodedBody :: [(ByteString, ByteString)] -> Request -> Request
Exceptions
data HttpException
Constructors