http-conduit-2.3.8.3: HTTP client package with conduit interface and HTTPS support.
Safe HaskellNone
LanguageHaskell2010

Network.HTTP.Conduit

Description

Simpler API

The API below is rather low-level. The Network.HTTP.Simple module provides a higher-level API with built-in support for things like JSON request and response bodies. For most users, this will be an easier place to start. You can read the tutorial at:

https://haskell-lang.org/library/http-client

Lower-level API

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) -- Exported from the package conduit-extra
import Network.HTTP.Conduit
import Conduit (runConduit, (.|))
import Control.Monad.Trans.Resource (runResourceT)

main :: IO ()
main = do
     request <- parseRequest "http://google.com/"
     manager <- newManager tlsManagerSettings
     runResourceT $ do
         response <- http request manager
         runConduit $ responseBody response .| 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
import Network.HTTP.Types.Status (statusCode)

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 = do
     request' <- parseRequest "http://example.com/secret-page"
     manager <- newManager tlsManagerSettings
     let request = request' { cookieJar = Just $ createCookieJar [cookie] }
     fmap Just (httpLbs request manager) `E.catch`
             (\ex -> case ex of
                 HttpExceptionRequest _ (StatusCodeException res _) ->
                     if statusCode (responseStatus res) == 403
                       then (putStrLn "login failed" >> return Nothing)
                       else return Nothing
                 _ -> E.throw ex)

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 = do
     request' <- parseRequest "http://www.yesodweb.com/does-not-exist"
     let request = request' { checkStatus = \_ _ _ -> Nothing }
     manager <- newManager tlsManagerSettings
     res <- httpLbs request manager
     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 <- parseRequest "https://github.com/"
    let settings = mkManagerSettings (TLSSettingsSimple True False False) Nothing
    manager <- newManager settings
    res <- httpLbs request manager
    print res

For more information, please be sure to read the documentation in the Network.HTTP.Client module.

Synopsis

Perform a request

simpleHttp :: MonadIO m => String -> m ByteString Source #

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 parseUrlThrow 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.

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). This behavior can be modified by changing the checkStatus field of your request.

Note: Unlike previous versions, this function will perform redirects, as specified by the redirectCount setting.

http :: MonadResource m => Request -> Manager -> m (Response (ConduitM i ByteString m ())) Source #

Datatypes

data Proxy #

Constructors

Proxy 

Fields

Instances

Instances details
Read Proxy 
Instance details

Defined in Network.HTTP.Client.Types

Methods

readsPrec :: Int -> ReadS Proxy

readList :: ReadS [Proxy]

readPrec :: ReadPrec Proxy

readListPrec :: ReadPrec [Proxy]

Show Proxy 
Instance details

Defined in Network.HTTP.Client.Types

Methods

showsPrec :: Int -> Proxy -> ShowS

show :: Proxy -> String

showList :: [Proxy] -> ShowS

Eq Proxy 
Instance details

Defined in Network.HTTP.Client.Types

Methods

(==) :: Proxy -> Proxy -> Bool

(/=) :: Proxy -> Proxy -> Bool

Ord Proxy 
Instance details

Defined in Network.HTTP.Client.Types

Methods

compare :: Proxy -> Proxy -> Ordering

(<) :: Proxy -> Proxy -> Bool

(<=) :: Proxy -> Proxy -> Bool

(>) :: Proxy -> Proxy -> Bool

(>=) :: Proxy -> Proxy -> Bool

max :: Proxy -> Proxy -> Proxy

min :: Proxy -> Proxy -> Proxy

data RequestBody #

Instances

Instances details
IsString RequestBody 
Instance details

Defined in Network.HTTP.Client.Types

Methods

fromString :: String -> RequestBody

Monoid RequestBody 
Instance details

Defined in Network.HTTP.Client.Types

Semigroup RequestBody 
Instance details

Defined in Network.HTTP.Client.Types

Methods

(<>) :: RequestBody -> RequestBody -> RequestBody

sconcat :: NonEmpty RequestBody -> RequestBody

stimes :: Integral b => b -> RequestBody -> RequestBody

Request

data Request #

Instances

Instances details
Show Request 
Instance details

Defined in Network.HTTP.Client.Types

Methods

showsPrec :: Int -> Request -> ShowS

show :: Request -> String

showList :: [Request] -> ShowS

method :: Request -> Method #

secure :: Request -> Bool #

host :: Request -> ByteString #

port :: Request -> Int #

path :: Request -> ByteString #

queryString :: Request -> ByteString #

proxy :: Request -> Maybe Proxy #

hostAddress :: Request -> Maybe HostAddress #

rawBody :: Request -> Bool #

decompress :: Request -> ByteString -> Bool #

shouldStripHeaderOnRedirect :: Request -> HeaderName -> Bool #

checkResponse :: Request -> Request -> Response BodyReader -> IO () #

requestVersion :: Request -> HttpVersion #

setQueryString :: [(ByteString, Maybe ByteString)] -> Request -> Request #

Request body

requestBodySource :: Int64 -> ConduitM () ByteString (ResourceT IO) () -> RequestBody Source #

requestBodySourceChunked :: ConduitM () ByteString (ResourceT IO) () -> RequestBody Source #

requestBodySourceIO :: Int64 -> ConduitM () ByteString IO () -> RequestBody Source #

requestBodySourceChunkedIO :: ConduitM () ByteString IO () -> RequestBody Source #

Response

data Response body #

Instances

Instances details
Foldable Response 
Instance details

Defined in Network.HTTP.Client.Types

Methods

fold :: Monoid m => Response m -> m

foldMap :: Monoid m => (a -> m) -> Response a -> m

foldMap' :: Monoid m => (a -> m) -> Response a -> m

foldr :: (a -> b -> b) -> b -> Response a -> b

foldr' :: (a -> b -> b) -> b -> Response a -> b

foldl :: (b -> a -> b) -> b -> Response a -> b

foldl' :: (b -> a -> b) -> b -> Response a -> b

foldr1 :: (a -> a -> a) -> Response a -> a

foldl1 :: (a -> a -> a) -> Response a -> a

toList :: Response a -> [a]

null :: Response a -> Bool

length :: Response a -> Int

elem :: Eq a => a -> Response a -> Bool

maximum :: Ord a => Response a -> a

minimum :: Ord a => Response a -> a

sum :: Num a => Response a -> a

product :: Num a => Response a -> a

Traversable Response 
Instance details

Defined in Network.HTTP.Client.Types

Methods

traverse :: Applicative f => (a -> f b) -> Response a -> f (Response b)

sequenceA :: Applicative f => Response (f a) -> f (Response a)

mapM :: Monad m => (a -> m b) -> Response a -> m (Response b)

sequence :: Monad m => Response (m a) -> m (Response a)

Functor Response 
Instance details

Defined in Network.HTTP.Client.Types

Methods

fmap :: (a -> b) -> Response a -> Response b

(<$) :: a -> Response b -> Response a

Show body => Show (Response body) 
Instance details

Defined in Network.HTTP.Client.Types

Methods

showsPrec :: Int -> Response body -> ShowS

show :: Response body -> String

showList :: [Response body] -> ShowS

responseStatus :: Response body -> Status #

responseVersion :: Response body -> HttpVersion #

responseBody :: Response body -> body #

Manager

data Manager #

Instances

Instances details
HasHttpManager Manager 
Instance details

Defined in Network.HTTP.Client.Types

closeManager :: Manager -> IO () #

Settings

mkManagerSettings :: TLSSettings -> Maybe SockSettings -> ManagerSettings #

managerTlsConnection :: ManagerSettings -> IO (Maybe HostAddress -> String -> Int -> IO Connection) #

Response timeout

data ResponseTimeout #

Instances

Instances details
Show ResponseTimeout 
Instance details

Defined in Network.HTTP.Client.Types

Methods

showsPrec :: Int -> ResponseTimeout -> ShowS

show :: ResponseTimeout -> String

showList :: [ResponseTimeout] -> ShowS

Eq ResponseTimeout 
Instance details

Defined in Network.HTTP.Client.Types

Cookies

data Cookie #

Constructors

Cookie 

Fields

Instances

Instances details
Read Cookie 
Instance details

Defined in Network.HTTP.Client.Types

Methods

readsPrec :: Int -> ReadS Cookie

readList :: ReadS [Cookie]

readPrec :: ReadPrec Cookie

readListPrec :: ReadPrec [Cookie]

Show Cookie 
Instance details

Defined in Network.HTTP.Client.Types

Methods

showsPrec :: Int -> Cookie -> ShowS

show :: Cookie -> String

showList :: [Cookie] -> ShowS

data CookieJar #

Instances

Instances details
Monoid CookieJar 
Instance details

Defined in Network.HTTP.Client.Types

Semigroup CookieJar 
Instance details

Defined in Network.HTTP.Client.Types

Methods

(<>) :: CookieJar -> CookieJar -> CookieJar

sconcat :: NonEmpty CookieJar -> CookieJar

stimes :: Integral b => b -> CookieJar -> CookieJar

Read CookieJar 
Instance details

Defined in Network.HTTP.Client.Types

Methods

readsPrec :: Int -> ReadS CookieJar

readList :: ReadS [CookieJar]

readPrec :: ReadPrec CookieJar

readListPrec :: ReadPrec [CookieJar]

Show CookieJar 
Instance details

Defined in Network.HTTP.Client.Types

Methods

showsPrec :: Int -> CookieJar -> ShowS

show :: CookieJar -> String

showList :: [CookieJar] -> ShowS

Utility functions

parseUrl :: MonadThrow m => String -> m Request #

parseUrlThrow :: MonadThrow m => String -> m Request #

parseRequest :: MonadThrow m => String -> m Request #

parseRequest_ :: String -> Request #

applyBasicAuth :: ByteString -> ByteString -> Request -> Request #

addProxy :: ByteString -> Int -> Request -> Request #

lbsResponse :: Monad m => Response (ConduitM () ByteString m ()) -> m (Response ByteString) Source #

Decompression predicates

alwaysDecompress :: ByteString -> Bool #

browserDecompress :: ByteString -> Bool #

Request bodies

Network.HTTP.Client.MultipartFormData provides an API for building form-data request bodies.

urlEncodedBody :: [(ByteString, ByteString)] -> Request -> Request #

Exceptions

data HttpException #

Instances

Instances details
Exception HttpException 
Instance details

Defined in Network.HTTP.Client.Types

Methods

toException :: HttpException -> SomeException

fromException :: SomeException -> Maybe HttpException

displayException :: HttpException -> String

Show HttpException 
Instance details

Defined in Network.HTTP.Client.Types

Methods

showsPrec :: Int -> HttpException -> ShowS

show :: HttpException -> String

showList :: [HttpException] -> ShowS