| Copyright | (c) 2014 Bryan O'Sullivan | 
|---|---|
| License | BSD-style | 
| Maintainer | bos@serpentine.com | 
| Stability | experimental | 
| Portability | GHC | 
| Safe Haskell | None | 
| Language | Haskell98 | 
Network.Wreq
Contents
Description
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 literalByteStringandTextvalues. {-# 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 ByteString)
- deleteWith :: Options -> String -> IO (Response ByteString)
- customMethod :: String -> String -> IO (Response ByteString)
- customMethodWith :: String -> Options -> String -> IO (Response ByteString)
- customPayloadMethod :: Postable a => String -> String -> a -> IO (Response ByteString)
- customPayloadMethodWith :: Postable a => String -> Options -> String -> a -> IO (Response ByteString)
- 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 (Maybe CookieJar)
- checkStatus :: Lens' Options (Maybe StatusChecker)
- data Auth
- data AWSAuthVersion = AWSv4
- auth :: Lens' Options (Maybe Auth)
- basicAuth :: ByteString -> ByteString -> Auth
- oauth1Auth :: ByteString -> ByteString -> ByteString -> ByteString -> Auth
- oauth2Bearer :: ByteString -> Auth
- oauth2Token :: ByteString -> Auth
- awsAuth :: AWSAuthVersion -> ByteString -> ByteString -> Auth
- data Proxy :: * = Proxy ByteString Int
- proxy :: Lens' Options (Maybe Proxy)
- httpProxy :: ByteString -> Int -> 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
- statusMessage :: Lens' Status ByteString
- 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
- atto_ :: Parser a -> Fold ByteString a
HTTP verbs
Sessions
The basic HTTP functions (get, post, and so on) in this module
 have a few key drawbacks:
- If several requests go to the same server, there is no reuse of TCP connections.
- There is no management of cookies across multiple requests.
This makes these functions inefficient and verbose for many common uses. For greater efficiency, use the Network.Wreq.Session module.
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 . statusCode200
getWith :: Options -> String -> IO (Response ByteString) Source
Issue a GET request, using the supplied Options.
Example:
let opts =defaults¶m"foo".~["bar"]getWithopts "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 0Just (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¶m"foo".~["bar"]postWithopts "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 ByteString) Source
Issue a DELETE request.
Example:
delete "http://httpbin.org/delete"
 >>>r <- delete "http://httpbin.org/delete">>>r ^. responseStatus . statusCode200
deleteWith :: Options -> String -> IO (Response ByteString) Source
Custom Method
customMethod :: String -> String -> IO (Response ByteString) Source
Issue a custom-method request
Example:
 
 customMethod "PATCH" "http://httpbin.org/patch"
 
>>>r <- customMethod "PATCH" "http://httpbin.org/patch">>>r ^. responseStatus . statusCode200
customMethodWith :: String -> Options -> String -> IO (Response ByteString) Source
Issue a custom request method request, using the supplied Options.
Example:
let opts =defaults&redirects.~0customMethodWith"PATCH" opts "http://httpbin.org/patch"
>>>let opts = defaults & redirects .~ 0>>>r <- customMethodWith "PATCH" opts "http://httpbin.org/patch">>>r ^. responseStatus . statusCode200
Custom Payload Method
customPayloadMethod :: Postable a => String -> String -> a -> IO (Response ByteString) Source
Issue a custom-method request with a payload
customPayloadMethodWith :: Postable a => String -> Options -> String -> a -> IO (Response ByteString) Source
Issue a custom-method request with a payload, using the supplied Options.
Incremental consumption of responses
GET
foldGetWith :: Options -> (a -> ByteString -> IO a) -> a -> String -> IO a Source
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 (opensslManagerSettingscontext)withOpenSSL$getWithopts "https://httpbin.org/get"
In this example, we also set the response timeout to 10000 microseconds:
import OpenSSL.Session (context) import Network.HTTP.Client.OpenSSL import Network.HTTP.Client (defaultManagerSettings,managerResponseTimeout) let opts =defaults&manager.~Left (opensslManagerSettingscontext)&manager.~Left (defaultManagerSettings{managerResponseTimeout= Just 10000 } )withOpenSSL$getWithopts "https://httpbin.org/get"
header :: HeaderName -> Lens' Options [ByteString] Source
redirects :: Lens' Options Int Source
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.~3getWithopts "http://httpbin.org/redirect/5"
cookie :: ByteString -> Traversal' Options Cookie Source
A traversal onto the cookie with the given name, if one exists.
N.B. This is an "illegal" Traversal': we can change the
 cookieName of the associated Cookie so that it differs from the
 name provided to this function.
checkStatus :: Lens' Options (Maybe StatusChecker) Source
A lens to get the optional status check function
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.
Arguments
| :: ByteString | Username. | 
| -> ByteString | Password. | 
| -> Auth | 
Basic authentication. This consists of a plain username and password.
Example (note the use of TLS):
let opts =defaults&auth?~basicAuth"user" "pass"getWithopts "https://httpbin.org/basic-auth/user/pass"
Note here the use of the ?~ setter to turn an Auth
 into a Maybe Auth, to make the type of the RHS compatible with
 the auth lens.
>>>let opts = defaults & auth ?~ basicAuth "user" "pass">>>r <- getWith opts "https://httpbin.org/basic-auth/user/pass">>>r ^? responseBody . key "authenticated"Just (Bool True)
Arguments
| :: ByteString | Consumer token | 
| -> ByteString | Consumer secret | 
| -> ByteString | OAuth token | 
| -> ByteString | OAuth token secret | 
| -> Auth | 
OAuth1 authentication. This consists of a consumer token, a consumer secret, a token and a token secret
oauth2Bearer :: ByteString -> Auth Source
An OAuth2 bearer token. This is treated by many services as the equivalent of a username and password.
Example (note the use of TLS):
let opts =defaults&auth?~oauth2Bearer"1234abcd"getWithopts "https://public-api.wordpress.com/rest/v1/me/"
oauth2Token :: ByteString -> Auth Source
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"getWithopts "https://api.github.com/user"
awsAuth :: AWSAuthVersion -> ByteString -> ByteString -> Auth Source
Proxy settings
data Proxy :: *
Define a HTTP proxy, consisting of a hostname and port number.
Constructors
| Proxy ByteString Int | 
httpProxy :: ByteString -> Int -> Proxy Source
Using a manager with defaults
withManager :: (Options -> IO a) -> IO a Source
Payloads for POST and PUT
A product type for representing more complex payload types.
Constructors
| Raw :: ContentType -> RequestBody -> Payload | 
URL-encoded form data
A key/value pair for an application/x-www-form-urlencoded
 POST request body.
Constructors
| (:=) :: FormValue v => ByteString -> v -> FormParam infixr 3 | 
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.
Minimal complete definition
Multipart form data
partName :: Lens' Part Text Source
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
Arguments
| :: 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.
Arguments
| :: 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.
Arguments
| :: Text | Name of the corresponding <input>. | 
| -> FilePath | The name of the local file to upload. | 
| -> Part | 
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 body1 Source
A lens onto the body of a response.
r <-get"http://httpbin.org/get" print (r^.responseBody)
Arguments
| :: 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")
Arguments
| :: 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)
Arguments
| :: ByteString | Name of cookie to match. | 
| -> Fold (Response body) Cookie | 
responseHeaders :: Lens' (Response body) ResponseHeaders Source
A lens onto all headers in an HTTP response.
responseCookieJar :: Lens' (Response body) CookieJar Source
A lens onto all cookies set in the response.
responseStatus :: Lens' (Response body) Status Source
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 Int Source
A lens onto the numeric identifier of an HTTP status.
statusMessage :: Lens' Status ByteString Source
A lens onto the textual description of an HTTP status.
Link headers
linkURL :: Lens' Link ByteString Source
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 a FromJSON instance for us.
instance FromJSON 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 ByteString Source
A lens onto the name of a cookie.
cookieValue :: Lens' Cookie ByteString Source
A lens onto the value of a cookie.
cookieExpiryTime :: Lens' Cookie UTCTime Source
A lens onto the expiry time of a cookie.
cookieDomain :: Lens' Cookie ByteString Source
A lens onto the domain of a cookie.
cookiePath :: Lens' Cookie ByteString Source
A lens onto the path of a cookie.
Parsing responses
atto :: Parser a -> Fold ByteString a Source
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"]
atto_ :: Parser a -> Fold ByteString a Source
The same as atto, but ensures that the parser consumes the
 entire input.
Equivalent to:
atto_myParser =atto(myParser<*endOfInput)