| Copyright | © 2016–present Mark Karpov | 
|---|---|
| License | BSD 3 clause | 
| Maintainer | Mark Karpov <markkarpov92@gmail.com> | 
| Stability | experimental | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Network.HTTP.Req
Contents
Description
The documentation below is structured in such a way that the most important information is presented first: you learn how to do HTTP requests, how to embed them in any monad you have, and then it gives you details about less-common things you may want to know about. The documentation is written with sufficient coverage of details and examples, and it's designed to be a complete tutorial on its own.
(A modest intro goes here, click on req to start making requests.)
About the library
Req is an easy-to-use, type-safe, expandable, high-level HTTP client library that just works without any fooling around.
What does the phrase “easy-to-use” mean? It means that the library is
 designed to be beginner-friendly so it's simple to add to your monad
 stack, intuitive to work with, well-documented, and does not get in your
 way. Doing HTTP requests is a common task and Haskell library for this
 should be very approachable and clear to beginners, thus certain
 compromises were made. For example, one cannot currently modify
 ManagerSettings of the default manager because the library always
 uses the same implicit global manager for simplicity and maximal
 connection sharing. There is a way to use your own manager with different
 settings, but it requires a bit more typing.
“Type-safe” means that the library is protective and eliminates certain
 classes of errors. For example, we have correct-by-construction Urls,
 it's guaranteed that the user does not send the request body when using
 methods like GET or OPTIONS, and the amount of implicit assumptions
 is minimized by making the user specify his/her intentions in an
 explicit form (for example, it's not possible to avoid specifying the
 body or method of request). Authentication methods that assume HTTPS
 force the user to use HTTPS at the type level. The library also carefully
 hides underlying types from the lower-level http-client package because
 those types are not safe enough (for example Request is an instance
 of IsString and, if it's malformed, it will blow up at
 run-time).
“Expandable” refers to the ability of the library to be expanded without having to resort to ugly hacking. For example, it's possible to define your own HTTP methods, create new ways to construct the body of a request, create new authorization options, perform a request in a different way, and create your own methods to parse and represent a response. As the user extends the library to satisfy his/her special needs, the new solutions will work just like the built-ins. However, all of the common cases are also covered by the library out-of-the-box.
“High-level” means that there are less details to worry about. The
 library is a result of my experiences as a Haskell consultant. Working
 for several clients, who had very different projects, showed me that the
 library should adapt easily to any particular style of writing Haskell
 applications. For example, some people prefer throwing exceptions, while
 others are concerned with purity. Just define handleHttpException
 accordingly when making your monad instance of MonadHttp and it will
 play together seamlessly. Finally, the library cuts down boilerplate
 considerably, and helps you write concise, easy to read, and maintainable
 code.
Using with other libraries
- You won't need the low-level interface of 
http-clientmost of the time, but when you do, it's better to do a qualified import, becausehttp-clienthas naming conflicts withreq. - For streaming of large request bodies see the companion package
       
req-conduit: https://hackage.haskell.org/package/req-conduit. 
Lightweight, no risk solution
The library uses the following mature packages under the hood to guarantee you the best experience:
- https://hackage.haskell.org/package/http-client—low level HTTP client used everywhere in Haskell.
 - https://hackage.haskell.org/package/http-client-tls—TLS (HTTPS)
       support for 
http-client. 
It's important to note that since we leverage well-known libraries that
 the whole Haskell ecosystem uses, there is no risk in using req. The
 machinery for performing requests is the same as with http-conduit and
 wreq. The only difference is the API.
Synopsis
- req :: (MonadHttp m, HttpMethod method, HttpBody body, HttpResponse response, HttpBodyAllowed (AllowsBody method) (ProvidesBody body)) => method -> Url scheme -> body -> Proxy response -> Option scheme -> m response
 - reqBr :: (MonadHttp m, HttpMethod method, HttpBody body, HttpBodyAllowed (AllowsBody method) (ProvidesBody body)) => method -> Url scheme -> body -> Option scheme -> (Response BodyReader -> IO a) -> m a
 - req' :: forall m method body scheme a. (MonadHttp m, HttpMethod method, HttpBody body, HttpBodyAllowed (AllowsBody method) (ProvidesBody body)) => method -> Url scheme -> body -> Option scheme -> (Request -> Manager -> m a) -> m a
 - withReqManager :: MonadIO m => (Manager -> m a) -> m a
 - class MonadIO m => MonadHttp m where
- handleHttpException :: HttpException -> m a
 - getHttpConfig :: m HttpConfig
 
 - data HttpConfig = HttpConfig {
- httpConfigProxy :: Maybe Proxy
 - httpConfigRedirectCount :: Int
 - httpConfigAltManager :: Maybe Manager
 - httpConfigCheckResponse :: forall b. Request -> Response b -> ByteString -> Maybe HttpExceptionContent
 - httpConfigRetryPolicy :: RetryPolicyM IO
 - httpConfigRetryJudge :: forall b. RetryStatus -> Response b -> Bool
 
 - defaultHttpConfig :: HttpConfig
 - data Req a
 - runReq :: MonadIO m => HttpConfig -> Req a -> m a
 - data GET = GET
 - data POST = POST
 - data HEAD = HEAD
 - data PUT = PUT
 - data DELETE = DELETE
 - data TRACE = TRACE
 - data CONNECT = CONNECT
 - data OPTIONS = OPTIONS
 - data PATCH = PATCH
 - class HttpMethod a where
- type AllowsBody a :: CanHaveBody
 - httpMethodName :: Proxy a -> ByteString
 
 - data Url (scheme :: Scheme)
 - http :: Text -> Url Http
 - https :: Text -> Url Https
 - (/~) :: ToHttpApiData a => Url scheme -> a -> Url scheme
 - (/:) :: Url scheme -> Text -> Url scheme
 - useHttpURI :: URI -> Maybe (Url Http, Option scheme)
 - useHttpsURI :: URI -> Maybe (Url Https, Option scheme)
 - useURI :: URI -> Maybe (Either (Url Http, Option scheme0) (Url Https, Option scheme1))
 - data NoReqBody = NoReqBody
 - newtype ReqBodyJson a = ReqBodyJson a
 - newtype ReqBodyFile = ReqBodyFile FilePath
 - newtype ReqBodyBs = ReqBodyBs ByteString
 - newtype ReqBodyLbs = ReqBodyLbs ByteString
 - newtype ReqBodyUrlEnc = ReqBodyUrlEnc FormUrlEncodedParam
 - data FormUrlEncodedParam
 - data ReqBodyMultipart
 - reqBodyMultipart :: MonadIO m => [Part] -> m ReqBodyMultipart
 - class HttpBody body where
- getRequestBody :: body -> RequestBody
 - getRequestContentType :: body -> Maybe ByteString
 
 - type family ProvidesBody body :: CanHaveBody where ...
 - type family HttpBodyAllowed (allowsBody :: CanHaveBody) (providesBody :: CanHaveBody) :: Constraint where ...
 - data Option (scheme :: Scheme)
 - (=:) :: (QueryParam param, ToHttpApiData a) => Text -> a -> param
 - queryFlag :: QueryParam param => Text -> param
 - class QueryParam param where
- queryParam :: ToHttpApiData a => Text -> Maybe a -> param
 
 - header :: ByteString -> ByteString -> Option scheme
 - attachHeader :: ByteString -> ByteString -> Request -> Request
 - cookieJar :: CookieJar -> Option scheme
 - basicAuth :: ByteString -> ByteString -> Option Https
 - basicAuthUnsafe :: ByteString -> ByteString -> Option scheme
 - basicProxyAuth :: ByteString -> ByteString -> Option scheme
 - oAuth1 :: ByteString -> ByteString -> ByteString -> ByteString -> Option scheme
 - oAuth2Bearer :: ByteString -> Option Https
 - oAuth2Token :: ByteString -> Option Https
 - customAuth :: (Request -> IO Request) -> Option scheme
 - port :: Int -> Option scheme
 - decompress :: (ByteString -> Bool) -> Option scheme
 - responseTimeout :: Int -> Option scheme
 - httpVersion :: Int -> Int -> Option scheme
 - data IgnoreResponse
 - ignoreResponse :: Proxy IgnoreResponse
 - data JsonResponse a
 - jsonResponse :: Proxy (JsonResponse a)
 - data BsResponse
 - bsResponse :: Proxy BsResponse
 - data LbsResponse
 - lbsResponse :: Proxy LbsResponse
 - responseBody :: HttpResponse response => response -> HttpResponseBody response
 - responseStatusCode :: HttpResponse response => response -> Int
 - responseStatusMessage :: HttpResponse response => response -> ByteString
 - responseHeader :: HttpResponse response => response -> ByteString -> Maybe ByteString
 - responseCookieJar :: HttpResponse response => response -> CookieJar
 - class HttpResponse response where
- type HttpResponseBody response :: Type
 - toVanillaResponse :: response -> Response (HttpResponseBody response)
 - getHttpResponse :: Response BodyReader -> IO response
 - acceptHeader :: Proxy response -> Maybe ByteString
 
 - data HttpException
 - data CanHaveBody
 - data Scheme
 
Making a request
To make an HTTP request you normally need only one function: req.
Arguments
| :: (MonadHttp m, HttpMethod method, HttpBody body, HttpResponse response, HttpBodyAllowed (AllowsBody method) (ProvidesBody body)) | |
| => method | HTTP method  | 
| -> Url scheme | 
  | 
| -> body | Body of the request  | 
| -> Proxy response | A hint how to interpret response  | 
| -> Option scheme | Collection of optional parameters  | 
| -> m response | Response  | 
Make an HTTP request. The function takes 5 arguments, 4 of which
 specify required parameters and the final Option argument is a
 collection of optional parameters.
Let's go through all the arguments first: req method url body response
 options.
method is an HTTP method such as GET or POST. The documentation has
 a dedicated section about HTTP methods below.
url is a Url that describes location of resource you want to interact
 with.
body is a body option such as NoReqBody or ReqBodyJson. The
 tutorial has a section about HTTP bodies, but usage is very
 straightforward and should be clear from the examples below.
response is a type hint how to make and interpret response of an HTTP
 request. Out-of-the-box it can be the following:
ignoreResponsejsonResponsebsResponse(to get a strictByteString)lbsResponse(to get a lazyByteString)
Finally, options is a Monoid that holds a composite Option for all
 other optional settings like query parameters, headers, non-standard port
 number, etc. There are quite a few things you can put there, see the
 corresponding section in the documentation. If you don't need anything at
 all, pass mempty.
Note that if you use req to do all your requests, connection
 sharing and reuse is done for you automatically.
See the examples below to get on the speed quickly.
Examples
First, this is a piece of boilerplate that should be in place before you try the examples:
{-# LANGUAGE DeriveGeneric     #-}
{-# LANGUAGE OverloadedStrings #-}
module Main (main) where
import Control.Monad
import Control.Monad.IO.Class
import Data.Aeson
import Data.Maybe (fromJust)
import Data.Monoid ((<>))
import Data.Text (Text)
import GHC.Generics
import Network.HTTP.Req
import qualified Data.ByteString.Char8 as B
import qualified Text.URI as URIWe will be making requests against the https://httpbin.org service.
Make a GET request, grab 5 random bytes:
main :: IO ()
main = runReq defaultHttpConfig $ do
  let n :: Int
      n = 5
  bs <- req GET (https "httpbin.org" /: "bytes" /~ n) NoReqBody bsResponse mempty
  liftIO $ B.putStrLn (responseBody bs)The same, but now we use a query parameter named "seed" to control
 seed of the generator:
main :: IO ()
main = runReq defaultHttpConfig $ do
  let n, seed :: Int
      n    = 5
      seed = 100
  bs <- req GET (https "httpbin.org" /: "bytes" /~ n) NoReqBody bsResponse $
    "seed" =: seed
  liftIO $ B.putStrLn (responseBody bs)POST JSON data and get some info about the POST request:
data MyData = MyData
  { size  :: Int
  , color :: Text
  } deriving (Show, Generic)
instance ToJSON MyData
instance FromJSON MyData
main :: IO ()
main = runReq defaultHttpConfig $ do
  let myData = MyData
        { size  = 6
        , color = "Green" }
  v <- req POST (https "httpbin.org" /: "post") (ReqBodyJson myData) jsonResponse mempty
  liftIO $ print (responseBody v :: Value)Sending URL-encoded body:
main :: IO ()
main = runReq defaultHttpConfig $ do
  let params =
        "foo" =: ("bar" :: Text) <>
        queryFlag "baz"
  response <- req POST (https "httpbin.org" /: "post") (ReqBodyUrlEnc params) jsonResponse mempty
  liftIO $ print (responseBody response :: Value)Using various optional parameters and URL that is not known in advance:
main :: IO ()
main = runReq defaultHttpConfig $ do
  -- This is an example of what to do when URL is given dynamically. Of
  -- course in a real application you may not want to use 'fromJust'.
  uri <- URI.mkURI "https://httpbin.org/get?foo=bar"
  let (url, options) = fromJust (useHttpsURI uri)
  response <- req GET url NoReqBody jsonResponse $
    "from" =: (15 :: Int)           <>
    "to"   =: (67 :: Int)           <>
    basicAuth "username" "password" <>
    options                         <> -- contains the ?foo=bar part
    port 443 -- here you can put any port of course
  liftIO $ print (responseBody response :: Value)Arguments
| :: (MonadHttp m, HttpMethod method, HttpBody body, HttpBodyAllowed (AllowsBody method) (ProvidesBody body)) | |
| => method | HTTP method  | 
| -> Url scheme | 
  | 
| -> body | Body of the request  | 
| -> Option scheme | Collection of optional parameters  | 
| -> (Response BodyReader -> IO a) | How to consume response  | 
| -> m a | Result  | 
A version of req that does not use one of the predefined instances of
 HttpResponse but instead allows the user to consume  manually, in a custom way.Response
 BodyReader
Since: 1.0.0
Arguments
| :: (MonadHttp m, HttpMethod method, HttpBody body, HttpBodyAllowed (AllowsBody method) (ProvidesBody body)) | |
| => method | HTTP method  | 
| -> Url scheme | 
  | 
| -> body | Body of the request  | 
| -> Option scheme | Collection of optional parameters  | 
| -> (Request -> Manager -> m a) | How to perform request  | 
| -> m a | Result  | 
Mostly like req with respect to its arguments, but accepts a callback
 that allows to perform a request in arbitrary fashion.
This function does not perform handling/wrapping exceptions, checking
 response (with httpConfigCheckResponse), and retrying. It only prepares
 Request and allows you to use it.
Since: 0.3.0
withReqManager :: MonadIO m => (Manager -> m a) -> m a Source #
Embedding requests in your monad
To use req in your monad, all you need to do is to make the monad an
 instance of the MonadHttp type class.
When writing a library, keep your API polymorphic in terms of
 MonadHttp, only define instance of MonadHttp in final application.
 Another option is to use a newtype-wrapped monad stack and define
 MonadHttp for it. As of version 0.4.0, the Req monad that follows
 this strategy is provided out-of-the-box (see below).
class MonadIO m => MonadHttp m where Source #
A type class for monads that support performing HTTP requests.
 Typically, you only need to define the handleHttpException method
 unless you want to tweak HttpConfig.
Minimal complete definition
Methods
handleHttpException :: HttpException -> m a Source #
This method describes how to deal with HttpException that was
 caught by the library. One option is to re-throw it if you are OK with
 exceptions, but if you prefer working with something like
 MonadError, this is the right place to pass it to
 throwError.
getHttpConfig :: m HttpConfig Source #
Return HttpConfig to be used when performing HTTP requests. Default
 implementation returns its def value, which is described in the
 documentation for the type. Common usage pattern with manually defined
 getHttpConfig is to return some hard-coded value, or a value
 extracted from MonadReader if a more flexible
 approach to configuration is desirable.
Instances
| MonadHttp Req Source # | |
Defined in Network.HTTP.Req Methods handleHttpException :: HttpException -> Req a Source #  | |
data HttpConfig Source #
HttpConfig contains general and default settings to be used when
 making HTTP requests.
Constructors
| HttpConfig | |
Fields 
  | |
defaultHttpConfig :: HttpConfig Source #
Default value of HttpConfig.
Since: 2.0.0
A monad that allows to run req in any IO-enabled monad without
 having to define new instances.
Since: 0.4.0
Instances
| Monad Req Source # | |
| Functor Req Source # | |
| Applicative Req Source # | |
| MonadIO Req Source # | |
Defined in Network.HTTP.Req  | |
| MonadHttp Req Source # | |
Defined in Network.HTTP.Req Methods handleHttpException :: HttpException -> Req a Source #  | |
| MonadBase IO Req Source # | |
Defined in Network.HTTP.Req  | |
| MonadBaseControl IO Req Source # | |
| type StM Req a Source # | |
Defined in Network.HTTP.Req  | |
Arguments
| :: MonadIO m | |
| => HttpConfig | 
  | 
| -> Req a | Computation to run  | 
| -> m a | 
Run a computation in the Req monad with the given HttpConfig. In
 case of exceptional situation an HttpException will be thrown.
Since: 0.4.0
Request
Method
The package supports all methods as defined by RFC 2616, and PATCH
 which is defined by RFC 5789—that should be enough to talk to RESTful
 APIs. In some cases, however, you may want to add more methods (e.g. you
 work with WebDAV https://en.wikipedia.org/wiki/WebDAV); no need to
 compromise on type safety and hack, it only takes a couple of seconds to
 define a new method that will works seamlessly, see HttpMethod.
GET method.
Constructors
| GET | 
Instances
| HttpMethod GET Source # | |
Defined in Network.HTTP.Req Associated Types type AllowsBody GET :: CanHaveBody Source # Methods httpMethodName :: Proxy GET -> ByteString Source #  | |
| type AllowsBody GET Source # | |
Defined in Network.HTTP.Req  | |
POST method.
Constructors
| POST | 
Instances
| HttpMethod POST Source # | |
Defined in Network.HTTP.Req Associated Types type AllowsBody POST :: CanHaveBody Source # Methods httpMethodName :: Proxy POST -> ByteString Source #  | |
| type AllowsBody POST Source # | |
Defined in Network.HTTP.Req  | |
HEAD method.
Constructors
| HEAD | 
Instances
| HttpMethod HEAD Source # | |
Defined in Network.HTTP.Req Associated Types type AllowsBody HEAD :: CanHaveBody Source # Methods httpMethodName :: Proxy HEAD -> ByteString Source #  | |
| type AllowsBody HEAD Source # | |
Defined in Network.HTTP.Req  | |
PUT method.
Constructors
| PUT | 
Instances
| HttpMethod PUT Source # | |
Defined in Network.HTTP.Req Associated Types type AllowsBody PUT :: CanHaveBody Source # Methods httpMethodName :: Proxy PUT -> ByteString Source #  | |
| type AllowsBody PUT Source # | |
Defined in Network.HTTP.Req  | |
DELETE method. This data type does not allow having request body with
 DELETE requests, as it should be. However some APIs may expect DELETE
 requests to have bodies, in that case define your own variation of
 DELETE method and allow it to have a body.
Constructors
| DELETE | 
Instances
| HttpMethod DELETE Source # | |
Defined in Network.HTTP.Req Associated Types type AllowsBody DELETE :: CanHaveBody Source # Methods httpMethodName :: Proxy DELETE -> ByteString Source #  | |
| type AllowsBody DELETE Source # | |
Defined in Network.HTTP.Req  | |
TRACE method.
Constructors
| TRACE | 
Instances
| HttpMethod TRACE Source # | |
Defined in Network.HTTP.Req Associated Types type AllowsBody TRACE :: CanHaveBody Source # Methods httpMethodName :: Proxy TRACE -> ByteString Source #  | |
| type AllowsBody TRACE Source # | |
Defined in Network.HTTP.Req  | |
CONNECT method.
Constructors
| CONNECT | 
Instances
| HttpMethod CONNECT Source # | |
Defined in Network.HTTP.Req Associated Types type AllowsBody CONNECT :: CanHaveBody Source # Methods httpMethodName :: Proxy CONNECT -> ByteString Source #  | |
| type AllowsBody CONNECT Source # | |
Defined in Network.HTTP.Req  | |
OPTIONS method.
Constructors
| OPTIONS | 
Instances
| HttpMethod OPTIONS Source # | |
Defined in Network.HTTP.Req Associated Types type AllowsBody OPTIONS :: CanHaveBody Source # Methods httpMethodName :: Proxy OPTIONS -> ByteString Source #  | |
| type AllowsBody OPTIONS Source # | |
Defined in Network.HTTP.Req  | |
PATCH method.
Constructors
| PATCH | 
Instances
| HttpMethod PATCH Source # | |
Defined in Network.HTTP.Req Associated Types type AllowsBody PATCH :: CanHaveBody Source # Methods httpMethodName :: Proxy PATCH -> ByteString Source #  | |
| type AllowsBody PATCH Source # | |
Defined in Network.HTTP.Req  | |
class HttpMethod a where Source #
A type class for types that can be used as an HTTP method. To define a
 non-standard method, follow this example that defines COPY:
data COPY = COPY instance HttpMethod COPY where type AllowsBody COPY = 'CanHaveBody httpMethodName Proxy = "COPY"
Associated Types
type AllowsBody a :: CanHaveBody Source #
Type function AllowsBody returns a type of kind CanHaveBody which
 tells the rest of the library whether the method can have body or not.
 We use the special type CanHaveBody lifted to the kind level instead
 of Bool to get more user-friendly compiler messages.
Instances
URL
We use Urls which are correct by construction, see Url. To build a
 Url from a URI, use useHttpURI, useHttpsURI, or generic useURI.
data Url (scheme :: Scheme) Source #
Request's Url. Start constructing your Url with http or https
 specifying the scheme and host at the same time. Then use the (
 and /~)( operators to grow the path one piece at a time. Every single
 piece of path will be url(percent)-encoded, so using /:)( and
 /~)( is the only way to have forward slashes between path segments.
 This approach makes working with dynamic path segments easy and safe. See
 examples below how to represent various /:)Urls (make sure the
 OverloadedStrings language extension is enabled).
Examples
http "httpbin.org" -- http://httpbin.org
https "httpbin.org" -- https://httpbin.org
https "httpbin.org" /: "encoding" /: "utf8" -- https://httpbin.org/encoding/utf8
https "httpbin.org" /: "foo" /: "bar/baz" -- https://httpbin.org/foo/bar%2Fbaz
https "httpbin.org" /: "bytes" /~ (10 :: Int) -- https://httpbin.org/bytes/10
https "юникод.рф" -- https://%D1%8E%D0%BD%D0%B8%D0%BA%D0%BE%D0%B4.%D1%80%D1%84
Instances
| Eq (Url scheme) Source # | |
| Typeable scheme => Data (Url scheme) Source # | |
Defined in Network.HTTP.Req Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Url scheme -> c (Url scheme) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Url scheme) # toConstr :: Url scheme -> Constr # dataTypeOf :: Url scheme -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Url scheme)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Url scheme)) # gmapT :: (forall b. Data b => b -> b) -> Url scheme -> Url scheme # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Url scheme -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Url scheme -> r # gmapQ :: (forall d. Data d => d -> u) -> Url scheme -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Url scheme -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Url scheme -> m (Url scheme) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Url scheme -> m (Url scheme) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Url scheme -> m (Url scheme) #  | |
| Ord (Url scheme) Source # | |
| Show (Url scheme) Source # | |
| Generic (Url scheme) Source # | |
| type Rep (Url scheme) Source # | |
Defined in Network.HTTP.Req type Rep (Url scheme) = D1 (MetaData "Url" "Network.HTTP.Req" "req-3.1.0-LJcsrrYlFDw9hNMYQjCCuF" False) (C1 (MetaCons "Url" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scheme) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty Text))))  | |
http :: Text -> Url Http Source #
Given host name, produce a Url which has “http” as its scheme and
 empty path. This also sets port to 80.
https :: Text -> Url Https Source #
Given host name, produce a Url which has “https” as its scheme and
 empty path. This also sets port to 443.
(/~) :: ToHttpApiData a => Url scheme -> a -> Url scheme infixl 5 Source #
Grow given Url appending a single path segment to it. Note that the
 path segment can be of any type that is an instance of ToHttpApiData.
useHttpURI :: URI -> Maybe (Url Http, Option scheme) Source #
The useHttpURI function provides an alternative method to get Url
 (possibly with some Options) from a URI. This is useful when you are
 given a URL to query dynamically and don't know it beforehand.
This function expects the scheme to be “http” and host to be present.
Since: 3.0.0
useHttpsURI :: URI -> Maybe (Url Https, Option scheme) Source #
Just like useHttpURI, but expects the “https” scheme.
Since: 3.0.0
useURI :: URI -> Maybe (Either (Url Http, Option scheme0) (Url Https, Option scheme1)) Source #
A combination of useHttpURI and useHttpsURI for cases when scheme
 is not known in advance.
Since: 3.0.0
Body
A number of options for request bodies are available. The Content-Type
 header is set for you automatically according to the body option you use
 (it's always specified in the documentation for a given body option). To
 add your own way to represent request body, define an instance of
 HttpBody.
This data type represents empty body of an HTTP request. This is the
 data type to use with HttpMethods that cannot have a body, as it's the
 only type for which ProvidesBody returns NoBody.
Using of this body option does not set the Content-Type header.
Constructors
| NoReqBody | 
Instances
| HttpBody NoReqBody Source # | |
Defined in Network.HTTP.Req Methods getRequestBody :: NoReqBody -> RequestBody Source # getRequestContentType :: NoReqBody -> Maybe ByteString Source #  | |
newtype ReqBodyJson a Source #
This body option allows to use a JSON object as request body—probably
 the most popular format right now. Just wrap a data type that is an
 instance of ToJSON type class and you are done: it will be converted to
 JSON and inserted as request body.
This body option sets the Content-Type header to "application/json;
 charset=utf-8" value.
Constructors
| ReqBodyJson a | 
Instances
| ToJSON a => HttpBody (ReqBodyJson a) Source # | |
Defined in Network.HTTP.Req Methods getRequestBody :: ReqBodyJson a -> RequestBody Source # getRequestContentType :: ReqBodyJson a -> Maybe ByteString Source #  | |
newtype ReqBodyFile Source #
This body option streams request body from a file. It is expected that the file size does not change during the streaming.
Using of this body option does not set the Content-Type header.
Constructors
| ReqBodyFile FilePath | 
Instances
| HttpBody ReqBodyFile Source # | |
Defined in Network.HTTP.Req Methods getRequestBody :: ReqBodyFile -> RequestBody Source # getRequestContentType :: ReqBodyFile -> Maybe ByteString Source #  | |
HTTP request body represented by a strict ByteString.
Using of this body option does not set the Content-Type header.
Constructors
| ReqBodyBs ByteString | 
Instances
| HttpBody ReqBodyBs Source # | |
Defined in Network.HTTP.Req Methods getRequestBody :: ReqBodyBs -> RequestBody Source # getRequestContentType :: ReqBodyBs -> Maybe ByteString Source #  | |
newtype ReqBodyLbs Source #
HTTP request body represented by a lazy ByteString.
Using of this body option does not set the Content-Type header.
Constructors
| ReqBodyLbs ByteString | 
Instances
| HttpBody ReqBodyLbs Source # | |
Defined in Network.HTTP.Req Methods getRequestBody :: ReqBodyLbs -> RequestBody Source # getRequestContentType :: ReqBodyLbs -> Maybe ByteString Source #  | |
newtype ReqBodyUrlEnc Source #
Form URL-encoded body. This can hold a collection of parameters which
 are encoded similarly to query parameters at the end of query string,
 with the only difference that they are stored in request body. The
 similarity is reflected in the API as well, as you can use the same
 combinators you would use to add query parameters: ( and
 =:)queryFlag.
This body option sets the Content-Type header to
 "application/x-www-form-urlencoded" value.
Constructors
| ReqBodyUrlEnc FormUrlEncodedParam | 
Instances
| HttpBody ReqBodyUrlEnc Source # | |
Defined in Network.HTTP.Req Methods getRequestBody :: ReqBodyUrlEnc -> RequestBody Source # getRequestContentType :: ReqBodyUrlEnc -> Maybe ByteString Source #  | |
data FormUrlEncodedParam Source #
An opaque monoidal value that allows to collect URL-encoded parameters
 to be wrapped in ReqBodyUrlEnc.
Instances
| Semigroup FormUrlEncodedParam Source # | |
Defined in Network.HTTP.Req Methods (<>) :: FormUrlEncodedParam -> FormUrlEncodedParam -> FormUrlEncodedParam # sconcat :: NonEmpty FormUrlEncodedParam -> FormUrlEncodedParam # stimes :: Integral b => b -> FormUrlEncodedParam -> FormUrlEncodedParam #  | |
| Monoid FormUrlEncodedParam Source # | |
Defined in Network.HTTP.Req Methods mempty :: FormUrlEncodedParam # mappend :: FormUrlEncodedParam -> FormUrlEncodedParam -> FormUrlEncodedParam #  | |
| QueryParam FormUrlEncodedParam Source # | |
Defined in Network.HTTP.Req Methods queryParam :: ToHttpApiData a => Text -> Maybe a -> FormUrlEncodedParam Source #  | |
data ReqBodyMultipart Source #
Multipart form data. Please consult the
 Network.HTTP.Client.MultipartFormData module for how to construct
 parts, then use reqBodyMultipart to create actual request body from the
 parts. reqBodyMultipart is the only way to get a value of the type
 ReqBodyMultipart, as its constructor is not exported on purpose.
Examples
import Control.Monad.IO.Class
import Data.Default.Class
import Network.HTTP.Req
import qualified Network.HTTP.Client.MultipartFormData as LM
main :: IO ()
main = runReq def $ do
  body <-
    reqBodyMultipart
      [ LM.partBS "title" "My Image"
      , LM.partFileSource "file1" "/tmp/image.jpg"
      ]
  response <-
    req POST (http "example.com" /: "post")
      body
      bsResponse
      mempty
  liftIO $ print (responseBody response)Since: 0.2.0
Instances
| HttpBody ReqBodyMultipart Source # | |
Defined in Network.HTTP.Req Methods getRequestBody :: ReqBodyMultipart -> RequestBody Source # getRequestContentType :: ReqBodyMultipart -> Maybe ByteString Source #  | |
reqBodyMultipart :: MonadIO m => [Part] -> m ReqBodyMultipart Source #
Create ReqBodyMultipart request body from a collection of Parts.
Since: 0.2.0
class HttpBody body where Source #
A type class for things that can be interpreted as an HTTP
 RequestBody.
Minimal complete definition
Methods
getRequestBody :: body -> RequestBody Source #
How to get actual RequestBody.
getRequestContentType :: body -> Maybe ByteString Source #
This method allows us to optionally specify the value of
 Content-Type header that should be used with particular body option.
 By default it returns Nothing and so Content-Type is not set.
Instances
type family ProvidesBody body :: CanHaveBody where ... Source #
The type function recognizes NoReqBody as having NoBody, while any
 other body option CanHaveBody. This forces the user to use NoReqBody
 with GET method and other methods that should not have body.
Equations
| ProvidesBody NoReqBody = NoBody | |
| ProvidesBody body = CanHaveBody | 
type family HttpBodyAllowed (allowsBody :: CanHaveBody) (providesBody :: CanHaveBody) :: Constraint where ... Source #
This type function allows any HTTP body if method says it
 CanHaveBody. When the method says it should have NoBody, the only
 body option to use is NoReqBody.
Note: users of GHC 8.0.1 and later will see a slightly more friendly error message when method does not allow a body and body is provided.
Equations
| HttpBodyAllowed NoBody NoBody = () | |
| HttpBodyAllowed CanHaveBody body = () | |
| HttpBodyAllowed NoBody CanHaveBody = TypeError (Text "This HTTP method does not allow attaching a request body.") | 
Optional parameters
Optional parameters of request include things like query parameters,
 headers, port number, etc. All optional parameters have the type
 Option, which is a Monoid. This means that you can use mempty as
 the last argument of req to specify no optional parameters, or combine
 Options using mappend or ( to have several of them at once.<>)
data Option (scheme :: Scheme) Source #
The opaque Option type is a Monoid you can use to pack collection
 of optional parameters like query parameters and headers. See sections
 below to learn which Option primitives are available.
Instances
| Semigroup (Option scheme) Source # | |
| Monoid (Option scheme) Source # | |
| QueryParam (Option scheme) Source # | |
Defined in Network.HTTP.Req Methods queryParam :: ToHttpApiData a => Text -> Maybe a -> Option scheme Source #  | |
Query parameters
This section describes a polymorphic interface that can be used to
 construct query parameters (of the type Option) and form URL-encoded
 bodies (of the type FormUrlEncodedParam).
(=:) :: (QueryParam param, ToHttpApiData a) => Text -> a -> param infix 7 Source #
This operator builds a query parameter that will be included in URL of
 your request after the question sign ?. This is the same syntax you use
 with form URL encoded request bodies.
This operator is defined in terms of queryParam:
name =: value = queryParam name (pure value)
queryFlag :: QueryParam param => Text -> param Source #
Construct a flag, that is, valueless query parameter. For example, in
 the following URL "a" is a flag, while "b" is a query parameter
 with a value:
https://httpbin.org/foo/bar?a&b=10
This operator is defined in terms of queryParam:
queryFlag name = queryParam name (Nothing :: Maybe ())
class QueryParam param where Source #
A type class for query-parameter-like things. The reason to have an
 overloaded queryParam is to be able to use it as an Option and as a
 FormUrlEncodedParam when constructing form URL encoded request bodies.
 Having the same syntax for these cases seems natural and user-friendly.
Methods
queryParam :: ToHttpApiData a => Text -> Maybe a -> param Source #
Instances
| QueryParam FormUrlEncodedParam Source # | |
Defined in Network.HTTP.Req Methods queryParam :: ToHttpApiData a => Text -> Maybe a -> FormUrlEncodedParam Source #  | |
| QueryParam (Option scheme) Source # | |
Defined in Network.HTTP.Req Methods queryParam :: ToHttpApiData a => Text -> Maybe a -> Option scheme Source #  | |
Headers
Arguments
| :: ByteString | Header name  | 
| -> ByteString | Header value  | 
| -> Option scheme | 
attachHeader :: ByteString -> ByteString -> Request -> Request Source #
Attach a header with given name and content to a Request.
Since: 1.1.0
Cookies
Support for cookies is quite minimalistic at the moment. It's possible to
 specify which cookies to send using cookieJar and inspect Response
 to extract CookieJar from it (see responseCookieJar).
Authentication
This section provides the common authentication helpers in the form of
 Options. You should always prefer the provided authentication Options
 to manual construction of headers because it ensures that you only use
 one authentication method at a time (they overwrite each other) and
 provides additional type safety that prevents leaking of credentials in
 the cases when authentication relies on HTTPS for encrypting sensitive
 data.
Arguments
| :: ByteString | Username  | 
| -> ByteString | Password  | 
| -> Option Https | Auth   | 
The Option adds basic authentication.
See also: https://en.wikipedia.org/wiki/Basic_access_authentication.
Arguments
| :: ByteString | Username  | 
| -> ByteString | Password  | 
| -> Option scheme | Auth   | 
Arguments
| :: ByteString | Username  | 
| -> ByteString | Password  | 
| -> Option scheme | Auth   | 
The Option set basic proxy authentication header.
Since: 1.1.0
Arguments
| :: ByteString | Consumer token  | 
| -> ByteString | Consumer secret  | 
| -> ByteString | OAuth token  | 
| -> ByteString | OAuth token secret  | 
| -> Option scheme | Auth   | 
The Option adds OAuth1 authentication.
Since: 0.2.0
Arguments
| :: ByteString | Token  | 
| -> Option Https | Auth   | 
The Option adds an OAuth2 bearer token. This is treated by many
 services as the equivalent of a username and password.
The Option is defined as:
oAuth2Bearer token = header "Authorization" ("Bearer " <> token)See also: https://en.wikipedia.org/wiki/OAuth.
Arguments
| :: ByteString | Token  | 
| -> Option Https | Auth   | 
The Option adds 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.
The Option is defined as:
oAuth2Token token = header "Authorization" ("token" <> token)See also: https://developer.github.com/v3/oauth#3-use-the-access-token-to-access-the-api.
Other
Arguments
| :: (ByteString -> Bool) | Predicate that is given MIME type, it
 returns   | 
| -> Option scheme | 
This Option controls whether gzipped data should be decompressed on
 the fly. By default everything except for "application/x-tar" is
 decompressed, i.e. we have:
decompress (/= "application/x-tar")
You can also choose to decompress everything like this:
decompress (const True)
Specify the number of microseconds to wait for response. The default
 value is 30 seconds (defined in ManagerSettings of connection
 Manager).
HTTP version to send to the server, the default is HTTP 1.1.
Response
Response interpretations
data IgnoreResponse Source #
Make a request and ignore the body of the response.
Instances
| HttpResponse IgnoreResponse Source # | |
Defined in Network.HTTP.Req Associated Types type HttpResponseBody IgnoreResponse :: Type Source #  | |
| type HttpResponseBody IgnoreResponse Source # | |
Defined in Network.HTTP.Req  | |
ignoreResponse :: Proxy IgnoreResponse Source #
Use this as the fourth argument of req to specify that you want it to
 ignore the response body.
data JsonResponse a Source #
Make a request and interpret the body of the response as JSON. The
 handleHttpException method of MonadHttp instance corresponding to
 monad in which you use req will determine what to do in the case when
 parsing fails (the JsonHttpException constructor will be used).
Instances
| FromJSON a => HttpResponse (JsonResponse a) Source # | |
Defined in Network.HTTP.Req Associated Types type HttpResponseBody (JsonResponse a) :: Type Source # Methods toVanillaResponse :: JsonResponse a -> Response (HttpResponseBody (JsonResponse a)) Source # getHttpResponse :: Response BodyReader -> IO (JsonResponse a) Source # acceptHeader :: Proxy (JsonResponse a) -> Maybe ByteString Source #  | |
| type HttpResponseBody (JsonResponse a) Source # | |
Defined in Network.HTTP.Req  | |
jsonResponse :: Proxy (JsonResponse a) Source #
Use this as the fourth argument of req to specify that you want it to
 return the JsonResponse interpretation.
data BsResponse Source #
Make a request and interpret the body of the response as a strict
 ByteString.
Instances
| HttpResponse BsResponse Source # | |
Defined in Network.HTTP.Req Associated Types type HttpResponseBody BsResponse :: Type Source # Methods toVanillaResponse :: BsResponse -> Response (HttpResponseBody BsResponse) Source # getHttpResponse :: Response BodyReader -> IO BsResponse Source # acceptHeader :: Proxy BsResponse -> Maybe ByteString Source #  | |
| type HttpResponseBody BsResponse Source # | |
Defined in Network.HTTP.Req  | |
bsResponse :: Proxy BsResponse Source #
Use this as the fourth argument of req to specify that you want to
 interpret the response body as a strict ByteString.
data LbsResponse Source #
Make a request and interpret the body of the response as a lazy
 ByteString.
Instances
| HttpResponse LbsResponse Source # | |
Defined in Network.HTTP.Req Associated Types type HttpResponseBody LbsResponse :: Type Source # Methods toVanillaResponse :: LbsResponse -> Response (HttpResponseBody LbsResponse) Source # getHttpResponse :: Response BodyReader -> IO LbsResponse Source # acceptHeader :: Proxy LbsResponse -> Maybe ByteString Source #  | |
| type HttpResponseBody LbsResponse Source # | |
Defined in Network.HTTP.Req  | |
lbsResponse :: Proxy LbsResponse Source #
Use this as the fourth argument of req to specify that you want to
 interpret the response body as a lazy ByteString.
Inspecting a response
responseBody :: HttpResponse response => response -> HttpResponseBody response Source #
Get the response body.
responseStatusCode :: HttpResponse response => response -> Int Source #
Get the response status code.
responseStatusMessage :: HttpResponse response => response -> ByteString Source #
Get the response status message.
Arguments
| :: HttpResponse response | |
| => response | Response interpretation  | 
| -> ByteString | Header to lookup  | 
| -> Maybe ByteString | Header value if found  | 
Lookup a particular header from a response.
responseCookieJar :: HttpResponse response => response -> CookieJar Source #
Get the response CookieJar.
Defining your own interpretation
To create a new response interpretation you just need to make your data
 type an instance of the HttpResponse type class.
class HttpResponse response where Source #
A type class for response interpretations. It allows to describe how to
 consume response from a  and produce the
 final result that is to be returned to the user.Response BodyReader
Minimal complete definition
Associated Types
type HttpResponseBody response :: Type Source #
The associated type is the type of body that can be extracted from an
 instance of HttpResponse.
Methods
toVanillaResponse :: response -> Response (HttpResponseBody response) Source #
The method describes how to get the underlying Response record.
Arguments
| :: Response BodyReader | Response with body reader inside  | 
| -> IO response | The final result  | 
This method describes how to consume response body and, more
 generally, obtain response value from .Response BodyReader
Note: BodyReader is nothing but . You should
 call this action repeatedly until it yields the empty IO ByteStringByteString. In
 that case streaming of response is finished (which apparently leads to
 closing of the connection, so don't call the reader after it has
 returned the empty ByteString once) and you can concatenate the
 chunks to obtain the final result. (Of course you could as well stream
 the contents to a file or do whatever you want.)
Note: signature of this function was changed in the version 1.0.0.
acceptHeader :: Proxy response -> Maybe ByteString Source #
The value of "Accept" header. This is useful, for example, if a
 website supports both XML and JSON responses, and decides what to
 reply with based on what Accept headers you have sent.
Note: manually specified Options that set the "Accept" header
 will take precedence.
Since: 2.1.0
Instances
Other
data HttpException Source #
Exceptions that this library throws.
Constructors
| VanillaHttpException HttpException | A wrapper with an   | 
| JsonHttpException String | A wrapper with Aeson-produced   | 
Instances
data CanHaveBody Source #
A simple type isomorphic to Bool that we only have for better error
 messages. We use it as a kind and its data constructors as type-level
 tags.
See also: HttpMethod and HttpBody.
Constructors
| CanHaveBody | Indeed can have a body  | 
| NoBody | Should not have a body  | 
A type-level tag that specifies URL scheme used (and thus if HTTPS is
 enabled). This is used to force TLS requirement for some authentication
 Options.
Instances
| Eq Scheme Source # | |
| Data Scheme Source # | |
Defined in Network.HTTP.Req Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Scheme -> c Scheme # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Scheme # toConstr :: Scheme -> Constr # dataTypeOf :: Scheme -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Scheme) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Scheme) # gmapT :: (forall b. Data b => b -> b) -> Scheme -> Scheme # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Scheme -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Scheme -> r # gmapQ :: (forall d. Data d => d -> u) -> Scheme -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Scheme -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Scheme -> m Scheme # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Scheme -> m Scheme # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Scheme -> m Scheme #  | |
| Ord Scheme Source # | |
| Show Scheme Source # | |
| Generic Scheme Source # | |
| type Rep Scheme Source # | |