polysemy-req-0.1.0: Polysemy effect for req
Copyright(C) 2021 Morrow
LicenseBSD3-3-Clause
MaintainerMorrow <themorrowm@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Polysemy.Req

Description

Network.HTTP.Req adapted for use with polysemy.

Synopsis

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.

responseHeader #

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.

httpVersion #

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.

responseTimeout #

Arguments

:: forall (scheme :: Scheme). Int

Number of microseconds to wait

-> Option scheme 

Specify the number of microseconds to wait for response. The default value is 30 seconds (defined in ManagerSettings of connection Manager).

decompress #

Arguments

:: forall (scheme :: Scheme). (ByteString -> Bool)

Predicate that is given MIME type, it returns True when content should be decompressed on the fly.

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

port :: forall (scheme :: Scheme). Int -> Option scheme #

Specify the port to connect to explicitly. Normally, Url you use determines the default port: 80 for HTTP and 443 for HTTPS. This Option allows us to choose an arbitrary port overwriting the defaults.

customAuth :: forall (scheme :: Scheme). (Request -> IO Request) -> Option scheme #

A helper to create custom authentication Options. The given IO-enabled request transformation is applied after all other modifications when constructing a request. Use wisely.

Since: req-1.1.0

oAuth2Token #

Arguments

:: ByteString

Token

-> Option 'Https

Auth Option

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.

oAuth2Bearer #

Arguments

:: ByteString

Token

-> Option 'Https

Auth Option

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.

oAuth1 #

Arguments

:: forall (scheme :: Scheme). ByteString

Consumer token

-> ByteString

Consumer secret

-> ByteString

OAuth token

-> ByteString

OAuth token secret

-> Option scheme

Auth Option

The Option adds OAuth1 authentication.

Since: req-0.2.0

basicProxyAuth #

Arguments

:: forall (scheme :: Scheme). ByteString

Username

-> ByteString

Password

-> Option scheme

Auth Option

The Option set basic proxy authentication header.

Since: req-1.1.0

basicAuthUnsafe #

Arguments

:: forall (scheme :: Scheme). ByteString

Username

-> ByteString

Password

-> Option scheme

Auth Option

An alternative to basicAuth which works for any scheme. Note that using basic access authentication without SSL/TLS is vulnerable to attacks. Use basicAuth instead unless you know what you are doing.

Since: req-0.3.1

basicAuth #

Arguments

:: ByteString

Username

-> ByteString

Password

-> Option 'Https

Auth Option

The Option adds basic authentication.

See also: https://en.wikipedia.org/wiki/Basic_access_authentication.

cookieJar :: forall (scheme :: Scheme). CookieJar -> Option scheme #

Use the given CookieJar. A CookieJar can be obtained from a Response record.

attachHeader :: ByteString -> ByteString -> Request -> Request #

Attach a header with given name and content to a Request.

Since: req-1.1.0

header #

Arguments

:: forall (scheme :: Scheme). ByteString

Header name

-> ByteString

Header value

-> Option scheme 

Create an Option that adds a header. Note that if you mappend two headers with the same names the leftmost header will win. This means, in particular, that you cannot create a request with several headers of the same name.

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 #

A quasiquoter to build an Url and Option tuple. The type of the generated expression is (Url scheme0, Option scheme1) with scheme0 being either Http or Https depending on the input.

Since: req-3.2.0

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

renderUrl :: forall (scheme :: Scheme). Url scheme -> Text #

Render a Url as Text.

Since: req-3.4.0

(/:) :: forall (scheme :: Scheme). Url scheme -> Text -> Url scheme infixl 5 #

A type-constrained version of (/~) to remove ambiguity in the cases when next URL piece is a Text literal.

(/~) :: 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.

https :: Text -> Url 'Https #

Given host name, produce a Url which has “https” as its scheme and empty path. This also sets port to 443.

http :: Text -> Url 'Http #

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 #

Perform an action using the global implicit Manager that the rest of the library uses. This allows to reuse connections that the Manager controls.

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

  • httpConfigProxy :: Maybe Proxy

    Proxy to use. By default values of HTTP_PROXY and HTTPS_PROXY environment variables are respected, this setting overwrites them. Default value: Nothing.

  • httpConfigRedirectCount :: Int

    How many redirects to follow when getting a resource. Default value: 10.

  • httpConfigAltManager :: Maybe Manager

    Alternative Manager to use. Nothing (default value) means that the default implicit manager will be used (that's what you want in 99% of cases).

  • httpConfigCheckResponse :: forall b. Request -> Response b -> ByteString -> Maybe HttpExceptionContent

    Function to check the response immediately after receiving the status and headers, before streaming of response body. The third argument is the beginning of response body (typically first 1024 bytes). This is used for throwing exceptions on non-success status codes by default (set to \_ _ _ -> Nothing if this behavior is not desirable).

    When the value this function returns is Nothing, nothing will happen. When it there is HttpExceptionContent inside Just, it will be thrown.

    Throwing is better then just returning a request with non-2xx status code because in that case something is wrong and we need a way to short-cut execution (also remember that Req retries automatically on request timeouts and such, so when your request fails, it's certainly something exceptional). The thrown exception is caught by the library though and is available in handleHttpException.

    Note: signature of this function was changed in the version 1.0.0.

    Since: req-0.3.0

  • httpConfigRetryPolicy :: RetryPolicyM IO

    The retry policy to use for request retrying. By default def is used (see RetryPolicyM).

    Note: signature of this function was changed in the version 1.0.0.

    Since: req-0.3.0

  • httpConfigRetryJudge :: forall b. RetryStatus -> Response b -> Bool

    The function is used to decide whether to retry a request. True means that the request should be retried.

    Note: signature of this function was changed in the version 1.0.0.

    Since: req-0.3.0

  • httpConfigRetryJudgeException :: RetryStatus -> SomeException -> Bool

    Similar to httpConfigRetryJudge, but is used to decide when to retry requests that resulted in an exception. By default it retries on response timeout and connection timeout (changed in version 3.8.0).

    Since: req-3.4.0

  • httpConfigBodyPreviewLength :: forall a. Num a => a

    Max length of preview fragment of response body.

    Since: req-3.6.0

Instances

Instances details
RequestComponent HttpConfig 
Instance details

Defined in Network.HTTP.Req

data GET #

GET method.

Constructors

GET 

Instances

Instances details
HttpMethod GET 
Instance details

Defined in Network.HTTP.Req

Associated Types

type AllowsBody GET :: CanHaveBody #

type AllowsBody GET 
Instance details

Defined in Network.HTTP.Req

data POST #

POST method.

Constructors

POST 

Instances

Instances details
HttpMethod POST 
Instance details

Defined in Network.HTTP.Req

Associated Types

type AllowsBody POST :: CanHaveBody #

type AllowsBody POST 
Instance details

Defined in Network.HTTP.Req

data HEAD #

HEAD method.

Constructors

HEAD 

Instances

Instances details
HttpMethod HEAD 
Instance details

Defined in Network.HTTP.Req

Associated Types

type AllowsBody HEAD :: CanHaveBody #

type AllowsBody HEAD 
Instance details

Defined in Network.HTTP.Req

data PUT #

PUT method.

Constructors

PUT 

Instances

Instances details
HttpMethod PUT 
Instance details

Defined in Network.HTTP.Req

Associated Types

type AllowsBody PUT :: CanHaveBody #

type AllowsBody PUT 
Instance details

Defined in Network.HTTP.Req

data DELETE #

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

Instances details
HttpMethod DELETE 
Instance details

Defined in Network.HTTP.Req

Associated Types

type AllowsBody DELETE :: CanHaveBody #

type AllowsBody DELETE 
Instance details

Defined in Network.HTTP.Req

data TRACE #

TRACE method.

Constructors

TRACE 

Instances

Instances details
HttpMethod TRACE 
Instance details

Defined in Network.HTTP.Req

Associated Types

type AllowsBody TRACE :: CanHaveBody #

type AllowsBody TRACE 
Instance details

Defined in Network.HTTP.Req

data CONNECT #

CONNECT method.

Constructors

CONNECT 

Instances

Instances details
HttpMethod CONNECT 
Instance details

Defined in Network.HTTP.Req

Associated Types

type AllowsBody CONNECT :: CanHaveBody #

type AllowsBody CONNECT 
Instance details

Defined in Network.HTTP.Req

data OPTIONS #

OPTIONS method.

Constructors

OPTIONS 

Instances

Instances details
HttpMethod OPTIONS 
Instance details

Defined in Network.HTTP.Req

Associated Types

type AllowsBody OPTIONS :: CanHaveBody #

type AllowsBody OPTIONS 
Instance details

Defined in Network.HTTP.Req

data PATCH #

PATCH method.

Constructors

PATCH 

Instances

Instances details
HttpMethod PATCH 
Instance details

Defined in Network.HTTP.Req

Associated Types

type AllowsBody PATCH :: CanHaveBody #

type AllowsBody PATCH 
Instance details

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

Instances details
type AllowsBody GET 
Instance details

Defined in Network.HTTP.Req

type AllowsBody POST 
Instance details

Defined in Network.HTTP.Req

type AllowsBody HEAD 
Instance details

Defined in Network.HTTP.Req

type AllowsBody PUT 
Instance details

Defined in Network.HTTP.Req

type AllowsBody DELETE 
Instance details

Defined in Network.HTTP.Req

type AllowsBody TRACE 
Instance details

Defined in Network.HTTP.Req

type AllowsBody CONNECT 
Instance details

Defined in Network.HTTP.Req

type AllowsBody OPTIONS 
Instance details

Defined in Network.HTTP.Req

type AllowsBody PATCH 
Instance details

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.

Methods

httpMethodName :: Proxy a -> ByteString #

Return name of the method as a ByteString.

Instances

Instances details
HttpMethod GET 
Instance details

Defined in Network.HTTP.Req

Associated Types

type AllowsBody GET :: CanHaveBody #

HttpMethod POST 
Instance details

Defined in Network.HTTP.Req

Associated Types

type AllowsBody POST :: CanHaveBody #

HttpMethod HEAD 
Instance details

Defined in Network.HTTP.Req

Associated Types

type AllowsBody HEAD :: CanHaveBody #

HttpMethod PUT 
Instance details

Defined in Network.HTTP.Req

Associated Types

type AllowsBody PUT :: CanHaveBody #

HttpMethod DELETE 
Instance details

Defined in Network.HTTP.Req

Associated Types

type AllowsBody DELETE :: CanHaveBody #

HttpMethod TRACE 
Instance details

Defined in Network.HTTP.Req

Associated Types

type AllowsBody TRACE :: CanHaveBody #

HttpMethod CONNECT 
Instance details

Defined in Network.HTTP.Req

Associated Types

type AllowsBody CONNECT :: CanHaveBody #

HttpMethod OPTIONS 
Instance details

Defined in Network.HTTP.Req

Associated Types

type AllowsBody OPTIONS :: CanHaveBody #

HttpMethod PATCH 
Instance details

Defined in Network.HTTP.Req

Associated Types

type AllowsBody PATCH :: CanHaveBody #

data Url (scheme :: Scheme) #

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

Expand
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

Instances details
Typeable scheme => Lift (Url scheme :: Type) 
Instance details

Defined in Network.HTTP.Req

Methods

lift :: Url scheme -> Q Exp #

liftTyped :: Url scheme -> Q (TExp (Url scheme)) #

Eq (Url scheme) 
Instance details

Defined in Network.HTTP.Req

Methods

(==) :: Url scheme -> Url scheme -> Bool #

(/=) :: Url scheme -> Url scheme -> Bool #

Typeable scheme => Data (Url scheme) 
Instance details

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) 
Instance details

Defined in Network.HTTP.Req

Methods

compare :: Url scheme -> Url scheme -> Ordering #

(<) :: Url scheme -> Url scheme -> Bool #

(<=) :: Url scheme -> Url scheme -> Bool #

(>) :: Url scheme -> Url scheme -> Bool #

(>=) :: Url scheme -> Url scheme -> Bool #

max :: Url scheme -> Url scheme -> Url scheme #

min :: Url scheme -> Url scheme -> Url scheme #

Show (Url scheme) 
Instance details

Defined in Network.HTTP.Req

Methods

showsPrec :: Int -> Url scheme -> ShowS #

show :: Url scheme -> String #

showList :: [Url scheme] -> ShowS #

Generic (Url scheme) 
Instance details

Defined in Network.HTTP.Req

Associated Types

type Rep (Url scheme) :: Type -> Type #

Methods

from :: Url scheme -> Rep (Url scheme) x #

to :: Rep (Url scheme) x -> Url scheme #

RequestComponent (Url scheme) 
Instance details

Defined in Network.HTTP.Req

Methods

getRequestMod :: Url scheme -> Endo Request

type Rep (Url scheme) 
Instance details

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

data NoReqBody #

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

Instances details
HttpBody NoReqBody 
Instance details

Defined in Network.HTTP.Req

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

Instances details
ToJSON a => HttpBody (ReqBodyJson a) 
Instance details

Defined in Network.HTTP.Req

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

Instances details
HttpBody ReqBodyFile 
Instance details

Defined in Network.HTTP.Req

newtype ReqBodyBs #

HTTP request body represented by a strict ByteString.

Using of this body option does not set the Content-Type header.

Constructors

ReqBodyBs ByteString 

Instances

Instances details
HttpBody ReqBodyBs 
Instance details

Defined in Network.HTTP.Req

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

Instances details
HttpBody ReqBodyLbs 
Instance details

Defined in Network.HTTP.Req

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.

Instances

Instances details
HttpBody ReqBodyUrlEnc 
Instance details

Defined in Network.HTTP.Req

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

Expand
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

class HttpBody body where #

A type class for things that can be interpreted as an HTTP RequestBody.

Minimal complete definition

getRequestBody

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.

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.

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

Instances details
Semigroup (Option scheme) 
Instance details

Defined in Network.HTTP.Req

Methods

(<>) :: Option scheme -> Option scheme -> Option scheme #

sconcat :: NonEmpty (Option scheme) -> Option scheme #

stimes :: Integral b => b -> Option scheme -> Option scheme #

Monoid (Option scheme) 
Instance details

Defined in Network.HTTP.Req

Methods

mempty :: Option scheme #

mappend :: Option scheme -> Option scheme -> Option scheme #

mconcat :: [Option scheme] -> Option scheme #

QueryParam (Option scheme) 
Instance details

Defined in Network.HTTP.Req

Methods

queryParam :: ToHttpApiData a => Text -> Maybe a -> Option scheme #

RequestComponent (Option scheme) 
Instance details

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 #

Create a query parameter with given name and value. If value is Nothing, it won't be included at all (i.e. you create a flag this way). It's recommended to use (=:) and queryFlag instead of this method, because they are easier to read.

Instances

Instances details
QueryParam FormUrlEncodedParam 
Instance details

Defined in Network.HTTP.Req

QueryParam (Option scheme) 
Instance details

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.

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

Instances details
Show a => Show (JsonResponse a) 
Instance details

Defined in Network.HTTP.Req

FromJSON a => HttpResponse (JsonResponse a) 
Instance details

Defined in Network.HTTP.Req

Associated Types

type HttpResponseBody (JsonResponse a) #

type HttpResponseBody (JsonResponse a) 
Instance details

Defined in Network.HTTP.Req

data BsResponse #

Make a request and interpret the body of the response as a strict ByteString.

data LbsResponse #

Make a request and interpret the body of the response as a lazy ByteString.

type family HttpResponseBody response #

The associated type is the type of body that can be extracted from an instance of HttpResponse.

Instances

Instances details
type HttpResponseBody IgnoreResponse 
Instance details

Defined in Network.HTTP.Req

type HttpResponseBody BsResponse 
Instance details

Defined in Network.HTTP.Req

type HttpResponseBody LbsResponse 
Instance details

Defined in Network.HTTP.Req

type HttpResponseBody (JsonResponse a) 
Instance details

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 Response BodyReader and produce the final result that is to be returned to the user.

Minimal complete definition

toVanillaResponse, getHttpResponse

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.

getHttpResponse #

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 IO ByteString. You should call this action repeatedly until it yields the empty ByteString. 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

data HttpException #

Exceptions that this library throws.

Constructors

VanillaHttpException HttpException

A wrapper with an HttpException from Network.HTTP.Client

JsonHttpException String

A wrapper with Aeson-produced String describing why decoding failed

Instances

Instances details
Show HttpException 
Instance details

Defined in Network.HTTP.Req

Generic HttpException 
Instance details

Defined in Network.HTTP.Req

Associated Types

type Rep HttpException :: Type -> Type #

Exception HttpException 
Instance details

Defined in Network.HTTP.Req

type Rep HttpException 
Instance details

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

data Scheme #

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.

Constructors

Http

HTTP

Https

HTTPS

Instances

Instances details
Eq Scheme 
Instance details

Defined in Network.HTTP.Req

Methods

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

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

Data Scheme 
Instance details

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 
Instance details

Defined in Network.HTTP.Req

Show Scheme 
Instance details

Defined in Network.HTTP.Req

Generic Scheme 
Instance details

Defined in Network.HTTP.Req

Associated Types

type Rep Scheme :: Type -> Type #

Methods

from :: Scheme -> Rep Scheme x #

to :: Rep Scheme x -> Scheme #

Lift Scheme 
Instance details

Defined in Network.HTTP.Req

Methods

lift :: Scheme -> Q Exp #

liftTyped :: Scheme -> Q (TExp Scheme) #

type Rep Scheme 
Instance details

Defined in Network.HTTP.Req

type Rep Scheme = D1 ('MetaData "Scheme" "Network.HTTP.Req" "req-3.9.1-IwV7o8rn04hHErfMVP9czI" 'False) (C1 ('MetaCons "Http" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Https" 'PrefixI 'False) (U1 :: Type -> Type))