Safe Haskell | None |
---|---|
Language | Haskell2010 |
An alternative to Verb
for end-points that respond with a resource value of any of an
open union of types, and specific status codes for each type in this union. (UVerb
is
short for UnionVerb
)
This can be used for returning (rather than throwing) exceptions in a server as in, say
'[Report, WaiError]
; or responding with either a 303 forward with a location header, or
201 created with a different body type, depending on the circumstances. (All of this can
be done with vanilla servant-server by throwing exceptions, but it can't be represented in
the API types without something like UVerb
.)
See https://docs.servant.dev/en/stable/cookbook/uverb/UVerb.html for a working example.
Synopsis
- data UVerb (method :: StdMethod) (contentTypes :: [*]) (as :: [*])
- class KnownStatus (StatusOf a) => HasStatus (a :: *) where
- statusOf :: forall a proxy. HasStatus a => proxy a -> Status
- class HasStatuses (as :: [*]) where
- newtype WithStatus (k :: Nat) a = WithStatus a
- module Servant.API.UVerb.Union
Documentation
data UVerb (method :: StdMethod) (contentTypes :: [*]) (as :: [*]) Source #
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
AtLeastOneFragment (UVerb m cts as) Source # | |
Defined in Servant.API.TypeLevel |
class KnownStatus (StatusOf a) => HasStatus (a :: *) Source #
Instances
HasStatus NoContent Source # | If an API can respond with |
KnownStatus n => HasStatus (WithStatus n a) Source # | 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 type StatusOf (WithStatus n a) :: Nat Source # |
class HasStatuses (as :: [*]) where Source #
Instances
HasStatuses ('[] :: [Type]) Source # | |
(HasStatus a, HasStatuses as) => HasStatuses (a ': as) Source # | |
newtype WithStatus (k :: Nat) a Source #
A simple newtype wrapper that pairs a type with its status code. It implements all the content types that Servant ships with by default.
Instances
MimeUnrender ctype a => MimeUnrender (ctype :: Type) (WithStatus _status a) Source # | |
Defined in Servant.API.UVerb mimeUnrender :: Proxy ctype -> ByteString -> Either String (WithStatus _status a) Source # mimeUnrenderWithType :: Proxy ctype -> MediaType -> ByteString -> Either String (WithStatus _status a) Source # | |
MimeRender ctype a => MimeRender (ctype :: Type) (WithStatus _status a) Source # | |
Defined in Servant.API.UVerb mimeRender :: Proxy ctype -> WithStatus _status a -> ByteString Source # | |
Eq a => Eq (WithStatus k a) Source # | |
Defined in Servant.API.UVerb (==) :: WithStatus k a -> WithStatus k a -> Bool # (/=) :: WithStatus k a -> WithStatus k a -> Bool # | |
Show a => Show (WithStatus k a) Source # | |
Defined in Servant.API.UVerb showsPrec :: Int -> WithStatus k a -> ShowS # show :: WithStatus k a -> String # showList :: [WithStatus k a] -> ShowS # | |
KnownStatus n => HasStatus (WithStatus n a) Source # | 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 type StatusOf (WithStatus n a) :: Nat Source # | |
type StatusOf (WithStatus n a) Source # | |
Defined in Servant.API.UVerb |
module Servant.API.UVerb.Union