Safe Haskell | None |
---|---|
Language | Haskell2010 |
Servant.Client
Description
This module provides client
which can automatically generate
querying functions for each endpoint just from the type representing your
API.
Synopsis
- client :: HasClient ClientM api => Proxy api -> Client ClientM api
- data ClientM a
- runClientM :: ClientM a -> ClientEnv -> IO (Either ClientError a)
- data ClientEnv = ClientEnv {
- manager :: Manager
- baseUrl :: BaseUrl
- cookieJar :: Maybe (TVar CookieJar)
- makeClientRequest :: BaseUrl -> Request -> IO Request
- middleware :: ClientMiddleware
- mkClientEnv :: Manager -> BaseUrl -> ClientEnv
- defaultMakeClientRequest :: Applicative f => BaseUrl -> Request -> f Request
- hoistClient :: HasClient ClientM api => Proxy api -> (forall a. m a -> n a) -> Client m api -> Client n api
- class RunClient m => HasClient (m :: Type -> Type) api where
- type Client (m :: Type -> Type) api
- clientWithRoute :: Proxy m -> Proxy api -> Request -> Client m api
- hoistClientMonad :: Proxy m -> Proxy api -> (forall x. mon x -> mon' x) -> Client mon api -> Client mon' api
- type family Client (m :: Type -> Type) api
- data BaseUrl = BaseUrl {
- baseUrlScheme :: Scheme
- baseUrlHost :: String
- baseUrlPort :: Int
- baseUrlPath :: String
- type Response = ResponseF ByteString
- data ResponseF a = Response {
- responseStatusCode :: Status
- responseHeaders :: Seq Header
- responseHttpVersion :: HttpVersion
- responseBody :: a
- data ClientError
- = FailureResponse (RequestF () (BaseUrl, ByteString)) Response
- | DecodeFailure Text Response
- | UnsupportedContentType MediaType Response
- | InvalidContentTypeHeader Response
- | ConnectionError SomeException
- data Scheme
- (//) :: a -> (a -> b) -> b
- (/:) :: (a -> b -> c) -> b -> a -> c
- data InvalidBaseUrlException
- parseBaseUrl :: MonadThrow m => String -> m BaseUrl
- showBaseUrl :: BaseUrl -> String
- data EmptyClient = EmptyClient
- type StreamingResponse = ResponseF (SourceIO ByteString)
- foldMapUnion :: forall c a (as :: [Type]). All c as => Proxy c -> (forall x. c x => x -> a) -> Union as -> a
- matchUnion :: forall a (as :: [Type]). IsMember a as => Union as -> Maybe a
- data AsClientT (m :: Type -> Type)
Documentation
client :: HasClient ClientM api => Proxy api -> Client ClientM api Source #
Generates a set of client functions for an API.
Example:
type API = Capture "no" Int :> Get '[JSON] Int :<|> Get '[JSON] [Bool] api :: Proxy API api = Proxy getInt :: Int -> ClientM Int getBools :: ClientM [Bool] getInt :<|> getBools = client api
ClientM
is the monad in which client functions run. Contains the
Manager
and BaseUrl
used for requests in the reader environment.
Instances
runClientM :: ClientM a -> ClientEnv -> IO (Either ClientError a) Source #
The environment in which a request is run.
The baseUrl
and makeClientRequest
function are used to create a http-client
request.
Cookies are then added to that request if a CookieJar
is set on the environment.
Finally the request is executed with the manager
.
The makeClientRequest
function can be used to modify the request to execute and set values which
are not specified on a servant
Request
like responseTimeout
or redirectCount
Constructors
ClientEnv | |
Fields
|
defaultMakeClientRequest :: Applicative f => BaseUrl -> Request -> f Request Source #
Create a http-client
Request
from a servant
Request
The host
, path
and port
fields are extracted from the BaseUrl
otherwise the body, headers and query string are derived from the servant
Request
Note that Applicative
dependency is not really needed for this function
implementation. But in the past the return type was wrapped into IO
without a necessity breaking the API backward-compatibility. In order to not
break the API again it was changed to Applicative
so that you can just use
something like Data.Functor.Identity
without a need to involve IO
but
still keeping it compatible with the code written when it was typed as IO
.
hoistClient :: HasClient ClientM api => Proxy api -> (forall a. m a -> n a) -> Client m api -> Client n api Source #
Change the monad the client functions live in, by supplying a conversion function (a natural transformation to be precise).
For example, assuming you have some manager ::
and
Manager
baseurl ::
around:BaseUrl
type API = Get '[JSON] Int :<|> Capture "n" Int :> Post '[JSON] Int api :: Proxy API api = Proxy getInt :: IO Int postInt :: Int -> IO Int getInt :<|> postInt = hoistClient api (flip runClientM cenv) (client api) where cenv = mkClientEnv manager baseurl
class RunClient m => HasClient (m :: Type -> Type) api where #
Methods
clientWithRoute :: Proxy m -> Proxy api -> Request -> Client m api #
hoistClientMonad :: Proxy m -> Proxy api -> (forall x. mon x -> mon' x) -> Client mon api -> Client mon' api #
Instances
RunClient m => HasClient m EmptyAPI | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy EmptyAPI -> Request -> Client m EmptyAPI # hoistClientMonad :: Proxy m -> Proxy EmptyAPI -> (forall x. mon x -> mon' x) -> Client mon EmptyAPI -> Client mon' EmptyAPI # | |||||||||||||
RunClient m => HasClient m Raw | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy Raw -> Request -> Client m Raw # hoistClientMonad :: Proxy m -> Proxy Raw -> (forall x. mon x -> mon' x) -> Client mon Raw -> Client mon' Raw # | |||||||||||||
RunClient m => HasClient m RawM | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy RawM -> Request -> Client m RawM # hoistClientMonad :: Proxy m -> Proxy RawM -> (forall x. mon x -> mon' x) -> Client mon RawM -> Client mon' RawM # | |||||||||||||
(RunClient m, TypeError (NoInstanceFor (HasClient m api)) :: Constraint) => HasClient m api | |||||||||||||
Defined in Servant.Client.Core.HasClient Methods clientWithRoute :: Proxy m -> Proxy api -> Request -> Client m api # hoistClientMonad :: Proxy m -> Proxy api -> (forall x. mon x -> mon' x) -> Client mon api -> Client mon' api # | |||||||||||||
(forall (n :: Type -> Type). GClient api n, HasClient m (ToServantApi api), RunClient m, ErrorIfNoGeneric api) => HasClient m (NamedRoutes api) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (NamedRoutes api) -> Request -> Client m (NamedRoutes api) # hoistClientMonad :: Proxy m -> Proxy (NamedRoutes api) -> (forall x. mon x -> mon' x) -> Client mon (NamedRoutes api) -> Client mon' (NamedRoutes api) # | |||||||||||||
(HasClient m a, HasClient m b) => HasClient m (a :<|> b) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (a :<|> b) -> Request -> Client m (a :<|> b) # hoistClientMonad :: Proxy m -> Proxy (a :<|> b) -> (forall x. mon x -> mon' x) -> Client mon (a :<|> b) -> Client mon' (a :<|> b) # | |||||||||||||
(RunClient m, ReflectMethod method) => HasClient m (NoContentVerb method) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (NoContentVerb method) -> Request -> Client m (NoContentVerb method) # hoistClientMonad :: Proxy m -> Proxy (NoContentVerb method) -> (forall x. mon x -> mon' x) -> Client mon (NoContentVerb method) -> Client mon' (NoContentVerb method) # | |||||||||||||
(RunClient m, TypeError (PartialApplication HasClient arr) :: Constraint) => HasClient m (arr :> sub) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (arr :> sub) -> Request -> Client m (arr :> sub) # hoistClientMonad :: Proxy m -> Proxy (arr :> sub) -> (forall x. mon x -> mon' x) -> Client mon (arr :> sub) -> Client mon' (arr :> sub) # | |||||||||||||
(KnownSymbol path, HasClient m api) => HasClient m (path :> api) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (path :> api) -> Request -> Client m (path :> api) # hoistClientMonad :: Proxy m -> Proxy (path :> api) -> (forall x. mon x -> mon' x) -> Client mon (path :> api) -> Client mon' (path :> api) # | |||||||||||||
HasClient m api => HasClient m (HttpVersion :> api) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (HttpVersion :> api) -> Request -> Client m (HttpVersion :> api) # hoistClientMonad :: Proxy m -> Proxy (HttpVersion :> api) -> (forall x. mon x -> mon' x) -> Client mon (HttpVersion :> api) -> Client mon' (HttpVersion :> api) # | |||||||||||||
HasClient m api => HasClient m (BasicAuth realm usr :> api) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (BasicAuth realm usr :> api) -> Request -> Client m (BasicAuth realm usr :> api) # hoistClientMonad :: Proxy m -> Proxy (BasicAuth realm usr :> api) -> (forall x. mon x -> mon' x) -> Client mon (BasicAuth realm usr :> api) -> Client mon' (BasicAuth realm usr :> api) # | |||||||||||||
(ToHttpApiData a, HasClient m api) => HasClient m (Capture' mods capture a :> api) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (Capture' mods capture a :> api) -> Request -> Client m (Capture' mods capture a :> api) # hoistClientMonad :: Proxy m -> Proxy (Capture' mods capture a :> api) -> (forall x. mon x -> mon' x) -> Client mon (Capture' mods capture a :> api) -> Client mon' (Capture' mods capture a :> api) # | |||||||||||||
(ToHttpApiData a, HasClient m sublayout) => HasClient m (CaptureAll capture a :> sublayout) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (CaptureAll capture a :> sublayout) -> Request -> Client m (CaptureAll capture a :> sublayout) # hoistClientMonad :: Proxy m -> Proxy (CaptureAll capture a :> sublayout) -> (forall x. mon x -> mon' x) -> Client mon (CaptureAll capture a :> sublayout) -> Client mon' (CaptureAll capture a :> sublayout) # | |||||||||||||
HasClient m api => HasClient m (Description desc :> api) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (Description desc :> api) -> Request -> Client m (Description desc :> api) # hoistClientMonad :: Proxy m -> Proxy (Description desc :> api) -> (forall x. mon x -> mon' x) -> Client mon (Description desc :> api) -> Client mon' (Description desc :> api) # | |||||||||||||
HasClient m api => HasClient m (Summary desc :> api) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (Summary desc :> api) -> Request -> Client m (Summary desc :> api) # hoistClientMonad :: Proxy m -> Proxy (Summary desc :> api) -> (forall x. mon x -> mon' x) -> Client mon (Summary desc :> api) -> Client mon' (Summary desc :> api) # | |||||||||||||
HasClient m api => HasClient m (AuthProtect tag :> api) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (AuthProtect tag :> api) -> Request -> Client m (AuthProtect tag :> api) # hoistClientMonad :: Proxy m -> Proxy (AuthProtect tag :> api) -> (forall x. mon x -> mon' x) -> Client mon (AuthProtect tag :> api) -> Client mon' (AuthProtect tag :> api) # | |||||||||||||
(AtMostOneFragment api, FragmentUnique (Fragment a :> api), HasClient m api) => HasClient m (Fragment a :> api) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (Fragment a :> api) -> Request -> Client m (Fragment a :> api) # hoistClientMonad :: Proxy m -> Proxy (Fragment a :> api) -> (forall x. mon x -> mon' x) -> Client mon (Fragment a :> api) -> Client mon' (Fragment a :> api) # | |||||||||||||
(KnownSymbol sym, ToHttpApiData a, HasClient m api, SBoolI (FoldRequired mods)) => HasClient m (Header' mods sym a :> api) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (Header' mods sym a :> api) -> Request -> Client m (Header' mods sym a :> api) # hoistClientMonad :: Proxy m -> Proxy (Header' mods sym a :> api) -> (forall x. mon x -> mon' x) -> Client mon (Header' mods sym a :> api) -> Client mon' (Header' mods sym a :> api) # | |||||||||||||
HasClient m api => HasClient m (IsSecure :> api) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (IsSecure :> api) -> Request -> Client m (IsSecure :> api) # hoistClientMonad :: Proxy m -> Proxy (IsSecure :> api) -> (forall x. mon x -> mon' x) -> Client mon (IsSecure :> api) -> Client mon' (IsSecure :> api) # | |||||||||||||
(KnownSymbol sym, HasClient m api) => HasClient m (QueryFlag sym :> api) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (QueryFlag sym :> api) -> Request -> Client m (QueryFlag sym :> api) # hoistClientMonad :: Proxy m -> Proxy (QueryFlag sym :> api) -> (forall x. mon x -> mon' x) -> Client mon (QueryFlag sym :> api) -> Client mon' (QueryFlag sym :> api) # | |||||||||||||
(KnownSymbol sym, ToHttpApiData a, HasClient m api, SBoolI (FoldRequired mods)) => HasClient m (QueryParam' mods sym a :> api) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (QueryParam' mods sym a :> api) -> Request -> Client m (QueryParam' mods sym a :> api) # hoistClientMonad :: Proxy m -> Proxy (QueryParam' mods sym a :> api) -> (forall x. mon x -> mon' x) -> Client mon (QueryParam' mods sym a :> api) -> Client mon' (QueryParam' mods sym a :> api) # | |||||||||||||
(KnownSymbol sym, ToHttpApiData a, HasClient m api) => HasClient m (QueryParams sym a :> api) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (QueryParams sym a :> api) -> Request -> Client m (QueryParams sym a :> api) # hoistClientMonad :: Proxy m -> Proxy (QueryParams sym a :> api) -> (forall x. mon x -> mon' x) -> Client mon (QueryParams sym a :> api) -> Client mon' (QueryParams sym a :> api) # | |||||||||||||
(KnownSymbol sym, ToDeepQuery a, HasClient m api) => HasClient m (DeepQuery sym a :> api) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (DeepQuery sym a :> api) -> Request -> Client m (DeepQuery sym a :> api) # hoistClientMonad :: Proxy m -> Proxy (DeepQuery sym a :> api) -> (forall x. mon x -> mon' x) -> Client mon (DeepQuery sym a :> api) -> Client mon' (DeepQuery sym a :> api) # | |||||||||||||
HasClient m api => HasClient m (QueryString :> api) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (QueryString :> api) -> Request -> Client m (QueryString :> api) # hoistClientMonad :: Proxy m -> Proxy (QueryString :> api) -> (forall x. mon x -> mon' x) -> Client mon (QueryString :> api) -> Client mon' (QueryString :> api) # | |||||||||||||
HasClient m api => HasClient m (RemoteHost :> api) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (RemoteHost :> api) -> Request -> Client m (RemoteHost :> api) # hoistClientMonad :: Proxy m -> Proxy (RemoteHost :> api) -> (forall x. mon x -> mon' x) -> Client mon (RemoteHost :> api) -> Client mon' (RemoteHost :> api) # | |||||||||||||
(MimeRender ct a, HasClient m api) => HasClient m (ReqBody' mods (ct ': cts) a :> api) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (ReqBody' mods (ct ': cts) a :> api) -> Request -> Client m (ReqBody' mods (ct ': cts) a :> api) # hoistClientMonad :: Proxy m -> Proxy (ReqBody' mods (ct ': cts) a :> api) -> (forall x. mon x -> mon' x) -> Client mon (ReqBody' mods (ct ': cts) a :> api) -> Client mon' (ReqBody' mods (ct ': cts) a :> api) # | |||||||||||||
(HasClient m api, MimeRender ctype chunk, FramingRender framing, ToSourceIO chunk a) => HasClient m (StreamBody' mods framing ctype a :> api) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (StreamBody' mods framing ctype a :> api) -> Request -> Client m (StreamBody' mods framing ctype a :> api) # hoistClientMonad :: Proxy m -> Proxy (StreamBody' mods framing ctype a :> api) -> (forall x. mon x -> mon' x) -> Client mon (StreamBody' mods framing ctype a :> api) -> Client mon' (StreamBody' mods framing ctype a :> api) # | |||||||||||||
HasClient m subapi => HasClient m (WithResource res :> subapi) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (WithResource res :> subapi) -> Request -> Client m (WithResource res :> subapi) # hoistClientMonad :: Proxy m -> Proxy (WithResource res :> subapi) -> (forall x. mon x -> mon' x) -> Client mon (WithResource res :> subapi) -> Client mon' (WithResource res :> subapi) # | |||||||||||||
HasClient m api => HasClient m (Vault :> api) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (Vault :> api) -> Request -> Client m (Vault :> api) # hoistClientMonad :: Proxy m -> Proxy (Vault :> api) -> (forall x. mon x -> mon' x) -> Client mon (Vault :> api) -> Client mon' (Vault :> api) # | |||||||||||||
(RunClient m, TypeError (NoInstanceForSub (HasClient m) ty) :: Constraint) => HasClient m (ty :> sub) | |||||||||||||
Defined in Servant.Client.Core.HasClient Methods clientWithRoute :: Proxy m -> Proxy (ty :> sub) -> Request -> Client m (ty :> sub) # hoistClientMonad :: Proxy m -> Proxy (ty :> sub) -> (forall x. mon x -> mon' x) -> Client mon (ty :> sub) -> Client mon' (ty :> sub) # | |||||||||||||
(RunClient m, contentTypes ~ (contentType ': otherContentTypes), as ~ (a ': as'), AllMime contentTypes, ReflectMethod method, All (UnrenderResponse contentTypes) as, All HasStatus as, HasStatuses as', Unique (Statuses as)) => HasClient m (UVerb method contentTypes as) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (UVerb method contentTypes as) -> Request -> Client m (UVerb method contentTypes as) # hoistClientMonad :: Proxy m -> Proxy (UVerb method contentTypes as) -> (forall x. mon x -> mon' x) -> Client mon (UVerb method contentTypes as) -> Client mon' (UVerb method contentTypes as) # | |||||||||||||
HasClient m subapi => HasClient m (WithNamedContext name context subapi) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (WithNamedContext name context subapi) -> Request -> Client m (WithNamedContext name context subapi) # hoistClientMonad :: Proxy m -> Proxy (WithNamedContext name context subapi) -> (forall x. mon x -> mon' x) -> Client mon (WithNamedContext name context subapi) -> Client mon' (WithNamedContext name context subapi) # | |||||||||||||
(RunClient m, ReflectMethod method, KnownNat status) => HasClient m (Verb method status cts NoContent) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (Verb method status cts NoContent) -> Request -> Client m (Verb method status cts NoContent) # hoistClientMonad :: Proxy m -> Proxy (Verb method status cts NoContent) -> (forall x. mon x -> mon' x) -> Client mon (Verb method status cts NoContent) -> Client mon' (Verb method status cts NoContent) # | |||||||||||||
(RunClient m, BuildHeadersTo ls, ReflectMethod method, KnownNat status) => HasClient m (Verb method status cts (Headers ls NoContent)) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (Verb method status cts (Headers ls NoContent)) -> Request -> Client m (Verb method status cts (Headers ls NoContent)) # hoistClientMonad :: Proxy m -> Proxy (Verb method status cts (Headers ls NoContent)) -> (forall x. mon x -> mon' x) -> Client mon (Verb method status cts (Headers ls NoContent)) -> Client mon' (Verb method status cts (Headers ls NoContent)) # | |||||||||||||
(RunClient m, MimeUnrender ct a, BuildHeadersTo ls, KnownNat status, ReflectMethod method, cts' ~ (ct ': cts)) => HasClient m (Verb method status cts' (Headers ls a)) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (Verb method status cts' (Headers ls a)) -> Request -> Client m (Verb method status cts' (Headers ls a)) # hoistClientMonad :: Proxy m -> Proxy (Verb method status cts' (Headers ls a)) -> (forall x. mon x -> mon' x) -> Client mon (Verb method status cts' (Headers ls a)) -> Client mon' (Verb method status cts' (Headers ls a)) # | |||||||||||||
(RunClient m, MimeUnrender ct a, ReflectMethod method, cts' ~ (ct ': cts), KnownNat status) => HasClient m (Verb method status cts' a) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (Verb method status cts' a) -> Request -> Client m (Verb method status cts' a) # hoistClientMonad :: Proxy m -> Proxy (Verb method status cts' a) -> (forall x. mon x -> mon' x) -> Client mon (Verb method status cts' a) -> Client mon' (Verb method status cts' a) # | |||||||||||||
(RunStreamingClient m, MimeUnrender ct chunk, ReflectMethod method, FramingUnrender framing, FromSourceIO chunk a, BuildHeadersTo hs) => HasClient m (Stream method status framing ct (Headers hs a)) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (Stream method status framing ct (Headers hs a)) -> Request -> Client m (Stream method status framing ct (Headers hs a)) # hoistClientMonad :: Proxy m -> Proxy (Stream method status framing ct (Headers hs a)) -> (forall x. mon x -> mon' x) -> Client mon (Stream method status framing ct (Headers hs a)) -> Client mon' (Stream method status framing ct (Headers hs a)) # | |||||||||||||
(RunStreamingClient m, MimeUnrender ct chunk, ReflectMethod method, FramingUnrender framing, FromSourceIO chunk a) => HasClient m (Stream method status framing ct a) | |||||||||||||
Defined in Servant.Client.Core.HasClient Associated Types
Methods clientWithRoute :: Proxy m -> Proxy (Stream method status framing ct a) -> Request -> Client m (Stream method status framing ct a) # hoistClientMonad :: Proxy m -> Proxy (Stream method status framing ct a) -> (forall x. mon x -> mon' x) -> Client mon (Stream method status framing ct a) -> Client mon' (Stream method status framing ct a) # |
type family Client (m :: Type -> Type) api #
Instances
type Client m EmptyAPI | |
Defined in Servant.Client.Core.HasClient | |
type Client m Raw | |
Defined in Servant.Client.Core.HasClient | |
type Client m RawM | |
Defined in Servant.Client.Core.HasClient | |
type Client m (NamedRoutes api) | |
Defined in Servant.Client.Core.HasClient | |
type Client m (a :<|> b) | |
Defined in Servant.Client.Core.HasClient | |
type Client m (NoContentVerb method) | |
Defined in Servant.Client.Core.HasClient type Client m (NoContentVerb method) = m NoContent | |
type Client m (arr :> sub) | |
Defined in Servant.Client.Core.HasClient | |
type Client m (path :> api) | |
Defined in Servant.Client.Core.HasClient | |
type Client m (HttpVersion :> api) | |
Defined in Servant.Client.Core.HasClient | |
type Client m (BasicAuth realm usr :> api) | |
Defined in Servant.Client.Core.HasClient | |
type Client m (Capture' mods capture a :> api) | |
Defined in Servant.Client.Core.HasClient | |
type Client m (CaptureAll capture a :> sublayout) | |
Defined in Servant.Client.Core.HasClient | |
type Client m (Description desc :> api) | |
Defined in Servant.Client.Core.HasClient | |
type Client m (Summary desc :> api) | |
Defined in Servant.Client.Core.HasClient | |
type Client m (AuthProtect tag :> api) | |
Defined in Servant.Client.Core.HasClient | |
type Client m (Fragment a :> api) | |
Defined in Servant.Client.Core.HasClient | |
type Client m (Header' mods sym a :> api) | |
Defined in Servant.Client.Core.HasClient | |
type Client m (IsSecure :> api) | |
Defined in Servant.Client.Core.HasClient | |
type Client m (QueryFlag sym :> api) | |
Defined in Servant.Client.Core.HasClient | |
type Client m (QueryParam' mods sym a :> api) | |
Defined in Servant.Client.Core.HasClient | |
type Client m (QueryParams sym a :> api) | |
Defined in Servant.Client.Core.HasClient | |
type Client m (DeepQuery sym a :> api) | |
Defined in Servant.Client.Core.HasClient | |
type Client m (QueryString :> api) | |
Defined in Servant.Client.Core.HasClient | |
type Client m (RemoteHost :> api) | |
Defined in Servant.Client.Core.HasClient | |
type Client m (ReqBody' mods (ct ': cts) a :> api) | |
Defined in Servant.Client.Core.HasClient | |
type Client m (StreamBody' mods framing ctype a :> api) | |
Defined in Servant.Client.Core.HasClient | |
type Client m (WithResource res :> subapi) | |
Defined in Servant.Client.Core.HasClient | |
type Client m (Vault :> api) | |
Defined in Servant.Client.Core.HasClient | |
type Client m (UVerb method contentTypes as) | |
Defined in Servant.Client.Core.HasClient type Client m (UVerb method contentTypes as) = m (Union as) | |
type Client m (WithNamedContext name context subapi) | |
Defined in Servant.Client.Core.HasClient | |
type Client m (Verb method status cts NoContent) | |
Defined in Servant.Client.Core.HasClient type Client m (Verb method status cts NoContent) = m NoContent | |
type Client m (Verb method status cts (Headers ls NoContent)) | |
Defined in Servant.Client.Core.HasClient type Client m (Verb method status cts (Headers ls NoContent)) = m (Headers ls NoContent) | |
type Client m (Verb method status cts' (Headers ls a)) | |
Defined in Servant.Client.Core.HasClient type Client m (Verb method status cts' (Headers ls a)) = m (Headers ls a) | |
type Client m (Verb method status cts' a) | |
Defined in Servant.Client.Core.HasClient type Client m (Verb method status cts' a) = m a | |
type Client m (Stream method status framing ct (Headers hs a)) | |
Defined in Servant.Client.Core.HasClient type Client m (Stream method status framing ct (Headers hs a)) = m (Headers hs a) | |
type Client m (Stream method status framing ct a) | |
Defined in Servant.Client.Core.HasClient type Client m (Stream method status framing ct a) = m a |
Constructors
BaseUrl | |
Fields
|
Instances
FromJSON BaseUrl | |||||
Defined in Servant.Client.Core.BaseUrl Methods parseJSON :: Value -> Parser BaseUrl parseJSONList :: Value -> Parser [BaseUrl] omittedField :: Maybe BaseUrl | |||||
FromJSONKey BaseUrl | |||||
Defined in Servant.Client.Core.BaseUrl | |||||
ToJSON BaseUrl | |||||
Defined in Servant.Client.Core.BaseUrl Methods toEncoding :: BaseUrl -> Encoding toJSONList :: [BaseUrl] -> Value toEncodingList :: [BaseUrl] -> Encoding | |||||
ToJSONKey BaseUrl | |||||
Defined in Servant.Client.Core.BaseUrl | |||||
NFData BaseUrl | |||||
Defined in Servant.Client.Core.BaseUrl | |||||
Data BaseUrl | |||||
Defined in Servant.Client.Core.BaseUrl Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BaseUrl -> c BaseUrl gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BaseUrl dataTypeOf :: BaseUrl -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BaseUrl) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BaseUrl) gmapT :: (forall b. Data b => b -> b) -> BaseUrl -> BaseUrl gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BaseUrl -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BaseUrl -> r gmapQ :: (forall d. Data d => d -> u) -> BaseUrl -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> BaseUrl -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> BaseUrl -> m BaseUrl gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BaseUrl -> m BaseUrl gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BaseUrl -> m BaseUrl | |||||
Generic BaseUrl | |||||
Defined in Servant.Client.Core.BaseUrl Associated Types
| |||||
Show BaseUrl | |||||
Eq BaseUrl | |||||
Ord BaseUrl | |||||
Lift BaseUrl | |||||
type Rep BaseUrl | |||||
Defined in Servant.Client.Core.BaseUrl type Rep BaseUrl = D1 ('MetaData "BaseUrl" "Servant.Client.Core.BaseUrl" "servant-client-core-0.20.2-L5ElDwTbUYTBmyljurWGev" 'False) (C1 ('MetaCons "BaseUrl" 'PrefixI 'True) ((S1 ('MetaSel ('Just "baseUrlScheme") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Scheme) :*: S1 ('MetaSel ('Just "baseUrlHost") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 String)) :*: (S1 ('MetaSel ('Just "baseUrlPort") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedUnpack) (Rec0 Int) :*: S1 ('MetaSel ('Just "baseUrlPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 String)))) |
Constructors
Response | |
Fields
|
Instances
Functor ResponseF | |||||
Foldable ResponseF | |||||
Defined in Servant.Client.Core.Response Methods fold :: Monoid m => ResponseF m -> m foldMap :: Monoid m => (a -> m) -> ResponseF a -> m foldMap' :: Monoid m => (a -> m) -> ResponseF a -> m foldr :: (a -> b -> b) -> b -> ResponseF a -> b foldr' :: (a -> b -> b) -> b -> ResponseF a -> b foldl :: (b -> a -> b) -> b -> ResponseF a -> b foldl' :: (b -> a -> b) -> b -> ResponseF a -> b foldr1 :: (a -> a -> a) -> ResponseF a -> a foldl1 :: (a -> a -> a) -> ResponseF a -> a elem :: Eq a => a -> ResponseF a -> Bool maximum :: Ord a => ResponseF a -> a minimum :: Ord a => ResponseF a -> a | |||||
Traversable ResponseF | |||||
Defined in Servant.Client.Core.Response | |||||
NFData a => NFData (ResponseF a) | |||||
Defined in Servant.Client.Core.Response | |||||
Generic (ResponseF a) | |||||
Defined in Servant.Client.Core.Response Associated Types
| |||||
Show a => Show (ResponseF a) | |||||
Eq a => Eq (ResponseF a) | |||||
type Rep (ResponseF a) | |||||
Defined in Servant.Client.Core.Response type Rep (ResponseF a) = D1 ('MetaData "ResponseF" "Servant.Client.Core.Response" "servant-client-core-0.20.2-L5ElDwTbUYTBmyljurWGev" 'False) (C1 ('MetaCons "Response" 'PrefixI 'True) ((S1 ('MetaSel ('Just "responseStatusCode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Status) :*: S1 ('MetaSel ('Just "responseHeaders") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Seq Header))) :*: (S1 ('MetaSel ('Just "responseHttpVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 HttpVersion) :*: S1 ('MetaSel ('Just "responseBody") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)))) |
data ClientError #
Constructors
FailureResponse (RequestF () (BaseUrl, ByteString)) Response | |
DecodeFailure Text Response | |
UnsupportedContentType MediaType Response | |
InvalidContentTypeHeader Response | |
ConnectionError SomeException |
Instances
NFData ClientError | |||||
Defined in Servant.Client.Core.ClientError Methods rnf :: ClientError -> () | |||||
Exception ClientError | |||||
Defined in Servant.Client.Core.ClientError Methods toException :: ClientError -> SomeException fromException :: SomeException -> Maybe ClientError displayException :: ClientError -> String backtraceDesired :: ClientError -> Bool | |||||
Generic ClientError | |||||
Defined in Servant.Client.Core.ClientError Associated Types
| |||||
Show ClientError | |||||
Defined in Servant.Client.Core.ClientError Methods showsPrec :: Int -> ClientError -> ShowS show :: ClientError -> String showList :: [ClientError] -> ShowS | |||||
Eq ClientError | |||||
Defined in Servant.Client.Core.ClientError | |||||
MonadError ClientError ClientM | |||||
Defined in Servant.Client.Internal.HttpClient Methods throwError :: ClientError -> ClientM a catchError :: ClientM a -> (ClientError -> ClientM a) -> ClientM a | |||||
MonadError ClientError ClientM | |||||
Defined in Servant.Client.Internal.HttpClient.Streaming Methods throwError :: ClientError -> ClientM a catchError :: ClientM a -> (ClientError -> ClientM a) -> ClientM a | |||||
type Rep ClientError | |||||
Defined in Servant.Client.Core.ClientError type Rep ClientError = D1 ('MetaData "ClientError" "Servant.Client.Core.ClientError" "servant-client-core-0.20.2-L5ElDwTbUYTBmyljurWGev" 'False) ((C1 ('MetaCons "FailureResponse" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (RequestF () (BaseUrl, ByteString))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Response)) :+: C1 ('MetaCons "DecodeFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Response))) :+: (C1 ('MetaCons "UnsupportedContentType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 MediaType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Response)) :+: (C1 ('MetaCons "InvalidContentTypeHeader" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Response)) :+: C1 ('MetaCons "ConnectionError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SomeException))))) |
Instances
Data Scheme | |||||
Defined in Servant.Client.Core.BaseUrl 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 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 | |||||
Generic Scheme | |||||
Defined in Servant.Client.Core.BaseUrl Associated Types
| |||||
Show Scheme | |||||
Eq Scheme | |||||
Ord Scheme | |||||
Lift Scheme | |||||
type Rep Scheme | |||||
Defined in Servant.Client.Core.BaseUrl type Rep Scheme = D1 ('MetaData "Scheme" "Servant.Client.Core.BaseUrl" "servant-client-core-0.20.2-L5ElDwTbUYTBmyljurWGev" 'False) (C1 ('MetaCons "Http" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Https" 'PrefixI 'False) (U1 :: Type -> Type)) |
data InvalidBaseUrlException #
Instances
Exception InvalidBaseUrlException | |
Defined in Servant.Client.Core.BaseUrl Methods toException :: InvalidBaseUrlException -> SomeException fromException :: SomeException -> Maybe InvalidBaseUrlException displayException :: InvalidBaseUrlException -> String backtraceDesired :: InvalidBaseUrlException -> Bool | |
Show InvalidBaseUrlException | |
Defined in Servant.Client.Core.BaseUrl Methods showsPrec :: Int -> InvalidBaseUrlException -> ShowS show :: InvalidBaseUrlException -> String showList :: [InvalidBaseUrlException] -> ShowS |
parseBaseUrl :: MonadThrow m => String -> m BaseUrl #
showBaseUrl :: BaseUrl -> String #
data EmptyClient #
Constructors
EmptyClient |
Instances
Bounded EmptyClient | |
Defined in Servant.Client.Core.HasClient | |
Enum EmptyClient | |
Defined in Servant.Client.Core.HasClient Methods succ :: EmptyClient -> EmptyClient pred :: EmptyClient -> EmptyClient toEnum :: Int -> EmptyClient fromEnum :: EmptyClient -> Int enumFrom :: EmptyClient -> [EmptyClient] enumFromThen :: EmptyClient -> EmptyClient -> [EmptyClient] enumFromTo :: EmptyClient -> EmptyClient -> [EmptyClient] enumFromThenTo :: EmptyClient -> EmptyClient -> EmptyClient -> [EmptyClient] | |
Show EmptyClient | |
Defined in Servant.Client.Core.HasClient Methods showsPrec :: Int -> EmptyClient -> ShowS show :: EmptyClient -> String showList :: [EmptyClient] -> ShowS | |
Eq EmptyClient | |
Defined in Servant.Client.Core.HasClient |
type StreamingResponse = ResponseF (SourceIO ByteString) #
foldMapUnion :: forall c a (as :: [Type]). All c as => Proxy c -> (forall x. c x => x -> a) -> Union as -> a #
matchUnion :: forall a (as :: [Type]). IsMember a as => Union as -> Maybe a #
data AsClientT (m :: Type -> Type) #
Instances
GenericMode (AsClientT m :: Type) | |
Defined in Servant.Client.Core.HasClient | |
type (AsClientT m :: Type) :- api | |
Defined in Servant.Client.Core.HasClient |