Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides client
which can automatically generate
querying functions for each endpoint just from the type representing your
API.
- client :: HasClient ClientM api => Proxy api -> Client ClientM api
- data ClientM a
- runClientM :: ClientM a -> ClientEnv -> IO (Either ServantError a)
- data ClientEnv = ClientEnv {}
- mkClientEnv :: Manager -> BaseUrl -> ClientEnv
- module Servant.Client.Core.Reexport
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.
Monad ClientM Source # | |
Functor ClientM Source # | |
Applicative ClientM Source # | |
MonadIO ClientM Source # | |
MonadThrow ClientM Source # | |
MonadCatch ClientM Source # | |
Alt ClientM Source # | Try clients in order, last error is preserved. |
RunClient ClientM Source # | |
MonadBase IO ClientM Source # | |
MonadBaseControl IO ClientM Source # | |
MonadReader ClientEnv ClientM Source # | |
MonadError ServantError ClientM Source # | |
Generic (ClientM a) Source # | |
ClientLike (ClientM a) (ClientM a) Source # | |
type StM ClientM a Source # | |
type Rep (ClientM a) Source # | |
runClientM :: ClientM a -> ClientEnv -> IO (Either ServantError a) Source #
The environment in which a request is run.
module Servant.Client.Core.Reexport