symantic-http-client-0.0.1.20190410: symantic-http applied to the derivation of HTTP clients

Safe HaskellNone
LanguageHaskell2010

Symantic.HTTP.Client

Contents

Description

See symantic-http-demo for an example of how to use this module.

Synopsis

Type Client

newtype Client callers k Source #

(Client a k) is a recipe to produce a ClientRequest 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.

Constructors

Client 

Fields

Instances
Cat Client Source # 
Instance details

Defined in Symantic.HTTP.Client

Methods

(<.>) :: Client a b -> Client b c -> Client a c #

Alt Client Source # 
Instance details

Defined in Symantic.HTTP.Client

Methods

(<!>) :: Client a k -> Client b k -> Client (a :!: b) k #

Pro Client Source # 
Instance details

Defined in Symantic.HTTP.Client

Methods

dimap :: (a -> b) -> (b -> a) -> Client (a -> k) k -> Client (b -> k) k #

HTTP_Raw Client Source # 
Instance details

Defined in Symantic.HTTP.Client

Associated Types

type RawConstraint Client :: Constraint #

type RawArgs Client :: Type #

type Raw Client :: Type #

HTTP_Path Client Source # 
Instance details

Defined in Symantic.HTTP.Client

Associated Types

type PathConstraint Client a :: Constraint #

Methods

segment :: PathSegment -> Client k k #

capture' :: PathConstraint Client a => Name -> Client (a -> k) k #

captureAll :: Client ([PathSegment] -> k) k #

HTTP_Header Client Source # 
Instance details

Defined in Symantic.HTTP.Client

Methods

header :: HeaderName -> Client (HeaderValue -> k) k #

HTTP_Body Client Source # 
Instance details

Defined in Symantic.HTTP.Client

Associated Types

type BodyArg Client a ts :: Type #

type BodyConstraint Client a ts :: Constraint #

Methods

body' :: BodyConstraint Client a ts => Client (BodyArg Client a ts -> k) k #

HTTP_BodyStream Client Source # 
Instance details

Defined in Symantic.HTTP.Client

Associated Types

type BodyStreamArg Client as ts framing :: Type #

type BodyStreamConstraint Client as ts framing :: Constraint #

Methods

bodyStream' :: BodyStreamConstraint Client as ts framing => Client (BodyStreamArg Client as ts framing -> k) k #

HTTP_Query Client Source # 
Instance details

Defined in Symantic.HTTP.Client

Associated Types

type QueryConstraint Client a :: Constraint #

HTTP_BasicAuth Client Source # 
Instance details

Defined in Symantic.HTTP.Client

Associated Types

type BasicAuthConstraint Client a :: Constraint #

type BasicAuthArgs Client a k :: Type #

HTTP_Version Client Source # 
Instance details

Defined in Symantic.HTTP.Client

Methods

version :: HttpVersion -> Client k k #

HTTP_Response Client Source # 
Instance details

Defined in Symantic.HTTP.Client

Associated Types

type ResponseConstraint Client a ts :: Constraint #

type ResponseArgs Client a ts :: Type #

type Response Client :: Type #

HTTP_ResponseStream Client Source # 
Instance details

Defined in Symantic.HTTP.Client

Associated Types

type ResponseStreamConstraint Client as ts framing :: Constraint #

type ResponseStreamArgs Client as ts framing :: Type #

type ResponseStream Client :: Type #

type Raw Client Source # 
Instance details

Defined in Symantic.HTTP.Client

type RawArgs Client Source # 
Instance details

Defined in Symantic.HTTP.Client

type RawConstraint Client Source # 
Instance details

Defined in Symantic.HTTP.Client

type Response Client Source # 
Instance details

Defined in Symantic.HTTP.Client

type ResponseStream Client Source # 
Instance details

Defined in Symantic.HTTP.Client

type PathConstraint Client a Source # 
Instance details

Defined in Symantic.HTTP.Client

type QueryConstraint Client a Source # 
Instance details

Defined in Symantic.HTTP.Client

type BasicAuthConstraint Client a Source # 
Instance details

Defined in Symantic.HTTP.Client

type BodyConstraint Client a ts Source # 
Instance details

Defined in Symantic.HTTP.Client

type BodyArg Client a ts Source # 
Instance details

Defined in Symantic.HTTP.Client

type BodyArg Client a ts = ClientBodyArg ts a
type BasicAuthArgs Client a k Source # 
Instance details

Defined in Symantic.HTTP.Client

type ResponseArgs Client a ts Source # 
Instance details

Defined in Symantic.HTTP.Client

type ResponseConstraint Client a ts Source # 
Instance details

Defined in Symantic.HTTP.Client

type BodyStreamConstraint Client as ts framing Source # 
Instance details

Defined in Symantic.HTTP.Client

type BodyStreamConstraint Client as ts framing = (FramingEncode framing as, MimeTypes ts (MimeEncodable (FramingYield as)))
type BodyStreamArg Client as ts framing Source # 
Instance details

Defined in Symantic.HTTP.Client

type BodyStreamArg Client as ts framing = ClientBodyStreamArg framing ts as
type ResponseStreamArgs Client as ts framing Source # 
Instance details

Defined in Symantic.HTTP.Client

type ResponseStreamArgs Client as ts framing = Proxy framing -> Proxy ts -> Proxy as -> ClientRequest
type ResponseStreamConstraint Client as ts framing Source # 
Instance details

Defined in Symantic.HTTP.Client

client :: Client callers ClientRequest -> callers Source #

client callers returns the ClientRequest builders from the given API.

Type ClientModifier

Type ClientBodyArg

newtype ClientBodyArg (ts :: [*]) a Source #

Constructors

ClientBodyArg a 

Type ClientBodyStreamArg

newtype ClientBodyStreamArg framing (ts :: [*]) as Source #

Constructors

ClientBodyStreamArg as 

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.

Constructors

ClientConn 

Fields

Instances
MonadTrans ClientConn Source # 
Instance details

Defined in Symantic.HTTP.Client

Methods

lift :: Monad m => m a -> ClientConn m a #

Monad m => Monad (ClientConn m) Source # 
Instance details

Defined in Symantic.HTTP.Client

Methods

(>>=) :: ClientConn m a -> (a -> ClientConn m b) -> ClientConn m b #

(>>) :: ClientConn m a -> ClientConn m b -> ClientConn m b #

return :: a -> ClientConn m a #

fail :: String -> ClientConn m a #

Functor m => Functor (ClientConn m) Source # 
Instance details

Defined in Symantic.HTTP.Client

Methods

fmap :: (a -> b) -> ClientConn m a -> ClientConn m b #

(<$) :: a -> ClientConn m b -> ClientConn m a #

Applicative m => Applicative (ClientConn m) Source # 
Instance details

Defined in Symantic.HTTP.Client

Methods

pure :: a -> ClientConn m a #

(<*>) :: ClientConn m (a -> b) -> ClientConn m a -> ClientConn m b #

liftA2 :: (a -> b -> c) -> ClientConn m a -> ClientConn m b -> ClientConn m c #

(*>) :: ClientConn m a -> ClientConn m b -> ClientConn m b #

(<*) :: ClientConn m a -> ClientConn m b -> ClientConn m a #

type CanDo (ClientConn m) (eff :: Type) Source #

All supported effects are handled by nested Monads.

Instance details

Defined in Symantic.HTTP.Client

type CanDo (ClientConn m) (eff :: Type) = False

Type ClientEnv

Type ClientError

data ClientError Source #

Constructors

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

ClientConn is empty

Type ClientRequest

Type ClientConnection

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.

Associated Types

type ClientConnectionConstraint a ts :: Constraint Source #

Instances
ClientConnectionClass ClientResponse ([] :: [Type]) Source # 
Instance details

Defined in Symantic.HTTP.Client

ClientConnectionClass a (t ': ts) Source # 
Instance details

Defined in Symantic.HTTP.Client

Associated Types

type ClientConnectionConstraint a (t ': ts) :: Constraint Source #

Type ClientResponse

Type ClientConnectionStream

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 #

Type Codensity

newtype Codensity m a Source #

Copy from the kan-extensions package to avoid the dependencies.

Constructors

Codensity 

Fields

Instances
MonadTrans Codensity Source # 
Instance details

Defined in Symantic.HTTP.Client

Methods

lift :: Monad m => m a -> Codensity m a #

Monad (Codensity f) Source # 
Instance details

Defined in Symantic.HTTP.Client

Methods

(>>=) :: Codensity f a -> (a -> Codensity f b) -> Codensity f b #

(>>) :: Codensity f a -> Codensity f b -> Codensity f b #

return :: a -> Codensity f a #

fail :: String -> Codensity f a #

Functor (Codensity k) Source # 
Instance details

Defined in Symantic.HTTP.Client

Methods

fmap :: (a -> b) -> Codensity k a -> Codensity k b #

(<$) :: a -> Codensity k b -> Codensity k a #

Applicative (Codensity f) Source # 
Instance details

Defined in Symantic.HTTP.Client

Methods

pure :: a -> Codensity f a #

(<*>) :: Codensity f (a -> b) -> Codensity f a -> Codensity f b #

liftA2 :: (a -> b -> c) -> Codensity f a -> Codensity f b -> Codensity f c #

(*>) :: Codensity f a -> Codensity f b -> Codensity f b #

(<*) :: Codensity f a -> Codensity f b -> Codensity f a #

type CanDo (Codensity m) (EffExec eff :: Type) Source # 
Instance details

Defined in Symantic.HTTP.Client

type CanDo (Codensity m) (EffExec eff :: Type) = False

Orphan instances