servant-docs-0.11.2: generate API docs for your servant webservice

Safe HaskellNone
LanguageHaskell2010

Servant.Docs

Contents

Description

This module lets you get API docs for free. It lets you generate an API from the type that represents your API using docs:

docs :: HasDocs api => Proxy api -> API

Alternatively, if you wish to add one or more introductions to your documentation, use docsWithIntros:

docsWithIntros :: HasDocs api => [DocIntro] -> Proxy api -> API

You can then call markdown on the API value:

markdown :: API -> String

or define a custom pretty printer:

yourPrettyDocs :: API -> String -- or blaze-html's HTML, or ...

The only thing you'll need to do will be to implement some classes for your captures, get parameters and request or response bodies.

See example/greet.hs for an example.

Synopsis

HasDocs class and key functions

class HasDocs api where Source #

The class that abstracts away the impact of API combinators on documentation generation.

Minimal complete definition

docsFor

Methods

docsFor :: Proxy api -> (Endpoint, Action) -> DocOptions -> API Source #

Instances

HasDocs * Raw Source # 

Methods

docsFor :: Proxy Raw api -> (Endpoint, Action) -> DocOptions -> API Source #

HasDocs * EmptyAPI Source #

The generated docs for EmptyAPI are empty.

(HasDocs * a, HasDocs * b) => HasDocs * ((:<|>) a b) Source #

The generated docs for a :<|> b just appends the docs for a with the docs for b.

Methods

docsFor :: Proxy (a :<|> b) api -> (Endpoint, Action) -> DocOptions -> API Source #

HasDocs * api => HasDocs * (WithNamedContext name context api) Source # 

Methods

docsFor :: Proxy (WithNamedContext name context api) api -> (Endpoint, Action) -> DocOptions -> API Source #

HasDocs * api => HasDocs * ((:>) * HttpVersion api) Source # 

Methods

docsFor :: Proxy ((* :> HttpVersion) api) api -> (Endpoint, Action) -> DocOptions -> API Source #

(ToSample a, AllMimeRender ((:) * ct cts) a, HasDocs * api) => HasDocs * ((:>) * (ReqBody' mods ((:) * ct cts) a) api) Source # 

Methods

docsFor :: Proxy ((* :> ReqBody' mods ((* ': ct) cts) a) api) api -> (Endpoint, Action) -> DocOptions -> API Source #

HasDocs * api => HasDocs * ((:>) * RemoteHost api) Source # 

Methods

docsFor :: Proxy ((* :> RemoteHost) api) api -> (Endpoint, Action) -> DocOptions -> API Source #

(KnownSymbol sym, ToParam * (QueryParam' mods sym a), HasDocs * api) => HasDocs * ((:>) * (QueryParam' mods sym a) api) Source # 

Methods

docsFor :: Proxy ((* :> QueryParam' mods sym a) api) api -> (Endpoint, Action) -> DocOptions -> API Source #

(KnownSymbol sym, ToParam * (QueryParams sym a), HasDocs * api) => HasDocs * ((:>) * (QueryParams sym a) api) Source # 

Methods

docsFor :: Proxy ((* :> QueryParams sym a) api) api -> (Endpoint, Action) -> DocOptions -> API Source #

(KnownSymbol sym, ToParam * (QueryFlag sym), HasDocs * api) => HasDocs * ((:>) * (QueryFlag sym) api) Source # 

Methods

docsFor :: Proxy ((* :> QueryFlag sym) api) api -> (Endpoint, Action) -> DocOptions -> API Source #

(KnownSymbol sym, HasDocs * api) => HasDocs * ((:>) * (Header' k mods sym a) api) Source # 

Methods

docsFor :: Proxy ((* :> Header' k mods sym a) api) api -> (Endpoint, Action) -> DocOptions -> API Source #

HasDocs * api => HasDocs * ((:>) * IsSecure api) Source # 

Methods

docsFor :: Proxy ((* :> IsSecure) api) api -> (Endpoint, Action) -> DocOptions -> API Source #

(KnownSymbol desc, HasDocs * api) => HasDocs * ((:>) * (Summary desc) api) Source # 

Methods

docsFor :: Proxy ((* :> Summary desc) api) api -> (Endpoint, Action) -> DocOptions -> API Source #

(KnownSymbol desc, HasDocs * api) => HasDocs * ((:>) * (Description desc) api) Source # 

Methods

docsFor :: Proxy ((* :> Description desc) api) api -> (Endpoint, Action) -> DocOptions -> API Source #

(KnownSymbol sym, ToCapture * (Capture sym a), HasDocs * api) => HasDocs * ((:>) * (Capture' mods sym a) api) Source #

"books" :> Capture "isbn" Text will appear as books:isbn in the docs.

Methods

docsFor :: Proxy ((* :> Capture' mods sym a) api) api -> (Endpoint, Action) -> DocOptions -> API Source #

(KnownSymbol sym, ToCapture * (CaptureAll sym a), HasDocs * sublayout) => HasDocs * ((:>) * (CaptureAll sym a) sublayout) Source #

"books" :> CaptureAll "isbn" Text will appear as books:isbn in the docs.

Methods

docsFor :: Proxy ((* :> CaptureAll sym a) sublayout) api -> (Endpoint, Action) -> DocOptions -> API Source #

(ToAuthInfo * (BasicAuth realm usr), HasDocs * api) => HasDocs * ((:>) * (BasicAuth realm usr) api) Source # 

Methods

docsFor :: Proxy ((* :> BasicAuth realm usr) api) api -> (Endpoint, Action) -> DocOptions -> API Source #

HasDocs * api => HasDocs * ((:>) * Vault api) Source # 

Methods

docsFor :: Proxy ((* :> Vault) api) api -> (Endpoint, Action) -> DocOptions -> API Source #

(KnownSymbol path, HasDocs * api) => HasDocs * ((:>) Symbol path api) Source # 

Methods

docsFor :: Proxy ((Symbol :> path) api) api -> (Endpoint, Action) -> DocOptions -> API Source #

(ToSample a, AllMimeRender ((:) * ct cts) a, KnownNat status, ReflectMethod k1 method) => HasDocs * (Verb k1 method status ((:) * ct cts) a) Source # 

Methods

docsFor :: Proxy (Verb k1 method status ((* ': ct) cts) a) api -> (Endpoint, Action) -> DocOptions -> API Source #

(ToSample a, AllMimeRender ((:) * ct cts) a, KnownNat status, ReflectMethod k1 method, AllHeaderSamples [*] ls, GetHeaders (HList ls)) => HasDocs * (Verb k1 method status ((:) * ct cts) (Headers ls a)) Source # 

Methods

docsFor :: Proxy (Verb k1 method status ((* ': ct) cts) (Headers ls a)) api -> (Endpoint, Action) -> DocOptions -> API Source #

docs :: HasDocs api => Proxy api -> API Source #

Generate the docs for a given API that implements HasDocs. This is the default way to create documentation.

docs == docsWithOptions defaultDocOptions

pretty :: Proxy api -> Proxy (Pretty api) Source #

Prettify generated JSON documentation.

docs (pretty (Proxy :: Proxy MyAPI))

markdown :: API -> String Source #

Generate documentation in Markdown format for the given API.

This is equivalent to markdownWith defRenderingOptions.

Customising generated documentation

markdownWith :: RenderingOptions -> API -> String Source #

Generate documentation in Markdown format for the given API using the specified options.

These options allow you to customise aspects such as:

  • Choose how many content-types for each request body example are shown with requestExamples.
  • Choose how many content-types for each response body example are shown with responseExamples.

For example, to only show the first content-type of each example:

  markdownWith (defRenderingOptions
                  & requestExamples  .~ FirstContentType
                  & responseExamples .~ FirstContentType )
               myAPI
  

Since: 0.11.1

data RenderingOptions Source #

Customise how an API is converted into documentation.

Since: 0.11.1

Constructors

RenderingOptions 

Fields

defRenderingOptions :: RenderingOptions Source #

Default API generation options.

All content types are shown for both requestExamples and responseExamples; notesHeading is set to Nothing (i.e. un-grouped).

Since: 0.11.1

data ShowContentTypes Source #

How many content-types for each example should be shown?

Since: 0.11.1

Constructors

AllContentTypes

For each example, show each content type.

FirstContentType

For each example, show only one content type.

Instances

Bounded ShowContentTypes Source # 
Enum ShowContentTypes Source # 
Eq ShowContentTypes Source # 
Ord ShowContentTypes Source # 
Read ShowContentTypes Source # 
Show ShowContentTypes Source # 

Generating docs with extra information

docsWith :: HasDocs api => DocOptions -> [DocIntro] -> ExtraInfo api -> Proxy api -> API Source #

Generate documentation given some extra introductions (in the form of DocInfo) and some extra endpoint documentation (in the form of ExtraInfo.

The extra introductions will be prepended to the top of the documentation, before the specific endpoint documentation. The extra endpoint documentation will be "unioned" with the automatically generated endpoint documentation.

You are expected to build up the ExtraInfo with the Monoid instance and extraInfo.

If you only want to add an introduction, use docsWithIntros.

docsWithIntros :: HasDocs api => [DocIntro] -> Proxy api -> API Source #

Generate the docs for a given API that implements HasDocs with with any number of introduction(s)

docsWithOptions :: HasDocs api => Proxy api -> DocOptions -> API Source #

Generate the docs for a given API that implements HasDocs.

newtype ExtraInfo api Source #

Type of extra information that a user may wish to "union" with their documentation.

These are intended to be built using extraInfo. Multiple ExtraInfo may be combined with the monoid instance.

Instances

Semigroup (ExtraInfo k a) Source # 

Methods

(<>) :: ExtraInfo k a -> ExtraInfo k a -> ExtraInfo k a #

sconcat :: NonEmpty (ExtraInfo k a) -> ExtraInfo k a #

stimes :: Integral b => b -> ExtraInfo k a -> ExtraInfo k a #

Monoid (ExtraInfo k a) Source # 

Methods

mempty :: ExtraInfo k a #

mappend :: ExtraInfo k a -> ExtraInfo k a -> ExtraInfo k a #

mconcat :: [ExtraInfo k a] -> ExtraInfo k a #

extraInfo :: (IsIn endpoint api, HasLink endpoint, HasDocs endpoint) => Proxy endpoint -> Action -> ExtraInfo api Source #

Create an ExtraInfo that is guaranteed to be within the given API layout.

The safety here is to ensure that you only add custom documentation to an endpoint that actually exists within your API.

extra :: ExtraInfo TestApi
extra =
    extraInfo (Proxy :: Proxy ("greet" :> Capture "greetid" Text :> Delete)) $
             defAction & headers <>~ ["unicorns"]
                       & notes   <>~ [ DocNote "Title" ["This is some text"]
                                     , DocNote "Second secton" ["And some more"]
                                     ]

data DocOptions Source #

Documentation options.

Constructors

DocOptions 

Fields

defaultDocOptions :: DocOptions Source #

Default documentation options.

Classes you need to implement for your types

class ToSample a where Source #

The class that lets us display a sample input or output in the supported content-types when generating documentation for endpoints that either:

  • expect a request body, or
  • return a non empty response body

Example of an instance:

{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}

import Data.Aeson
import Data.Text
import GHC.Generics

data Greet = Greet { _msg :: Text }
  deriving (Generic, Show)

instance FromJSON Greet
instance ToJSON Greet

instance ToSample Greet where
  toSamples _ = singleSample g

    where g = Greet "Hello, haskeller!"

You can also instantiate this class using toSamples instead of toSample: it lets you specify different responses along with some context (as Text) that explains when you're supposed to get the corresponding response.

Methods

toSamples :: Proxy a -> [(Text, a)] Source #

toSamples :: (Generic a, GToSample (Rep a)) => Proxy a -> [(Text, a)] Source #

Instances

ToSample Bool Source # 

Methods

toSamples :: Proxy * Bool -> [(Text, Bool)] Source #

ToSample Ordering Source # 
ToSample All Source # 

Methods

toSamples :: Proxy * All -> [(Text, All)] Source #

ToSample Any Source # 

Methods

toSamples :: Proxy * Any -> [(Text, Any)] Source #

ToSample NoContent Source # 
ToSample a => ToSample [a] Source # 

Methods

toSamples :: Proxy * [a] -> [(Text, [a])] Source #

ToSample a => ToSample (Maybe a) Source # 

Methods

toSamples :: Proxy * (Maybe a) -> [(Text, Maybe a)] Source #

ToSample a => ToSample (ZipList a) Source # 

Methods

toSamples :: Proxy * (ZipList a) -> [(Text, ZipList a)] Source #

ToSample a => ToSample (Dual a) Source # 

Methods

toSamples :: Proxy * (Dual a) -> [(Text, Dual a)] Source #

ToSample a => ToSample (Sum a) Source # 

Methods

toSamples :: Proxy * (Sum a) -> [(Text, Sum a)] Source #

ToSample a => ToSample (Product a) Source # 

Methods

toSamples :: Proxy * (Product a) -> [(Text, Product a)] Source #

ToSample a => ToSample (First a) Source # 

Methods

toSamples :: Proxy * (First a) -> [(Text, First a)] Source #

ToSample a => ToSample (Last a) Source # 

Methods

toSamples :: Proxy * (Last a) -> [(Text, Last a)] Source #

(ToSample a, ToSample b) => ToSample (Either a b) Source # 

Methods

toSamples :: Proxy * (Either a b) -> [(Text, Either a b)] Source #

(ToSample a, ToSample b) => ToSample (a, b) Source # 

Methods

toSamples :: Proxy * (a, b) -> [(Text, (a, b))] Source #

(ToSample a, ToSample b, ToSample c) => ToSample (a, b, c) Source # 

Methods

toSamples :: Proxy * (a, b, c) -> [(Text, (a, b, c))] Source #

ToSample a => ToSample (Const k a b) Source # 

Methods

toSamples :: Proxy * (Const k a b) -> [(Text, Const k a b)] Source #

(ToSample a, ToSample b, ToSample c, ToSample d) => ToSample (a, b, c, d) Source # 

Methods

toSamples :: Proxy * (a, b, c, d) -> [(Text, (a, b, c, d))] Source #

(ToSample a, ToSample b, ToSample c, ToSample d, ToSample e) => ToSample (a, b, c, d, e) Source # 

Methods

toSamples :: Proxy * (a, b, c, d, e) -> [(Text, (a, b, c, d, e))] Source #

(ToSample a, ToSample b, ToSample c, ToSample d, ToSample e, ToSample f) => ToSample (a, b, c, d, e, f) Source # 

Methods

toSamples :: Proxy * (a, b, c, d, e, f) -> [(Text, (a, b, c, d, e, f))] Source #

(ToSample a, ToSample b, ToSample c, ToSample d, ToSample e, ToSample f, ToSample g) => ToSample (a, b, c, d, e, f, g) Source # 

Methods

toSamples :: Proxy * (a, b, c, d, e, f, g) -> [(Text, (a, b, c, d, e, f, g))] Source #

toSample :: forall a. ToSample a => Proxy a -> Maybe a Source #

Sample input or output (if there is at least one).

noSamples :: [(Text, a)] Source #

No samples.

singleSample :: a -> [(Text, a)] Source #

Single sample without description.

samples :: [a] -> [(Text, a)] Source #

Samples without documentation.

sampleByteString :: forall ct cts a. (ToSample a, AllMimeRender (ct ': cts) a) => Proxy (ct ': cts) -> Proxy a -> [(MediaType, ByteString)] Source #

Synthesise a sample value of a type, encoded in the specified media types.

sampleByteStrings :: forall ct cts a. (ToSample a, AllMimeRender (ct ': cts) a) => Proxy (ct ': cts) -> Proxy a -> [(Text, MediaType, ByteString)] Source #

Synthesise a list of sample values of a particular type, encoded in the specified media types.

class ToParam t where Source #

The class that helps us automatically get documentation for GET (or other Method) parameters.

Example of an instance:

instance ToParam (QueryParam' mods "capital" Bool) where
  toParam _ =
    DocQueryParam "capital"
                  ["true", "false"]
                  "Get the greeting message in uppercase (true) or not (false). Default is false."

Minimal complete definition

toParam

class ToCapture c where Source #

The class that helps us automatically get documentation for URL captures.

Example of an instance:

instance ToCapture (Capture "name" Text) where
  toCapture _ = DocCapture "name" "name of the person to greet"

Minimal complete definition

toCapture

ADTs to represent an API

data Endpoint Source #

An Endpoint type that holds the path and the method.

Gets used as the key in the API hashmap. Modify defEndpoint or any Endpoint value you want using the path and method lenses to tweak.

λ> defEndpoint
GET /
λ> defEndpoint & path <>~ ["foo"]
GET /foo
λ> defEndpoint & path <>~ ["foo"] & method .~ methodPost
POST /foo

defEndpoint :: Endpoint Source #

An Endpoint whose path is `"/"` and whose method is GET

Here's how you can modify it:

λ> defEndpoint
GET /
λ> defEndpoint & path <>~ ["foo"]
GET /foo
λ> defEndpoint & path <>~ ["foo"] & method .~ methodPost
POST /foo

data API Source #

Our API documentation type, a product of top-level information and a good old hashmap from Endpoint to Action

Instances

Eq API Source # 

Methods

(==) :: API -> API -> Bool #

(/=) :: API -> API -> Bool #

Show API Source # 

Methods

showsPrec :: Int -> API -> ShowS #

show :: API -> String #

showList :: [API] -> ShowS #

Semigroup API Source # 

Methods

(<>) :: API -> API -> API #

sconcat :: NonEmpty API -> API #

stimes :: Integral b => b -> API -> API #

Monoid API Source # 

Methods

mempty :: API #

mappend :: API -> API -> API #

mconcat :: [API] -> API #

emptyAPI :: API Source #

An empty API

data DocCapture Source #

A type to represent captures. Holds the name of the capture and a description.

Write a ToCapture instance for your captured types.

Constructors

DocCapture 

data DocQueryParam Source #

A type to represent a GET (or other possible Method) parameter from the Query String. Holds its name, the possible values (leave empty if there isn't a finite number of them), and a description of how it influences the output or behavior.

Write a ToParam instance for your GET parameter types

data ParamKind Source #

Type of GET (or other Method) parameter:

  • Normal corresponds to QueryParam, i.e your usual GET parameter
  • List corresponds to QueryParams, i.e GET parameters with multiple values
  • Flag corresponds to QueryFlag, i.e a value-less GET parameter

Constructors

Normal 
List 
Flag 

data DocNote Source #

A type to represent extra notes that may be attached to an Action.

This is intended to be used when writing your own HasDocs instances to add extra sections to your endpoint's documentation.

Constructors

DocNote 

data DocIntro Source #

An introductory paragraph for your documentation. You can pass these to docsWithIntros.

Constructors

DocIntro 

Fields

data Response Source #

A type to represent an HTTP response. Has an Int status, a list of possible MediaTypes, and a list of example ByteString response bodies. Tweak defResponse using the respStatus, respTypes and respBody lenses if you want.

If you want to respond with a non-empty response body, you'll most likely want to write a ToSample instance for the type that'll be represented as encoded data in the response.

Can be tweaked with three lenses.

λ> defResponse
Response {_respStatus = 200, _respTypes = [], _respBody = []}
λ> defResponse & respStatus .~ 204 & respBody .~ [("If everything goes well", "{ \"status\": \"ok\" }")]
Response {_respStatus = 204, _respTypes = [], _respBody = [("If everything goes well", "{ \"status\": \"ok\" }")]}

defResponse :: Response Source #

Default response: status code 200, no response body.

Can be tweaked with two lenses.

λ> defResponse
Response {_respStatus = 200, _respBody = Nothing}
λ> defResponse & respStatus .~ 204 & respBody .~ Just "[]"
Response {_respStatus = 204, _respBody = Just "[]"}

data Action Source #

A datatype that represents everything that can happen at an endpoint, with its lenses:

  • List of captures (captures)
  • List of GET (or other Method) parameters (params)
  • What the request body should look like, if any is requested (rqbody)
  • What the response should be if everything goes well (response)

You can tweak an Action (like the default defAction) with these lenses to transform an action and add some information to it.

defAction :: Action Source #

Default Action. Has no captures, no query params, expects no request body (rqbody) and the typical response is defResponse.

Tweakable with lenses.

λ> defAction
Action {_captures = [], _headers = [], _params = [], _mxParams = [], _rqbody = Nothing, _response = Response {_respStatus = 200, _respBody = Nothing}}
λ> defAction & response.respStatus .~ 201
Action {_captures = [], _headers = [], _params = [], _mxParams = [], _rqbody = Nothing, _response = Response {_respStatus = 201, _respBody = Nothing}}

single :: Endpoint -> Action -> API Source #

Create an API that's comprised of a single endpoint. API is a Monoid, so combine multiple endpoints with mappend or <>.