servant-0.16: A family of combinators for defining webservices APIs

Safe HaskellSafe
LanguageHaskell2010

Servant.API.Description

Contents

Synopsis

Combinators

data Description (sym :: Symbol) Source #

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 support is not perfect \
 \but it's still very readable."
:> Get '[JSON] Book
:}
Instances
HasLink sub => HasLink (Description s :> sub :: Type) Source # 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (Description s :> sub) a :: Type Source #

Methods

toLink :: (Link -> a) -> Proxy (Description s :> sub) -> Link -> MkLink (Description s :> sub) a Source #

type MkLink (Description s :> sub :: Type) a Source # 
Instance details

Defined in Servant.Links

type MkLink (Description s :> sub :: Type) a = MkLink sub a

data Summary (sym :: Symbol) Source #

Add a short summary for (part of) API.

Example:

>>> type MyApi = Summary "Get book by ISBN." :> "books" :> Capture "isbn" Text :> Get '[JSON] Book
Instances
HasLink sub => HasLink (Summary s :> sub :: Type) Source # 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (Summary s :> sub) a :: Type Source #

Methods

toLink :: (Link -> a) -> Proxy (Summary s :> sub) -> Link -> MkLink (Summary s :> sub) a Source #

type MkLink (Summary s :> sub :: Type) a Source # 
Instance details

Defined in Servant.Links

type MkLink (Summary s :> sub :: Type) a = MkLink sub a

Used as modifiers

type FoldDescription mods = FoldDescription' "" mods Source #

Fold modifier list to decide whether argument should be parsed strictly or leniently.

>>> :kind! FoldDescription '[]
FoldDescription '[] :: Symbol
= ""
>>> :kind! FoldDescription '[Required, Description "foobar", Lenient]
FoldDescription '[Required, Description "foobar", Lenient] :: Symbol
= "foobar"

type family FoldDescription' (acc :: Symbol) (mods :: [*]) :: Symbol where ... Source #

Implementation of FoldDescription.

Equations

FoldDescription' acc '[] = acc 
FoldDescription' acc (Description desc ': mods) = FoldDescription' desc mods 
FoldDescription' acc (mod ': mods) = FoldDescription' acc mods 

reflectDescription :: forall mods. KnownSymbol (FoldDescription mods) => Proxy mods -> String Source #

Reflect description to the term level.

>>> reflectDescription (Proxy :: Proxy '[Required, Description "foobar", Lenient])
"foobar"