servant-client-0.20.2: Automatic derivation of querying functions for servant
Safe HaskellNone
LanguageHaskell2010

Servant.Client.Internal.HttpClient

Synopsis

Documentation

data ClientEnv Source #

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

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

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 :: Manager and baseurl :: BaseUrl around:

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

newtype ClientM a Source #

ClientM is the monad in which client functions run. Contains the Manager and BaseUrl used for requests in the reader environment.

Instances

Instances details
MonadIO ClientM Source # 
Instance details

Defined in Servant.Client.Internal.HttpClient

Methods

liftIO :: IO a -> ClientM a #

Applicative ClientM Source # 
Instance details

Defined in Servant.Client.Internal.HttpClient

Methods

pure :: a -> ClientM a #

(<*>) :: ClientM (a -> b) -> ClientM a -> ClientM b #

liftA2 :: (a -> b -> c) -> ClientM a -> ClientM b -> ClientM c #

(*>) :: ClientM a -> ClientM b -> ClientM b #

(<*) :: ClientM a -> ClientM b -> ClientM a #

Functor ClientM Source # 
Instance details

Defined in Servant.Client.Internal.HttpClient

Methods

fmap :: (a -> b) -> ClientM a -> ClientM b #

(<$) :: a -> ClientM b -> ClientM a #

Monad ClientM Source # 
Instance details

Defined in Servant.Client.Internal.HttpClient

Methods

(>>=) :: ClientM a -> (a -> ClientM b) -> ClientM b #

(>>) :: ClientM a -> ClientM b -> ClientM b #

return :: a -> ClientM a #

MonadCatch ClientM Source # 
Instance details

Defined in Servant.Client.Internal.HttpClient

Methods

catch :: (HasCallStack, Exception e) => ClientM a -> (e -> ClientM a) -> ClientM a #

MonadMask ClientM Source # 
Instance details

Defined in Servant.Client.Internal.HttpClient

Methods

mask :: HasCallStack => ((forall a. ClientM a -> ClientM a) -> ClientM b) -> ClientM b #

uninterruptibleMask :: HasCallStack => ((forall a. ClientM a -> ClientM a) -> ClientM b) -> ClientM b #

generalBracket :: HasCallStack => ClientM a -> (a -> ExitCase b -> ClientM c) -> (a -> ClientM b) -> ClientM (b, c) #

MonadThrow ClientM Source # 
Instance details

Defined in Servant.Client.Internal.HttpClient

Methods

throwM :: (HasCallStack, Exception e) => e -> ClientM a #

Alt ClientM Source #

Try clients in order, last error is preserved.

Instance details

Defined in Servant.Client.Internal.HttpClient

RunClient ClientM Source # 
Instance details

Defined in Servant.Client.Internal.HttpClient

MonadBaseControl IO ClientM Source # 
Instance details

Defined in Servant.Client.Internal.HttpClient

Associated Types

type StM ClientM a #

MonadError ClientError ClientM Source # 
Instance details

Defined in Servant.Client.Internal.HttpClient

MonadReader ClientEnv ClientM Source # 
Instance details

Defined in Servant.Client.Internal.HttpClient

Methods

ask :: ClientM ClientEnv #

local :: (ClientEnv -> ClientEnv) -> ClientM a -> ClientM a #

reader :: (ClientEnv -> a) -> ClientM a #

MonadBase IO ClientM Source # 
Instance details

Defined in Servant.Client.Internal.HttpClient

Methods

liftBase :: IO α -> ClientM α #

Generic (ClientM a) Source # 
Instance details

Defined in Servant.Client.Internal.HttpClient

Associated Types

type Rep (ClientM a) :: Type -> Type #

Methods

from :: ClientM a -> Rep (ClientM a) x #

to :: Rep (ClientM a) x -> ClientM a #

type StM ClientM a Source # 
Instance details

Defined in Servant.Client.Internal.HttpClient

type Rep (ClientM a) Source # 
Instance details

Defined in Servant.Client.Internal.HttpClient

defaultMakeClientRequest :: BaseUrl -> Request -> IO Request Source #

Create a http-client Request from a servant RequestF The host, path and port fields are extracted from the BaseUrl otherwise the body, headers and query string are derived from the servant RequestF