Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Simplified interface for common HTTP client interactions. Tutorial available at https://haskell-lang.org/library/http-client
Important note: Request
is an instance of IsString
, and
therefore recommended usage is to turn on OverloadedStrings
, e.g.
{-# LANGUAGE OverloadedStrings #-} import Network.HTTP.Simple import qualified Data.ByteString.Char8 as B8 main :: IO () main = httpBS "http://example.com" >>= B8.putStrLn . getResponseBody
The IsString
instance uses parseRequest
behind the scenes and inherits its behavior.
Synopsis
- httpBS :: MonadIO m => Request -> m (Response ByteString)
- httpLBS :: MonadIO m => Request -> m (Response ByteString)
- httpNoBody :: MonadIO m => Request -> m (Response ())
- httpJSON :: (MonadIO m, FromJSON a) => Request -> m (Response a)
- httpJSONEither :: (MonadIO m, FromJSON a) => Request -> m (Response (Either JSONException a))
- httpSink :: MonadUnliftIO m => Request -> (Response () -> ConduitM ByteString Void m a) -> m a
- httpSource :: (MonadResource m, MonadIO n) => Request -> (Response (ConduitM i ByteString n ()) -> ConduitM i o m r) -> ConduitM i o m r
- withResponse :: (MonadUnliftIO m, MonadIO n) => Request -> (Response (ConduitM i ByteString n ()) -> m a) -> m a
- type Header = (HeaderName, ByteString)
- type Query = [QueryItem]
- type QueryItem = (ByteString, Maybe ByteString)
- data Request
- type RequestHeaders = [Header]
- data Response body
- type ResponseHeaders = [Header]
- data JSONException
- data HttpException
- data Proxy = Proxy {
- proxyHost :: ByteString
- proxyPort :: Int
- defaultRequest :: Request
- parseRequest :: MonadThrow m => String -> m Request
- parseRequest_ :: String -> Request
- parseRequestThrow :: MonadThrow m => String -> m Request
- parseRequestThrow_ :: String -> Request
- setRequestMethod :: ByteString -> Request -> Request
- setRequestSecure :: Bool -> Request -> Request
- setRequestHost :: ByteString -> Request -> Request
- setRequestPort :: Int -> Request -> Request
- setRequestPath :: ByteString -> Request -> Request
- addRequestHeader :: HeaderName -> ByteString -> Request -> Request
- getRequestHeader :: HeaderName -> Request -> [ByteString]
- setRequestHeader :: HeaderName -> [ByteString] -> Request -> Request
- setRequestHeaders :: RequestHeaders -> Request -> Request
- setRequestQueryString :: Query -> Request -> Request
- getRequestQueryString :: Request -> Query
- addToRequestQueryString :: Query -> Request -> Request
- setRequestBody :: RequestBody -> Request -> Request
- setRequestBodyJSON :: ToJSON a => a -> Request -> Request
- setRequestBodyLBS :: ByteString -> Request -> Request
- setRequestBodySource :: Int64 -> ConduitM () ByteString IO () -> Request -> Request
- setRequestBodyFile :: FilePath -> Request -> Request
- setRequestBodyURLEncoded :: [(ByteString, ByteString)] -> Request -> Request
- setRequestIgnoreStatus :: Request -> Request
- setRequestCheckStatus :: Request -> Request
- setRequestBasicAuth :: ByteString -> ByteString -> Request -> Request
- setRequestBearerAuth :: ByteString -> Request -> Request
- setRequestManager :: Manager -> Request -> Request
- setRequestProxy :: Maybe Proxy -> Request -> Request
- setRequestResponseTimeout :: ResponseTimeout -> Request -> Request
- getResponseStatus :: Response a -> Status
- getResponseStatusCode :: Response a -> Int
- getResponseHeader :: HeaderName -> Response a -> [ByteString]
- getResponseHeaders :: Response a -> [(HeaderName, ByteString)]
- getResponseBody :: Response a -> a
- httpLbs :: MonadIO m => Request -> m (Response ByteString)
Perform requests
httpBS :: MonadIO m => Request -> m (Response ByteString) Source #
Perform an HTTP request and return the body as a ByteString
.
Since: 2.2.4
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). The advantage of a lazy
ByteString
here (versus using httpBS
) is--if needed--a better
in-memory representation.
Since: 2.1.10
httpNoBody :: MonadIO m => Request -> m (Response ()) Source #
Perform an HTTP request and ignore the response body.
Since: 2.2.2
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.
NOTE: Depends on the aeson
cabal flag being enabled
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.
NOTE: Depends on the aeson
cabal flag being enabled
Since: 2.1.10
httpSink :: MonadUnliftIO m => Request -> (Response () -> ConduitM ByteString Void m a) -> m a Source #
Perform an HTTP request and consume the body with the given Sink
Since: 2.1.10
httpSource :: (MonadResource m, MonadIO n) => Request -> (Response (ConduitM i ByteString n ()) -> ConduitM i o m r) -> ConduitM i o m r Source #
Perform an HTTP request, and get the response body as a Source.
The second argument to this function tells us how to make the
Source from the Response itself. This allows you to perform actions
with the status or headers, for example, in addition to the raw
bytes themselves. If you just care about the response body, you can
use getResponseBody
as the second argument here.
{-# LANGUAGE OverloadedStrings #-} import Control.Monad.IO.Class (liftIO) import Control.Monad.Trans.Resource (runResourceT) import Data.Conduit (($$)) import qualified Data.Conduit.Binary as CB import qualified Data.Conduit.List as CL import Network.HTTP.Simple import System.IO (stdout) main :: IO () main = runResourceT $ httpSource "http://httpbin.org/robots.txt" getSrc $$ CB.sinkHandle stdout where getSrc res = do liftIO $ print (getResponseStatus res, getResponseHeaders res) getResponseBody res
Since: 2.2.1
withResponse :: (MonadUnliftIO m, MonadIO n) => Request -> (Response (ConduitM i ByteString n ()) -> m a) -> m a Source #
Perform an action with the given request. This employes the bracket pattern.
This is similar to httpSource
, but does not require
MonadResource
and allows the result to not contain a ConduitM
value.
Since: 2.2.3
Types
type Header = (HeaderName, ByteString) #
Header
Query.
General form: a=b&c=d
, but if the value is Nothing, it becomes
a&c=d
.
type QueryItem = (ByteString, Maybe ByteString) #
Query item
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
type RequestHeaders = [Header] #
Request Headers
A simple representation of the HTTP response.
Since 0.1.0
Instances
Foldable Response | |
Defined in Network.HTTP.Client.Types 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 # elem :: Eq a => a -> Response a -> Bool # maximum :: Ord a => Response a -> a # minimum :: Ord a => Response a -> a # | |
Traversable Response | |
Functor Response | |
Show body => Show (Response body) | |
type ResponseHeaders = [Header] #
Response Headers
data JSONException Source #
An exception that can occur when parsing JSON
NOTE: Depends on the aeson
cabal flag being enabled
Since: 2.1.10
JSONParseException Request (Response ()) ParseError | |
JSONConversionException Request (Response Value) String |
Instances
Exception JSONException Source # | |
Defined in Network.HTTP.Simple | |
Show JSONException Source # | |
Defined in Network.HTTP.Simple showsPrec :: Int -> JSONException -> ShowS # show :: JSONException -> String # showList :: [JSONException] -> ShowS # |
data HttpException #
An exception which may be generated by this library
Since: http-client-0.5.0
HttpExceptionRequest Request HttpExceptionContent | Most exceptions are specific to a Since: http-client-0.5.0 |
InvalidUrlException String String | A URL (first field) is invalid for a given reason (second argument). Since: http-client-0.5.0 |
Instances
Exception HttpException | |
Defined in Network.HTTP.Client.Types | |
Show HttpException | |
Defined in Network.HTTP.Client.Types showsPrec :: Int -> HttpException -> ShowS # show :: HttpException -> String # showList :: [HttpException] -> ShowS # |
Define a HTTP proxy, consisting of a hostname and port number.
Proxy | |
|
Request constructions
A default request value, a GET request of localhost/:80, with an empty request body.
Note that the default checkResponse
does nothing.
Since: http-client-0.4.30
parseRequest :: MonadThrow m => String -> m Request #
Convert a URL into a Request
.
This function 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.:
@@
parseRequest "POST http://httpbin.org/post"
@@
Note that the request method must be provided as all capital letters.
A Request
created by this function won't cause exceptions on non-2XX
response status codes.
To create a request which throws on non-2XX status codes, see parseUrlThrow
Since: http-client-0.4.30
parseRequest_ :: String -> Request #
Same as parseRequest
, but parse errors cause an impure exception.
Mostly useful for static strings which are known to be correctly
formatted.
parseRequestThrow :: MonadThrow m => String -> m Request Source #
Same as parseRequest
, except will throw an HttpException
in the
event of a non-2XX response. This uses throwErrorStatusCodes
to
implement checkResponse
.
Exactly the same as parseUrlThrow
, but has a name that is more
consistent with the other parseRequest functions.
Since: 2.3.2
parseRequestThrow_ :: String -> Request Source #
Same as parseRequestThrow
, but parse errors cause an impure
exception. Mostly useful for static strings which are known to be
correctly formatted.
Since: 2.3.2
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 :: RequestHeaders -> Request -> Request Source #
Set the request headers, wiping out all previously set headers. This
means if you use setRequestHeaders
to set some headers and also use one of
the other setters that modifies the content-type
header (such as
setRequestBodyJSON
), be sure that setRequestHeaders
is evaluated
first.
Since: 2.1.10
setRequestQueryString :: Query -> Request -> Request Source #
Set the query string parameters
Since: 2.1.10
getRequestQueryString :: Request -> Query Source #
Get the query string parameters
Since: 2.1.10
addToRequestQueryString :: Query -> Request -> Request Source #
Add to the existing query string parameters.
Since: 2.3.5
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; charset=utf-8
NOTE: Depends on the aeson
cabal flag being enabled
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
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 change the request method to POST
and set the content-type
to application/x-www-form-urlencoded
Since: 2.1.10
Special fields
setRequestIgnoreStatus :: Request -> Request #
Modify the request so that non-2XX status codes do not generate a runtime
StatusCodeException
.
Since: http-client-0.4.29
setRequestCheckStatus :: Request -> Request #
Modify the request so that non-2XX status codes generate a runtime
StatusCodeException
, by using throwErrorStatusCodes
Since: http-client-0.5.13
:: ByteString | username |
-> ByteString | password |
-> Request | |
-> Request |
Set basic auth with the given username and password
Since: 2.1.10
:: ByteString | token |
-> Request | |
-> Request |
Set bearer auth with the given token
Since: 2.3.8
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
setRequestResponseTimeout :: ResponseTimeout -> Request -> Request Source #
Set the maximum time to wait for a response
Since: 2.3.8
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