Safe Haskell | None |
---|---|
Language | Haskell2010 |
Servant.API
Contents
- Combinators
- Accessing information from the request
- Actual endpoints, distinguished by HTTP method
- Sub-APIs defined as records of routes
- Streaming endpoints, distinguished by HTTP method
- Authentication
- Endpoints description
- Content Types
- Response Headers
- Untyped endpoints
- FromHttpApiData and ToHttpApiData
- Experimental modules
- Links
- Re-exports
Synopsis
- module Servant.API.Sub
- module Servant.API.Alternative
- module Servant.API.Empty
- data Strict
- data Lenient
- data Optional
- data Required
- module Servant.API.Capture
- module Servant.API.Header
- module Servant.API.HttpVersion
- module Servant.API.QueryParam
- module Servant.API.Fragment
- module Servant.API.ReqBody
- module Servant.API.RemoteHost
- module Servant.API.IsSecure
- module Servant.API.Vault
- module Servant.API.WithNamedContext
- module Servant.API.WithResource
- type Get = Verb 'GET 200
- type Put = Verb 'PUT 200
- data StdMethod
- type Delete = Verb 'DELETE 200
- type DeleteAccepted = Verb 'DELETE 202
- type DeleteNoContent = NoContentVerb 'DELETE
- type DeleteNonAuthoritative = Verb 'DELETE 203
- type GetAccepted = Verb 'GET 202
- type GetNoContent = NoContentVerb 'GET
- type GetNonAuthoritative = Verb 'GET 203
- type GetPartialContent = Verb 'GET 206
- type GetResetContent = Verb 'GET 205
- data NoContentVerb (method :: k1)
- type Patch = Verb 'PATCH 200
- type PatchAccepted = Verb 'PATCH 202
- type PatchNoContent = NoContentVerb 'PATCH
- type PatchNonAuthoritative = Verb 'PATCH 203
- type Post = Verb 'POST 200
- type PostAccepted = Verb 'POST 202
- type PostCreated = Verb 'POST 201
- type PostNoContent = NoContentVerb 'POST
- type PostNonAuthoritative = Verb 'POST 203
- type PostResetContent = Verb 'POST 205
- type PutAccepted = Verb 'PUT 202
- type PutCreated = Verb 'PUT 201
- type PutNoContent = NoContentVerb 'PUT
- type PutNonAuthoritative = Verb 'PUT 203
- class ReflectMethod (a :: k) where
- reflectMethod :: Proxy a -> Method
- data Verb (method :: k1) (statusCode :: Nat) (contentTypes :: [Type]) a
- type family Unique (xs :: [k]) where ...
- type Union = NS I
- data UVerb (method :: StdMethod) (contentTypes :: [Type]) (as :: [Type])
- class KnownStatus (StatusOf a) => HasStatus a where
- type IsMember (a :: u) (as :: [u]) = (Unique as, CheckElemIsMember a as, UElem a as)
- type family StatusOf a :: Nat
- type family Statuses (as :: [Type]) :: [Nat]
- type family Statuses (as :: [Type]) :: [Nat]
- newtype WithStatus (k :: Nat) a = WithStatus a
- inject :: UElem x xs => f x -> NS f xs
- statusOf :: HasStatus a => proxy a -> Status
- module Servant.API.NamedRoutes
- class GenericMode mode where
- type mode :- api
- type family mode :- api
- data AsApi
- class GServantProduct (f :: Type -> Type)
- type GenericServant (routes :: Type -> Type) mode = (GenericMode mode, Generic (routes mode), GServantProduct (Rep (routes mode)))
- type ToServant (routes :: Type -> Type) mode = GToServant (Rep (routes mode))
- type ToServantApi (routes :: Type -> Type) = ToServant routes AsApi
- fromServant :: GenericServant routes mode => ToServant routes mode -> routes mode
- genericApi :: forall (routes :: Type -> Type). GenericServant routes AsApi => Proxy routes -> Proxy (ToServantApi routes)
- toServant :: GenericServant routes mode => routes mode -> ToServant routes mode
- data Stream (method :: k1) (status :: Nat) framing contentType a
- class FramingRender (strategy :: k) where
- framingRender :: forall (m :: Type -> Type) a. Monad m => Proxy strategy -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString
- class FramingUnrender (strategy :: k) where
- framingUnrender :: forall (m :: Type -> Type) a. Monad m => Proxy strategy -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a
- class FromSourceIO chunk a | a -> chunk where
- fromSourceIO :: SourceIO chunk -> IO a
- data NetstringFraming
- data NewlineFraming
- data NoFraming
- type SourceIO = SourceT IO
- type StreamBody = StreamBody' ('[] :: [Type])
- data StreamBody' (mods :: [Type]) framing contentType a
- type StreamGet = Stream 'GET 200
- type StreamPost = Stream 'POST 200
- class ToSourceIO chunk a | a -> chunk where
- toSourceIO :: a -> SourceIO chunk
- module Servant.API.BasicAuth
- data Description (sym :: Symbol)
- data Summary (sym :: Symbol)
- class Accept (ctype :: k) where
- contentType :: Proxy ctype -> MediaType
- contentTypes :: Proxy ctype -> NonEmpty MediaType
- data FormUrlEncoded
- data JSON
- class Accept ctype => MimeRender (ctype :: k) a where
- mimeRender :: Proxy ctype -> a -> ByteString
- class Accept ctype => MimeUnrender (ctype :: k) a where
- mimeUnrender :: Proxy ctype -> ByteString -> Either String a
- mimeUnrenderWithType :: Proxy ctype -> MediaType -> ByteString -> Either String a
- data NoContent = NoContent
- data OctetStream
- data PlainText
- data ResponseHeader (sym :: Symbol) a
- class AddHeader (h :: Symbol) v orig new | h v orig -> new, new -> h, new -> v, new -> orig
- class BuildHeadersTo (hs :: [Type]) where
- buildHeadersTo :: [Header] -> HList hs
- class GetHeaders ls where
- getHeaders :: ls -> [Header]
- data HList (a :: [Type]) where
- class HasResponseHeader (h :: Symbol) a (headers :: [Type])
- data Headers (ls :: [Type]) a = Headers {
- getResponse :: a
- getHeadersHList :: HList ls
- addHeader :: forall (h :: Symbol) v orig new. AddHeader h v orig new => v -> orig -> new
- lookupResponseHeader :: forall (h :: Symbol) a (headers :: [Type]) r. HasResponseHeader h a headers => Headers headers r -> ResponseHeader h a
- noHeader :: forall (h :: Symbol) v orig new. AddHeader h v orig new => orig -> new
- module Servant.API.Raw
- class FromHttpApiData a where
- parseUrlPiece :: Text -> Either Text a
- parseHeader :: ByteString -> Either Text a
- parseQueryParam :: Text -> Either Text a
- class ToHttpApiData a where
- toUrlPiece :: a -> Text
- toEncodedUrlPiece :: a -> Builder
- toHeader :: a -> ByteString
- toQueryParam :: a -> Text
- toEncodedQueryParam :: a -> Builder
- module Servant.API.Experimental.Auth
- data URI = URI {}
- class HasLink (endpoint :: k) where
- type family IsElem endpoint api where ...
- type family IsElem' a s
- data Link
- safeLink :: (IsElem endpoint api, HasLink endpoint) => Proxy api -> Proxy endpoint -> MkLink endpoint Link
- type family MkLink (endpoint :: k) a
- type family If (cond :: Bool) (tru :: k) (fls :: k) :: k where ...
- data SBool (b :: Bool) where
- class SBoolI (b :: Bool) where
Combinators
module Servant.API.Sub
Type-level combinator for expressing subrouting: :>
module Servant.API.Alternative
Type-level combinator for alternative endpoints: :<|>
module Servant.API.Empty
Type-level combinator for an empty API: EmptyAPI
Strictly parsed argument. Not wrapped.
Instances
(KnownSymbol h, ToHttpApiData v) => AddHeader h v (Headers (fst ': rest) a) (Headers (Header h v ': (fst ': rest)) a) # | |
Defined in Servant.API.ResponseHeaders Methods addOptionalHeader :: ResponseHeader h v -> Headers (fst ': rest) a -> Headers (Header h v ': (fst ': rest)) a | |
HasResponseHeader h a (Header h a ': rest) # | |
Defined in Servant.API.ResponseHeaders Methods hlistLookupHeader :: HList (Header h a ': rest) -> ResponseHeader h a | |
(FromHttpApiData v, BuildHeadersTo xs, KnownSymbol h) => BuildHeadersTo (Header h v ': xs) # | |
Defined in Servant.API.ResponseHeaders Methods buildHeadersTo :: [Header] -> HList (Header h v ': xs) # | |
(KnownSymbol h, GetHeadersFromHList rest, ToHttpApiData v) => GetHeaders' (Header h v ': rest) # | |
Defined in Servant.API.ResponseHeaders Methods getHeaders' :: Headers (Header h v ': rest) a -> [Header] |
Optional argument. Wrapped in Maybe
.
Instances
(KnownSymbol h, ToHttpApiData v) => AddHeader h v (Headers (fst ': rest) a) (Headers (Header h v ': (fst ': rest)) a) # | |
Defined in Servant.API.ResponseHeaders Methods addOptionalHeader :: ResponseHeader h v -> Headers (fst ': rest) a -> Headers (Header h v ': (fst ': rest)) a | |
HasResponseHeader h a (Header h a ': rest) # | |
Defined in Servant.API.ResponseHeaders Methods hlistLookupHeader :: HList (Header h a ': rest) -> ResponseHeader h a | |
(FromHttpApiData v, BuildHeadersTo xs, KnownSymbol h) => BuildHeadersTo (Header h v ': xs) # | |
Defined in Servant.API.ResponseHeaders Methods buildHeadersTo :: [Header] -> HList (Header h v ': xs) # | |
(KnownSymbol h, GetHeadersFromHList rest, ToHttpApiData v) => GetHeaders' (Header h v ': rest) # | |
Defined in Servant.API.ResponseHeaders Methods getHeaders' :: Headers (Header h v ': rest) a -> [Header] |
Type-level modifiers for QueryParam
, Header
and ReqBody
.
Accessing information from the request
module Servant.API.Capture
Capturing parts of the url path as parsed values:
and Capture
CaptureAll
module Servant.API.Header
Retrieving specific headers from the request
module Servant.API.HttpVersion
Retrieving the HTTP version of the request
module Servant.API.QueryParam
Retrieving parameters from the query string of the URI
: QueryParam
module Servant.API.Fragment
module Servant.API.ReqBody
Accessing the request body as a JSON-encoded type: ReqBody
module Servant.API.RemoteHost
Retrieving the IP of the client
module Servant.API.IsSecure
Is the request made through HTTPS?
module Servant.API.Vault
Access the location for arbitrary data to be shared by applications and middleware
module Servant.API.WithNamedContext
Access context entries in combinators in servant-server
module Servant.API.WithResource
Access a managed resource scoped to a single request
Actual endpoints, distinguished by HTTP method
HTTP standard method (as defined by RFC 2616, and PATCH which is defined by RFC 5789).
Since: http-types-0.2.0
Instances
type DeleteAccepted = Verb 'DELETE 202 #
DELETE
with 202 status code.
type DeleteNoContent = NoContentVerb 'DELETE #
DELETE
with 204 status code.
type DeleteNonAuthoritative = Verb 'DELETE 203 #
DELETE
with 203 status code.
type GetAccepted = Verb 'GET 202 #
GET
with 202 status code.
type GetNoContent = NoContentVerb 'GET #
GET
with 204 status code.
type GetNonAuthoritative = Verb 'GET 203 #
GET
with 203 status code.
type GetPartialContent = Verb 'GET 206 #
GET
with 206 status code.
type GetResetContent = Verb 'GET 205 #
GET
with 205 status code.
data NoContentVerb (method :: k1) #
NoContentVerb
is a specific type to represent NoContent
responses.
It does not require either a list of content types (because there's
no content) or a status code (because it should always be 204).
Instances
HasLink (NoContentVerb m :: Type) # | |||||
Defined in Servant.Links Methods toLink :: (Link -> a) -> Proxy (NoContentVerb m) -> Link -> MkLink (NoContentVerb m) a # | |||||
Generic (NoContentVerb method) # | |||||
Defined in Servant.API.Verbs Associated Types
Methods from :: NoContentVerb method -> Rep (NoContentVerb method) x # to :: Rep (NoContentVerb method) x -> NoContentVerb method # | |||||
type MkLink (NoContentVerb m :: Type) r # | |||||
Defined in Servant.Links | |||||
type Rep (NoContentVerb method) # | |||||
Defined in Servant.API.Verbs |
type PatchAccepted = Verb 'PATCH 202 #
PATCH
with 202 status code.
type PatchNoContent = NoContentVerb 'PATCH #
PATCH
with 204 status code.
type PatchNonAuthoritative = Verb 'PATCH 203 #
PATCH
with 203 status code.
type PostAccepted = Verb 'POST 202 #
POST
with 202 status code.
type PostCreated = Verb 'POST 201 #
POST
with 201 status code.
type PostNoContent = NoContentVerb 'POST #
POST
with 204 status code.
type PostNonAuthoritative = Verb 'POST 203 #
POST
with 203 status code.
type PostResetContent = Verb 'POST 205 #
POST
with 205 status code.
type PutAccepted = Verb 'PUT 202 #
PUT
with 202 status code.
type PutCreated = Verb 'PUT 201 #
PUT
with 201 status code.
type PutNoContent = NoContentVerb 'PUT #
PUT
with 204 status code.
type PutNonAuthoritative = Verb 'PUT 203 #
PUT
with 203 status code.
class ReflectMethod (a :: k) where #
Methods
reflectMethod :: Proxy a -> Method #
Instances
ReflectMethod 'CONNECT # | |
Defined in Servant.API.Verbs Methods reflectMethod :: Proxy 'CONNECT -> Method # | |
ReflectMethod 'DELETE # | |
Defined in Servant.API.Verbs Methods reflectMethod :: Proxy 'DELETE -> Method # | |
ReflectMethod 'GET # | |
Defined in Servant.API.Verbs Methods reflectMethod :: Proxy 'GET -> Method # | |
ReflectMethod 'HEAD # | |
Defined in Servant.API.Verbs Methods reflectMethod :: Proxy 'HEAD -> Method # | |
ReflectMethod 'OPTIONS # | |
Defined in Servant.API.Verbs Methods reflectMethod :: Proxy 'OPTIONS -> Method # | |
ReflectMethod 'PATCH # | |
Defined in Servant.API.Verbs Methods reflectMethod :: Proxy 'PATCH -> Method # | |
ReflectMethod 'POST # | |
Defined in Servant.API.Verbs Methods reflectMethod :: Proxy 'POST -> Method # | |
ReflectMethod 'PUT # | |
Defined in Servant.API.Verbs Methods reflectMethod :: Proxy 'PUT -> Method # | |
ReflectMethod 'TRACE # | |
Defined in Servant.API.Verbs Methods reflectMethod :: Proxy 'TRACE -> Method # |
data Verb (method :: k1) (statusCode :: Nat) (contentTypes :: [Type]) a #
Verb
is a general type for representing HTTP verbs (a.k.a. methods). For
convenience, type synonyms for each verb with a 200 response code are
provided, but you are free to define your own:
>>>
type Post204 contentTypes a = Verb 'POST 204 contentTypes a
Instances
HasLink (Verb m s ct a :: Type) # | |
Generic (Verb method statusCode contentTypes a) # | |
Defined in Servant.API.Verbs | |
AtLeastOneFragment (Verb m s ct typ) # | If fragment appeared in API endpoint twice, compile-time error would be raised.
|
Defined in Servant.API.TypeLevel | |
type MkLink (Verb m s ct a :: Type) r # | |
Defined in Servant.Links | |
type Rep (Verb method statusCode contentTypes a) # | |
type family Unique (xs :: [k]) where ... #
Check whether all values in a type-level list are distinct. This will throw a nice error if there are any duplicate elements in the list.
data UVerb (method :: StdMethod) (contentTypes :: [Type]) (as :: [Type]) #
A variant of Verb
that can have any of a number of response values and status codes.
FUTUREWORK: it would be nice to make Verb
a special case of UVerb
, and only write
instances for HasServer
etc. for the latter, getting them for the former for free.
Something like:
type Verb method statusCode contentTypes a = UVerb method contentTypes [WithStatus statusCode a]
Backwards compatibility is tricky, though: this type alias would mean people would have to
use respond
instead of pure
or return
, so all old handlers would have to be rewritten.
Instances
HasLink (UVerb m ct a :: Type) # | |
AtLeastOneFragment (UVerb m cts as) # | |
Defined in Servant.API.TypeLevel | |
type MkLink (UVerb m ct a :: Type) r # | |
Defined in Servant.Links |
class KnownStatus (StatusOf a) => HasStatus a #
Instances
HasStatus NoContent # | If an API can respond with | ||||
Defined in Servant.API.UVerb Associated Types
| |||||
HasStatus a => HasStatus (Headers ls a) # | |||||
Defined in Servant.API.UVerb | |||||
KnownStatus n => HasStatus (WithStatus n a) # | an instance of this typeclass assigns a HTTP status code to a return type Example: data NotFoundError = NotFoundError String instance HasStatus NotFoundError where type StatusOf NotFoundError = 404 You can also use the convience newtype wrapper | ||||
Defined in Servant.API.UVerb Associated Types
|
type family StatusOf a :: Nat #
Instances
type StatusOf NoContent # | |
Defined in Servant.API.UVerb | |
type StatusOf (Headers ls a) # | |
Defined in Servant.API.UVerb | |
type StatusOf (WithStatus n a) # | |
Defined in Servant.API.UVerb |
newtype WithStatus (k :: Nat) a #
A simple newtype wrapper that pairs a type with its status code. It implements all the content types that Servant ships with by default.
Constructors
WithStatus a |
Instances
MimeRender FormUrlEncoded a => MimeRender FormUrlEncoded (WithStatus _status a) # | |||||
Defined in Servant.API.UVerb Methods mimeRender :: Proxy FormUrlEncoded -> WithStatus _status a -> ByteString # | |||||
MimeRender JSON a => MimeRender JSON (WithStatus _status a) # | |||||
Defined in Servant.API.UVerb Methods mimeRender :: Proxy JSON -> WithStatus _status a -> ByteString # | |||||
MimeRender OctetStream a => MimeRender OctetStream (WithStatus _status a) # | |||||
Defined in Servant.API.UVerb Methods mimeRender :: Proxy OctetStream -> WithStatus _status a -> ByteString # | |||||
MimeRender PlainText a => MimeRender PlainText (WithStatus _status a) # | |||||
Defined in Servant.API.UVerb Methods mimeRender :: Proxy PlainText -> WithStatus _status a -> ByteString # | |||||
MimeUnrender FormUrlEncoded a => MimeUnrender FormUrlEncoded (WithStatus _status a) # | |||||
Defined in Servant.API.UVerb Methods mimeUnrender :: Proxy FormUrlEncoded -> ByteString -> Either String (WithStatus _status a) # mimeUnrenderWithType :: Proxy FormUrlEncoded -> MediaType -> ByteString -> Either String (WithStatus _status a) # | |||||
MimeUnrender JSON a => MimeUnrender JSON (WithStatus _status a) # | |||||
Defined in Servant.API.UVerb Methods mimeUnrender :: Proxy JSON -> ByteString -> Either String (WithStatus _status a) # mimeUnrenderWithType :: Proxy JSON -> MediaType -> ByteString -> Either String (WithStatus _status a) # | |||||
MimeUnrender OctetStream a => MimeUnrender OctetStream (WithStatus _status a) # | |||||
Defined in Servant.API.UVerb Methods mimeUnrender :: Proxy OctetStream -> ByteString -> Either String (WithStatus _status a) # mimeUnrenderWithType :: Proxy OctetStream -> MediaType -> ByteString -> Either String (WithStatus _status a) # | |||||
MimeUnrender PlainText a => MimeUnrender PlainText (WithStatus _status a) # | |||||
Defined in Servant.API.UVerb Methods mimeUnrender :: Proxy PlainText -> ByteString -> Either String (WithStatus _status a) # mimeUnrenderWithType :: Proxy PlainText -> MediaType -> ByteString -> Either String (WithStatus _status a) # | |||||
Show a => Show (WithStatus k a) # | |||||
Defined in Servant.API.UVerb Methods showsPrec :: Int -> WithStatus k a -> ShowS # show :: WithStatus k a -> String # showList :: [WithStatus k a] -> ShowS # | |||||
Eq a => Eq (WithStatus k a) # | |||||
Defined in Servant.API.UVerb Methods (==) :: WithStatus k a -> WithStatus k a -> Bool # (/=) :: WithStatus k a -> WithStatus k a -> Bool # | |||||
KnownStatus n => HasStatus (WithStatus n a) # | an instance of this typeclass assigns a HTTP status code to a return type Example: data NotFoundError = NotFoundError String instance HasStatus NotFoundError where type StatusOf NotFoundError = 404 You can also use the convience newtype wrapper | ||||
Defined in Servant.API.UVerb Associated Types
| |||||
type StatusOf (WithStatus n a) # | |||||
Defined in Servant.API.UVerb |
Sub-APIs defined as records of routes
module Servant.API.NamedRoutes
class GenericMode mode #
A class with a type family that applies an appropriate type family to the api
parameter. For example, AsApi
will leave api
untouched, while
will produce AsServerT
m
.ServerT
api m
Instances
GenericMode AsApi # | |||||
Defined in Servant.API.Generic Associated Types
| |||||
GenericMode (AsLink a) # | |||||
Defined in Servant.Links |
A type that specifies that an API record contains an API definition. Only useful at type-level.
Instances
GenericMode AsApi # | |||||
Defined in Servant.API.Generic Associated Types
| |||||
type AsApi :- api # | |||||
Defined in Servant.API.Generic |
class GServantProduct (f :: Type -> Type) #
Minimal complete definition
gtoServant, gfromServant
Instances
(GServantProduct l, GServantProduct r) => GServantProduct (l :*: r) # | |
Defined in Servant.API.Generic Methods gtoServant :: (l :*: r) p -> GToServant (l :*: r) gfromServant :: GToServant (l :*: r) -> (l :*: r) p | |
GServantProduct (K1 i c :: Type -> Type) # | |
Defined in Servant.API.Generic Methods gtoServant :: K1 i c p -> GToServant (K1 i c :: Type -> Type) gfromServant :: GToServant (K1 i c :: Type -> Type) -> K1 i c p | |
GServantProduct f => GServantProduct (M1 i c f) # | |
Defined in Servant.API.Generic Methods gtoServant :: M1 i c f p -> GToServant (M1 i c f) gfromServant :: GToServant (M1 i c f) -> M1 i c f p |
type GenericServant (routes :: Type -> Type) mode = (GenericMode mode, Generic (routes mode), GServantProduct (Rep (routes mode))) #
A constraint alias, for work with mode
and routes
.
type ToServant (routes :: Type -> Type) mode = GToServant (Rep (routes mode)) #
Turns a generic product type into a tree of :<|>
combinators.
fromServant :: GenericServant routes mode => ToServant routes mode -> routes mode #
Inverse of toServant
.
This can be used to turn generated
values such as client functions into records.
You may need to provide a type signature for the output type (your record type).
genericApi :: forall (routes :: Type -> Type). GenericServant routes AsApi => Proxy routes -> Proxy (ToServantApi routes) #
Get a Proxy
of an API type.
toServant :: GenericServant routes mode => routes mode -> ToServant routes mode #
See ToServant
, but at value-level.
Streaming endpoints, distinguished by HTTP method
data Stream (method :: k1) (status :: Nat) framing contentType a #
A Stream endpoint for a given method emits a stream of encoded values at a
given Content-Type
, delimited by a framing
strategy.
Type synonyms are provided for standard methods.
Instances
HasLink (Stream m status fr ct a :: Type) # | |
Generic (Stream method status framing contentType a) # | |
Defined in Servant.API.Stream | |
type MkLink (Stream m status fr ct a :: Type) r # | |
Defined in Servant.Links | |
type Rep (Stream method status framing contentType a) # | |
class FramingRender (strategy :: k) where #
The FramingRender
class provides the logic for emitting a framing strategy.
The strategy transforms a
into SourceT
m a
,
therefore it can prepend, append and intercalate framing structure
around chunks.SourceT
m ByteString
Note: as the
is generic, this is pure transformation.Monad
m
Methods
framingRender :: forall (m :: Type -> Type) a. Monad m => Proxy strategy -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString #
Instances
FramingRender NetstringFraming # | |
Defined in Servant.API.Stream Methods framingRender :: forall (m :: Type -> Type) a. Monad m => Proxy NetstringFraming -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString # | |
FramingRender NewlineFraming # | |
Defined in Servant.API.Stream Methods framingRender :: forall (m :: Type -> Type) a. Monad m => Proxy NewlineFraming -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString # | |
FramingRender NoFraming # | |
Defined in Servant.API.Stream Methods framingRender :: forall (m :: Type -> Type) a. Monad m => Proxy NoFraming -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString # |
class FramingUnrender (strategy :: k) where #
The FramingUnrender
class provides the logic for parsing a framing
strategy.
Methods
framingUnrender :: forall (m :: Type -> Type) a. Monad m => Proxy strategy -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a #
Instances
FramingUnrender NetstringFraming # | |
Defined in Servant.API.Stream Methods framingUnrender :: forall (m :: Type -> Type) a. Monad m => Proxy NetstringFraming -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a # | |
FramingUnrender NewlineFraming # | |
Defined in Servant.API.Stream Methods framingUnrender :: forall (m :: Type -> Type) a. Monad m => Proxy NewlineFraming -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a # | |
FramingUnrender NoFraming # | As That works well when |
Defined in Servant.API.Stream Methods framingUnrender :: forall (m :: Type -> Type) a. Monad m => Proxy NoFraming -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a # |
class FromSourceIO chunk a | a -> chunk where #
FromSourceIO
is intended to be implemented for types such as Conduit,
Pipe, etc. By implementing this class, all such streaming abstractions can
be used directly on the client side for talking to streaming endpoints.
Methods
fromSourceIO :: SourceIO chunk -> IO a #
Instances
MonadIO m => FromSourceIO a (SourceT m a) # | |
Defined in Servant.API.Stream Methods fromSourceIO :: SourceIO a -> IO (SourceT m a) # |
data NetstringFraming #
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:,"
.
Instances
FramingRender NetstringFraming # | |
Defined in Servant.API.Stream Methods framingRender :: forall (m :: Type -> Type) a. Monad m => Proxy NetstringFraming -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString # | |
FramingUnrender NetstringFraming # | |
Defined in Servant.API.Stream Methods framingUnrender :: forall (m :: Type -> Type) a. Monad m => Proxy NetstringFraming -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a # |
data NewlineFraming #
A simple framing strategy that has no header, and inserts a newline character after each frame. This assumes that it is used with a Content-Type that encodes without newlines (e.g. JSON).
Instances
FramingRender NewlineFraming # | |
Defined in Servant.API.Stream Methods framingRender :: forall (m :: Type -> Type) a. Monad m => Proxy NewlineFraming -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString # | |
FramingUnrender NewlineFraming # | |
Defined in Servant.API.Stream Methods framingUnrender :: forall (m :: Type -> Type) a. Monad m => Proxy NewlineFraming -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a # |
A framing strategy that does not do any framing at all, it just passes the input data This will be used most of the time with binary data, such as files
Instances
FramingRender NoFraming # | |
Defined in Servant.API.Stream Methods framingRender :: forall (m :: Type -> Type) a. Monad m => Proxy NoFraming -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString # | |
FramingUnrender NoFraming # | As That works well when |
Defined in Servant.API.Stream Methods framingUnrender :: forall (m :: Type -> Type) a. Monad m => Proxy NoFraming -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a # |
type StreamBody = StreamBody' ('[] :: [Type]) #
A stream request body.
data StreamBody' (mods :: [Type]) framing contentType a #
Instances
HasLink sub => HasLink (StreamBody' mods framing ct a :> sub :: Type) # | |||||
Defined in Servant.Links Methods toLink :: (Link -> a0) -> Proxy (StreamBody' mods framing ct a :> sub) -> Link -> MkLink (StreamBody' mods framing ct a :> sub) a0 # | |||||
Generic (StreamBody' mods framing contentType a) # | |||||
Defined in Servant.API.Stream Associated Types
Methods from :: StreamBody' mods framing contentType a -> Rep (StreamBody' mods framing contentType a) x # to :: Rep (StreamBody' mods framing contentType a) x -> StreamBody' mods framing contentType a # | |||||
type MkLink (StreamBody' mods framing ct a :> sub :: Type) r # | |||||
Defined in Servant.Links | |||||
type Rep (StreamBody' mods framing contentType a) # | |||||
Defined in Servant.API.Stream |
type StreamPost = Stream 'POST 200 #
class ToSourceIO chunk a | a -> chunk where #
ToSourceIO
is intended to be implemented for types such as Conduit, Pipe,
etc. By implementing this class, all such streaming abstractions can be used
directly as endpoints.
Methods
toSourceIO :: a -> SourceIO chunk #
Instances
ToSourceIO a (NonEmpty a) # | |
Defined in Servant.API.Stream Methods toSourceIO :: NonEmpty a -> SourceIO a # | |
ToSourceIO a [a] # | |
Defined in Servant.API.Stream Methods toSourceIO :: [a] -> SourceIO a # | |
SourceToSourceIO m => ToSourceIO chunk (SourceT m chunk) # | Relax to use auxiliary class, have m |
Defined in Servant.API.Stream Methods toSourceIO :: SourceT m chunk -> SourceIO chunk # |
Authentication
module Servant.API.BasicAuth
Endpoints description
data Description (sym :: Symbol) #
Add more verbose description for (part of) API.
Example:
>>>
:{
type MyApi = Description "This comment is visible in multiple Servant interpretations \ \and can be really long if necessary. \ \Haskell multiline String support is not perfect \ \but it's still very readable." :> Get '[JSON] Book :}
Instances
HasLink sub => HasLink (Description s :> sub :: Type) # | |
Defined in Servant.Links Methods toLink :: (Link -> a) -> Proxy (Description s :> sub) -> Link -> MkLink (Description s :> sub) a # | |
type MkLink (Description s :> sub :: Type) a # | |
Defined in Servant.Links |
data Summary (sym :: Symbol) #
Add a short summary for (part of) API.
Example:
>>>
type MyApi = Summary "Get book by ISBN." :> "books" :> Capture "isbn" Text :> Get '[JSON] Book
Instances
Content Types
class Accept (ctype :: k) where #
Instances of Accept
represent mimetypes. They are used for matching
against the Accept
HTTP header of the request, and for setting the
Content-Type
header of the response
Example:
>>>
import Network.HTTP.Media ((//), (/:))
>>>
data HTML
>>>
:{
instance Accept HTML where contentType _ = "text" // "html" /: ("charset", "utf-8") :}
Minimal complete definition
Instances
Accept FormUrlEncoded # | application/x-www-form-urlencoded |
Defined in Servant.API.ContentTypes Methods contentType :: Proxy FormUrlEncoded -> MediaType # contentTypes :: Proxy FormUrlEncoded -> NonEmpty MediaType # | |
Accept JSON # | application/json |
Defined in Servant.API.ContentTypes | |
Accept OctetStream # | application/octet-stream |
Defined in Servant.API.ContentTypes Methods contentType :: Proxy OctetStream -> MediaType # | |
Accept PlainText # | text/plain;charset=utf-8 |
Defined in Servant.API.ContentTypes |
data FormUrlEncoded #
Instances
Accept FormUrlEncoded # | application/x-www-form-urlencoded |
Defined in Servant.API.ContentTypes Methods contentType :: Proxy FormUrlEncoded -> MediaType # contentTypes :: Proxy FormUrlEncoded -> NonEmpty MediaType # | |
ToForm a => MimeRender FormUrlEncoded a # |
|
Defined in Servant.API.ContentTypes Methods mimeRender :: Proxy FormUrlEncoded -> a -> ByteString # | |
FromForm a => MimeUnrender FormUrlEncoded a # |
|
Defined in Servant.API.ContentTypes Methods mimeUnrender :: Proxy FormUrlEncoded -> ByteString -> Either String a # mimeUnrenderWithType :: Proxy FormUrlEncoded -> MediaType -> ByteString -> Either String a # | |
MimeRender FormUrlEncoded a => MimeRender FormUrlEncoded (WithStatus _status a) # | |
Defined in Servant.API.UVerb Methods mimeRender :: Proxy FormUrlEncoded -> WithStatus _status a -> ByteString # | |
MimeUnrender FormUrlEncoded a => MimeUnrender FormUrlEncoded (WithStatus _status a) # | |
Defined in Servant.API.UVerb Methods mimeUnrender :: Proxy FormUrlEncoded -> ByteString -> Either String (WithStatus _status a) # mimeUnrenderWithType :: Proxy FormUrlEncoded -> MediaType -> ByteString -> Either String (WithStatus _status a) # |
Instances
Accept JSON # | application/json |
Defined in Servant.API.ContentTypes | |
ToJSON a => MimeRender JSON a # | |
Defined in Servant.API.ContentTypes Methods mimeRender :: Proxy JSON -> a -> ByteString # | |
FromJSON a => MimeUnrender JSON a # | |
Defined in Servant.API.ContentTypes Methods mimeUnrender :: Proxy JSON -> ByteString -> Either String a # mimeUnrenderWithType :: Proxy JSON -> MediaType -> ByteString -> Either String a # | |
MimeRender JSON a => MimeRender JSON (WithStatus _status a) # | |
Defined in Servant.API.UVerb Methods mimeRender :: Proxy JSON -> WithStatus _status a -> ByteString # | |
MimeUnrender JSON a => MimeUnrender JSON (WithStatus _status a) # | |
Defined in Servant.API.UVerb Methods mimeUnrender :: Proxy JSON -> ByteString -> Either String (WithStatus _status a) # mimeUnrenderWithType :: Proxy JSON -> MediaType -> ByteString -> Either String (WithStatus _status a) # |
class Accept ctype => MimeRender (ctype :: k) a where #
Instantiate this class to register a way of serializing a type based
on the Accept
header.
Example:
data MyContentType instance Accept MyContentType where contentType _ = "example" // "prs.me.mine" /: ("charset", "utf-8") instance Show a => MimeRender MyContentType a where mimeRender _ val = pack ("This is MINE! " ++ show val) type MyAPI = "path" :> Get '[MyContentType] Int
Methods
mimeRender :: Proxy ctype -> a -> ByteString #
Instances
ToForm a => MimeRender FormUrlEncoded a # |
|
Defined in Servant.API.ContentTypes Methods mimeRender :: Proxy FormUrlEncoded -> a -> ByteString # | |
ToJSON a => MimeRender JSON a # | |
Defined in Servant.API.ContentTypes Methods mimeRender :: Proxy JSON -> a -> ByteString # | |
MimeRender OctetStream ByteString # | |
Defined in Servant.API.ContentTypes Methods mimeRender :: Proxy OctetStream -> ByteString -> ByteString # | |
MimeRender OctetStream ByteString # | id |
Defined in Servant.API.ContentTypes Methods mimeRender :: Proxy OctetStream -> ByteString -> ByteString # | |
MimeRender PlainText Text # | fromStrict . TextS.encodeUtf8 |
Defined in Servant.API.ContentTypes Methods mimeRender :: Proxy PlainText -> Text -> ByteString # | |
MimeRender PlainText Text # | |
Defined in Servant.API.ContentTypes Methods mimeRender :: Proxy PlainText -> Text -> ByteString # | |
MimeRender PlainText String # | BC.pack |
Defined in Servant.API.ContentTypes Methods mimeRender :: Proxy PlainText -> String -> ByteString # | |
MimeRender FormUrlEncoded a => MimeRender FormUrlEncoded (WithStatus _status a) # | |
Defined in Servant.API.UVerb Methods mimeRender :: Proxy FormUrlEncoded -> WithStatus _status a -> ByteString # | |
MimeRender JSON a => MimeRender JSON (WithStatus _status a) # | |
Defined in Servant.API.UVerb Methods mimeRender :: Proxy JSON -> WithStatus _status a -> ByteString # | |
MimeRender OctetStream a => MimeRender OctetStream (WithStatus _status a) # | |
Defined in Servant.API.UVerb Methods mimeRender :: Proxy OctetStream -> WithStatus _status a -> ByteString # | |
MimeRender PlainText a => MimeRender PlainText (WithStatus _status a) # | |
Defined in Servant.API.UVerb Methods mimeRender :: Proxy PlainText -> WithStatus _status a -> ByteString # |
class Accept ctype => MimeUnrender (ctype :: k) a where #
Instantiate this class to register a way of deserializing a type based
on the request's Content-Type
header.
>>>
import Network.HTTP.Media hiding (Accept)
>>>
import qualified Data.ByteString.Lazy.Char8 as BSC
>>>
data MyContentType = MyContentType String
>>>
:{
instance Accept MyContentType where contentType _ = "example" // "prs.me.mine" /: ("charset", "utf-8") :}
>>>
:{
instance Read a => MimeUnrender MyContentType a where mimeUnrender _ bs = case BSC.take 12 bs of "MyContentType" -> return . read . BSC.unpack $ BSC.drop 12 bs _ -> Left "didn't start with the magic incantation" :}
>>>
type MyAPI = "path" :> ReqBody '[MyContentType] Int :> Get '[JSON] Int
Minimal complete definition
Methods
mimeUnrender :: Proxy ctype -> ByteString -> Either String a #
mimeUnrenderWithType :: Proxy ctype -> MediaType -> ByteString -> Either String a #
Instances
FromForm a => MimeUnrender FormUrlEncoded a # |
|
Defined in Servant.API.ContentTypes Methods mimeUnrender :: Proxy FormUrlEncoded -> ByteString -> Either String a # mimeUnrenderWithType :: Proxy FormUrlEncoded -> MediaType -> ByteString -> Either String a # | |
FromJSON a => MimeUnrender JSON a # | |
Defined in Servant.API.ContentTypes Methods mimeUnrender :: Proxy JSON -> ByteString -> Either String a # mimeUnrenderWithType :: Proxy JSON -> MediaType -> ByteString -> Either String a # | |
MimeUnrender OctetStream ByteString # | Right . toStrict |
Defined in Servant.API.ContentTypes Methods mimeUnrender :: Proxy OctetStream -> ByteString -> Either String ByteString # mimeUnrenderWithType :: Proxy OctetStream -> MediaType -> ByteString -> Either String ByteString # | |
MimeUnrender OctetStream ByteString # | Right . id |
Defined in Servant.API.ContentTypes Methods mimeUnrender :: Proxy OctetStream -> ByteString -> Either String ByteString # mimeUnrenderWithType :: Proxy OctetStream -> MediaType -> ByteString -> Either String ByteString # | |
MimeUnrender PlainText Text # | left show . TextS.decodeUtf8' . toStrict |
Defined in Servant.API.ContentTypes Methods mimeUnrender :: Proxy PlainText -> ByteString -> Either String Text # mimeUnrenderWithType :: Proxy PlainText -> MediaType -> ByteString -> Either String Text # | |
MimeUnrender PlainText Text # | left show . TextL.decodeUtf8' |
Defined in Servant.API.ContentTypes Methods mimeUnrender :: Proxy PlainText -> ByteString -> Either String Text # mimeUnrenderWithType :: Proxy PlainText -> MediaType -> ByteString -> Either String Text # | |
MimeUnrender PlainText String # | Right . BC.unpack |
Defined in Servant.API.ContentTypes Methods mimeUnrender :: Proxy PlainText -> ByteString -> Either String String # mimeUnrenderWithType :: Proxy PlainText -> MediaType -> ByteString -> Either String String # | |
MimeUnrender FormUrlEncoded a => MimeUnrender FormUrlEncoded (WithStatus _status a) # | |
Defined in Servant.API.UVerb Methods mimeUnrender :: Proxy FormUrlEncoded -> ByteString -> Either String (WithStatus _status a) # mimeUnrenderWithType :: Proxy FormUrlEncoded -> MediaType -> ByteString -> Either String (WithStatus _status a) # | |
MimeUnrender JSON a => MimeUnrender JSON (WithStatus _status a) # | |
Defined in Servant.API.UVerb Methods mimeUnrender :: Proxy JSON -> ByteString -> Either String (WithStatus _status a) # mimeUnrenderWithType :: Proxy JSON -> MediaType -> ByteString -> Either String (WithStatus _status a) # | |
MimeUnrender OctetStream a => MimeUnrender OctetStream (WithStatus _status a) # | |
Defined in Servant.API.UVerb Methods mimeUnrender :: Proxy OctetStream -> ByteString -> Either String (WithStatus _status a) # mimeUnrenderWithType :: Proxy OctetStream -> MediaType -> ByteString -> Either String (WithStatus _status a) # | |
MimeUnrender PlainText a => MimeUnrender PlainText (WithStatus _status a) # | |
Defined in Servant.API.UVerb Methods mimeUnrender :: Proxy PlainText -> ByteString -> Either String (WithStatus _status a) # mimeUnrenderWithType :: Proxy PlainText -> MediaType -> ByteString -> Either String (WithStatus _status a) # |
A type for responses without content-body.
Constructors
NoContent |
Instances
Generic NoContent # | |||||
Defined in Servant.API.ContentTypes | |||||
Read NoContent # | |||||
Show NoContent # | |||||
NFData NoContent # | |||||
Defined in Servant.API.ContentTypes | |||||
Eq NoContent # | |||||
HasStatus NoContent # | If an API can respond with | ||||
Defined in Servant.API.UVerb Associated Types
| |||||
AllMime (ctyp ': (ctyp' ': ctyps)) => AllMimeRender (ctyp ': (ctyp' ': ctyps)) NoContent # | |||||
Defined in Servant.API.ContentTypes Methods allMimeRender :: Proxy (ctyp ': (ctyp' ': ctyps)) -> NoContent -> [(MediaType, ByteString)] # | |||||
Accept ctyp => AllMimeRender '[ctyp] NoContent # | |||||
Defined in Servant.API.ContentTypes Methods allMimeRender :: Proxy '[ctyp] -> NoContent -> [(MediaType, ByteString)] # | |||||
type Rep NoContent # | |||||
type StatusOf NoContent # | |||||
Defined in Servant.API.UVerb |
data OctetStream #
Instances
Accept OctetStream # | application/octet-stream |
Defined in Servant.API.ContentTypes Methods contentType :: Proxy OctetStream -> MediaType # | |
MimeRender OctetStream ByteString # | |
Defined in Servant.API.ContentTypes Methods mimeRender :: Proxy OctetStream -> ByteString -> ByteString # | |
MimeRender OctetStream ByteString # | id |
Defined in Servant.API.ContentTypes Methods mimeRender :: Proxy OctetStream -> ByteString -> ByteString # | |
MimeUnrender OctetStream ByteString # | Right . toStrict |
Defined in Servant.API.ContentTypes Methods mimeUnrender :: Proxy OctetStream -> ByteString -> Either String ByteString # mimeUnrenderWithType :: Proxy OctetStream -> MediaType -> ByteString -> Either String ByteString # | |
MimeUnrender OctetStream ByteString # | Right . id |
Defined in Servant.API.ContentTypes Methods mimeUnrender :: Proxy OctetStream -> ByteString -> Either String ByteString # mimeUnrenderWithType :: Proxy OctetStream -> MediaType -> ByteString -> Either String ByteString # | |
MimeRender OctetStream a => MimeRender OctetStream (WithStatus _status a) # | |
Defined in Servant.API.UVerb Methods mimeRender :: Proxy OctetStream -> WithStatus _status a -> ByteString # | |
MimeUnrender OctetStream a => MimeUnrender OctetStream (WithStatus _status a) # | |
Defined in Servant.API.UVerb Methods mimeUnrender :: Proxy OctetStream -> ByteString -> Either String (WithStatus _status a) # mimeUnrenderWithType :: Proxy OctetStream -> MediaType -> ByteString -> Either String (WithStatus _status a) # |
Instances
Accept PlainText # | text/plain;charset=utf-8 |
Defined in Servant.API.ContentTypes | |
MimeRender PlainText Text # | fromStrict . TextS.encodeUtf8 |
Defined in Servant.API.ContentTypes Methods mimeRender :: Proxy PlainText -> Text -> ByteString # | |
MimeRender PlainText Text # | |
Defined in Servant.API.ContentTypes Methods mimeRender :: Proxy PlainText -> Text -> ByteString # | |
MimeRender PlainText String # | BC.pack |
Defined in Servant.API.ContentTypes Methods mimeRender :: Proxy PlainText -> String -> ByteString # | |
MimeUnrender PlainText Text # | left show . TextS.decodeUtf8' . toStrict |
Defined in Servant.API.ContentTypes Methods mimeUnrender :: Proxy PlainText -> ByteString -> Either String Text # mimeUnrenderWithType :: Proxy PlainText -> MediaType -> ByteString -> Either String Text # | |
MimeUnrender PlainText Text # | left show . TextL.decodeUtf8' |
Defined in Servant.API.ContentTypes Methods mimeUnrender :: Proxy PlainText -> ByteString -> Either String Text # mimeUnrenderWithType :: Proxy PlainText -> MediaType -> ByteString -> Either String Text # | |
MimeUnrender PlainText String # | Right . BC.unpack |
Defined in Servant.API.ContentTypes Methods mimeUnrender :: Proxy PlainText -> ByteString -> Either String String # mimeUnrenderWithType :: Proxy PlainText -> MediaType -> ByteString -> Either String String # | |
MimeRender PlainText a => MimeRender PlainText (WithStatus _status a) # | |
Defined in Servant.API.UVerb Methods mimeRender :: Proxy PlainText -> WithStatus _status a -> ByteString # | |
MimeUnrender PlainText a => MimeUnrender PlainText (WithStatus _status a) # | |
Defined in Servant.API.UVerb Methods mimeUnrender :: Proxy PlainText -> ByteString -> Either String (WithStatus _status a) # mimeUnrenderWithType :: Proxy PlainText -> MediaType -> ByteString -> Either String (WithStatus _status a) # |
Serializing and deserializing types based on Accept
and
Content-Type
headers.
Response Headers
data ResponseHeader (sym :: Symbol) a #
Constructors
Header a | |
MissingHeader | |
UndecodableHeader ByteString |
Instances
Functor (ResponseHeader sym) # | |
Defined in Servant.API.ResponseHeaders Methods fmap :: (a -> b) -> ResponseHeader sym a -> ResponseHeader sym b # (<$) :: a -> ResponseHeader sym b -> ResponseHeader sym a # | |
Show a => Show (ResponseHeader sym a) # | |
Defined in Servant.API.ResponseHeaders Methods showsPrec :: Int -> ResponseHeader sym a -> ShowS # show :: ResponseHeader sym a -> String # showList :: [ResponseHeader sym a] -> ShowS # | |
NFData a => NFData (ResponseHeader sym a) # | |
Defined in Servant.API.ResponseHeaders Methods rnf :: ResponseHeader sym a -> () # | |
Eq a => Eq (ResponseHeader sym a) # | |
Defined in Servant.API.ResponseHeaders Methods (==) :: ResponseHeader sym a -> ResponseHeader sym a -> Bool # (/=) :: ResponseHeader sym a -> ResponseHeader sym a -> Bool # |
class AddHeader (h :: Symbol) v orig new | h v orig -> new, new -> h, new -> v, new -> orig #
Minimal complete definition
addOptionalHeader
Instances
(KnownSymbol h, ToHttpApiData v, new ~ Headers '[Header h v] a) => AddHeader h v a new # | |
Defined in Servant.API.ResponseHeaders Methods addOptionalHeader :: ResponseHeader h v -> a -> new | |
(AddHeader h v old new, AddHeader h v (Union oldrest) (Union newrest), oldrest ~ (a ': as), newrest ~ (b ': bs)) => AddHeader h v (Union (old ': (a ': as))) (Union (new ': (b ': bs))) # | |
Defined in Servant.API.ResponseHeaders Methods addOptionalHeader :: ResponseHeader h v -> Union (old ': (a ': as)) -> Union (new ': (b ': bs)) | |
AddHeader h v old new => AddHeader h v (Union '[old]) (Union '[new]) # | |
Defined in Servant.API.ResponseHeaders Methods addOptionalHeader :: ResponseHeader h v -> Union '[old] -> Union '[new] | |
(KnownSymbol h, ToHttpApiData v) => AddHeader h v (Headers (fst ': rest) a) (Headers (Header h v ': (fst ': rest)) a) # | |
Defined in Servant.API.ResponseHeaders Methods addOptionalHeader :: ResponseHeader h v -> Headers (fst ': rest) a -> Headers (Header h v ': (fst ': rest)) a |
class BuildHeadersTo (hs :: [Type]) where #
Methods
buildHeadersTo :: [Header] -> HList hs #
Instances
BuildHeadersTo ('[] :: [Type]) # | |
Defined in Servant.API.ResponseHeaders Methods buildHeadersTo :: [Header] -> HList ('[] :: [Type]) # | |
(FromHttpApiData v, BuildHeadersTo xs, KnownSymbol h) => BuildHeadersTo (Header h v ': xs) # | |
Defined in Servant.API.ResponseHeaders Methods buildHeadersTo :: [Header] -> HList (Header h v ': xs) # |
class GetHeaders ls where #
Methods
getHeaders :: ls -> [Header] #
Instances
GetHeadersFromHList hs => GetHeaders (HList hs) # | |
Defined in Servant.API.ResponseHeaders Methods getHeaders :: HList hs -> [Header] # | |
GetHeaders' hs => GetHeaders (Headers hs a) # | |
Defined in Servant.API.ResponseHeaders Methods getHeaders :: Headers hs a -> [Header] # |
data HList (a :: [Type]) where #
Constructors
HNil :: HList ('[] :: [Type]) | |
HCons :: forall (h :: Symbol) x (xs :: [Type]). ResponseHeader h x -> HList xs -> HList (Header h x ': xs) |
Instances
NFDataHList xs => NFData (HList xs) # | |
Defined in Servant.API.ResponseHeaders | |
GetHeadersFromHList hs => GetHeaders (HList hs) # | |
Defined in Servant.API.ResponseHeaders Methods getHeaders :: HList hs -> [Header] # |
class HasResponseHeader (h :: Symbol) a (headers :: [Type]) #
Minimal complete definition
hlistLookupHeader
Instances
HasResponseHeader h a (Header h a ': rest) # | |
Defined in Servant.API.ResponseHeaders Methods hlistLookupHeader :: HList (Header h a ': rest) -> ResponseHeader h a | |
HasResponseHeader h a rest => HasResponseHeader h a (first ': rest) # | |
Defined in Servant.API.ResponseHeaders Methods hlistLookupHeader :: HList (first ': rest) -> ResponseHeader h a |
data Headers (ls :: [Type]) a #
Response Header objects. You should never need to construct one directly.
Instead, use addOptionalHeader
.
Constructors
Headers | |
Fields
|
Instances
(KnownSymbol h, ToHttpApiData v) => AddHeader h v (Headers (fst ': rest) a) (Headers (Header h v ': (fst ': rest)) a) # | |
Defined in Servant.API.ResponseHeaders Methods addOptionalHeader :: ResponseHeader h v -> Headers (fst ': rest) a -> Headers (Header h v ': (fst ': rest)) a | |
Functor (Headers ls) # | |
(NFDataHList ls, NFData a) => NFData (Headers ls a) # | |
Defined in Servant.API.ResponseHeaders | |
GetHeaders' hs => GetHeaders (Headers hs a) # | |
Defined in Servant.API.ResponseHeaders Methods getHeaders :: Headers hs a -> [Header] # | |
HasStatus a => HasStatus (Headers ls a) # | |
Defined in Servant.API.UVerb | |
type StatusOf (Headers ls a) # | |
Defined in Servant.API.UVerb |
addHeader :: forall (h :: Symbol) v orig new. AddHeader h v orig new => v -> orig -> new #
addHeader
adds a header to a response. Note that it changes the type of
the value in the following ways:
- A simple value is wrapped in "Headers '[hdr]":
>>>
let example0 = addHeader 5 "hi" :: Headers '[Header "someheader" Int] String;
>>>
getHeaders example0
[("someheader","5")]
- A value that already has a header has its new header *prepended* to the existing list:
>>>
let example1 = addHeader 5 "hi" :: Headers '[Header "someheader" Int] String;
>>>
let example2 = addHeader True example1 :: Headers '[Header "1st" Bool, Header "someheader" Int] String
>>>
getHeaders example2
[("1st","true"),("someheader","5")]
Note that while in your handlers type annotations are not required, since the type can be inferred from the API type, in other cases you may find yourself needing to add annotations.
lookupResponseHeader :: forall (h :: Symbol) a (headers :: [Type]) r. HasResponseHeader h a headers => Headers headers r -> ResponseHeader h a #
Look up a specific ResponseHeader, without having to know what position it is in the HList.
>>>
let example1 = addHeader 5 "hi" :: Headers '[Header "someheader" Int] String
>>>
let example2 = addHeader True example1 :: Headers '[Header "1st" Bool, Header "someheader" Int] String
>>>
lookupResponseHeader example2 :: ResponseHeader "someheader" Int
Header 5
>>>
lookupResponseHeader example2 :: ResponseHeader "1st" Bool
Header True
Usage of this function relies on an explicit type annotation of the header to be looked up. This can be done with type annotations on the result, or with an explicit type application. In this example, the type of header value is determined by the type-inference, we only specify the name of the header:
>>>
:set -XTypeApplications
>>>
case lookupResponseHeader @"1st" example2 of { Header b -> b ; _ -> False }
True
Since: 0.15
noHeader :: forall (h :: Symbol) v orig new. AddHeader h v orig new => orig -> new #
Deliberately do not add a header to a value.
>>>
let example1 = noHeader "hi" :: Headers '[Header "someheader" Int] String
>>>
getHeaders example1
[]
Untyped endpoints
module Servant.API.Raw
Plugging in a wai Application
, serving directories
FromHttpApiData and ToHttpApiData
class FromHttpApiData a where #
Parse value from HTTP API data.
WARNING: Do not derive this using DeriveAnyClass
as the generated
instance will loop indefinitely.
Minimal complete definition
Methods
parseUrlPiece :: Text -> Either Text a #
Parse URL path piece.
parseHeader :: ByteString -> Either Text a #
Parse HTTP header value.
parseQueryParam :: Text -> Either Text a #
Parse query param value.
Instances
FromHttpApiData All | |
Defined in Web.Internal.HttpApiData | |
FromHttpApiData Any | |
Defined in Web.Internal.HttpApiData | |
FromHttpApiData Version |
|
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text Version # parseHeader :: ByteString -> Either Text Version # | |
FromHttpApiData Void | Parsing a |
Defined in Web.Internal.HttpApiData | |
FromHttpApiData Int16 | |
Defined in Web.Internal.HttpApiData | |
FromHttpApiData Int32 | |
Defined in Web.Internal.HttpApiData | |
FromHttpApiData Int64 | |
Defined in Web.Internal.HttpApiData | |
FromHttpApiData Int8 | |
Defined in Web.Internal.HttpApiData | |
FromHttpApiData Word16 | |
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text Word16 # parseHeader :: ByteString -> Either Text Word16 # | |
FromHttpApiData Word32 | |
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text Word32 # parseHeader :: ByteString -> Either Text Word32 # | |
FromHttpApiData Word64 | |
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text Word64 # parseHeader :: ByteString -> Either Text Word64 # | |
FromHttpApiData Word8 | |
Defined in Web.Internal.HttpApiData | |
FromHttpApiData SetCookie | Note: this instance works correctly for alphanumeric name and value
|
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text SetCookie # parseHeader :: ByteString -> Either Text SetCookie # | |
FromHttpApiData Ordering | |
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text Ordering # parseHeader :: ByteString -> Either Text Ordering # | |
FromHttpApiData Text | |
Defined in Web.Internal.HttpApiData | |
FromHttpApiData Text | |
Defined in Web.Internal.HttpApiData | |
FromHttpApiData Day |
|
Defined in Web.Internal.HttpApiData | |
FromHttpApiData Month |
|
Defined in Web.Internal.HttpApiData | |
FromHttpApiData Quarter |
|
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text Quarter # parseHeader :: ByteString -> Either Text Quarter # | |
FromHttpApiData QuarterOfYear |
|
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text QuarterOfYear # parseHeader :: ByteString -> Either Text QuarterOfYear # parseQueryParam :: Text -> Either Text QuarterOfYear # | |
FromHttpApiData DayOfWeek |
|
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text DayOfWeek # parseHeader :: ByteString -> Either Text DayOfWeek # | |
FromHttpApiData NominalDiffTime | |
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text NominalDiffTime # | |
FromHttpApiData UTCTime |
|
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text UTCTime # parseHeader :: ByteString -> Either Text UTCTime # | |
FromHttpApiData LocalTime |
|
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text LocalTime # parseHeader :: ByteString -> Either Text LocalTime # | |
FromHttpApiData TimeOfDay |
|
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text TimeOfDay # parseHeader :: ByteString -> Either Text TimeOfDay # | |
FromHttpApiData ZonedTime |
|
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text ZonedTime # parseHeader :: ByteString -> Either Text ZonedTime # | |
FromHttpApiData UUID | |
Defined in Web.Internal.HttpApiData | |
FromHttpApiData String | |
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text String # parseHeader :: ByteString -> Either Text String # | |
FromHttpApiData Integer | |
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text Integer # parseHeader :: ByteString -> Either Text Integer # | |
FromHttpApiData Natural | |
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text Natural # parseHeader :: ByteString -> Either Text Natural # | |
FromHttpApiData () |
|
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text () # parseHeader :: ByteString -> Either Text () # parseQueryParam :: Text -> Either Text () # | |
FromHttpApiData Bool | |
Defined in Web.Internal.HttpApiData | |
FromHttpApiData Char | |
Defined in Web.Internal.HttpApiData | |
FromHttpApiData Double | |
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text Double # parseHeader :: ByteString -> Either Text Double # | |
FromHttpApiData Float | |
Defined in Web.Internal.HttpApiData | |
FromHttpApiData Int | |
Defined in Web.Internal.HttpApiData | |
FromHttpApiData Word | |
Defined in Web.Internal.HttpApiData | |
FromHttpApiData a => FromHttpApiData (Identity a) | Since: http-api-data-0.4.2 |
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text (Identity a) # parseHeader :: ByteString -> Either Text (Identity a) # | |
FromHttpApiData a => FromHttpApiData (First a) | |
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text (First a) # parseHeader :: ByteString -> Either Text (First a) # | |
FromHttpApiData a => FromHttpApiData (Last a) | |
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text (Last a) # parseHeader :: ByteString -> Either Text (Last a) # | |
FromHttpApiData a => FromHttpApiData (First a) | |
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text (First a) # parseHeader :: ByteString -> Either Text (First a) # | |
FromHttpApiData a => FromHttpApiData (Last a) | |
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text (Last a) # parseHeader :: ByteString -> Either Text (Last a) # | |
FromHttpApiData a => FromHttpApiData (Max a) | |
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text (Max a) # parseHeader :: ByteString -> Either Text (Max a) # | |
FromHttpApiData a => FromHttpApiData (Min a) | |
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text (Min a) # parseHeader :: ByteString -> Either Text (Min a) # | |
FromHttpApiData a => FromHttpApiData (Dual a) | |
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text (Dual a) # parseHeader :: ByteString -> Either Text (Dual a) # | |
FromHttpApiData a => FromHttpApiData (Product a) | |
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text (Product a) # parseHeader :: ByteString -> Either Text (Product a) # | |
FromHttpApiData a => FromHttpApiData (Sum a) | |
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text (Sum a) # parseHeader :: ByteString -> Either Text (Sum a) # | |
FromHttpApiData a => FromHttpApiData (LenientData a) | |
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text (LenientData a) # parseHeader :: ByteString -> Either Text (LenientData a) # parseQueryParam :: Text -> Either Text (LenientData a) # | |
FromHttpApiData a => FromHttpApiData (Maybe a) |
|
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text (Maybe a) # parseHeader :: ByteString -> Either Text (Maybe a) # | |
(FromHttpApiData a, FromHttpApiData b) => FromHttpApiData (Either a b) |
|
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text (Either a b) # parseHeader :: ByteString -> Either Text (Either a b) # | |
HasResolution a => FromHttpApiData (Fixed a) | Note: this instance is not polykinded |
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text (Fixed a) # parseHeader :: ByteString -> Either Text (Fixed a) # | |
FromHttpApiData a => FromHttpApiData (Const a b) | Since: http-api-data-0.4.2 |
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text (Const a b) # parseHeader :: ByteString -> Either Text (Const a b) # | |
FromHttpApiData a => FromHttpApiData (Tagged b a) | Note: this instance is not polykinded |
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text (Tagged b a) # parseHeader :: ByteString -> Either Text (Tagged b a) # |
class ToHttpApiData a where #
Convert value to HTTP API data.
WARNING: Do not derive this using DeriveAnyClass
as the generated
instance will loop indefinitely.
Minimal complete definition
Methods
toUrlPiece :: a -> Text #
Convert to URL path piece.
toEncodedUrlPiece :: a -> Builder #
Convert to a URL path piece, making sure to encode any special chars.
The default definition uses
but this may be overriden with a more efficient version.urlEncodeBuilder
False
toHeader :: a -> ByteString #
Convert to HTTP header value.
toQueryParam :: a -> Text #
Convert to query param value.
toEncodedQueryParam :: a -> Builder #
Convert to URL query param,
The default definition uses
but this may be overriden with a more efficient version.urlEncodeBuilder
True
Since: http-api-data-0.5.1
Instances
ToHttpApiData All | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: All -> Text # toEncodedUrlPiece :: All -> Builder # toHeader :: All -> ByteString # toQueryParam :: All -> Text # toEncodedQueryParam :: All -> Builder # | |
ToHttpApiData Any | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Any -> Text # toEncodedUrlPiece :: Any -> Builder # toHeader :: Any -> ByteString # toQueryParam :: Any -> Text # toEncodedQueryParam :: Any -> Builder # | |
ToHttpApiData Version |
|
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Version -> Text # toEncodedUrlPiece :: Version -> Builder # toHeader :: Version -> ByteString # toQueryParam :: Version -> Text # toEncodedQueryParam :: Version -> Builder # | |
ToHttpApiData Void | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Void -> Text # toEncodedUrlPiece :: Void -> Builder # toHeader :: Void -> ByteString # toQueryParam :: Void -> Text # toEncodedQueryParam :: Void -> Builder # | |
ToHttpApiData Int16 | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Int16 -> Text # toEncodedUrlPiece :: Int16 -> Builder # toHeader :: Int16 -> ByteString # toQueryParam :: Int16 -> Text # toEncodedQueryParam :: Int16 -> Builder # | |
ToHttpApiData Int32 | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Int32 -> Text # toEncodedUrlPiece :: Int32 -> Builder # toHeader :: Int32 -> ByteString # toQueryParam :: Int32 -> Text # toEncodedQueryParam :: Int32 -> Builder # | |
ToHttpApiData Int64 | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Int64 -> Text # toEncodedUrlPiece :: Int64 -> Builder # toHeader :: Int64 -> ByteString # toQueryParam :: Int64 -> Text # toEncodedQueryParam :: Int64 -> Builder # | |
ToHttpApiData Int8 | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Int8 -> Text # toEncodedUrlPiece :: Int8 -> Builder # toHeader :: Int8 -> ByteString # toQueryParam :: Int8 -> Text # toEncodedQueryParam :: Int8 -> Builder # | |
ToHttpApiData Word16 | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Word16 -> Text # toEncodedUrlPiece :: Word16 -> Builder # toHeader :: Word16 -> ByteString # toQueryParam :: Word16 -> Text # toEncodedQueryParam :: Word16 -> Builder # | |
ToHttpApiData Word32 | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Word32 -> Text # toEncodedUrlPiece :: Word32 -> Builder # toHeader :: Word32 -> ByteString # toQueryParam :: Word32 -> Text # toEncodedQueryParam :: Word32 -> Builder # | |
ToHttpApiData Word64 | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Word64 -> Text # toEncodedUrlPiece :: Word64 -> Builder # toHeader :: Word64 -> ByteString # toQueryParam :: Word64 -> Text # toEncodedQueryParam :: Word64 -> Builder # | |
ToHttpApiData Word8 | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Word8 -> Text # toEncodedUrlPiece :: Word8 -> Builder # toHeader :: Word8 -> ByteString # toQueryParam :: Word8 -> Text # toEncodedQueryParam :: Word8 -> Builder # | |
ToHttpApiData SetCookie | Note: this instance works correctly for alphanumeric name and value
|
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: SetCookie -> Text # toEncodedUrlPiece :: SetCookie -> Builder # toHeader :: SetCookie -> ByteString # toQueryParam :: SetCookie -> Text # toEncodedQueryParam :: SetCookie -> Builder # | |
ToHttpApiData Ordering | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Ordering -> Text # toEncodedUrlPiece :: Ordering -> Builder # toHeader :: Ordering -> ByteString # toQueryParam :: Ordering -> Text # toEncodedQueryParam :: Ordering -> Builder # | |
ToHttpApiData Link # | |
Defined in Servant.Links Methods toUrlPiece :: Link -> Text # toEncodedUrlPiece :: Link -> Builder # toHeader :: Link -> ByteString # toQueryParam :: Link -> Text # toEncodedQueryParam :: Link -> Builder # | |
ToHttpApiData Text | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Text -> Text # toEncodedUrlPiece :: Text -> Builder # toHeader :: Text -> ByteString # toQueryParam :: Text -> Text # toEncodedQueryParam :: Text -> Builder # | |
ToHttpApiData Text | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Text -> Text # toEncodedUrlPiece :: Text -> Builder # toHeader :: Text -> ByteString # toQueryParam :: Text -> Text # toEncodedQueryParam :: Text -> Builder # | |
ToHttpApiData Day |
|
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Day -> Text # toEncodedUrlPiece :: Day -> Builder # toHeader :: Day -> ByteString # toQueryParam :: Day -> Text # toEncodedQueryParam :: Day -> Builder # | |
ToHttpApiData Month |
|
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Month -> Text # toEncodedUrlPiece :: Month -> Builder # toHeader :: Month -> ByteString # toQueryParam :: Month -> Text # toEncodedQueryParam :: Month -> Builder # | |
ToHttpApiData Quarter |
|
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Quarter -> Text # toEncodedUrlPiece :: Quarter -> Builder # toHeader :: Quarter -> ByteString # toQueryParam :: Quarter -> Text # toEncodedQueryParam :: Quarter -> Builder # | |
ToHttpApiData QuarterOfYear |
|
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: QuarterOfYear -> Text # toEncodedUrlPiece :: QuarterOfYear -> Builder # toHeader :: QuarterOfYear -> ByteString # toQueryParam :: QuarterOfYear -> Text # | |
ToHttpApiData DayOfWeek |
|
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: DayOfWeek -> Text # toEncodedUrlPiece :: DayOfWeek -> Builder # toHeader :: DayOfWeek -> ByteString # toQueryParam :: DayOfWeek -> Text # toEncodedQueryParam :: DayOfWeek -> Builder # | |
ToHttpApiData NominalDiffTime | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: NominalDiffTime -> Text # toEncodedUrlPiece :: NominalDiffTime -> Builder # toHeader :: NominalDiffTime -> ByteString # toQueryParam :: NominalDiffTime -> Text # | |
ToHttpApiData UTCTime |
|
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: UTCTime -> Text # toEncodedUrlPiece :: UTCTime -> Builder # toHeader :: UTCTime -> ByteString # toQueryParam :: UTCTime -> Text # toEncodedQueryParam :: UTCTime -> Builder # | |
ToHttpApiData LocalTime |
|
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: LocalTime -> Text # toEncodedUrlPiece :: LocalTime -> Builder # toHeader :: LocalTime -> ByteString # toQueryParam :: LocalTime -> Text # toEncodedQueryParam :: LocalTime -> Builder # | |
ToHttpApiData TimeOfDay |
|
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: TimeOfDay -> Text # toEncodedUrlPiece :: TimeOfDay -> Builder # toHeader :: TimeOfDay -> ByteString # toQueryParam :: TimeOfDay -> Text # toEncodedQueryParam :: TimeOfDay -> Builder # | |
ToHttpApiData ZonedTime |
|
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: ZonedTime -> Text # toEncodedUrlPiece :: ZonedTime -> Builder # toHeader :: ZonedTime -> ByteString # toQueryParam :: ZonedTime -> Text # toEncodedQueryParam :: ZonedTime -> Builder # | |
ToHttpApiData UUID | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: UUID -> Text # toEncodedUrlPiece :: UUID -> Builder # toHeader :: UUID -> ByteString # toQueryParam :: UUID -> Text # toEncodedQueryParam :: UUID -> Builder # | |
ToHttpApiData String | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: String -> Text # toEncodedUrlPiece :: String -> Builder # toHeader :: String -> ByteString # toQueryParam :: String -> Text # toEncodedQueryParam :: String -> Builder # | |
ToHttpApiData Integer | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Integer -> Text # toEncodedUrlPiece :: Integer -> Builder # toHeader :: Integer -> ByteString # toQueryParam :: Integer -> Text # toEncodedQueryParam :: Integer -> Builder # | |
ToHttpApiData Natural | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Natural -> Text # toEncodedUrlPiece :: Natural -> Builder # toHeader :: Natural -> ByteString # toQueryParam :: Natural -> Text # toEncodedQueryParam :: Natural -> Builder # | |
ToHttpApiData () |
|
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: () -> Text # toEncodedUrlPiece :: () -> Builder # toHeader :: () -> ByteString # toQueryParam :: () -> Text # toEncodedQueryParam :: () -> Builder # | |
ToHttpApiData Bool | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Bool -> Text # toEncodedUrlPiece :: Bool -> Builder # toHeader :: Bool -> ByteString # toQueryParam :: Bool -> Text # toEncodedQueryParam :: Bool -> Builder # | |
ToHttpApiData Char | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Char -> Text # toEncodedUrlPiece :: Char -> Builder # toHeader :: Char -> ByteString # toQueryParam :: Char -> Text # toEncodedQueryParam :: Char -> Builder # | |
ToHttpApiData Double | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Double -> Text # toEncodedUrlPiece :: Double -> Builder # toHeader :: Double -> ByteString # toQueryParam :: Double -> Text # toEncodedQueryParam :: Double -> Builder # | |
ToHttpApiData Float | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Float -> Text # toEncodedUrlPiece :: Float -> Builder # toHeader :: Float -> ByteString # toQueryParam :: Float -> Text # toEncodedQueryParam :: Float -> Builder # | |
ToHttpApiData Int | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Int -> Text # toEncodedUrlPiece :: Int -> Builder # toHeader :: Int -> ByteString # toQueryParam :: Int -> Text # toEncodedQueryParam :: Int -> Builder # | |
ToHttpApiData Word | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Word -> Text # toEncodedUrlPiece :: Word -> Builder # toHeader :: Word -> ByteString # toQueryParam :: Word -> Text # toEncodedQueryParam :: Word -> Builder # | |
ToHttpApiData a => ToHttpApiData (Identity a) | Since: http-api-data-0.4.2 |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Identity a -> Text # toEncodedUrlPiece :: Identity a -> Builder # toHeader :: Identity a -> ByteString # toQueryParam :: Identity a -> Text # toEncodedQueryParam :: Identity a -> Builder # | |
ToHttpApiData a => ToHttpApiData (First a) | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: First a -> Text # toEncodedUrlPiece :: First a -> Builder # toHeader :: First a -> ByteString # toQueryParam :: First a -> Text # toEncodedQueryParam :: First a -> Builder # | |
ToHttpApiData a => ToHttpApiData (Last a) | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Last a -> Text # toEncodedUrlPiece :: Last a -> Builder # toHeader :: Last a -> ByteString # toQueryParam :: Last a -> Text # toEncodedQueryParam :: Last a -> Builder # | |
ToHttpApiData a => ToHttpApiData (First a) | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: First a -> Text # toEncodedUrlPiece :: First a -> Builder # toHeader :: First a -> ByteString # toQueryParam :: First a -> Text # toEncodedQueryParam :: First a -> Builder # | |
ToHttpApiData a => ToHttpApiData (Last a) | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Last a -> Text # toEncodedUrlPiece :: Last a -> Builder # toHeader :: Last a -> ByteString # toQueryParam :: Last a -> Text # toEncodedQueryParam :: Last a -> Builder # | |
ToHttpApiData a => ToHttpApiData (Max a) | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Max a -> Text # toEncodedUrlPiece :: Max a -> Builder # toHeader :: Max a -> ByteString # toQueryParam :: Max a -> Text # toEncodedQueryParam :: Max a -> Builder # | |
ToHttpApiData a => ToHttpApiData (Min a) | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Min a -> Text # toEncodedUrlPiece :: Min a -> Builder # toHeader :: Min a -> ByteString # toQueryParam :: Min a -> Text # toEncodedQueryParam :: Min a -> Builder # | |
ToHttpApiData a => ToHttpApiData (Dual a) | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Dual a -> Text # toEncodedUrlPiece :: Dual a -> Builder # toHeader :: Dual a -> ByteString # toQueryParam :: Dual a -> Text # toEncodedQueryParam :: Dual a -> Builder # | |
ToHttpApiData a => ToHttpApiData (Product a) | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Product a -> Text # toEncodedUrlPiece :: Product a -> Builder # toHeader :: Product a -> ByteString # toQueryParam :: Product a -> Text # toEncodedQueryParam :: Product a -> Builder # | |
ToHttpApiData a => ToHttpApiData (Sum a) | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Sum a -> Text # toEncodedUrlPiece :: Sum a -> Builder # toHeader :: Sum a -> ByteString # toQueryParam :: Sum a -> Text # toEncodedQueryParam :: Sum a -> Builder # | |
ToHttpApiData a => ToHttpApiData (Maybe a) |
|
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Maybe a -> Text # toEncodedUrlPiece :: Maybe a -> Builder # toHeader :: Maybe a -> ByteString # toQueryParam :: Maybe a -> Text # toEncodedQueryParam :: Maybe a -> Builder # | |
(ToHttpApiData a, ToHttpApiData b) => ToHttpApiData (Either a b) |
|
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Either a b -> Text # toEncodedUrlPiece :: Either a b -> Builder # toHeader :: Either a b -> ByteString # toQueryParam :: Either a b -> Text # toEncodedQueryParam :: Either a b -> Builder # | |
HasResolution a => ToHttpApiData (Fixed a) | Note: this instance is not polykinded |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Fixed a -> Text # toEncodedUrlPiece :: Fixed a -> Builder # toHeader :: Fixed a -> ByteString # toQueryParam :: Fixed a -> Text # toEncodedQueryParam :: Fixed a -> Builder # | |
ToHttpApiData a => ToHttpApiData (Const a b) | Since: http-api-data-0.4.2 |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Const a b -> Text # toEncodedUrlPiece :: Const a b -> Builder # toHeader :: Const a b -> ByteString # toQueryParam :: Const a b -> Text # toEncodedQueryParam :: Const a b -> Builder # | |
ToHttpApiData a => ToHttpApiData (Tagged b a) | Note: this instance is not polykinded |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Tagged b a -> Text # toEncodedUrlPiece :: Tagged b a -> Builder # toHeader :: Tagged b a -> ByteString # toQueryParam :: Tagged b a -> Text # toEncodedQueryParam :: Tagged b a -> Builder # |
Classes and instances for types that can be converted to and from HTTP API data.
Experimental modules
General Authentication
Links
Represents a general universal resource identifier using its component parts.
For example, for the URI
foo://anonymous@www.haskell.org:42/ghc?query#frag
the components are:
Constructors
URI | |
Instances
FromJSON URI | Since: aeson-2.2.0.0 | ||||
Defined in Data.Aeson.Types.FromJSON | |||||
FromJSONKey URI | Since: aeson-2.2.0.0 | ||||
Defined in Data.Aeson.Types.FromJSON | |||||
ToJSON URI | Since: aeson-2.2.0.0 | ||||
ToJSONKey URI | Since: aeson-2.2.0.0 | ||||
Defined in Data.Aeson.Types.ToJSON | |||||
Data URI | |||||
Defined in Network.URI Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> URI -> c URI # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c URI # dataTypeOf :: URI -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c URI) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c URI) # gmapT :: (forall b. Data b => b -> b) -> URI -> URI # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> URI -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> URI -> r # gmapQ :: (forall d. Data d => d -> u) -> URI -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> URI -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> URI -> m URI # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> URI -> m URI # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> URI -> m URI # | |||||
Generic URI | |||||
Defined in Network.URI Associated Types
| |||||
Show URI | |||||
NFData URI | |||||
Defined in Network.URI | |||||
Eq URI | |||||
Ord URI | |||||
Lift URI | |||||
type Rep URI | |||||
Defined in Network.URI type Rep URI = D1 ('MetaData "URI" "Network.URI" "network-uri-2.6.4.2-1dWojNPLXrt1C0Ods6iJ1k" 'False) (C1 ('MetaCons "URI" 'PrefixI 'True) ((S1 ('MetaSel ('Just "uriScheme") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "uriAuthority") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe URIAuth))) :*: (S1 ('MetaSel ('Just "uriPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Just "uriQuery") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "uriFragment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))) |
class HasLink (endpoint :: k) where #
Construct a toLink for an endpoint.
Methods
Instances
HasLink EmptyAPI # | |
HasLink Raw # | |
HasLink RawM # | |
(TypeError (NoInstanceFor (HasLink api)) :: Constraint) => HasLink (api :: k) # | |
(HasLink (ToServantApi routes), forall a. GLink routes a, ErrorIfNoGeneric routes) => HasLink (NamedRoutes routes :: Type) # | |
Defined in Servant.Links Methods toLink :: (Link -> a) -> Proxy (NamedRoutes routes) -> Link -> MkLink (NamedRoutes routes) a # | |
(HasLink a, HasLink b) => HasLink (a :<|> b :: Type) # | |
HasLink (NoContentVerb m :: Type) # | |
Defined in Servant.Links Methods toLink :: (Link -> a) -> Proxy (NoContentVerb m) -> Link -> MkLink (NoContentVerb m) a # | |
(TypeError (PartialApplication (HasLink :: Type -> Constraint) arr) :: Constraint) => HasLink (arr :> sub :: Type) # | |
(KnownSymbol sym, HasLink sub) => HasLink (sym :> sub :: Type) # | |
HasLink sub => HasLink (HttpVersion :> sub :: Type) # | |
Defined in Servant.Links Methods toLink :: (Link -> a) -> Proxy (HttpVersion :> sub) -> Link -> MkLink (HttpVersion :> sub) a # | |
HasLink sub => HasLink (BasicAuth realm a :> sub :: Type) # | |
(ToHttpApiData v, HasLink sub) => HasLink (Capture' mods sym v :> sub :: Type) # | |
(ToHttpApiData v, HasLink sub) => HasLink (CaptureAll sym v :> sub :: Type) # | |
Defined in Servant.Links Methods toLink :: (Link -> a) -> Proxy (CaptureAll sym v :> sub) -> Link -> MkLink (CaptureAll sym v :> sub) a # | |
HasLink sub => HasLink (Description s :> sub :: Type) # | |
Defined in Servant.Links Methods toLink :: (Link -> a) -> Proxy (Description s :> sub) -> Link -> MkLink (Description s :> sub) a # | |
HasLink sub => HasLink (Summary s :> sub :: Type) # | |
HasLink sub => HasLink (AuthProtect tag :> sub :: Type) # | |
Defined in Servant.Links Methods toLink :: (Link -> a) -> Proxy (AuthProtect tag :> sub) -> Link -> MkLink (AuthProtect tag :> sub) a # | |
(HasLink sub, ToHttpApiData v) => HasLink (Fragment v :> sub :: Type) # | |
HasLink sub => HasLink (Header' mods sym a :> sub :: Type) # | |
HasLink sub => HasLink (IsSecure :> sub :: Type) # | |
(KnownSymbol sym, HasLink sub) => HasLink (QueryFlag sym :> sub :: Type) # | |
(KnownSymbol sym, ToHttpApiData v, HasLink sub, SBoolI (FoldRequired mods)) => HasLink (QueryParam' mods sym v :> sub :: Type) # | |
Defined in Servant.Links Methods toLink :: (Link -> a) -> Proxy (QueryParam' mods sym v :> sub) -> Link -> MkLink (QueryParam' mods sym v :> sub) a # | |
(KnownSymbol sym, ToHttpApiData v, HasLink sub) => HasLink (QueryParams sym v :> sub :: Type) # | |
Defined in Servant.Links Methods toLink :: (Link -> a) -> Proxy (QueryParams sym v :> sub) -> Link -> MkLink (QueryParams sym v :> sub) a # | |
HasLink sub => HasLink (RemoteHost :> sub :: Type) # | |
Defined in Servant.Links Methods toLink :: (Link -> a) -> Proxy (RemoteHost :> sub) -> Link -> MkLink (RemoteHost :> sub) a # | |
HasLink sub => HasLink (ReqBody' mods ct a :> sub :: Type) # | |
HasLink sub => HasLink (StreamBody' mods framing ct a :> sub :: Type) # | |
Defined in Servant.Links Methods toLink :: (Link -> a0) -> Proxy (StreamBody' mods framing ct a :> sub) -> Link -> MkLink (StreamBody' mods framing ct a :> sub) a0 # | |
HasLink sub => HasLink (WithResource res :> sub :: Type) # | |
Defined in Servant.Links Methods toLink :: (Link -> a) -> Proxy (WithResource res :> sub) -> Link -> MkLink (WithResource res :> sub) a # | |
HasLink sub => HasLink (Vault :> sub :: Type) # | |
(TypeError (NoInstanceForSub (HasLink :: Type -> Constraint) ty) :: Constraint) => HasLink (ty :> sub :: Type) # | |
HasLink (UVerb m ct a :: Type) # | |
HasLink sub => HasLink (WithNamedContext name context sub :: Type) # | |
Defined in Servant.Links Methods toLink :: (Link -> a) -> Proxy (WithNamedContext name context sub) -> Link -> MkLink (WithNamedContext name context sub) a # | |
HasLink (Verb m s ct a :: Type) # | |
HasLink (Stream m status fr ct a :: Type) # | |
type family IsElem endpoint api where ... #
Closed type family, check if endpoint
is within api
.
Uses
if it exhausts all other options.IsElem'
>>>
ok (Proxy :: Proxy (IsElem ("hello" :> Get '[JSON] Int) SampleAPI))
OK
>>>
ok (Proxy :: Proxy (IsElem ("bye" :> Get '[JSON] Int) SampleAPI))
... ... Could not ... ...
An endpoint is considered within an api even if it is missing combinators that don't affect the URL:
>>>
ok (Proxy :: Proxy (IsElem (Get '[JSON] Int) (Header "h" Bool :> Get '[JSON] Int)))
OK
>>>
ok (Proxy :: Proxy (IsElem (Get '[JSON] Int) (ReqBody '[JSON] Bool :> Get '[JSON] Int)))
OK
- N.B.:*
IsElem a b
can be seen as capturing the notion of whether the URL represented bya
would match the URL represented byb
, *not* whether a request represented bya
matches the endpoints servingb
(for the latter, useIsIn
).
Equations
IsElem e (sa :<|> sb) = Or (IsElem e sa) (IsElem e sb) | |
IsElem (e :> sa) (e :> sb) = IsElem sa sb | |
IsElem sa (Header sym x :> sb) = IsElem sa sb | |
IsElem sa (ReqBody y x :> sb) = IsElem sa sb | |
IsElem (CaptureAll z y :> sa) (CaptureAll x y :> sb) = IsElem sa sb | |
IsElem (Capture z y :> sa) (Capture x y :> sb) = IsElem sa sb | |
IsElem sa (QueryParam x y :> sb) = IsElem sa sb | |
IsElem sa (QueryParams x y :> sb) = IsElem sa sb | |
IsElem sa (QueryFlag x :> sb) = IsElem sa sb | |
IsElem sa (Fragment x :> sb) = IsElem sa sb | |
IsElem (Verb m s ct typ) (Verb m s ct' typ) = IsSubList ct ct' | |
IsElem e e = () | |
IsElem e a = IsElem' e a |
You may use this type family to tell the type checker that your custom
type may be skipped as part of a link. This is useful for things like
that are optional in a URI and do not affect them if they are
omitted.QueryParam
>>>
data CustomThing
>>>
type instance IsElem' e (CustomThing :> s) = IsElem e s
Note that
is called, which will mutually recurse back to IsElem
if it exhausts all other options again.IsElem'
Once you have written a HasLink
instance for CustomThing
you are ready to go.
A safe link datatype.
The only way of constructing a Link
is using safeLink
, which means any
Link
is guaranteed to be part of the mentioned API.
Instances
Show Link # | |
ToHttpApiData Link # | |
Defined in Servant.Links Methods toUrlPiece :: Link -> Text # toEncodedUrlPiece :: Link -> Builder # toHeader :: Link -> ByteString # toQueryParam :: Link -> Text # toEncodedQueryParam :: Link -> Builder # |
Arguments
:: (IsElem endpoint api, HasLink endpoint) | |
=> Proxy api | The whole API that this endpoint is a part of |
-> Proxy endpoint | The API endpoint you would like to point to |
-> MkLink endpoint Link |
Create a valid (by construction) relative URI with query params.
This function will only typecheck if endpoint
is part of the API api
type family MkLink (endpoint :: k) a #
Instances
type MkLink EmptyAPI a # | |
Defined in Servant.Links | |
type MkLink Raw a # | |
Defined in Servant.Links | |
type MkLink RawM a # | |
Defined in Servant.Links | |
type MkLink (NamedRoutes routes :: Type) a # | |
Defined in Servant.Links | |
type MkLink (a :<|> b :: Type) r # | |
type MkLink (NoContentVerb m :: Type) r # | |
Defined in Servant.Links | |
type MkLink (arr :> sub :: Type) _1 # | |
Defined in Servant.Links type MkLink (arr :> sub :: Type) _1 = TypeError (PartialApplication (HasLink :: Type -> Constraint) arr) :: Type | |
type MkLink (sym :> sub :: Type) a # | |
Defined in Servant.Links | |
type MkLink (HttpVersion :> sub :: Type) a # | |
Defined in Servant.Links | |
type MkLink (BasicAuth realm a :> sub :: Type) r # | |
type MkLink (Capture' mods sym v :> sub :: Type) a # | |
type MkLink (CaptureAll sym v :> sub :: Type) a # | |
Defined in Servant.Links | |
type MkLink (Description s :> sub :: Type) a # | |
Defined in Servant.Links | |
type MkLink (Summary s :> sub :: Type) a # | |
type MkLink (AuthProtect tag :> sub :: Type) a # | |
Defined in Servant.Links | |
type MkLink (Fragment v :> sub :: Type) a # | |
type MkLink (Header' mods sym a :> sub :: Type) r # | |
type MkLink (IsSecure :> sub :: Type) a # | |
type MkLink (QueryFlag sym :> sub :: Type) a # | |
type MkLink (QueryParam' mods sym v :> sub :: Type) a # | |
Defined in Servant.Links type MkLink (QueryParam' mods sym v :> sub :: Type) a = If (FoldRequired mods) v (Maybe v) -> MkLink sub a | |
type MkLink (QueryParams sym v :> sub :: Type) a # | |
Defined in Servant.Links | |
type MkLink (RemoteHost :> sub :: Type) a # | |
Defined in Servant.Links | |
type MkLink (ReqBody' mods ct a :> sub :: Type) r # | |
type MkLink (StreamBody' mods framing ct a :> sub :: Type) r # | |
Defined in Servant.Links | |
type MkLink (WithResource res :> sub :: Type) a # | |
Defined in Servant.Links | |
type MkLink (Vault :> sub :: Type) a # | |
type MkLink (UVerb m ct a :: Type) r # | |
Defined in Servant.Links | |
type MkLink (WithNamedContext name context sub :: Type) a # | |
Defined in Servant.Links | |
type MkLink (Verb m s ct a :: Type) r # | |
Defined in Servant.Links | |
type MkLink (Stream m status fr ct a :: Type) r # | |
Defined in Servant.Links |
Type-safe internal URIs
Re-exports
type family If (cond :: Bool) (tru :: k) (fls :: k) :: k where ... #
Type-level If. If True a b
==> a
; If False a b
==> b
data SBool (b :: Bool) where #
Instances
EqP SBool | Since: singleton-bool-0.1.7 |
GNFData SBool | Since: singleton-bool-0.1.6 |
Defined in Data.Singletons.Bool | |
GCompare SBool | Since: singleton-bool-0.1.6 |
GEq SBool |
Since: singleton-bool-0.1.6 |
GRead SBool |
Since: singleton-bool-0.1.6 |
Defined in Data.Singletons.Bool Methods greadsPrec :: Int -> GReadS SBool # | |
GShow SBool |
Since: singleton-bool-0.1.6 |
Defined in Data.Singletons.Bool | |
OrdP SBool | Since: singleton-bool-0.1.7 |
Show (SBool b) | Since: singleton-bool-0.1.5 |
SBoolI b => Boring (SBool b) | Since: singleton-bool-0.1.6 |
Defined in Data.Singletons.Bool | |
NFData (SBool b) | Since: singleton-bool-0.1.6 |
Defined in Data.Singletons.Bool | |
Eq (SBool b) | Since: singleton-bool-0.1.5 |
Ord (SBool b) | Since: singleton-bool-0.1.5 |
Defined in Data.Singletons.Bool |