Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Combinators to build a Web API.
Synopsis
- class Cat repr where
- (<.>) :: repr a b -> repr b c -> repr a c
- class Alt repr where
- data a :!: b = a :!: b
- class Pro repr where
- dimap :: (a -> b) -> (b -> a) -> repr (a -> k) k -> repr (b -> k) k
- class HTTP_Path repr where
- type PathConstraint repr a :: Constraint
- segment :: Segment -> repr k k
- capture' :: PathConstraint repr a => Name -> repr (a -> k) k
- captureAll :: repr ([Segment] -> k) k
- (</>) :: Cat repr => HTTP_Path repr => Segment -> repr a b -> repr a b
- capture :: forall a k repr. HTTP_Path repr => PathConstraint repr a => Name -> repr (a -> k) k
- type Segment = Text
- type Path = [Segment]
- type Name = String
- class HTTP_Header repr where
- header :: HeaderName -> repr (HeaderValue -> k) k
- type HeaderValue = ByteString
- class HTTP_Body repr where
- type BodyArg repr a (ts :: [*]) :: *
- type BodyConstraint repr a (ts :: [*]) :: Constraint
- body' :: forall a (ts :: [*]) k. BodyConstraint repr a ts => repr (BodyArg repr a ts -> k) k
- body :: forall a ts k repr. HTTP_Body repr => BodyConstraint repr a ts => repr (BodyArg repr a ts -> k) k
- class HTTP_BodyStream repr where
- type BodyStreamArg repr as (ts :: [*]) framing :: *
- type BodyStreamConstraint repr as (ts :: [*]) framing :: Constraint
- bodyStream' :: BodyStreamConstraint repr as ts framing => repr (BodyStreamArg repr as ts framing -> k) k
- bodyStream :: forall as ts framing k repr. HTTP_BodyStream repr => BodyStreamConstraint repr as ts framing => repr (BodyStreamArg repr as ts framing -> k) k
- class HTTP_Query repr where
- type QueryConstraint repr a :: Constraint
- queryParams' :: QueryConstraint repr a => QueryName -> repr ([a] -> k) k
- queryFlag :: QueryConstraint repr Bool => QueryName -> repr (Bool -> k) k
- type QueryName = ByteString
- type QueryValue = ByteString
- queryParams :: forall a k repr. HTTP_Query repr => QueryConstraint repr a => QueryName -> repr ([a] -> k) k
- class HTTP_BasicAuth repr where
- type BasicAuthConstraint repr a :: Constraint
- type BasicAuthArgs repr a k :: *
- basicAuth' :: BasicAuthConstraint repr a => BasicAuthRealm -> repr (BasicAuthArgs repr a k) k
- basicAuth :: forall a k repr. HTTP_BasicAuth repr => BasicAuthConstraint repr a => BasicAuthRealm -> repr (BasicAuthArgs repr a k) k
- data BasicAuth usr
- type BasicAuthRealm = Text
- type BasicAuthUser = Text
- type BasicAuthPass = Text
- class HTTP_Version repr where
- version :: HttpVersion -> repr k k
- class HTTP_Response repr where
- type ResponseConstraint repr a (ts :: [*]) :: Constraint
- type ResponseArgs repr a (ts :: [*]) :: *
- type Response repr :: *
- response :: ResponseConstraint repr a ts => Method -> repr (ResponseArgs repr a ts) (Response repr)
- get :: forall a ts repr. HTTP_Response repr => ResponseConstraint repr a ts => repr (ResponseArgs repr a ts) (Response repr)
- head :: forall a ts repr. HTTP_Response repr => ResponseConstraint repr a ts => repr (ResponseArgs repr a ts) (Response repr)
- put :: forall a ts repr. HTTP_Response repr => ResponseConstraint repr a ts => repr (ResponseArgs repr a ts) (Response repr)
- post :: forall a ts repr. HTTP_Response repr => ResponseConstraint repr a ts => repr (ResponseArgs repr a ts) (Response repr)
- delete :: forall a ts repr. HTTP_Response repr => ResponseConstraint repr a ts => repr (ResponseArgs repr a ts) (Response repr)
- trace :: forall a ts repr. HTTP_Response repr => ResponseConstraint repr a ts => repr (ResponseArgs repr a ts) (Response repr)
- connect :: forall a ts repr. HTTP_Response repr => ResponseConstraint repr a ts => repr (ResponseArgs repr a ts) (Response repr)
- options :: forall a ts repr. HTTP_Response repr => ResponseConstraint repr a ts => repr (ResponseArgs repr a ts) (Response repr)
- patch :: forall a ts repr. HTTP_Response repr => ResponseConstraint repr a ts => repr (ResponseArgs repr a ts) (Response repr)
- class HTTP_ResponseStream repr where
- type ResponseStreamConstraint repr as (ts :: [*]) framing :: Constraint
- type ResponseStreamArgs repr as (ts :: [*]) framing :: *
- type ResponseStream repr :: *
- responseStream :: ResponseStreamConstraint repr as ts framing => Method -> repr (ResponseStreamArgs repr as ts framing) (ResponseStream repr)
- getStream :: forall as ts framing repr. HTTP_ResponseStream repr => ResponseStreamConstraint repr as ts framing => repr (ResponseStreamArgs repr as ts framing) (ResponseStream repr)
- headStream :: forall as ts framing repr. HTTP_ResponseStream repr => ResponseStreamConstraint repr as ts framing => repr (ResponseStreamArgs repr as ts framing) (ResponseStream repr)
- putStream :: forall as ts framing repr. HTTP_ResponseStream repr => ResponseStreamConstraint repr as ts framing => repr (ResponseStreamArgs repr as ts framing) (ResponseStream repr)
- postStream :: forall as ts framing repr. HTTP_ResponseStream repr => ResponseStreamConstraint repr as ts framing => repr (ResponseStreamArgs repr as ts framing) (ResponseStream repr)
- deleteStream :: forall as ts framing repr. HTTP_ResponseStream repr => ResponseStreamConstraint repr as ts framing => repr (ResponseStreamArgs repr as ts framing) (ResponseStream repr)
- traceStream :: forall as ts framing repr. HTTP_ResponseStream repr => ResponseStreamConstraint repr as ts framing => repr (ResponseStreamArgs repr as ts framing) (ResponseStream repr)
- connectStream :: forall as ts framing repr. HTTP_ResponseStream repr => ResponseStreamConstraint repr as ts framing => repr (ResponseStreamArgs repr as ts framing) (ResponseStream repr)
- optionsStream :: forall as ts framing repr. HTTP_ResponseStream repr => ResponseStreamConstraint repr as ts framing => repr (ResponseStreamArgs repr as ts framing) (ResponseStream repr)
- patchStream :: forall as ts framing repr. HTTP_ResponseStream repr => ResponseStreamConstraint repr as ts framing => repr (ResponseStreamArgs repr as ts framing) (ResponseStream repr)
- type family FramingMonad p :: * -> *
- type family FramingYield p :: *
- type family FramingReturn p :: *
- class FramingEncode framing p where
- framingEncode :: Proxy framing -> (FramingYield p -> ByteString) -> p -> IO (Either (FramingReturn p) (ByteString, p))
- class FramingDecode framing p where
- framingDecode :: FramingMonad p ~ m => Monad m => Proxy framing -> (ByteString -> Either String (FramingYield p)) -> m ByteString -> p
- data NoFraming
- data NewlineFraming
- data NetstringFraming
Class Cat
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.
Class Alt
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.
Type (:!:
)
data a :!: b infixl 3 Source #
Like (,)
but infixl
.
Used to get alternative commands from a Client
or to supply alternative handlers to a Server
.
a :!: b infixl 3 |
Class Pro
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
.
Class HTTP_Path
class HTTP_Path repr where Source #
type PathConstraint repr a :: Constraint Source #
(</>) :: Cat repr => HTTP_Path repr => Segment -> repr a b -> repr a b infixr 5 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 #
header :: HeaderName -> repr (HeaderValue -> k) k Source #
type HeaderValue = ByteString Source #
Class HTTP_Body
class HTTP_Body repr where Source #
type BodyArg repr a (ts :: [*]) :: * Source #
type BodyConstraint repr a (ts :: [*]) :: Constraint Source #
body' :: forall a (ts :: [*]) k. BodyConstraint 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 #
type BodyStreamArg repr as (ts :: [*]) framing :: * Source #
type BodyStreamConstraint repr as (ts :: [*]) framing :: Constraint Source #
bodyStream' :: BodyStreamConstraint 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 #
type QueryConstraint repr a :: Constraint Source #
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 #
type QueryName = ByteString Source #
type QueryValue = ByteString 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 #
type BasicAuthConstraint repr a :: Constraint Source #
type BasicAuthArgs repr a k :: * Source #
basicAuth' :: BasicAuthConstraint repr a => 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
type BasicAuthRealm = Text Source #
type BasicAuthUser = Text Source #
type BasicAuthPass = Text Source #
Class HTTP_Version
class HTTP_Version repr where Source #
version :: HttpVersion -> repr k k Source #
Class HTTP_Response
class HTTP_Response repr where Source #
type ResponseConstraint repr a (ts :: [*]) :: Constraint Source #
type ResponseArgs repr a (ts :: [*]) :: * Source #
response :: ResponseConstraint repr a ts => 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 #
head :: forall a ts repr. HTTP_Response repr => ResponseConstraint repr a ts => repr (ResponseArgs repr a ts) (Response repr) Source #
put :: forall a ts repr. HTTP_Response repr => ResponseConstraint repr a ts => repr (ResponseArgs repr a ts) (Response repr) Source #
post :: forall a ts repr. HTTP_Response repr => ResponseConstraint repr a ts => repr (ResponseArgs repr a ts) (Response repr) Source #
delete :: forall a ts repr. HTTP_Response repr => ResponseConstraint repr a ts => repr (ResponseArgs repr a ts) (Response repr) Source #
trace :: forall a ts repr. HTTP_Response repr => ResponseConstraint repr a ts => repr (ResponseArgs repr a ts) (Response repr) Source #
connect :: forall a ts repr. HTTP_Response repr => ResponseConstraint repr a ts => repr (ResponseArgs repr a ts) (Response repr) Source #
options :: forall a ts repr. HTTP_Response repr => ResponseConstraint repr a ts => repr (ResponseArgs repr a ts) (Response repr) Source #
patch :: forall a ts repr. HTTP_Response repr => ResponseConstraint repr a ts => repr (ResponseArgs repr a ts) (Response repr) Source #
Class HTTP_ResponseStream
class HTTP_ResponseStream repr where Source #
type ResponseStreamConstraint repr as (ts :: [*]) framing :: Constraint Source #
type ResponseStreamArgs repr as (ts :: [*]) framing :: * Source #
type ResponseStream repr :: * Source #
responseStream :: ResponseStreamConstraint repr as ts framing => 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 #
framingEncode :: Proxy framing -> (FramingYield p -> ByteString) -> p -> IO (Either (FramingReturn p) (ByteString, p)) Source #
Class FramingDecode
class FramingDecode framing p where Source #
framingDecode :: FramingMonad p ~ m => Monad m => Proxy framing -> (ByteString -> Either String (FramingYield p)) -> m ByteString -> p Source #
Type NoFraming
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:,"
.