symantic-http-0.1.1.20190410: Symantic combinators for deriving clients or a server from an HTTP API

Safe HaskellSafe
LanguageHaskell2010

Symantic.HTTP.API

Contents

Description

Combinators to build a Web API.

Synopsis

Class Cat

class Cat repr where Source #

A soft and cute animal asking strokes and croquettes. Or rather here a composition of two combinators (as in a category without an identity morphism).

Note that the order of combinators generally matters (the left one is applied first), with the notable exception of the server instance where some HTTP error codes must be prioritized.

Minimal complete definition

Nothing

Methods

(<.>) :: repr a b -> repr b c -> repr a c infixr 4 Source #

(<.>) :: Trans repr => Cat (UnTrans repr) => repr a b -> repr b c -> repr a c infixr 4 Source #

Class Alt

class Alt repr where Source #

There are two choices, either the right one or the left one. The (:!:) data type will be used in the instances to get multiple client callers or to supply multiple server handlers.

Minimal complete definition

Nothing

Methods

(<!>) :: repr a k -> repr b k -> repr (a :!: b) k infixr 3 Source #

(<!>) :: Trans repr => Alt (UnTrans repr) => repr a k -> repr b k -> repr (a :!: b) k infixr 3 Source #

Type (:!:)

data a :!: b infixr 3 Source #

Like (,) but infixr. Used to get alternative commands from a Client or to supply alternative handlers to a Server.

Constructors

a :!: b infixr 3 

Class Trans

class Trans repr where Source #

A Transformation from one representation (UnTrans repr) to another one (repr).

  • noTrans lifts to the identity Transformation (the one which does nothing wrt. the UnTransformed (repr)esentation).
  • unTrans unlifts a Transformed value to its underlying (repr)esentation.

At its class definition, a combinator should be defined with a default value using noTrans. And at its instance definition, a combinator can be overwritten to apply a specific Transformation for (repr).

For an example, see the (Trans (Router repr)) instance in symantic-http-server.

Associated Types

type UnTrans repr :: * -> * -> * Source #

The (repr)esentation that (repr) Transforms.

Methods

noTrans :: UnTrans repr a b -> repr a b Source #

Lift the underlying (repr)esentation to (repr). Useful to define a combinator that does nothing in a Transformation.

unTrans :: repr a b -> UnTrans repr a b Source #

Unlift a (repr)esentation. Useful when a Transformation combinator needs to access the UnTransformed (repr)esentation, or at the end to get the underlying UnTransformed (repr)esentation from the inferred (repr) value (eg. in server).

Class Pro

class Pro repr where Source #

Mainly useful to write a combinator which is a specialization of another (eg. queryFlag wrt. queryParams), by calling it directly in the class declaration instead of rewriting its logic in the instance declaration.

Because type (a) is asked by a Client but given to a Server, both (a->b) and (b->a) are used. This is reminiscent of a Profunctor. Hence the names Pro and dimap.

Minimal complete definition

Nothing

Methods

dimap :: (a -> b) -> (b -> a) -> repr (a -> k) k -> repr (b -> k) k Source #

dimap :: Trans repr => Pro (UnTrans repr) => (a -> b) -> (b -> a) -> repr (a -> k) k -> repr (b -> k) k Source #

Class HTTP_Raw

class HTTP_Raw repr where Source #

Minimal complete definition

Nothing

Associated Types

type RawConstraint repr :: Constraint Source #

type RawArgs repr :: * Source #

type Raw repr :: * Source #

Methods

raw :: RawConstraint repr => repr (RawArgs repr) (Raw repr) Source #

raw :: Trans repr => HTTP_Raw (UnTrans repr) => RawConstraint (UnTrans repr) => RawArgs (UnTrans repr) ~ RawArgs repr => Raw (UnTrans repr) ~ Raw repr => repr (RawArgs repr) (Raw repr) Source #

Class HTTP_Path

class HTTP_Path repr where Source #

Minimal complete definition

Nothing

Associated Types

type PathConstraint repr a :: Constraint Source #

Methods

segment :: PathSegment -> repr k k Source #

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

captureAll :: repr ([PathSegment] -> k) k Source #

segment :: Trans repr => HTTP_Path (UnTrans repr) => PathSegment -> repr k k Source #

capture' :: Trans repr => HTTP_Path (UnTrans repr) => PathConstraint (UnTrans repr) a => Name -> repr (a -> k) k Source #

captureAll :: Trans repr => HTTP_Path (UnTrans repr) => repr ([PathSegment] -> k) k Source #

(</>) :: Cat repr => HTTP_Path repr => PathSegment -> repr a b -> repr a b infixr 4 Source #

Convenient wrapper of segment.

capture :: forall a k repr. HTTP_Path repr => PathConstraint repr a => Name -> repr (a -> k) k Source #

Like capture' but with the type variable (a) first instead or (repr) so it can be passed using TypeApplications without adding a |@_| for (repr).

Class HTTP_Header

class HTTP_Header repr where Source #

Minimal complete definition

Nothing

Methods

header :: HeaderName -> repr (HeaderValue -> k) k Source #

header :: Trans repr => HTTP_Header (UnTrans repr) => HeaderName -> repr (HeaderValue -> k) k Source #

Class HTTP_Body

class HTTP_Body repr where Source #

Minimal complete definition

Nothing

Associated Types

type BodyArg repr a (ts :: [*]) :: * Source #

type BodyConstraint repr a (ts :: [*]) :: Constraint Source #

Methods

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

body' :: forall a (ts :: [*]) k. Trans repr => HTTP_Body (UnTrans repr) => BodyConstraint (UnTrans repr) a ts => BodyArg repr a ts ~ BodyArg (UnTrans repr) a ts => repr (BodyArg repr a ts -> k) k Source #

body :: forall a ts k repr. HTTP_Body repr => BodyConstraint repr a ts => repr (BodyArg repr a ts -> k) k Source #

Like body' but with the type variables (a) and (ts) first instead or (repr), so it can be passed using TypeApplications without adding a |@_| for (repr).

Class HTTP_BodyStream

class HTTP_BodyStream repr where Source #

Minimal complete definition

Nothing

Associated Types

type BodyStreamArg repr as (ts :: [*]) framing :: * Source #

type BodyStreamConstraint repr as (ts :: [*]) framing :: Constraint Source #

Methods

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

bodyStream' :: forall as ts framing k. Trans repr => HTTP_BodyStream (UnTrans repr) => BodyStreamConstraint (UnTrans repr) as ts framing => BodyStreamArg repr as ts framing ~ BodyStreamArg (UnTrans repr) as ts framing => repr (BodyStreamArg repr as ts framing -> k) k Source #

bodyStream :: forall as ts framing k repr. HTTP_BodyStream repr => BodyStreamConstraint repr as ts framing => repr (BodyStreamArg repr as ts framing -> k) k Source #

Like bodyStream' but with the type variables (as), (ts) and (framing) first instead or (repr), so it can be passed using TypeApplications without adding a |@_| for (repr).

Class HTTP_Query

class HTTP_Query repr where Source #

Minimal complete definition

Nothing

Associated Types

type QueryConstraint repr a :: Constraint Source #

Methods

queryParams' :: QueryConstraint repr a => QueryName -> repr ([a] -> k) k Source #

queryFlag :: QueryConstraint repr Bool => QueryName -> repr (Bool -> k) k Source #

queryFlag :: Pro repr => QueryConstraint repr Bool => QueryName -> repr (Bool -> k) k Source #

queryParams' :: Trans repr => HTTP_Query (UnTrans repr) => QueryConstraint (UnTrans repr) a => QueryName -> repr ([a] -> k) k Source #

queryParams :: forall a k repr. HTTP_Query repr => QueryConstraint repr a => QueryName -> repr ([a] -> k) k Source #

Like capture' but with the type variable (a) first instead or (repr) so it can be passed using TypeApplications without adding a |@_| for (repr).

Class HTTP_BasicAuth

class HTTP_BasicAuth repr where Source #

Minimal complete definition

Nothing

Associated Types

type BasicAuthConstraint repr a :: Constraint Source #

type BasicAuthArgs repr a k :: * Source #

Methods

basicAuth' :: BasicAuthConstraint repr a => BasicAuthRealm -> repr (BasicAuthArgs repr a k) k Source #

basicAuth' :: forall a k. Trans repr => HTTP_BasicAuth (UnTrans repr) => BasicAuthConstraint (UnTrans repr) a => BasicAuthArgs repr a k ~ BasicAuthArgs (UnTrans repr) a k => BasicAuthRealm -> repr (BasicAuthArgs repr a k) k Source #

basicAuth :: forall a k repr. HTTP_BasicAuth repr => BasicAuthConstraint repr a => BasicAuthRealm -> repr (BasicAuthArgs repr a k) k Source #

Like basicAuth' but with the type variable (a) first instead or (repr) so it can be passed using TypeApplications without adding a |@_| for (repr).

Type BasicAuth

data BasicAuth usr Source #

Instances
Functor BasicAuth Source # 
Instance details

Defined in Symantic.HTTP.API

Methods

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

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

Eq usr => Eq (BasicAuth usr) Source # 
Instance details

Defined in Symantic.HTTP.API

Methods

(==) :: BasicAuth usr -> BasicAuth usr -> Bool #

(/=) :: BasicAuth usr -> BasicAuth usr -> Bool #

Show usr => Show (BasicAuth usr) Source # 
Instance details

Defined in Symantic.HTTP.API

Methods

showsPrec :: Int -> BasicAuth usr -> ShowS #

show :: BasicAuth usr -> String #

showList :: [BasicAuth usr] -> ShowS #

Class HTTP_Version

class HTTP_Version repr where Source #

Methods

version :: HttpVersion -> repr k k Source #

Class HTTP_Response

class HTTP_Response repr where Source #

Minimal complete definition

Nothing

Associated Types

type ResponseConstraint repr a (ts :: [*]) :: Constraint Source #

type ResponseArgs repr a (ts :: [*]) :: * Source #

type Response repr :: * Source #

Methods

response :: ResponseConstraint repr a ts => Method -> repr (ResponseArgs repr a ts) (Response repr) Source #

response :: forall a ts. Trans repr => HTTP_Response (UnTrans repr) => ResponseConstraint (UnTrans repr) a ts => ResponseArgs repr a ts ~ ResponseArgs (UnTrans repr) a ts => Response repr ~ Response (UnTrans repr) => Method -> repr (ResponseArgs repr a ts) (Response repr) Source #

get :: forall a ts repr. HTTP_Response repr => ResponseConstraint repr a ts => repr (ResponseArgs repr a ts) (Response repr) Source #

Wrap response by giving it the corresponding Method, and put the type variables (a) then (ts) first instead or (repr) so they can be passed using TypeApplications without adding a |_| for (repr)@.

head :: forall a ts repr. HTTP_Response repr => ResponseConstraint repr a ts => repr (ResponseArgs repr a ts) (Response repr) Source #

Wrap response by giving it the corresponding Method, and put the type variables (a) then (ts) first instead or (repr) so they can be passed using TypeApplications without adding a |_| for (repr)@.

put :: forall a ts repr. HTTP_Response repr => ResponseConstraint repr a ts => repr (ResponseArgs repr a ts) (Response repr) Source #

Wrap response by giving it the corresponding Method, and put the type variables (a) then (ts) first instead or (repr) so they can be passed using TypeApplications without adding a |_| for (repr)@.

post :: forall a ts repr. HTTP_Response repr => ResponseConstraint repr a ts => repr (ResponseArgs repr a ts) (Response repr) Source #

Wrap response by giving it the corresponding Method, and put the type variables (a) then (ts) first instead or (repr) so they can be passed using TypeApplications without adding a |_| for (repr)@.

delete :: forall a ts repr. HTTP_Response repr => ResponseConstraint repr a ts => repr (ResponseArgs repr a ts) (Response repr) Source #

Wrap response by giving it the corresponding Method, and put the type variables (a) then (ts) first instead or (repr) so they can be passed using TypeApplications without adding a |_| for (repr)@.

trace :: forall a ts repr. HTTP_Response repr => ResponseConstraint repr a ts => repr (ResponseArgs repr a ts) (Response repr) Source #

Wrap response by giving it the corresponding Method, and put the type variables (a) then (ts) first instead or (repr) so they can be passed using TypeApplications without adding a |_| for (repr)@.

connect :: forall a ts repr. HTTP_Response repr => ResponseConstraint repr a ts => repr (ResponseArgs repr a ts) (Response repr) Source #

Wrap response by giving it the corresponding Method, and put the type variables (a) then (ts) first instead or (repr) so they can be passed using TypeApplications without adding a |_| for (repr)@.

options :: forall a ts repr. HTTP_Response repr => ResponseConstraint repr a ts => repr (ResponseArgs repr a ts) (Response repr) Source #

Wrap response by giving it the corresponding Method, and put the type variables (a) then (ts) first instead or (repr) so they can be passed using TypeApplications without adding a |_| for (repr)@.

patch :: forall a ts repr. HTTP_Response repr => ResponseConstraint repr a ts => repr (ResponseArgs repr a ts) (Response repr) Source #

Wrap response by giving it the corresponding Method, and put the type variables (a) then (ts) first instead or (repr) so they can be passed using TypeApplications without adding a |_| for (repr)@.

Class HTTP_ResponseStream

class HTTP_ResponseStream repr where Source #

Minimal complete definition

Nothing

Associated Types

type ResponseStreamConstraint repr as (ts :: [*]) framing :: Constraint Source #

type ResponseStreamArgs repr as (ts :: [*]) framing :: * Source #

type ResponseStream repr :: * Source #

Methods

responseStream :: ResponseStreamConstraint repr as ts framing => Method -> repr (ResponseStreamArgs repr as ts framing) (ResponseStream repr) Source #

responseStream :: forall as ts framing. Trans repr => HTTP_ResponseStream (UnTrans repr) => ResponseStreamConstraint (UnTrans repr) as ts framing => ResponseStreamArgs repr as ts framing ~ ResponseStreamArgs (UnTrans repr) as ts framing => ResponseStream repr ~ ResponseStream (UnTrans repr) => Method -> repr (ResponseStreamArgs repr as ts framing) (ResponseStream repr) Source #

getStream :: forall as ts framing repr. HTTP_ResponseStream repr => ResponseStreamConstraint repr as ts framing => repr (ResponseStreamArgs repr as ts framing) (ResponseStream repr) Source #

headStream :: forall as ts framing repr. HTTP_ResponseStream repr => ResponseStreamConstraint repr as ts framing => repr (ResponseStreamArgs repr as ts framing) (ResponseStream repr) Source #

putStream :: forall as ts framing repr. HTTP_ResponseStream repr => ResponseStreamConstraint repr as ts framing => repr (ResponseStreamArgs repr as ts framing) (ResponseStream repr) Source #

postStream :: forall as ts framing repr. HTTP_ResponseStream repr => ResponseStreamConstraint repr as ts framing => repr (ResponseStreamArgs repr as ts framing) (ResponseStream repr) Source #

deleteStream :: forall as ts framing repr. HTTP_ResponseStream repr => ResponseStreamConstraint repr as ts framing => repr (ResponseStreamArgs repr as ts framing) (ResponseStream repr) Source #

traceStream :: forall as ts framing repr. HTTP_ResponseStream repr => ResponseStreamConstraint repr as ts framing => repr (ResponseStreamArgs repr as ts framing) (ResponseStream repr) Source #

connectStream :: forall as ts framing repr. HTTP_ResponseStream repr => ResponseStreamConstraint repr as ts framing => repr (ResponseStreamArgs repr as ts framing) (ResponseStream repr) Source #

optionsStream :: forall as ts framing repr. HTTP_ResponseStream repr => ResponseStreamConstraint repr as ts framing => repr (ResponseStreamArgs repr as ts framing) (ResponseStream repr) Source #

patchStream :: forall as ts framing repr. HTTP_ResponseStream repr => ResponseStreamConstraint repr as ts framing => repr (ResponseStreamArgs repr as ts framing) (ResponseStream repr) Source #

Framing

Type family FramingMonad

type family FramingMonad p :: * -> * Source #

Type family FramingYield

type family FramingYield p :: * Source #

Type family FramingReturn

type family FramingReturn p :: * Source #

Class FramingEncode

class FramingEncode framing p where Source #

Methods

framingEncode :: Proxy framing -> (FramingYield p -> ByteString) -> p -> IO (Either (FramingReturn p) (ByteString, p)) Source #

Class FramingDecode

class FramingDecode framing p where Source #

Methods

framingDecode :: FramingMonad p ~ m => Monad m => Proxy framing -> (ByteString -> Either String (FramingYield p)) -> m ByteString -> p Source #

Type NoFraming

data NoFraming Source #

A framing strategy that does not do any framing at all, it just passes the input data. Most of the time this will be used with binary data, such as files.

Type NewlineFraming

data NewlineFraming Source #

A simple framing strategy that has no header, and inserts a newline character after each frame. WARNING: this assumes that it is used with a Content-Type that encodes without newlines (e.g. JSON).

Type NetstringFraming

data NetstringFraming Source #

The netstring framing strategy as defined by djb: http://cr.yp.to/proto/netstrings.txt

Any string of 8-bit bytes may be encoded as [len]":"[string]",". Here [string] is the string and [len] is a nonempty sequence of ASCII digits giving the length of [string] in decimal. The ASCII digits are 30 for 0, 31 for 1, and so on up through 39 for 9. Extra zeros at the front of [len] are prohibited: [len] begins with 30 exactly when [string] is empty.

For example, the string "hello world!" is encoded as 32 3a 68 65 6c 6c 6f 20 77 6f 72 6c 64 21 2c, i.e., "12:hello world!,". The empty string is encoded as "0:,".