servant-client-0.10: automatical derivation of querying functions for servant webservices

Safe HaskellNone
LanguageHaskell2010

Servant.Common.Req

Contents

Synopsis

Documentation

data Req Source #

Constructors

Req 

appendToQueryString Source #

Arguments

:: Text

param name

-> Maybe Text

param value

-> Req 
-> Req 

setRQBody :: ByteString -> MediaType -> Req -> Req Source #

Deprecated: Use setReqBodyLBS instead

Set body and media type of the request being constructed.

The body is set to the given bytestring using the RequestBodyLBS constructor.

setReqBodyLBS :: ByteString -> MediaType -> Req -> Req Source #

Set body and media type of the request being constructed.

The body is set to the given bytestring using the RequestBodyLBS constructor.

Since: 0.9.2.0

setReqBody :: RequestBody -> MediaType -> Req -> Req Source #

Set body and media type of the request being constructed.

Since: 0.9.2.0

performing requests

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

Monad ClientM Source # 

Methods

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

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

return :: a -> ClientM a #

fail :: String -> ClientM a #

Functor ClientM Source # 

Methods

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

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

Applicative ClientM Source # 

Methods

pure :: a -> ClientM a #

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

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

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

MonadIO ClientM Source # 

Methods

liftIO :: IO a -> ClientM a #

MonadThrow ClientM Source # 

Methods

throwM :: Exception e => e -> ClientM a #

MonadCatch ClientM Source # 

Methods

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

Alt ClientM Source #

Try clients in order, last error is preserved.

MonadBase IO ClientM Source # 

Methods

liftBase :: IO α -> ClientM α #

MonadBaseControl IO ClientM Source # 

Associated Types

type StM (ClientM :: * -> *) a :: * #

MonadError ServantError ClientM Source # 
MonadReader ClientEnv ClientM Source # 

Methods

ask :: ClientM ClientEnv #

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

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

Generic (ClientM a) Source # 

Associated Types

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

Methods

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

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

ClientLike (ClientM a) (ClientM a) Source # 

Methods

mkClient :: ClientM a -> ClientM a Source #

type StM ClientM a Source # 
type Rep (ClientM a) Source # 
type Rep (ClientM a) = D1 (MetaData "ClientM" "Servant.Common.Req" "servant-client-0.10-5hSWIFWz0Ou26EqOFBVxb2" True) (C1 (MetaCons "ClientM" PrefixI True) (S1 (MetaSel (Just Symbol "runClientM'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ReaderT * ClientEnv (ExceptT ServantError IO) a))))

performRequestCT :: MimeUnrender ct result => Proxy ct -> Method -> Req -> ClientM ([Header], result) Source #