| Copyright | (C) 2021 Morrow |
|---|---|
| License | BSD3-3-Clause |
| Maintainer | Morrow <themorrowm@gmail.com> |
| Safe Haskell | None |
| Language | Haskell2010 |
Polysemy.Req
Description
Network.HTTP.Req adapted for use with polysemy.
Synopsis
- data Req m response where
- Req :: (HttpMethod method, HttpBody body, HttpResponse response, HttpBodyAllowed (AllowsBody method) (ProvidesBody body)) => method -> Url scheme -> body -> Proxy response -> Option scheme -> Req m response
- req :: forall r method body response scheme. (MemberWithError Req r, HttpMethod method, HttpBody body, HttpResponse response, HttpBodyAllowed (AllowsBody method) (ProvidesBody body)) => method -> Url scheme -> body -> Proxy response -> Option scheme -> Sem r response
- interpretReq :: Member (Embed IO) r => InterpreterFor Req r
- interpretReqWith :: Member (Embed IO) r => HttpConfig -> InterpreterFor Req r
- responseCookieJar :: HttpResponse response => response -> CookieJar
- responseHeader :: HttpResponse response => response -> ByteString -> Maybe ByteString
- responseStatusMessage :: HttpResponse response => response -> ByteString
- responseStatusCode :: HttpResponse response => response -> Int
- responseBody :: HttpResponse response => response -> HttpResponseBody response
- lbsResponse :: Proxy LbsResponse
- bsResponse :: Proxy BsResponse
- jsonResponse :: Proxy (JsonResponse a)
- ignoreResponse :: Proxy IgnoreResponse
- httpVersion :: forall (scheme :: Scheme). Int -> Int -> Option scheme
- responseTimeout :: forall (scheme :: Scheme). Int -> Option scheme
- decompress :: forall (scheme :: Scheme). (ByteString -> Bool) -> Option scheme
- port :: forall (scheme :: Scheme). Int -> Option scheme
- customAuth :: forall (scheme :: Scheme). (Request -> IO Request) -> Option scheme
- oAuth2Token :: ByteString -> Option 'Https
- oAuth2Bearer :: ByteString -> Option 'Https
- oAuth1 :: forall (scheme :: Scheme). ByteString -> ByteString -> ByteString -> ByteString -> Option scheme
- basicProxyAuth :: forall (scheme :: Scheme). ByteString -> ByteString -> Option scheme
- basicAuthUnsafe :: forall (scheme :: Scheme). ByteString -> ByteString -> Option scheme
- basicAuth :: ByteString -> ByteString -> Option 'Https
- cookieJar :: forall (scheme :: Scheme). CookieJar -> Option scheme
- attachHeader :: ByteString -> ByteString -> Request -> Request
- header :: forall (scheme :: Scheme). ByteString -> ByteString -> Option scheme
- queryFlag :: QueryParam param => Text -> param
- (=:) :: (QueryParam param, ToHttpApiData a) => Text -> a -> param
- reqBodyMultipart :: MonadIO m => [Part] -> m ReqBodyMultipart
- urlQ :: QuasiQuoter
- useURI :: forall (scheme0 :: Scheme) (scheme1 :: Scheme). URI -> Maybe (Either (Url 'Http, Option scheme0) (Url 'Https, Option scheme1))
- useHttpsURI :: forall (scheme :: Scheme). URI -> Maybe (Url 'Https, Option scheme)
- useHttpURI :: forall (scheme :: Scheme). URI -> Maybe (Url 'Http, Option scheme)
- renderUrl :: forall (scheme :: Scheme). Url scheme -> Text
- (/:) :: forall (scheme :: Scheme). Url scheme -> Text -> Url scheme
- (/~) :: forall a (scheme :: Scheme). ToHttpApiData a => Url scheme -> a -> Url scheme
- https :: Text -> Url 'Https
- http :: Text -> Url 'Http
- defaultHttpConfig :: HttpConfig
- withReqManager :: MonadIO m => (Manager -> m a) -> m a
- handleHttpException :: MonadHttp m => HttpException -> m a
- getHttpConfig :: MonadHttp m => 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
- httpConfigRetryJudgeException :: RetryStatus -> SomeException -> Bool
- httpConfigBodyPreviewLength :: forall a. Num a => 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
- type family AllowsBody a :: CanHaveBody
- class HttpMethod a where
- type AllowsBody a :: CanHaveBody
- httpMethodName :: Proxy a -> ByteString
- data Url (scheme :: Scheme)
- 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
- class HttpBody body where
- getRequestBody :: body -> RequestBody
- getRequestContentType :: body -> Maybe ByteString
- type family ProvidesBody body :: CanHaveBody where ...
- type family HttpBodyAllowed (allowsBody :: CanHaveBody) (providesBody :: CanHaveBody) where ...
- data Option (scheme :: Scheme)
- class QueryParam param where
- queryParam :: ToHttpApiData a => Text -> Maybe a -> param
- data IgnoreResponse
- data JsonResponse a
- data BsResponse
- data LbsResponse
- type family HttpResponseBody response
- class HttpResponse response where
- type HttpResponseBody response
- toVanillaResponse :: response -> Response (HttpResponseBody response)
- getHttpResponse :: Response BodyReader -> IO response
- acceptHeader :: Proxy response -> Maybe ByteString
- data HttpException
- data CanHaveBody
- data Scheme
Effect
data Req m response where Source #
An effect for making http requests.
@since 0.1.0
Constructors
| Req | |
Fields
| |
Actions
req :: forall r method body response scheme. (MemberWithError Req r, HttpMethod method, HttpBody body, HttpResponse response, HttpBodyAllowed (AllowsBody method) (ProvidesBody body)) => method -> Url scheme -> body -> Proxy response -> Option scheme -> Sem r response Source #
See req.
@since 0.1.0
Interpretations
interpretReq :: Member (Embed IO) r => InterpreterFor Req r Source #
Run a Req effect with the defaultHttpConfig.
@since 0.1.0
interpretReqWith :: Member (Embed IO) r => HttpConfig -> InterpreterFor Req r Source #
Run a Req effect with a custom HttpConfig.
@since 0.1.0
Re-exports
responseCookieJar :: HttpResponse response => response -> CookieJar #
Get the response CookieJar.
Arguments
| :: HttpResponse response | |
| => response | Response interpretation |
| -> ByteString | Header to lookup |
| -> Maybe ByteString | Header value if found |
Lookup a particular header from a response.
responseStatusMessage :: HttpResponse response => response -> ByteString #
Get the response status message.
responseStatusCode :: HttpResponse response => response -> Int #
Get the response status code.
responseBody :: HttpResponse response => response -> HttpResponseBody response #
Get the response body.
lbsResponse :: Proxy LbsResponse #
Use this as the fourth argument of req to specify that you want to
interpret the response body as a lazy ByteString.
bsResponse :: Proxy BsResponse #
Use this as the fourth argument of req to specify that you want to
interpret the response body as a strict ByteString.
jsonResponse :: Proxy (JsonResponse a) #
Use this as the fourth argument of req to specify that you want it to
return the JsonResponse interpretation.
ignoreResponse :: Proxy IgnoreResponse #
Use this as the fourth argument of req to specify that you want it to
ignore the response body.
Arguments
| :: forall (scheme :: Scheme). Int | Major version number |
| -> Int | Minor version number |
| -> Option scheme |
HTTP version to send to the server, the default is HTTP 1.1.
Specify the number of microseconds to wait for response. The default
value is 30 seconds (defined in ManagerSettings of connection
Manager).
Arguments
| :: forall (scheme :: Scheme). (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)
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.
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
| :: forall (scheme :: Scheme). ByteString | Consumer token |
| -> ByteString | Consumer secret |
| -> ByteString | OAuth token |
| -> ByteString | OAuth token secret |
| -> Option scheme | Auth |
The Option adds OAuth1 authentication.
Since: req-0.2.0
Arguments
| :: forall (scheme :: Scheme). ByteString | Username |
| -> ByteString | Password |
| -> Option scheme | Auth |
The Option set basic proxy authentication header.
Since: req-1.1.0
Arguments
| :: forall (scheme :: Scheme). ByteString | Username |
| -> ByteString | Password |
| -> Option scheme | Auth |
Arguments
| :: ByteString | Username |
| -> ByteString | Password |
| -> Option 'Https | Auth |
The Option adds basic authentication.
See also: https://en.wikipedia.org/wiki/Basic_access_authentication.
attachHeader :: ByteString -> ByteString -> Request -> Request #
Attach a header with given name and content to a Request.
Since: req-1.1.0
Arguments
| :: forall (scheme :: Scheme). ByteString | Header name |
| -> ByteString | Header value |
| -> Option scheme |
queryFlag :: QueryParam param => Text -> param #
Construct a flag, that is, a 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 ())
(=:) :: (QueryParam param, ToHttpApiData a) => Text -> a -> param infix 7 #
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)
reqBodyMultipart :: MonadIO m => [Part] -> m ReqBodyMultipart #
Create ReqBodyMultipart request body from a collection of Parts.
Since: req-0.2.0
urlQ :: QuasiQuoter #
useURI :: forall (scheme0 :: Scheme) (scheme1 :: Scheme). URI -> Maybe (Either (Url 'Http, Option scheme0) (Url 'Https, Option scheme1)) #
A combination of useHttpURI and useHttpsURI for cases when scheme
is not known in advance.
Since: req-3.0.0
useHttpsURI :: forall (scheme :: Scheme). URI -> Maybe (Url 'Https, Option scheme) #
Just like useHttpURI, but expects the “https” scheme.
Since: req-3.0.0
useHttpURI :: forall (scheme :: Scheme). URI -> Maybe (Url 'Http, Option scheme) #
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: req-3.0.0
(/~) :: forall a (scheme :: Scheme). ToHttpApiData a => Url scheme -> a -> Url scheme infixl 5 #
Grow a 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.
Given host name, produce a Url which has “https” as its scheme and
empty path. This also sets port to 443.
Given host name, produce a Url which has “http” as its scheme and
empty path. This also sets port to 80.
defaultHttpConfig :: HttpConfig #
The default value of HttpConfig.
Since: req-2.0.0
withReqManager :: MonadIO m => (Manager -> m a) -> m a #
handleHttpException :: MonadHttp m => HttpException -> m a #
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 :: MonadHttp m => m HttpConfig #
Return the 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.
data HttpConfig #
HttpConfig contains settings to be used when making HTTP requests.
Constructors
| HttpConfig | |
Fields
| |
Instances
| RequestComponent HttpConfig | |
Defined in Network.HTTP.Req Methods getRequestMod :: HttpConfig -> Endo Request | |
GET method.
Constructors
| GET |
Instances
| HttpMethod GET | |
Defined in Network.HTTP.Req Associated Types type AllowsBody GET :: CanHaveBody # Methods httpMethodName :: Proxy GET -> ByteString # | |
| type AllowsBody GET | |
Defined in Network.HTTP.Req | |
POST method.
Constructors
| POST |
Instances
| HttpMethod POST | |
Defined in Network.HTTP.Req Associated Types type AllowsBody POST :: CanHaveBody # Methods httpMethodName :: Proxy POST -> ByteString # | |
| type AllowsBody POST | |
Defined in Network.HTTP.Req | |
HEAD method.
Constructors
| HEAD |
Instances
| HttpMethod HEAD | |
Defined in Network.HTTP.Req Associated Types type AllowsBody HEAD :: CanHaveBody # Methods httpMethodName :: Proxy HEAD -> ByteString # | |
| type AllowsBody HEAD | |
Defined in Network.HTTP.Req | |
PUT method.
Constructors
| PUT |
Instances
| HttpMethod PUT | |
Defined in Network.HTTP.Req Associated Types type AllowsBody PUT :: CanHaveBody # Methods httpMethodName :: Proxy PUT -> ByteString # | |
| type AllowsBody PUT | |
Defined in Network.HTTP.Req | |
DELETE method. RFC 7231 allows a payload in DELETE but without
semantics.
Note: before version 3.4.0 this method did not allow request bodies.
Constructors
| DELETE |
Instances
| HttpMethod DELETE | |
Defined in Network.HTTP.Req Associated Types type AllowsBody DELETE :: CanHaveBody # Methods httpMethodName :: Proxy DELETE -> ByteString # | |
| type AllowsBody DELETE | |
Defined in Network.HTTP.Req | |
TRACE method.
Constructors
| TRACE |
Instances
| HttpMethod TRACE | |
Defined in Network.HTTP.Req Associated Types type AllowsBody TRACE :: CanHaveBody # Methods httpMethodName :: Proxy TRACE -> ByteString # | |
| type AllowsBody TRACE | |
Defined in Network.HTTP.Req | |
CONNECT method.
Constructors
| CONNECT |
Instances
| HttpMethod CONNECT | |
Defined in Network.HTTP.Req Associated Types type AllowsBody CONNECT :: CanHaveBody # Methods httpMethodName :: Proxy CONNECT -> ByteString # | |
| type AllowsBody CONNECT | |
Defined in Network.HTTP.Req | |
OPTIONS method.
Constructors
| OPTIONS |
Instances
| HttpMethod OPTIONS | |
Defined in Network.HTTP.Req Associated Types type AllowsBody OPTIONS :: CanHaveBody # Methods httpMethodName :: Proxy OPTIONS -> ByteString # | |
| type AllowsBody OPTIONS | |
Defined in Network.HTTP.Req | |
PATCH method.
Constructors
| PATCH |
Instances
| HttpMethod PATCH | |
Defined in Network.HTTP.Req Associated Types type AllowsBody PATCH :: CanHaveBody # Methods httpMethodName :: Proxy PATCH -> ByteString # | |
| type AllowsBody PATCH | |
Defined in Network.HTTP.Req | |
type family AllowsBody a :: CanHaveBody #
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
| type AllowsBody GET | |
Defined in Network.HTTP.Req | |
| type AllowsBody POST | |
Defined in Network.HTTP.Req | |
| type AllowsBody HEAD | |
Defined in Network.HTTP.Req | |
| type AllowsBody PUT | |
Defined in Network.HTTP.Req | |
| type AllowsBody DELETE | |
Defined in Network.HTTP.Req | |
| type AllowsBody TRACE | |
Defined in Network.HTTP.Req | |
| type AllowsBody CONNECT | |
Defined in Network.HTTP.Req | |
| type AllowsBody OPTIONS | |
Defined in Network.HTTP.Req | |
| type AllowsBody PATCH | |
Defined in Network.HTTP.Req | |
class HttpMethod a where #
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 #
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
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
| Typeable scheme => Lift (Url scheme :: Type) | |
| Eq (Url scheme) | |
| Typeable scheme => Data (Url scheme) | |
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 :: forall r r'. (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) | |
| Show (Url scheme) | |
| Generic (Url scheme) | |
| RequestComponent (Url scheme) | |
Defined in Network.HTTP.Req Methods getRequestMod :: Url scheme -> Endo Request | |
| type Rep (Url scheme) | |
Defined in Network.HTTP.Req type Rep (Url scheme) = D1 ('MetaData "Url" "Network.HTTP.Req" "req-3.9.1-IwV7o8rn04hHErfMVP9czI" '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)))) | |
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 | |
Defined in Network.HTTP.Req Methods getRequestBody :: NoReqBody -> RequestBody # | |
newtype ReqBodyJson a #
This body option allows us to use a JSON object as the 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) | |
Defined in Network.HTTP.Req Methods getRequestBody :: ReqBodyJson a -> RequestBody # getRequestContentType :: ReqBodyJson a -> Maybe ByteString # | |
newtype ReqBodyFile #
This body option streams request body from a file. It is expected that the file size does not change during streaming.
Using of this body option does not set the Content-Type header.
Constructors
| ReqBodyFile FilePath |
Instances
| HttpBody ReqBodyFile | |
Defined in Network.HTTP.Req Methods | |
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 | |
Defined in Network.HTTP.Req Methods getRequestBody :: ReqBodyBs -> RequestBody # | |
newtype ReqBodyLbs #
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 | |
Defined in Network.HTTP.Req Methods getRequestBody :: ReqBodyLbs -> RequestBody # | |
newtype ReqBodyUrlEnc #
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 | |
Defined in Network.HTTP.Req Methods getRequestBody :: ReqBodyUrlEnc -> RequestBody # getRequestContentType :: ReqBodyUrlEnc -> Maybe ByteString # | |
data FormUrlEncodedParam #
An opaque monoidal value that allows to collect URL-encoded parameters
to be wrapped in ReqBodyUrlEnc.
Instances
| Semigroup FormUrlEncodedParam | |
Defined in Network.HTTP.Req Methods (<>) :: FormUrlEncodedParam -> FormUrlEncodedParam -> FormUrlEncodedParam # sconcat :: NonEmpty FormUrlEncodedParam -> FormUrlEncodedParam # stimes :: Integral b => b -> FormUrlEncodedParam -> FormUrlEncodedParam # | |
| Monoid FormUrlEncodedParam | |
Defined in Network.HTTP.Req Methods mempty :: FormUrlEncodedParam # mappend :: FormUrlEncodedParam -> FormUrlEncodedParam -> FormUrlEncodedParam # | |
| QueryParam FormUrlEncodedParam | |
Defined in Network.HTTP.Req Methods queryParam :: ToHttpApiData a => Text -> Maybe a -> FormUrlEncodedParam # | |
data ReqBodyMultipart #
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: req-0.2.0
Instances
| HttpBody ReqBodyMultipart | |
Defined in Network.HTTP.Req Methods getRequestBody :: ReqBodyMultipart -> RequestBody # getRequestContentType :: ReqBodyMultipart -> Maybe ByteString # | |
A type class for things that can be interpreted as an HTTP
RequestBody.
Minimal complete definition
Methods
getRequestBody :: body -> RequestBody #
How to get actual RequestBody.
getRequestContentType :: body -> Maybe ByteString #
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
| HttpBody NoReqBody | |
Defined in Network.HTTP.Req Methods getRequestBody :: NoReqBody -> RequestBody # | |
| HttpBody ReqBodyFile | |
Defined in Network.HTTP.Req Methods | |
| HttpBody ReqBodyBs | |
Defined in Network.HTTP.Req Methods getRequestBody :: ReqBodyBs -> RequestBody # | |
| HttpBody ReqBodyLbs | |
Defined in Network.HTTP.Req Methods getRequestBody :: ReqBodyLbs -> RequestBody # | |
| HttpBody ReqBodyUrlEnc | |
Defined in Network.HTTP.Req Methods getRequestBody :: ReqBodyUrlEnc -> RequestBody # getRequestContentType :: ReqBodyUrlEnc -> Maybe ByteString # | |
| HttpBody ReqBodyMultipart | |
Defined in Network.HTTP.Req Methods getRequestBody :: ReqBodyMultipart -> RequestBody # getRequestContentType :: ReqBodyMultipart -> Maybe ByteString # | |
| ToJSON a => HttpBody (ReqBodyJson a) | |
Defined in Network.HTTP.Req Methods getRequestBody :: ReqBodyJson a -> RequestBody # getRequestContentType :: ReqBodyJson a -> Maybe ByteString # | |
type family ProvidesBody body :: CanHaveBody where ... #
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) where ... #
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.
Equations
| HttpBodyAllowed 'NoBody 'NoBody = () | |
| HttpBodyAllowed 'CanHaveBody body = () | |
| HttpBodyAllowed 'NoBody 'CanHaveBody = TypeError ('Text "This HTTP method does not allow attaching a request body.") :: Constraint |
data Option (scheme :: Scheme) #
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) | |
| Monoid (Option scheme) | |
| QueryParam (Option scheme) | |
Defined in Network.HTTP.Req Methods queryParam :: ToHttpApiData a => Text -> Maybe a -> Option scheme # | |
| RequestComponent (Option scheme) | |
Defined in Network.HTTP.Req Methods getRequestMod :: Option scheme -> Endo Request | |
class QueryParam param where #
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 #
Instances
| QueryParam FormUrlEncodedParam | |
Defined in Network.HTTP.Req Methods queryParam :: ToHttpApiData a => Text -> Maybe a -> FormUrlEncodedParam # | |
| QueryParam (Option scheme) | |
Defined in Network.HTTP.Req Methods queryParam :: ToHttpApiData a => Text -> Maybe a -> Option scheme # | |
data IgnoreResponse #
Make a request and ignore the body of the response.
Instances
| Show IgnoreResponse | |
Defined in Network.HTTP.Req Methods showsPrec :: Int -> IgnoreResponse -> ShowS # show :: IgnoreResponse -> String # showList :: [IgnoreResponse] -> ShowS # | |
| HttpResponse IgnoreResponse | |
Defined in Network.HTTP.Req Associated Types Methods toVanillaResponse :: IgnoreResponse -> Response (HttpResponseBody IgnoreResponse) # getHttpResponse :: Response BodyReader -> IO IgnoreResponse # | |
| type HttpResponseBody IgnoreResponse | |
Defined in Network.HTTP.Req | |
data JsonResponse a #
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
| Show a => Show (JsonResponse a) | |
Defined in Network.HTTP.Req Methods showsPrec :: Int -> JsonResponse a -> ShowS # show :: JsonResponse a -> String # showList :: [JsonResponse a] -> ShowS # | |
| FromJSON a => HttpResponse (JsonResponse a) | |
Defined in Network.HTTP.Req Associated Types type HttpResponseBody (JsonResponse a) # Methods toVanillaResponse :: JsonResponse a -> Response (HttpResponseBody (JsonResponse a)) # getHttpResponse :: Response BodyReader -> IO (JsonResponse a) # acceptHeader :: Proxy (JsonResponse a) -> Maybe ByteString # | |
| type HttpResponseBody (JsonResponse a) | |
Defined in Network.HTTP.Req | |
data BsResponse #
Make a request and interpret the body of the response as a strict
ByteString.
Instances
| Show BsResponse | |
Defined in Network.HTTP.Req Methods showsPrec :: Int -> BsResponse -> ShowS # show :: BsResponse -> String # showList :: [BsResponse] -> ShowS # | |
| HttpResponse BsResponse | |
Defined in Network.HTTP.Req Associated Types type HttpResponseBody BsResponse # Methods toVanillaResponse :: BsResponse -> Response (HttpResponseBody BsResponse) # getHttpResponse :: Response BodyReader -> IO BsResponse # acceptHeader :: Proxy BsResponse -> Maybe ByteString # | |
| type HttpResponseBody BsResponse | |
Defined in Network.HTTP.Req | |
data LbsResponse #
Make a request and interpret the body of the response as a lazy
ByteString.
Instances
| Show LbsResponse | |
Defined in Network.HTTP.Req Methods showsPrec :: Int -> LbsResponse -> ShowS # show :: LbsResponse -> String # showList :: [LbsResponse] -> ShowS # | |
| HttpResponse LbsResponse | |
Defined in Network.HTTP.Req Associated Types type HttpResponseBody LbsResponse # Methods toVanillaResponse :: LbsResponse -> Response (HttpResponseBody LbsResponse) # getHttpResponse :: Response BodyReader -> IO LbsResponse # acceptHeader :: Proxy LbsResponse -> Maybe ByteString # | |
| type HttpResponseBody LbsResponse | |
Defined in Network.HTTP.Req | |
type family HttpResponseBody response #
The associated type is the type of body that can be extracted from an
instance of HttpResponse.
Instances
| type HttpResponseBody IgnoreResponse | |
Defined in Network.HTTP.Req | |
| type HttpResponseBody BsResponse | |
Defined in Network.HTTP.Req | |
| type HttpResponseBody LbsResponse | |
Defined in Network.HTTP.Req | |
| type HttpResponseBody (JsonResponse a) | |
Defined in Network.HTTP.Req | |
class HttpResponse response where #
A type class for response interpretations. It allows us to describe how
to consume the 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 #
The associated type is the type of body that can be extracted from an
instance of HttpResponse.
Methods
toVanillaResponse :: response -> Response (HttpResponseBody response) #
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 #
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: req-2.1.0
Instances
data HttpException #
Exceptions that this library throws.
Constructors
| VanillaHttpException HttpException | A wrapper with an |
| JsonHttpException String | A wrapper with Aeson-produced |
Instances
| Show HttpException | |
Defined in Network.HTTP.Req Methods showsPrec :: Int -> HttpException -> ShowS # show :: HttpException -> String # showList :: [HttpException] -> ShowS # | |
| Generic HttpException | |
Defined in Network.HTTP.Req Associated Types type Rep HttpException :: Type -> Type # | |
| Exception HttpException | |
Defined in Network.HTTP.Req Methods toException :: HttpException -> SomeException # fromException :: SomeException -> Maybe HttpException # displayException :: HttpException -> String # | |
| type Rep HttpException | |
Defined in Network.HTTP.Req type Rep HttpException = D1 ('MetaData "HttpException" "Network.HTTP.Req" "req-3.9.1-IwV7o8rn04hHErfMVP9czI" 'False) (C1 ('MetaCons "VanillaHttpException" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HttpException)) :+: C1 ('MetaCons "JsonHttpException" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) | |
data CanHaveBody #
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 | |
| Data Scheme | |
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 :: forall r r'. (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 | |
| Show Scheme | |
| Generic Scheme | |
| Lift Scheme | |
| type Rep Scheme | |