http-conduit-2.1.11: HTTP client package with conduit interface and HTTPS support.

Safe HaskellNone
LanguageHaskell98

Network.HTTP.Simple

Contents

Description

Simplified interface for common HTTP client interactions. Tutorial available at https://github.com/commercialhaskell/jump/blob/master/doc/http-client.md.

Important note: Request is an instance of IsString, and therefore recommended usage is to turn on OverloadedStrings, e.g.

@@@ {--} import Network.HTTP.Simple import qualified Data.ByteString.Lazy.Char8 as L8

main :: IO () main = httpLBS "http://example.com" >>= L8.putStrLn @@@

Synopsis

Perform requests

httpLBS :: MonadIO m => Request -> m (Response ByteString) Source #

Perform an HTTP request and return the body as a lazy ByteString. Note that the entire value will be read into memory at once (no lazy I/O will be performed).

Since: 2.1.10

httpJSON :: (MonadIO m, FromJSON a) => Request -> m (Response a) Source #

Perform an HTTP request and parse the body as JSON. In the event of an JSON parse errors, a JSONException runtime exception will be thrown.

Since: 2.1.10

httpJSONEither :: (MonadIO m, FromJSON a) => Request -> m (Response (Either JSONException a)) Source #

Perform an HTTP request and parse the body as JSON. In the event of an JSON parse errors, a Left value will be returned.

Since: 2.1.10

httpSink :: (MonadIO m, MonadMask m) => Request -> (Response () -> Sink ByteString m a) -> m a Source #

Perform an HTTP request and consume the body with the given Sink

Since: 2.1.10

Types

data Request :: * #

All information on how to connect to a host and what should be sent in the HTTP request.

If you simply wish to download from a URL, see parseRequest.

The constructor for this data type is not exposed. Instead, you should use either the defaultRequest value, or parseRequest to construct from a URL, and then use the records below to make modifications. This approach allows http-client to add configuration options without breaking backwards compatibility.

For example, to construct a POST request, you could do something like:

initReq <- parseRequest "http://www.example.com/path"
let req = initReq
            { method = "POST"
            }

For more information, please see http://www.yesodweb.com/book/settings-types.

Since 0.1.0

data Response body :: * -> * #

A simple representation of the HTTP response.

Since 0.1.0

Instances

Functor Response 

Methods

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

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

Foldable Response 

Methods

fold :: Monoid m => Response m -> 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 

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) #

Eq body => Eq (Response body) 

Methods

(==) :: Response body -> Response body -> Bool #

(/=) :: Response body -> Response body -> Bool #

Show body => Show (Response body) 

Methods

showsPrec :: Int -> Response body -> ShowS #

show :: Response body -> String #

showList :: [Response body] -> ShowS #

data HttpException :: * #

Constructors

StatusCodeException Status ResponseHeaders CookieJar 
InvalidUrlException String String 
TooManyRedirects [Response ByteString]

List of encountered responses containing redirects in reverse chronological order; including last redirect, which triggered the exception and was not followed.

UnparseableRedirect (Response ByteString)

Response containing unparseable redirect.

TooManyRetries 
HttpParserException String 
HandshakeFailed 
OverlongHeaders 
ResponseTimeout 
FailedConnectionException String Int

host/port

Note that in old versions of http-client and http-conduit, this exception would indicate a failed attempt to create a connection. However, since (at least) http-client 0.4, it indicates a timeout occurred while trying to establish the connection. For more information on this, see:

https://github.com/snoyberg/http-client/commit/b86b1cdd91e56ee33150433dedb32954d2082621#commitcomment-10718689

FailedConnectionException2 String Int Bool SomeException

host/port/secure

ExpectedBlankAfter100Continue 
InvalidStatusLine ByteString 
InvalidHeader ByteString 
InternalIOException IOException 
ProxyConnectException ByteString Int (Either ByteString HttpException)

host/port

NoResponseDataReceived 
TlsException SomeException 
TlsNotSupported 
ResponseBodyTooShort Word64 Word64

Expected size/actual size.

Since 1.9.4

InvalidChunkHeaders

Since 1.9.4

IncompleteHeaders 
InvalidDestinationHost ByteString 
HttpZlibException ZlibException

Since 0.3

InvalidProxyEnvironmentVariable Text Text

Environment name and value

Since 0.4.7

ResponseLengthAndChunkingBothUsed

Detect a case where both the content-length header and transfer-encoding: chunked are used. Since 0.4.8.

Since 0.4.11 this exception isn't thrown anymore.

TlsExceptionHostPort SomeException ByteString Int

TLS exception, together with the host and port

Since: 0.4.24

data Proxy :: * #

Define a HTTP proxy, consisting of a hostname and port number.

Constructors

Proxy 

Fields

Request constructions

defaultRequest :: Request #

A default request value

Since: 0.4.30

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

Convert a URL into a Request.

This defaults some of the values in Request, such as setting method to GET and requestHeaders to [].

Since this function uses MonadThrow, the return monad can be anything that is an instance of MonadThrow, such as IO or Maybe.

You can place the request method at the beginning of the URL separated by a space, e.g.:

@@ parseRequeset "POST http://httpbin.org/post" @@

Note that the request method must be provided as all capital letters.

Since: 0.4.30

parseRequest_ :: String -> Request #

Same as parseRequest, but in the cases of a parse error generates an impure exception. Mostly useful for static strings which are known to be correctly formatted.

Request lenses

Basics

setRequestMethod :: ByteString -> Request -> Request Source #

Set the request method

Since: 2.1.10

setRequestSecure :: Bool -> Request -> Request Source #

Set whether this is a secureHTTPS (True) or insecureHTTP (False) request

Since: 2.1.10

setRequestHost :: ByteString -> Request -> Request Source #

Set the destination host of the request

Since: 2.1.10

setRequestPort :: Int -> Request -> Request Source #

Set the destination port of the request

Since: 2.1.10

setRequestPath :: ByteString -> Request -> Request Source #

Lens for the requested path info of the request

Since: 2.1.10

addRequestHeader :: HeaderName -> ByteString -> Request -> Request Source #

Add a request header name/value combination

Since: 2.1.10

getRequestHeader :: HeaderName -> Request -> [ByteString] Source #

Get all request header values for the given name

Since: 2.1.10

setRequestHeader :: HeaderName -> [ByteString] -> Request -> Request Source #

Set the given request header to the given list of values. Removes any previously set header values with the same name.

Since: 2.1.10

setRequestHeaders :: [(HeaderName, ByteString)] -> Request -> Request Source #

Set the request headers, wiping out any previously set headers

Since: 2.1.10

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

Set the query string parameters

Since: 2.1.10

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

Get the query string parameters

Since: 2.1.10

Request body

setRequestBody :: RequestBody -> Request -> Request Source #

Set the request body to the given RequestBody. You may want to consider using one of the convenience functions in the modules, e.g. requestBodyJSON.

Note: This will not modify the request method. For that, please use requestMethod. You likely don't want the default of GET.

Since: 2.1.10

setRequestBodyJSON :: ToJSON a => a -> Request -> Request Source #

Set the request body as a JSON value

Note: This will not modify the request method. For that, please use requestMethod. You likely don't want the default of GET.

This also sets the content-type to application/json; chatset=utf8

Since: 2.1.10

setRequestBodyLBS :: ByteString -> Request -> Request Source #

Set the request body as a lazy ByteString

Note: This will not modify the request method. For that, please use requestMethod. You likely don't want the default of GET.

Since: 2.1.10

setRequestBodySource Source #

Arguments

:: Int64

length of source

-> Source IO ByteString 
-> Request 
-> Request 

Set the request body as a Source

Note: This will not modify the request method. For that, please use requestMethod. You likely don't want the default of GET.

Since: 2.1.10

setRequestBodyFile :: FilePath -> Request -> Request Source #

Set the request body as a file

Note: This will not modify the request method. For that, please use requestMethod. You likely don't want the default of GET.

Since: 2.1.10

setRequestBodyURLEncoded :: [(ByteString, ByteString)] -> Request -> Request Source #

Set the request body as URL encoded data

Note: This will not modify the request method. For that, please use requestMethod. You likely don't want the default of GET.

This also sets the content-type to application/x-www-form-urlencoded

Since: 2.1.10

Special fields

setRequestIgnoreStatus :: Request -> Request Source #

Modify the request so that non-2XX status codes do not generate a runtime exception.

Since: 2.1.10

setRequestBasicAuth Source #

Arguments

:: ByteString

username

-> ByteString

password

-> Request 
-> Request 

Set basic auth with the given username and password

Since: 2.1.10

setRequestManager :: Manager -> Request -> Request Source #

Instead of using the default global Manager, use the supplied Manager.

Since: 2.1.10

setRequestProxy :: Maybe Proxy -> Request -> Request Source #

Override the default proxy server settings

Since: 2.1.10

Response lenses

getResponseStatus :: Response a -> Status Source #

Get the status of the response

Since: 2.1.10

getResponseStatusCode :: Response a -> Int Source #

Get the integral status code of the response

Since: 2.1.10

getResponseHeader :: HeaderName -> Response a -> [ByteString] Source #

Get all response header values with the given name

Since: 2.1.10

getResponseHeaders :: Response a -> [(HeaderName, ByteString)] Source #

Get all response headers

Since: 2.1.10

getResponseBody :: Response a -> a Source #

Get the response body

Since: 2.1.10

Alternate spellings

httpLbs :: MonadIO m => Request -> m (Response ByteString) Source #

Alternate spelling of httpLBS

Since: 2.1.10