servant-openapi3-2.0.0: Generate a Swagger/OpenAPI/OAS 3.0 specification for your servant API.

Safe HaskellNone
LanguageHaskell2010

Servant.OpenApi.Internal.TypeLevel.API

Synopsis

Documentation

type family EndpointsList api where ... Source #

Build a list of endpoints from an API.

type family IsSubAPI sub api :: Constraint where ... Source #

Check whether sub is a sub API of api.

Equations

IsSubAPI sub api = AllIsElem (EndpointsList sub) api 

type family AllIsElem xs api :: Constraint where ... Source #

Check that every element of xs is an endpoint of api.

Equations

AllIsElem '[] api = () 
AllIsElem (x ': xs) api = (IsIn x api, AllIsElem xs api) 

type family MapSub e xs where ... Source #

Apply (e :>) to every API in xs.

Equations

MapSub e '[] = '[] 
MapSub e (x ': xs) = (e :> x) ': MapSub e xs 

type family AppendList xs ys where ... Source #

Append two type-level lists.

Equations

AppendList '[] ys = ys 
AppendList (x ': xs) ys = x ': AppendList xs ys 

type family Or (a :: Constraint) (b :: Constraint) :: Constraint where ... Source #

Equations

Or () b = () 
Or a () = () 

type family IsIn sub api :: Constraint where ... Source #

Equations

IsIn e (a :<|> b) = Or (IsIn e a) (IsIn e b) 
IsIn (e :> a) (e :> b) = IsIn a b 
IsIn e e = () 

type family Elem x xs where ... Source #

Check whether a type is a member of a list of types. This is a type-level analogue of elem.

Equations

Elem x '[] = False 
Elem x (x ': xs) = True 
Elem x (y ': xs) = Elem x xs 

type family Nub xs where ... Source #

Remove duplicates from a type-level list.

Equations

Nub '[] = '[] 
Nub (x ': xs) = x ': Nub (Remove x xs) 

type family Remove x xs where ... Source #

Remove element from a type-level list.

Equations

Remove x '[] = '[] 
Remove x (x ': ys) = Remove x ys 
Remove x (y ': ys) = y ': Remove x ys 

type BodyTypes c api = Nub (BodyTypes' c api) Source #

Extract a list of unique "body" types for a specific content-type from a servant API.

type AddBodyType c cs a as = If (Elem c cs) (a ': as) as Source #

AddBodyType c cs a as adds type a to the list as only if c is in cs.

type family BodyTypes' c api :: [*] where ... Source #

Extract a list of "body" types for a specific content-type from a servant API. To extract unique types see BodyTypes.

NoContent is removed from the list and not tested. (This allows for leaving the body completely empty on responses to requests that only accept 'application/json', while setting the content-type in the response accordingly.)

Equations

BodyTypes' c (Verb verb b cs (Headers hdrs a)) = AddBodyType c cs a '[] 
BodyTypes' c (Verb verb b cs NoContent) = '[] 
BodyTypes' c (Verb verb b cs a) = AddBodyType c cs a '[] 
BodyTypes' c (ReqBody' mods cs a :> api) = AddBodyType c cs a (BodyTypes' c api) 
BodyTypes' c (e :> api) = BodyTypes' c api 
BodyTypes' c (a :<|> b) = AppendList (BodyTypes' c a) (BodyTypes' c b) 
BodyTypes' c api = '[]