| 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 {}
- mkClientEnv :: Manager -> BaseUrl -> ClientEnv
- defaultMakeClientRequest :: BaseUrl -> Request -> Request
- hoistClient :: HasClient ClientM api => Proxy api -> (forall a. m a -> n a) -> Client m api -> Client n api
- 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 apiClientM 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 
 | |
Instances
| MonadReader ClientEnv ClientM Source # | |
| MonadReader ClientEnv ClientM Source # | |
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
   Managerbaseurl ::  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
module Servant.Client.Core.Reexport