servant-0.18.2: A family of combinators for defining webservices APIs
Safe HaskellNone
LanguageHaskell2010

Servant.API.UVerb

Description

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

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

Instances details
AtLeastOneFragment (UVerb m cts as) Source # 
Instance details

Defined in Servant.API.TypeLevel

class KnownStatus (StatusOf a) => HasStatus (a :: *) Source #

Associated Types

type StatusOf (a :: *) :: Nat Source #

Instances

Instances details
HasStatus NoContent Source #

If an API can respond with NoContent we assume that this will happen with the status code 204 No Content. If this needs to be overridden, WithStatus can be used.

Instance details

Defined in Servant.API.UVerb

Associated Types

type StatusOf NoContent :: Nat Source #

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 WithStatus if you want to avoid writing a HasStatus instance manually. It also has the benefit of showing the status code in the type; which might aid in readability.

Instance details

Defined in Servant.API.UVerb

Associated Types

type StatusOf (WithStatus n a) :: Nat Source #

statusOf :: forall a proxy. HasStatus a => proxy a -> Status Source #

class HasStatuses (as :: [*]) where Source #

Associated Types

type Statuses (as :: [*]) :: [Nat] Source #

Methods

statuses :: Proxy as -> [Status] Source #

Instances

Instances details
HasStatuses ('[] :: [Type]) Source # 
Instance details

Defined in Servant.API.UVerb

Associated Types

type Statuses '[] :: [Nat] Source #

Methods

statuses :: Proxy '[] -> [Status] Source #

(HasStatus a, HasStatuses as) => HasStatuses (a ': as) Source # 
Instance details

Defined in Servant.API.UVerb

Associated Types

type Statuses (a ': as) :: [Nat] Source #

Methods

statuses :: Proxy (a ': as) -> [Status] 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.

Constructors

WithStatus a 

Instances

Instances details
MimeUnrender ctype a => MimeUnrender (ctype :: Type) (WithStatus _status a) Source # 
Instance details

Defined in Servant.API.UVerb

MimeRender ctype a => MimeRender (ctype :: Type) (WithStatus _status a) Source # 
Instance details

Defined in Servant.API.UVerb

Methods

mimeRender :: Proxy ctype -> WithStatus _status a -> ByteString Source #

Eq a => Eq (WithStatus k a) Source # 
Instance details

Defined in Servant.API.UVerb

Methods

(==) :: WithStatus k a -> WithStatus k a -> Bool #

(/=) :: WithStatus k a -> WithStatus k a -> Bool #

Show a => Show (WithStatus k a) Source # 
Instance details

Defined in Servant.API.UVerb

Methods

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 WithStatus if you want to avoid writing a HasStatus instance manually. It also has the benefit of showing the status code in the type; which might aid in readability.

Instance details

Defined in Servant.API.UVerb

Associated Types

type StatusOf (WithStatus n a) :: Nat Source #

type StatusOf (WithStatus n a) Source # 
Instance details

Defined in Servant.API.UVerb

type StatusOf (WithStatus n a) = n