Portability | GHC |
---|---|
Stability | experimental |
Maintainer | bos@serpentine.com |
Safe Haskell | None |
A library for client-side HTTP requests, focused on ease of use.
When reading the examples in this module, you should assume the following environment:
-- Make it easy to write literalByteString
andText
values. {-# LANGUAGE OverloadedStrings #-} -- Our handy module. import Network.Wreq -- Operators such as (&
) and (.~
). import Control.Lens -- Conversion of Haskell values to JSON. import Data.Aeson (toJSON
) -- Easy traversal of JSON data. import Data.Aeson.Lens (key
,nth
)
There exist some less frequently used lenses that are not exported from this module; these can be found in Network.Wreq.Lens.
- get :: String -> IO (Response ByteString)
- getWith :: Options -> String -> IO (Response ByteString)
- post :: Postable a => String -> a -> IO (Response ByteString)
- postWith :: Postable a => Options -> String -> a -> IO (Response ByteString)
- head_ :: String -> IO (Response ())
- headWith :: Options -> String -> IO (Response ())
- options :: String -> IO (Response ())
- optionsWith :: Options -> String -> IO (Response ())
- put :: Putable a => String -> a -> IO (Response ByteString)
- putWith :: Putable a => Options -> String -> a -> IO (Response ByteString)
- delete :: String -> IO (Response ())
- deleteWith :: Options -> String -> IO (Response ())
- foldGet :: (a -> ByteString -> IO a) -> a -> String -> IO a
- foldGetWith :: Options -> (a -> ByteString -> IO a) -> a -> String -> IO a
- data Options
- defaults :: Options
- manager :: Lens' Options (Either ManagerSettings Manager)
- header :: HeaderName -> Lens' Options [ByteString]
- param :: Text -> Lens' Options [Text]
- redirects :: Lens' Options Int
- headers :: Lens' Options [Header]
- params :: Lens' Options [(Text, Text)]
- cookie :: ByteString -> Traversal' Options Cookie
- cookies :: Lens' Options CookieJar
- data Auth
- auth :: Lens' Options (Maybe Auth)
- basicAuth :: ByteString -> ByteString -> Maybe Auth
- oauth2Bearer :: ByteString -> Maybe Auth
- oauth2Token :: ByteString -> Maybe Auth
- data Proxy = Proxy ByteString Int
- proxy :: Lens' Options (Maybe Proxy)
- httpProxy :: ByteString -> Int -> Maybe Proxy
- withManager :: (Options -> IO a) -> IO a
- data Payload where
- Raw :: ContentType -> RequestBody -> Payload
- data FormParam where
- := :: FormValue v => ByteString -> v -> FormParam
- class FormValue a
- data Part
- partName :: Lens' Part Text
- partFileName :: Lens' Part (Maybe String)
- partContentType :: Traversal' Part (Maybe MimeType)
- partGetBody :: Lens' Part (IO RequestBody)
- partBS :: Text -> ByteString -> Part
- partLBS :: Text -> ByteString -> Part
- partText :: Text -> Text -> Part
- partString :: Text -> String -> Part
- partFile :: Text -> FilePath -> Part
- partFileSource :: Text -> FilePath -> Part
- data Response body
- responseBody :: Lens (Response body0) (Response body1) body0 body1
- responseHeader :: HeaderName -> Traversal' (Response body) ByteString
- responseLink :: ByteString -> ByteString -> Fold (Response body) Link
- responseCookie :: ByteString -> Fold (Response body) Cookie
- responseHeaders :: Lens' (Response body) ResponseHeaders
- responseCookieJar :: Lens' (Response body) CookieJar
- responseStatus :: Lens' (Response body) Status
- data Status
- statusCode :: Lens' Status Int
- data Link
- linkURL :: Lens' Link ByteString
- linkParams :: Lens' Link [(ByteString, ByteString)]
- data JSONError = JSONError String
- asJSON :: (MonadThrow m, FromJSON a) => Response ByteString -> m (Response a)
- asValue :: MonadThrow m => Response ByteString -> m (Response Value)
- data Cookie
- cookieName :: Lens' Cookie ByteString
- cookieValue :: Lens' Cookie ByteString
- cookieExpiryTime :: Lens' Cookie UTCTime
- cookieDomain :: Lens' Cookie ByteString
- cookiePath :: Lens' Cookie ByteString
- atto :: Parser a -> Fold ByteString a
HTTP verbs
GET
get :: String -> IO (Response ByteString)Source
Issue a GET request.
Example:
get
"http://httpbin.org/get"
>>>
r <- get "http://httpbin.org/get"
>>>
r ^. responseStatus . statusCode
200
getWith :: Options -> String -> IO (Response ByteString)Source
Issue a GET request, using the supplied Options
.
Example:
let opts =defaults
&
param
"foo".~
["bar"]getWith
opts "http://httpbin.org/get"
>>>
let opts = defaults & param "foo" .~ ["bar"]
>>>
r <- getWith opts "http://httpbin.org/get"
>>>
r ^? responseBody . key "url"
Just (String "http://httpbin.org/get?foo=bar")
POST
The Postable
class determines which Haskell types can be used as
POST payloads.
Part
and [Part
] give a request body with a
Content-Type
of multipart/form-data
. Constructor functions
include partText
and partFile
.
>>>
r <- post "http://httpbin.org/post" (partText "hello" "world")
>>>
r ^? responseBody . key "form" . key "hello"
Just (String "world")
(ByteString
, ByteString
) and FormParam
(and lists of
each) give a request body with a Content-Type
of
application/x-www-form-urlencoded
. The easiest way to use this is
via the (:=
) constructor.
>>>
r <- post "http://httpbin.org/post" ["num" := 31337, "str" := "foo"]
>>>
r ^? responseBody . key "form" . key "num"
Just (String "31337")
The "magical" type conversion on the right-hand side of :=
above is due to the FormValue
class. This package provides
sensible instances for the standard string and number types.
The Value
type gives a JSON request body with a
Content-Type
of application/json
. Any instance of
ToJSON
can of course be converted to a Value
using
toJSON
.
>>>
r <- post "http://httpbin.org/post" (toJSON [1,2,3])
>>>
r ^? responseBody . key "json" . nth 0
Just (Number 1.0)
postWith :: Postable a => Options -> String -> a -> IO (Response ByteString)Source
Issue a POST request, using the supplied Options
.
Example:
let opts =defaults
&
param
"foo".~
["bar"]postWith
opts "http://httpbin.org/post" (toJSON
[1,2,3])
>>>
let opts = defaults & param "foo" .~ ["bar"]
>>>
r <- postWith opts "http://httpbin.org/post" (toJSON [1,2,3])
>>>
r ^? responseBody . key "url"
Just (String "http://httpbin.org/post?foo=bar")
HEAD
head_ :: String -> IO (Response ())Source
Issue a HEAD request.
Example:
head_
"http://httpbin.org/get"
>>>
r <- head_ "http://httpbin.org/get"
>>>
r ^? responseHeader "Content-Type"
Just "application/json"
OPTIONS
PUT
putWith :: Putable a => Options -> String -> a -> IO (Response ByteString)Source
Issue a PUT request, using the supplied Options
.
DELETE
delete :: String -> IO (Response ())Source
Issue a DELETE request.
Example:
delete
"http://httpbin.org/delete"
>>>
r <- delete "http://httpbin.org/delete"
>>>
r ^. responseStatus . statusCode
200
Incremental consumption of responses
GET
foldGetWith :: Options -> (a -> ByteString -> IO a) -> a -> String -> IO aSource
Configuration
manager :: Lens' Options (Either ManagerSettings Manager)Source
A lens onto configuration of the connection manager provided by the http-client package.
In this example, we enable the use of OpenSSL for (hopefully) secure connections:
import OpenSSL.Session (context
) import Network.HTTP.Client.OpenSSL let opts =defaults
&
manager
.~
Left (opensslManagerSettings
context
)withOpenSSL
$getWith
opts "https://httpbin.org/get"
header :: HeaderName -> Lens' Options [ByteString]Source
redirects :: Lens' Options IntSource
A lens onto the maximum number of redirects that will be followed before an exception is thrown.
In this example, a HttpException
will be
thrown with a TooManyRedirects
constructor,
because the maximum number of redirects allowed will be exceeded.
let opts =defaults
&
redirects
.~
3getWith
opts "http://httpbin.org/redirect/5"
cookie :: ByteString -> Traversal' Options CookieSource
A traversal onto the cookie with the given name, if one exists.
Authentication
Do not use HTTP authentication unless you are using TLS encryption. These authentication tokens can easily be captured and reused by an attacker if transmitted in the clear.
Supported authentication types.
Do not use HTTP authentication unless you are using TLS encryption. These authentication tokens can easily be captured and reused by an attacker if transmitted in the clear.
:: ByteString | Username. |
-> ByteString | Password. |
-> Maybe Auth |
Basic authentication. This consists of a plain username and password.
Example (note the use of TLS):
let opts =defaults
&
auth
.~
basicAuth
"user" "pass"getWith
opts "https://httpbin.org/basic-auth/user/pass"
>>>
let opts = defaults & auth .~ basicAuth "user" "pass"
>>>
r <- getWith opts "https://httpbin.org/basic-auth/user/pass"
>>>
r ^? responseBody . key "authenticated"
Just (Bool True)
oauth2Token :: ByteString -> Maybe AuthSource
A not-quite-standard OAuth2 bearer token (that seems to be used only by GitHub). This will be treated by whatever services accept it as the equivalent of a username and password.
Example (note the use of TLS):
let opts =defaults
&
auth
.~
oauth2Token
"abcd1234"getWith
opts "https://api.github.com/user"
Proxy settings
data Proxy
Define a HTTP proxy, consisting of a hostname and port number.
httpProxy :: ByteString -> Int -> Maybe ProxySource
Proxy configuration.
Example:
let opts =defaults
&
proxy
.~
httpProxy
"localhost" 8000getWith
opts "http://httpbin.org/get"
(You may wonder why this function returns a 'Maybe Proxy'. This
allows it to be easily used on the right hand side of an operation,
as above, without its result needing to be wrapped in Just
.)
Using a manager with defaults
withManager :: (Options -> IO a) -> IO aSource
Payloads for POST and PUT
A product type for representing more complex payload types.
Raw :: ContentType -> RequestBody -> Payload |
URL-encoded form data
A key/value pair for an application/x-www-form-urlencoded
POST request body.
:= :: FormValue v => ByteString -> v -> FormParam |
A type that can be rendered as the value portion of a key/value
pair for use in an application/x-www-form-urlencoded
POST
body. Intended for use with the FormParam
type.
The instances for String
, strict Text
, and lazy
Text
are all encoded using UTF-8 before being
URL-encoded.
The instance for Maybe
gives an empty string on Nothing
,
and otherwise uses the contained type's instance.
Multipart form data
partName :: Lens' Part TextSource
A lens onto the name of the input
element associated with
part of a multipart form upload.
partFileName :: Lens' Part (Maybe String)Source
A lens onto the filename associated with part of a multipart form upload.
partContentType :: Traversal' Part (Maybe MimeType)Source
A lens onto the content-type associated with part of a multipart form upload.
partGetBody :: Lens' Part (IO RequestBody)Source
A lens onto the code that fetches the data associated with part of a multipart form upload.
Smart constructors
:: Text | Name of the corresponding <input>. |
-> ByteString | The body for this |
-> Part |
Make a Part
whose content is a strict ByteString
.
The Part
does not have a file name or content type associated
with it.
:: Text | Name of the corresponding <input>. |
-> ByteString | The body for this |
-> Part |
Make a Part
whose content is a lazy ByteString
.
The Part
does not have a file name or content type associated
with it.
Make a Part
whose content is a strict Text
, encoded as
UTF-8.
The Part
does not have a file name or content type associated
with it.
Make a Part
whose content is a String
, encoded as UTF-8.
The Part
does not have a file name or content type associated
with it.
Make a Part
from a file.
The entire file will reside in memory at once. If you want
constant memory usage, use partFileSource
.
The FilePath
supplied will be used as the file name of the
Part
. If you do not want to reveal this name to the server, you
must remove it prior to uploading.
The Part
does not have a content type associated with it.
Responses
data Response body
A simple representation of the HTTP response.
Since 0.1.0
responseBody :: Lens (Response body0) (Response body1) body0 body1Source
A lens onto the body of a response.
r <-get
"http://httpbin.org/get" print (r^.
responseBody
)
:: HeaderName | Header name to match. |
-> Traversal' (Response body) ByteString |
A lens onto all matching named headers in an HTTP response.
To access exactly one header (the result will be the empty string if
there is no match), use the (^.
) operator.
r <-get
"http://httpbin.org/get" print (r^.
responseHeader
"Content-Type")
To access at most one header (the result will be Nothing
if there
is no match), use the (^?
) operator.
r <-get
"http://httpbin.org/get" print (r^?
responseHeader
"Content-Transfer-Encoding")
To access all (zero or more) matching headers, use the
(^..
) operator.
r <-get
"http://httpbin.org/get" print (r^..
responseHeader
"Set-Cookie")
:: ByteString | Parameter name to match. |
-> ByteString | Parameter value to match. |
-> Fold (Response body) Link |
A fold over Link
headers, matching on both parameter name
and value.
For example, here is a Link
header returned by the GitHub search API.
Link: <https://api.github.com/search/code?q=addClass+user%3Amozilla&page=2>; rel="next", <https://api.github.com/search/code?q=addClass+user%3Amozilla&page=34>; rel="last"
And here is an example of how we can retrieve the URL for the next
link
programatically.
r <-get
"https://api.github.com/search/code?q=addClass+user:mozilla" print (r^?
responseLink
"rel" "next" .linkURL
)
:: ByteString | Name of cookie to match. |
-> Fold (Response body) Cookie |
responseHeaders :: Lens' (Response body) ResponseHeadersSource
A lens onto all headers in an HTTP response.
responseCookieJar :: Lens' (Response body) CookieJarSource
A lens onto all cookies set in the response.
responseStatus :: Lens' (Response body) StatusSource
A lens onto the status of an HTTP response.
data Status
HTTP Status.
Only the statusCode
is used for comparisons.
Please use mkStatus
to create status codes from code and message, or the Enum
instance or the
status code constants (like ok200
). There might be additional record members in the future.
Note that the Show instance is only for debugging.
statusCode :: Lens' Status IntSource
A lens onto the numeric identifier of an HTTP status.
Link headers
linkURL :: Lens' Link ByteStringSource
A lens onto the URL portion of a Link
element.
linkParams :: Lens' Link [(ByteString, ByteString)]Source
A lens onto the parameters of a Link
element.
Decoding responses
asJSON :: (MonadThrow m, FromJSON a) => Response ByteString -> m (Response a)Source
Convert the body of an HTTP response from JSON to a suitable Haskell type.
In this example, we use asJSON
in the IO
monad, where it will
throw a JSONError
exception if conversion to the desired type
fails.
{-# LANGUAGE DeriveGeneric #-} import GHC.Generics (Generic
) {- This Haskell type corresponds to the structure of a response body from httpbin.org. -} data GetBody = GetBody { headers ::Map
Text
Text
, args ::Map
Text
Text
, origin ::Text
, url ::Text
} deriving (Show,Generic
) -- Get GHC to derive aFromJSON
instance for us. instanceFromJSON
GetBody {- The fact that we want a GetBody below will be inferred by our use of the "headers" accessor function. -} foo = do r <-asJSON
=<<get
"http://httpbin.org/get" print (headers (r^.
responseBody
))
If we use asJSON
in the Either
monad, it will return Left
with a JSONError
payload if conversion fails, and Right
with a
Response
whose responseBody
is the converted value on success.
asValue :: MonadThrow m => Response ByteString -> m (Response Value)Source
Cookies
These are only the most frequently-used cookie-related lenses. See Network.Wreq.Lens for the full accounting of them all.
cookieName :: Lens' Cookie ByteStringSource
A lens onto the name of a cookie.
cookieValue :: Lens' Cookie ByteStringSource
A lens onto the value of a cookie.
cookieExpiryTime :: Lens' Cookie UTCTimeSource
A lens onto the expiry time of a cookie.
cookieDomain :: Lens' Cookie ByteStringSource
A lens onto the domain of a cookie.
cookiePath :: Lens' Cookie ByteStringSource
A lens onto the path of a cookie.
Parsing responses
atto :: Parser a -> Fold ByteString aSource
Turn an attoparsec Parser
into a Fold
.
Both headers and bodies can contain complicated data that we may need to parse.
Example: when responding to an OPTIONS request, a server may return the list of verbs it supports in any order, up to and including changing the order on every request (which httpbin.org /actually does/!). To deal with this possibility, we parse the list, then sort it.
>>>
import Data.Attoparsec.ByteString.Char8 as A
>>>
import Data.List (sort)
>>>
>>>
let comma = skipSpace >> "," >> skipSpace
>>>
let verbs = A.takeWhile isAlpha_ascii `sepBy` comma
>>>
>>>
r <- options "http://httpbin.org/get"
>>>
r ^. responseHeader "Allow" . atto verbs . to sort
["GET","HEAD","OPTIONS"]