wreq-0.5.3.1: An easy-to-use HTTP client library.

Copyright(c) 2014 Bryan O'Sullivan
LicenseBSD-style
Maintainerbos@serpentine.com
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell98

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 literal ByteString and Text 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.

Synopsis

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

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

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. You may need to explicitly add types to the values (e.g. :: String) in order to evade ambigous type errors.

>>> r <- post "http://httpbin.org/post" ["num" := (31337 :: Int), "str" := ("foo" :: String)]

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)

post :: Postable a => String -> a -> IO (Response ByteString) #

Issue a POST request.

Example:

post "http://httpbin.org/post" (toJSON [1,2,3])
 
>>> r <- post "http://httpbin.org/post" (toJSON [1,2,3])
>>> r ^? responseBody . key "json" . nth 2
Just (Number 3.0)

postWith :: Postable a => Options -> String -> a -> IO (Response ByteString) #

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

Issue a HEAD request.

Example:

head_ "http://httpbin.org/get"
 
>>> r <- head_ "http://httpbin.org/get"
>>> r ^? responseHeader "Content-Type"
Just "application/json"

headWith :: Options -> String -> IO (Response ()) #

Issue a HEAD request, using the supplied Options.

Example:

let opts = defaults & param "foo" .~ ["bar"]
headWith opts "http://httpbin.org/get"
 
>>> let opts = defaults & param "foo" .~ ["bar"]
>>> r <- headWith opts "http://httpbin.org/get"
>>> r ^? responseHeader "Connection"
Just "keep-alive"

OPTIONS

options :: String -> IO (Response ()) #

Issue an OPTIONS request.

Example:

options "http://httpbin.org/get"
 

See atto for a more complex worked example.

optionsWith :: Options -> String -> IO (Response ()) #

Issue an OPTIONS request, using the supplied Options.

Example:

let opts = defaults & param "foo" .~ ["bar"]
optionsWith opts "http://httpbin.org/get"
 

PUT

put :: Putable a => String -> a -> IO (Response ByteString) #

Issue a PUT request.

putWith :: Putable a => Options -> String -> a -> IO (Response ByteString) #

Issue a PUT request, using the supplied Options.

DELETE

delete :: String -> IO (Response ByteString) #

Issue a DELETE request.

Example:

delete "http://httpbin.org/delete"
 
>>> r <- delete "http://httpbin.org/delete"
>>> r ^. responseStatus . statusCode
200

deleteWith :: Options -> String -> IO (Response ByteString) #

Issue a DELETE request, using the supplied Options.

Example:

let opts = defaults & redirects .~ 0
deleteWith opts "http://httpbin.org/delete"
 
>>> let opts = defaults & redirects .~ 0
>>> r <- deleteWith opts "http://httpbin.org/delete"
>>> r ^. responseStatus . statusCode
200

Custom Method

customMethod :: String -> String -> IO (Response ByteString) #

Issue a custom-method request

Example:

customMethod "PATCH" "http://httpbin.org/patch"
>>> r <- customMethod "PATCH" "http://httpbin.org/patch"
>>> r ^. responseStatus . statusCode
200

customMethodWith :: String -> Options -> String -> IO (Response ByteString) #

Issue a custom request method request, using the supplied Options.

Example:

let opts = defaults & redirects .~ 0
customMethodWith "PATCH" opts "http://httpbin.org/patch"
 
>>> let opts = defaults & redirects .~ 0
>>> r <- customMethodWith "PATCH" opts "http://httpbin.org/patch"
>>> r ^. responseStatus . statusCode
200

customHistoriedMethod :: String -> String -> IO (HistoriedResponse ByteString) #

Issue a custom request method. Keep track of redirects and return the HistoriedResponse

Example:

customHistoriedMethod "GET" "http://httpbin.org/redirect/3"
>>> r <- customHistoriedMethod "GET" "http://httpbin.org/redirect/3"
>>> length (r ^. hrRedirects)
3

Since: 0.5.2.0

customHistoriedMethodWith :: String -> Options -> String -> IO (HistoriedResponse ByteString) #

Issue a custom request method request, using the supplied Options. Keep track of redirects and return the HistoriedResponse.

Since: 0.5.2.0

Custom Payload Method

customPayloadMethod :: Postable a => String -> String -> a -> IO (Response ByteString) #

Issue a custom-method request with a payload

customPayloadMethodWith :: Postable a => String -> Options -> String -> a -> IO (Response ByteString) #

Issue a custom-method request with a payload, using the supplied Options.

customHistoriedPayloadMethod :: Postable a => String -> String -> a -> IO (HistoriedResponse ByteString) #

Issue a custom-method historied request with a payload

customHistoriedPayloadMethodWith :: Postable a => String -> Options -> String -> a -> IO (HistoriedResponse ByteString) #

Issue a custom-method historied request with a paylod, using the supplied Options.

Incremental consumption of responses

GET

foldGet :: (a -> ByteString -> IO a) -> a -> String -> IO a #

foldGetWith :: Options -> (a -> ByteString -> IO a) -> a -> String -> IO a #

Configuration

data Options #

Options for configuring a client.

Instances
Show Options # 
Instance details

Defined in Network.Wreq.Internal.Types

manager :: Lens' Options (Either ManagerSettings Manager) #

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"
 

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 (opensslManagerSettings context)
                    & manager .~ Left (defaultManagerSettings { managerResponseTimeout = responseTimeoutMicro 10000 } )

withOpenSSL $
  getWith opts "https://httpbin.org/get"
 

header :: HeaderName -> Lens' Options [ByteString] #

A lens onto all headers with the given name (there can legitimately be zero or more).

Example:

let opts = defaults & header "Accept" .~ ["*/*"]
getWith opts "http://httpbin.org/get"
 

param :: Text -> Lens' Options [Text] #

A lens onto all query parameters with the given name (there can legitimately be zero or more).

In this example, we construct the query URL "http://httpbin.org/get?foo=bar&foo=quux".

let opts = defaults & param "foo" .~ ["bar", "quux"]
getWith opts "http://httpbin.org/get"
 

redirects :: Lens' Options Int #

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 .~ 3
getWith opts "http://httpbin.org/redirect/5"
 

headers :: Lens' Options [Header] #

A lens onto all headers (there can legitimately be zero or more).

In this example, we print all the headers sent by default with every request.

print (defaults ^. headers)
 

params :: Lens' Options [(Text, Text)] #

A lens onto all query parameters.

cookie :: ByteString -> Traversal' Options Cookie #

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.

cookies :: Lens' Options (Maybe CookieJar) #

A lens onto all cookies.

checkResponse :: Lens' Options (Maybe ResponseChecker) #

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.

data Auth #

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.

Instances
Eq Auth # 
Instance details

Defined in Network.Wreq.Internal.Types

Methods

(==) :: Auth -> Auth -> Bool #

(/=) :: Auth -> Auth -> Bool #

Show Auth # 
Instance details

Defined in Network.Wreq.Internal.Types

Methods

showsPrec :: Int -> Auth -> ShowS #

show :: Auth -> String #

showList :: [Auth] -> ShowS #

data AWSAuthVersion #

Constructors

AWSv4

AWS request signing version 4

auth :: Lens' Options (Maybe Auth) #

A lens onto request authentication.

Example (note the use of TLS):

let opts = defaults & auth ?~ basicAuth "user" "pass"
getWith opts "https://httpbin.org/basic-auth/user/pass"
 

basicAuth #

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"
getWith opts "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)

oauth1Auth #

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 #

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"
getWith opts "https://public-api.wordpress.com/rest/v1/me/"
 

oauth2Token :: ByteString -> Auth #

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"
 

awsAuth :: AWSAuthVersion -> ByteString -> ByteString -> Auth #

AWS v4 request signature.

Example (note the use of TLS):

let opts = defaults & auth ?~ 'awsAuth AWSv4' "key" "secret"
getWith opts "https://dynamodb.us-west-2.amazonaws.com"
 

awsFullAuth :: AWSAuthVersion -> ByteString -> ByteString -> Maybe ByteString -> Maybe (ByteString, ByteString) -> Auth #

AWS v4 request signature.

Example (note the use of TLS):

let opts = defaults & auth ?~ awsFullAuth AWSv4 "key" "secret" (Just ("service", "region"))
getWith opts "https://dynamodb.us-west-2.amazonaws.com"
 

awsSessionTokenAuth #

Arguments

:: AWSAuthVersion

Signature version (V4)

-> ByteString

AWS AccessKeyId

-> ByteString

AWS SecretAccessKey

-> ByteString

AWS STS SessionToken

-> Auth 

AWS v4 request signature using a AWS STS Session Token.

Example (note the use of TLS):

let opts = defaults
           & auth
           ?~ 'awsAuth AWSv4' "key" "secret" "stsSessionToken"
getWith opts "https://dynamodb.us-west-2.amazonaws.com"
 

Proxy settings

data Proxy #

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

Constructors

Proxy ByteString Int 
Instances
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 #

Read Proxy 
Instance details

Defined in Network.HTTP.Client.Types

Show Proxy 
Instance details

Defined in Network.HTTP.Client.Types

Methods

showsPrec :: Int -> Proxy -> ShowS #

show :: Proxy -> String #

showList :: [Proxy] -> ShowS #

proxy :: Lens' Options (Maybe Proxy) #

A lens onto proxy configuration.

Example:

let opts = defaults & proxy ?~ httpProxy "localhost" 8000
getWith opts "http://httpbin.org/get"
 

Note here the use of the ?~ setter to turn a Proxy into a Maybe Proxy, to make the type of the RHS compatible with the proxy lens.

httpProxy :: ByteString -> Int -> Proxy #

Proxy configuration.

Example:

let opts = defaults & proxy ?~ httpProxy "localhost" 8000
getWith opts "http://httpbin.org/get"
 

Note here the use of the ?~ setter to turn a Proxy into a Maybe Proxy, to make the type of the RHS compatible with the proxy lens.

Using a manager with defaults

withManager :: (Options -> IO a) -> IO a #

Payloads for POST and PUT

data Payload where #

A product type for representing more complex payload types.

Constructors

Raw :: ContentType -> RequestBody -> Payload 
Instances
Putable Payload # 
Instance details

Defined in Network.Wreq.Types

Postable Payload # 
Instance details

Defined in Network.Wreq.Types

URL-encoded form data

data FormParam where #

A key/value pair for an application/x-www-form-urlencoded POST request body.

Constructors

(:=) :: FormValue v => ByteString -> v -> FormParam infixr 3 
Instances
Show FormParam # 
Instance details

Defined in Network.Wreq.Internal.Types

Putable FormParam # 
Instance details

Defined in Network.Wreq.Types

Postable FormParam # 
Instance details

Defined in Network.Wreq.Types

Putable [FormParam] # 
Instance details

Defined in Network.Wreq.Types

Postable [FormParam] # 
Instance details

Defined in Network.Wreq.Types

class FormValue a #

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

renderFormValue

Instances
FormValue Double # 
Instance details

Defined in Network.Wreq.Types

FormValue Float # 
Instance details

Defined in Network.Wreq.Types

FormValue Int # 
Instance details

Defined in Network.Wreq.Types

FormValue Int8 # 
Instance details

Defined in Network.Wreq.Types

FormValue Int16 # 
Instance details

Defined in Network.Wreq.Types

FormValue Int32 # 
Instance details

Defined in Network.Wreq.Types

FormValue Int64 # 
Instance details

Defined in Network.Wreq.Types

FormValue Integer # 
Instance details

Defined in Network.Wreq.Types

FormValue Word # 
Instance details

Defined in Network.Wreq.Types

FormValue Word8 # 
Instance details

Defined in Network.Wreq.Types

FormValue Word16 # 
Instance details

Defined in Network.Wreq.Types

FormValue Word32 # 
Instance details

Defined in Network.Wreq.Types

FormValue Word64 # 
Instance details

Defined in Network.Wreq.Types

FormValue () # 
Instance details

Defined in Network.Wreq.Types

Methods

renderFormValue :: () -> ByteString #

FormValue ByteString # 
Instance details

Defined in Network.Wreq.Types

FormValue ByteString # 
Instance details

Defined in Network.Wreq.Types

FormValue Builder # 
Instance details

Defined in Network.Wreq.Types

FormValue Text # 
Instance details

Defined in Network.Wreq.Types

FormValue String # 
Instance details

Defined in Network.Wreq.Types

FormValue Text # 
Instance details

Defined in Network.Wreq.Types

FormValue a => FormValue (Maybe a) # 
Instance details

Defined in Network.Wreq.Types

Multipart form data

data Part #

A single part of a multipart message.

Instances
Show Part 
Instance details

Defined in Network.HTTP.Client.MultipartFormData

Methods

showsPrec :: Int -> Part -> ShowS #

show :: Part -> String #

showList :: [Part] -> ShowS #

Putable Part # 
Instance details

Defined in Network.Wreq.Types

Methods

putPayload :: Part -> Request -> IO Request #

Postable Part # 
Instance details

Defined in Network.Wreq.Types

Putable [Part] # 
Instance details

Defined in Network.Wreq.Types

Methods

putPayload :: [Part] -> Request -> IO Request #

Postable [Part] # 
Instance details

Defined in Network.Wreq.Types

Methods

postPayload :: [Part] -> Request -> IO Request #

partName :: Lens' Part Text #

A lens onto the name of the input element associated with part of a multipart form upload.

partFileName :: Lens' Part (Maybe String) #

A lens onto the filename associated with part of a multipart form upload.

partContentType :: Traversal' Part (Maybe MimeType) #

A lens onto the content-type associated with part of a multipart form upload.

partGetBody :: Lens' Part (IO RequestBody) #

A lens onto the code that fetches the data associated with part of a multipart form upload.

Smart constructors

partBS #

Arguments

:: Text

Name of the corresponding <input>.

-> ByteString

The body for this Part.

-> Part 

Make a Part whose content is a strict ByteString.

The Part does not have a file name or content type associated with it.

partLBS #

Arguments

:: Text

Name of the corresponding <input>.

-> ByteString

The body for this Part.

-> Part 

Make a Part whose content is a lazy ByteString.

The Part does not have a file name or content type associated with it.

partText #

Arguments

:: Text

Name of the corresponding <input>.

-> Text

The body for this Part.

-> Part 

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.

partString #

Arguments

:: Text

Name of the corresponding <input>.

-> String

The body for this Part.

-> Part 

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.

partFile #

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.

partFileSource #

Arguments

:: Text

Name of the corresponding <input>.

-> FilePath

The name of the local file to upload.

-> Part 

Stream a Part from a file.

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

Instances
Functor Response 
Instance details

Defined in Network.HTTP.Client.Types

Methods

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

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

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 #

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

Eq body => Eq (Response body) 
Instance details

Defined in Network.HTTP.Client.Types

Methods

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

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

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 #

responseBody :: Lens (Response body0) (Response body1) body0 body1 #

A lens onto the body of a response.

r <- get "http://httpbin.org/get"
print (r ^. responseBody)
 

responseHeader #

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

responseLink #

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)
 

responseCookie #

Arguments

:: ByteString

Name of cookie to match.

-> Fold (Response body) Cookie 

A fold over any cookies that match the given name.

r <- get "http://www.nytimes.com/"
print (r ^? responseCookie "RMID")
 

responseHeaders :: Lens' (Response body) ResponseHeaders #

A lens onto all headers in an HTTP response.

responseCookieJar :: Lens' (Response body) CookieJar #

A lens onto all cookies set in the response.

responseStatus :: Lens' (Response body) Status #

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.

Instances
Bounded Status 
Instance details

Defined in Network.HTTP.Types.Status

Enum Status 
Instance details

Defined in Network.HTTP.Types.Status

Eq Status 
Instance details

Defined in Network.HTTP.Types.Status

Methods

(==) :: Status -> Status -> Bool #

(/=) :: Status -> Status -> Bool #

Ord Status 
Instance details

Defined in Network.HTTP.Types.Status

Show Status 
Instance details

Defined in Network.HTTP.Types.Status

statusCode :: Lens' Status Int #

A lens onto the numeric identifier of an HTTP status.

statusMessage :: Lens' Status ByteString #

A lens onto the textual description of an HTTP status.

data HistoriedResponse body #

A datatype holding information on redirected requests and the final response.

Since 0.4.1

Instances
Functor HistoriedResponse 
Instance details

Defined in Network.HTTP.Client

Foldable HistoriedResponse 
Instance details

Defined in Network.HTTP.Client

Methods

fold :: Monoid m => HistoriedResponse m -> m #

foldMap :: Monoid m => (a -> m) -> HistoriedResponse a -> m #

foldr :: (a -> b -> b) -> b -> HistoriedResponse a -> b #

foldr' :: (a -> b -> b) -> b -> HistoriedResponse a -> b #

foldl :: (b -> a -> b) -> b -> HistoriedResponse a -> b #

foldl' :: (b -> a -> b) -> b -> HistoriedResponse a -> b #

foldr1 :: (a -> a -> a) -> HistoriedResponse a -> a #

foldl1 :: (a -> a -> a) -> HistoriedResponse a -> a #

toList :: HistoriedResponse a -> [a] #

null :: HistoriedResponse a -> Bool #

length :: HistoriedResponse a -> Int #

elem :: Eq a => a -> HistoriedResponse a -> Bool #

maximum :: Ord a => HistoriedResponse a -> a #

minimum :: Ord a => HistoriedResponse a -> a #

sum :: Num a => HistoriedResponse a -> a #

product :: Num a => HistoriedResponse a -> a #

Traversable HistoriedResponse 
Instance details

Defined in Network.HTTP.Client

Methods

traverse :: Applicative f => (a -> f b) -> HistoriedResponse a -> f (HistoriedResponse b) #

sequenceA :: Applicative f => HistoriedResponse (f a) -> f (HistoriedResponse a) #

mapM :: Monad m => (a -> m b) -> HistoriedResponse a -> m (HistoriedResponse b) #

sequence :: Monad m => HistoriedResponse (m a) -> m (HistoriedResponse a) #

Show body => Show (HistoriedResponse body) 
Instance details

Defined in Network.HTTP.Client

Generic (HistoriedResponse body) 
Instance details

Defined in Network.HTTP.Client

Associated Types

type Rep (HistoriedResponse body) :: Type -> Type #

Methods

from :: HistoriedResponse body -> Rep (HistoriedResponse body) x #

to :: Rep (HistoriedResponse body) x -> HistoriedResponse body #

type Rep (HistoriedResponse body) 
Instance details

Defined in Network.HTTP.Client

type Rep (HistoriedResponse body) = D1 (MetaData "HistoriedResponse" "Network.HTTP.Client" "http-client-0.5.14-6HlyPPnTjKxFR6Q6lLdMcY" False) (C1 (MetaCons "HistoriedResponse" PrefixI True) (S1 (MetaSel (Just "hrRedirects") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Request, Response ByteString)]) :*: (S1 (MetaSel (Just "hrFinalRequest") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Request) :*: S1 (MetaSel (Just "hrFinalResponse") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Response body)))))

hrFinalRequest :: Lens' (HistoriedResponse body) Request #

A lens onto the final request of a historied response.

hrFinalResponse :: Lens' (HistoriedResponse body) (Response body) #

A lens onto the final response of a historied response.

hrRedirects :: Lens' (HistoriedResponse body) [(Request, Response ByteString)] #

A lens onto the list of redirects of a historied response.

Link headers

data Link #

An element of a Link header.

linkURL :: Lens' Link ByteString #

A lens onto the URL portion of a Link element.

linkParams :: Lens' Link [(ByteString, ByteString)] #

A lens onto the parameters of a Link element.

Decoding responses

data JSONError #

The error type used by asJSON and asValue if a failure occurs when parsing a response body as JSON.

Constructors

JSONError String 

asJSON :: (MonadThrow m, FromJSON a) => Response ByteString -> m (Response a) #

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

Convert the body of an HTTP response from JSON to a Value.

In this example, we use asValue in the IO monad, where it will throw a JSONError exception if the conversion to Value fails.

foo = do
  r <- asValue =<< get "http://httpbin.org/get"
  print (r ^? responseBody . key "headers" . key "User-Agent")
 

Cookies

These are only the most frequently-used cookie-related lenses. See Network.Wreq.Lens for the full accounting of them all.

data Cookie #

Instances
Eq Cookie 
Instance details

Defined in Network.HTTP.Client.Types

Methods

(==) :: Cookie -> Cookie -> Bool #

(/=) :: Cookie -> Cookie -> Bool #

Ord Cookie 
Instance details

Defined in Network.HTTP.Client.Types

Read Cookie 
Instance details

Defined in Network.HTTP.Client.Types

Show Cookie 
Instance details

Defined in Network.HTTP.Client.Types

cookieName :: Lens' Cookie ByteString #

A lens onto the name of a cookie.

cookieValue :: Lens' Cookie ByteString #

A lens onto the value of a cookie.

cookieExpiryTime :: Lens' Cookie UTCTime #

A lens onto the expiry time of a cookie.

cookieDomain :: Lens' Cookie ByteString #

A lens onto the domain of a cookie.

cookiePath :: Lens' Cookie ByteString #

A lens onto the path of a cookie.

Parsing responses

atto :: Parser a -> Fold ByteString a #

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 #

The same as atto, but ensures that the parser consumes the entire input.

Equivalent to:

atto_ myParser = atto (myParser <* endOfInput)