| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Servant.Client.Internal.HttpClient
Synopsis
- data ClientEnv = ClientEnv {
- manager :: Manager
 - baseUrl :: BaseUrl
 - cookieJar :: Maybe (TVar CookieJar)
 - makeClientRequest :: BaseUrl -> Request -> IO Request
 - middleware :: ClientMiddleware
 
 - type ClientApplication = Request -> ClientM Response
 - type ClientMiddleware = ClientApplication -> ClientApplication
 - mkClientEnv :: Manager -> BaseUrl -> ClientEnv
 - client :: HasClient ClientM api => Proxy api -> Client ClientM api
 - hoistClient :: HasClient ClientM api => Proxy api -> (forall a. m a -> n a) -> Client m api -> Client n api
 - newtype ClientM a = ClientM {}
 - runClientM :: ClientM a -> ClientEnv -> IO (Either ClientError a)
 - performRequest :: Maybe [Status] -> Request -> ClientM Response
 - mkFailureResponse :: BaseUrl -> Request -> ResponseF ByteString -> ClientError
 - clientResponseToResponse :: (a -> b) -> Response a -> ResponseF b
 - defaultMakeClientRequest :: BaseUrl -> Request -> IO Request
 - catchConnectionError :: IO a -> IO (Either ClientError a)
 
Documentation
The environment in which a request is run.
   The $sel:baseUrl:ClientEnv and $sel:makeClientRequest:ClientEnv 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 $sel:manager:ClientEnv.
   The $sel:makeClientRequest:ClientEnv function can be used to modify the request to execute and set values which
   are not specified on a servant RequestF like responseTimeout or redirectCount
Constructors
| ClientEnv | |
Fields 
  | |
Instances
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 apihoistClient :: 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
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 #
mkFailureResponse :: BaseUrl -> Request -> ResponseF ByteString -> ClientError Source #
clientResponseToResponse :: (a -> b) -> Response a -> ResponseF b Source #
catchConnectionError :: IO a -> IO (Either ClientError a) Source #