Safe Haskell | None |
---|---|
Language | Haskell2010 |
See symantic-http-demo for an example of how to use this module.
Synopsis
- newtype Client callers k = Client {
- unClient :: (ClientModifier -> k) -> callers
- client :: Client callers ClientRequest -> callers
- type ClientModifier = ClientRequest -> ClientRequest
- newtype ClientBodyArg (ts :: [*]) a = ClientBodyArg a
- newtype ClientBodyStreamArg framing (ts :: [*]) as = ClientBodyStreamArg as
- newtype ClientConn m a = ClientConn {
- unClientConn :: m a
- data ClientEnv = ClientEnv {}
- clientEnv :: Manager -> URI -> ClientEnv
- data ClientError
- data ClientRequest = ClientRequest {}
- clientRequest :: URI -> ClientRequest -> Request
- type ClientConnection = ClientConn (ReaderT ClientEnv (ExceptT ClientError IO))
- runClient :: ClientConnectionConstraint a ts => ClientConnectionClass a ts => ClientEnv -> (Proxy ts -> Proxy a -> ClientRequest) -> IO (Either ClientError a)
- class ClientConnectionClass a (ts :: [*]) where
- type ClientConnectionConstraint a ts :: Constraint
- clientConnection :: ClientConnectionConstraint a ts => (Proxy ts -> Proxy a -> ClientRequest) -> ClientConnection a
- doClientRequest :: ClientRequest -> ClientConnection ClientResponse
- catchClientConnectionError :: IO a -> IO (Either ClientError a)
- type ClientResponse = Response ByteString
- type ClientConnectionStream = ClientConn (ReaderT ClientEnv (Codensity (ExceptT ClientError IO)))
- runClientStream :: FramingDecode framing as => MonadExec IO (FramingMonad as) => MimeTypes ts (MimeDecodable (FramingYield as)) => ClientEnv -> (Proxy framing -> Proxy ts -> Proxy as -> ClientRequest) -> (as -> IO b) -> IO (Either ClientError b)
- clientConnectionStream :: forall as ts framing. FramingDecode framing as => MonadExec IO (FramingMonad as) => MimeTypes ts (MimeDecodable (FramingYield as)) => (Proxy framing -> Proxy ts -> Proxy as -> ClientRequest) -> ClientConnectionStream as
- doClientRequestStream :: forall (ts :: [*]) as. MimeTypes ts (MimeDecodable (FramingYield as)) => Proxy ts -> ClientRequest -> (MimeType (MimeDecodable (FramingYield as)) -> Response BodyReader -> ExceptT ClientError IO as) -> ClientConnectionStream as
- newtype Codensity m a = Codensity {
- runCodensity :: forall b. (a -> m b) -> m b
Type Client
newtype Client callers k Source #
(
) is a recipe to produce a Client
a kClientRequest
from returned (callers
) (one per number of alternative routes)
separated by (:!:
).
Client
is analogous to a printf using the API as a format customized for HTTP routing.
Client | |
|
Instances
client :: Client callers ClientRequest -> callers Source #
returns the client
callersClientRequest
builders from the given API.
Type ClientModifier
type ClientModifier = ClientRequest -> ClientRequest Source #
Type ClientBodyArg
newtype ClientBodyArg (ts :: [*]) a Source #
Type ClientBodyStreamArg
newtype ClientBodyStreamArg framing (ts :: [*]) as Source #
Type ClientConn
newtype ClientConn m a Source #
A monadic connection from a client to a server.
It is specialized in ClientConnection
and ClientConnectionStream
.
NOTE: no Monad
transformer is put within this newtype
to let monad-classes
handle all the |lift|ing.
ClientConn | |
|
Instances
Type ClientEnv
Type ClientError
data ClientError Source #
ClientError_FailureResponse ClientResponse | The server returned an error response |
ClientError_DecodeFailure String ClientResponse | The body could not be decoded at the expected type |
ClientError_UnsupportedContentType ByteString ClientResponse | The content-type of the response is not supported |
ClientError_ConnectionError HttpException | There was a connection error, and no response was received |
ClientError_EmptyClient |
|
Instances
Eq ClientError Source # | |
Defined in Symantic.HTTP.Client (==) :: ClientError -> ClientError -> Bool # (/=) :: ClientError -> ClientError -> Bool # | |
Show ClientError Source # | |
Defined in Symantic.HTTP.Client showsPrec :: Int -> ClientError -> ShowS # show :: ClientError -> String # showList :: [ClientError] -> ShowS # | |
Exception ClientError Source # | |
Defined in Symantic.HTTP.Client |
Type ClientRequest
data ClientRequest Source #
Instances
Show ClientRequest Source # | |
Defined in Symantic.HTTP.Client showsPrec :: Int -> ClientRequest -> ShowS # show :: ClientRequest -> String # showList :: [ClientRequest] -> ShowS # |
clientRequest :: URI -> ClientRequest -> Request Source #
Type ClientConnection
type ClientConnection = ClientConn (ReaderT ClientEnv (ExceptT ClientError IO)) Source #
runClient :: ClientConnectionConstraint a ts => ClientConnectionClass a ts => ClientEnv -> (Proxy ts -> Proxy a -> ClientRequest) -> IO (Either ClientError a) Source #
Class ClientConnectionClass
class ClientConnectionClass a (ts :: [*]) where Source #
clientConnection
is different when ts
is empty:
no mimeDecode
is performed.
This is used by the raw
combinator.
type ClientConnectionConstraint a ts :: Constraint Source #
clientConnection :: ClientConnectionConstraint a ts => (Proxy ts -> Proxy a -> ClientRequest) -> ClientConnection a Source #
Instances
ClientConnectionClass ClientResponse ([] :: [Type]) Source # | |
Defined in Symantic.HTTP.Client type ClientConnectionConstraint ClientResponse [] :: Constraint Source # clientConnection :: (Proxy [] -> Proxy ClientResponse -> ClientRequest) -> ClientConnection ClientResponse Source # | |
ClientConnectionClass a (t ': ts) Source # | |
Defined in Symantic.HTTP.Client type ClientConnectionConstraint a (t ': ts) :: Constraint Source # clientConnection :: (Proxy (t ': ts) -> Proxy a -> ClientRequest) -> ClientConnection a Source # |
catchClientConnectionError :: IO a -> IO (Either ClientError a) Source #
Type ClientResponse
type ClientResponse = Response ByteString Source #
Type ClientConnectionStream
type ClientConnectionStream = ClientConn (ReaderT ClientEnv (Codensity (ExceptT ClientError IO))) Source #
runClientStream :: FramingDecode framing as => MonadExec IO (FramingMonad as) => MimeTypes ts (MimeDecodable (FramingYield as)) => ClientEnv -> (Proxy framing -> Proxy ts -> Proxy as -> ClientRequest) -> (as -> IO b) -> IO (Either ClientError b) Source #
clientConnectionStream :: forall as ts framing. FramingDecode framing as => MonadExec IO (FramingMonad as) => MimeTypes ts (MimeDecodable (FramingYield as)) => (Proxy framing -> Proxy ts -> Proxy as -> ClientRequest) -> ClientConnectionStream as Source #
doClientRequestStream :: forall (ts :: [*]) as. MimeTypes ts (MimeDecodable (FramingYield as)) => Proxy ts -> ClientRequest -> (MimeType (MimeDecodable (FramingYield as)) -> Response BodyReader -> ExceptT ClientError IO as) -> ClientConnectionStream as Source #
Type Codensity
newtype Codensity m a Source #
Copy from the kan-extensions
package to avoid the dependencies.
Codensity | |
|
Orphan instances
Eq HttpException Source # | |
(==) :: HttpException -> HttpException -> Bool # (/=) :: HttpException -> HttpException -> Bool # | |
ToHttpApiData ByteString Source # | |
toUrlPiece :: ByteString -> Text # toEncodedUrlPiece :: ByteString -> Builder # toHeader :: ByteString -> ByteString # toQueryParam :: ByteString -> Text # |