servant-routes-0.1.0.0: Generate route descriptions from Servant APIs
Copyright(c) Frederick Pringle 2024
LicenseBSD-3-Clause
Maintainerfreddyjepringle@gmail.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

Servant.API.Routes.Internal.Body

Description

Internal module, subject to change.

Synopsis

Documentation

data Body Source #

A more expressive sum-type than just a list. This can be useful in situations where a body (request or response) may have several interpretations.

For example, the UVerb combinator lets us represent an endpoint that may return one of several types: hence the _routeResponseType field needs to be able to contain several TypeReps as a disjunction.

On the other hand, if multiple ReqBody's are chained together with :>, the resulting type's HasServer instance would try to parse the request body as all of the relevant types. In this case the _routeRequestBody field needs to be able to contain several TypeReps as a conjunction.

Constructors

NoBody 
OneType TypeRep 
ManyTypes [TypeRep]

invariant: list needs to have length > 1

Instances

Instances details
Monoid Body Source # 
Instance details

Defined in Servant.API.Routes.Internal.Body

Semigroup Body Source # 
Instance details

Defined in Servant.API.Routes.Internal.Body

Show Body Source # 
Instance details

Defined in Servant.API.Routes.Internal.Body

Eq Body Source # 
Instance details

Defined in Servant.API.Routes.Internal.Body

Methods

(==) :: Body -> Body -> Bool Source #

(/=) :: Body -> Body -> Bool Source #

bodyToList :: Body -> [TypeRep] Source #

Convert a Body to a list of TypeReps. Inverse of listToBody.

listToBody :: [TypeRep] -> Body Source #

Convert a list of TypeReps to a Body. Inverse of listToBody.

This maintains the invariant that the argument of ManyTypes has to be of length > 1.

class AllTypeable (as :: [Type]) where Source #

This class does 2 things:

  • It lets us get a term-level list of TypeReps from a type-level list of types, all of which have Typeable instances.
  • More impressively, its instances enforce that typeReps will only type-check for type-level lists of length 2 or more. This is because AllTypeable will only ever be used by manyTypes (and its aliases), which is the only way to construct a ManyTypes and thus lets us enforce the invariant that ManyTypes will always have more than 1 argument. This lets us make sure that there's only ever one way to represent a list of TypeReps using Body.

Of course, someone might import this Internal module and define a Typeable a => AllTypeable '[a] instance. Don't do that.

Methods

typeReps :: [TypeRep] Source #

Instances

Instances details
(Typeable a, AllTypeable (b ': (c ': as))) => AllTypeable (a ': (b ': (c ': as))) Source # 
Instance details

Defined in Servant.API.Routes.Internal.Body

Methods

typeReps :: [TypeRep] Source #

(Typeable a, Typeable b) => AllTypeable '[a, b] Source # 
Instance details

Defined in Servant.API.Routes.Internal.Body

Methods

typeReps :: [TypeRep] Source #