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

Safe HaskellNone
LanguageHaskell2010

Servant.Docs.Internal

Contents

Synopsis

Documentation

data Method

Supported HTTP request methods

Constructors

DocDELETE

the DELETE method

DocGET

the GET method

DocPOST

the POST method

DocPUT

the PUT method

Instances

data Endpoint

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 .~ DocPOST
POST /foo

Constructors

Endpoint 

Fields

_path :: [String]
 
_method :: Method
 

showPath :: [String] -> String

Render a path as a /-delimited string

defEndpoint :: Endpoint

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

Here's how you can modify it:

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

data API

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

Constructors

API 

Instances

emptyAPI :: API

An empty API

data DocCapture

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

A type to represent a GET 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 DocIntro

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

Constructors

DocIntro 

Fields

_introTitle :: String

Appears above the intro blob

_introBody :: [String]

Each String is a paragraph.

data DocNote

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 

newtype ExtraInfo layout

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.

Constructors

ExtraInfo (HashMap Endpoint Action) 

Instances

data DocOptions

Documentation options.

Constructors

DocOptions 

Fields

_maxSamples :: Int

Maximum samples allowed.

Instances

defaultDocOptions :: DocOptions

Default documentation options.

data ParamKind

Type of GET 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 Response

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\" }")]}

Constructors

Response 

Fields

_respStatus :: Int
 
_respTypes :: [MediaType]
 
_respBody :: [(Text, MediaType, ByteString)]
 
_respHeaders :: [Header]
 

defResponse :: Response

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

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

  • List of captures (captures)
  • List of GET 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.

Constructors

Action 

Fields

_captures :: [DocCapture]
 
_headers :: [Text]
 
_params :: [DocQueryParam]
 
_notes :: [DocNote]
 
_mxParams :: [(String, [DocQueryParam])]
 
_rqtypes :: [MediaType]
 
_rqbody :: [(MediaType, ByteString)]
 
_response :: Response
 

Instances

combineAction :: Action -> Action -> Action

Combine two Actions, we can't make a monoid as merging Response breaks the laws.

As such, we invent a non-commutative, left associative operation combineAction to mush two together taking the response, body and content types from the very left.

single :: Endpoint -> Action -> API

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

apiEndpoints :: Lens' API (HashMap Endpoint Action)

path :: Lens' Endpoint [String]

respTypes :: Lens' Response [MediaType]

respHeaders :: Lens' Response [Header]

respBody :: Lens' Response [(Text, MediaType, ByteString)]

rqtypes :: Lens' Action [MediaType]

rqbody :: Lens' Action [(MediaType, ByteString)]

notes :: Lens' Action [DocNote]

headers :: Lens' Action [Text]

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

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

docs == docsWithOptions defaultDocOptions

docsWithOptions :: HasDocs layout => Proxy layout -> DocOptions -> API

Generate the docs for a given API that implements HasDocs.

type family IsIn endpoint api :: Constraint

Closed type family, check if endpoint is exactly within API.

Equations

IsIn e (sa :<|> sb) = Or (IsIn e sa) (IsIn e sb) 
IsIn (e :> sa) (e :> sb) = IsIn sa sb 
IsIn e e = () 

extraInfo :: (IsIn endpoint layout, HasLink endpoint, HasDocs endpoint) => Proxy endpoint -> Action -> ExtraInfo layout

Create an ExtraInfo that is garunteed 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"]
                                     ]

docsWith :: HasDocs layout => DocOptions -> [DocIntro] -> ExtraInfo layout -> Proxy layout -> API

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 layout => [DocIntro] -> Proxy layout -> API

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

class HasDocs layout where

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

Methods

docsFor :: Proxy layout -> (Endpoint, Action) -> DocOptions -> API

Instances

HasDocs * Raw 
(HasDocs * layout1, HasDocs * layout2) => HasDocs * ((:<|>) layout1 layout2)

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

(ToSample a, IsNonEmpty cts, AllMimeRender cts a, AllHeaderSamples [*] ls, GetHeaders (HList ls)) => HasDocs * (Get cts (Headers ls a)) 
(ToSample a, IsNonEmpty cts, AllMimeRender cts a) => HasDocs * (Get cts a) 
(ToSample a, IsNonEmpty cts, AllMimeRender cts a, AllHeaderSamples [*] ls, GetHeaders (HList ls)) => HasDocs * (Post cts (Headers ls a)) 
(ToSample a, IsNonEmpty cts, AllMimeRender cts a) => HasDocs * (Post cts a) 
(ToSample a, IsNonEmpty cts, AllMimeRender cts a, AllHeaderSamples [*] ls, GetHeaders (HList ls)) => HasDocs * (Delete cts (Headers ls a)) 
(ToSample a, IsNonEmpty cts, AllMimeRender cts a) => HasDocs * (Delete cts a) 
(ToSample a, IsNonEmpty cts, AllMimeRender cts a, AllHeaderSamples [*] ls, GetHeaders (HList ls)) => HasDocs * (Put cts (Headers ls a)) 
(ToSample a, IsNonEmpty cts, AllMimeRender cts a) => HasDocs * (Put cts a) 
HasDocs k sublayout => HasDocs * ((:>) * k Vault sublayout) 
HasDocs k sublayout => HasDocs * ((:>) * k HttpVersion sublayout) 
HasDocs k sublayout => HasDocs * ((:>) * k IsSecure sublayout) 
HasDocs k sublayout => HasDocs * ((:>) * k RemoteHost sublayout) 
(ToSample a, IsNonEmpty cts, AllMimeRender cts a, HasDocs k sublayout) => HasDocs * ((:>) * k (ReqBody * cts a) sublayout) 
(KnownSymbol sym, ToParam * (QueryFlag sym), HasDocs k sublayout) => HasDocs * ((:>) * k (QueryFlag sym) sublayout) 
(KnownSymbol sym, ToParam * (QueryParams k1 sym a), HasDocs k sublayout) => HasDocs * ((:>) * k (QueryParams k sym a) sublayout) 
(KnownSymbol sym, ToParam * (QueryParam k1 sym a), HasDocs k sublayout) => HasDocs * ((:>) * k (QueryParam k sym a) sublayout) 
(KnownSymbol sym, HasDocs k sublayout) => HasDocs * ((:>) * k (Header sym a) sublayout) 
(KnownSymbol sym, ToCapture * (Capture k1 sym a), HasDocs k sublayout) => HasDocs * ((:>) * k (Capture k sym a) sublayout)

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

(KnownSymbol path, HasDocs k sublayout) => HasDocs * ((:>) Symbol k path sublayout) 

class ToSample a where

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.

Minimal complete definition

Nothing

Methods

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

Instances

ToSample Bool 
ToSample Ordering 
ToSample () 
ToSample All 
ToSample Any 
ToSample a => ToSample [a] 
ToSample a => ToSample (ZipList a) 
ToSample a => ToSample (Dual a) 
ToSample a => ToSample (Sum a) 
ToSample a => ToSample (Product a) 
ToSample a => ToSample (First a) 
ToSample a => ToSample (Last a) 
ToSample a => ToSample (Maybe a) 
(ToSample a, ToSample b) => ToSample (Either a b) 
(ToSample a, ToSample b) => ToSample (a, b) 
ToSample a => ToSample (Const a b) 
(ToSample a, ToSample b, ToSample c) => ToSample (a, b, c) 
(ToSample a, ToSample b, ToSample c, ToSample d) => ToSample (a, b, c, d) 
(ToSample a, ToSample b, ToSample c, ToSample d, ToSample e) => ToSample (a, b, c, d, e) 
(ToSample a, ToSample b, ToSample c, ToSample d, ToSample e, ToSample f) => ToSample (a, b, c, d, e, f) 
(ToSample a, ToSample b, ToSample c, ToSample d, ToSample e, ToSample f, ToSample g) => ToSample (a, b, c, d, e, f, g) 

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

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

noSamples :: [(Text, a)]

No samples.

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

Single sample without description.

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

Samples without documentation.

defaultSamples :: forall a. (Generic a, GToSample (Rep a)) => Proxy a -> [(Text, a)]

Default sample Generic-based inputs/outputs.

class GToSample t where

ToSample for Generics.

The use of Omega allows for more productive sample generation.

Methods

gtoSamples :: proxy t -> Omega (Text, t x)

Instances

GToSample * V1 
GToSample * U1 
ToSample a => GToSample * (K1 i a) 
(GToSample * p, GToSample * q) => GToSample * ((:+:) p q) 
(GToSample * p, GToSample * q) => GToSample * ((:*:) p q) 
GToSample * f => GToSample * (M1 i a f) 

class AllHeaderSamples ls where

Methods

allHeaderToSample :: Proxy ls -> [Header]

Instances

AllHeaderSamples [k] ([] k) 
(ToByteString l, AllHeaderSamples [*] ls, ToSample l, KnownSymbol h) => AllHeaderSamples [*] ((:) * (Header h l) ls) 

sampleByteString :: forall ctypes a. (ToSample a, IsNonEmpty ctypes, AllMimeRender ctypes a) => Proxy ctypes -> Proxy a -> [(MediaType, ByteString)]

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

sampleByteStrings :: forall ctypes a. (ToSample a, IsNonEmpty ctypes, AllMimeRender ctypes a) => Proxy ctypes -> Proxy a -> [(Text, MediaType, ByteString)]

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

class ToParam t where

The class that helps us automatically get documentation for GET parameters.

Example of an instance:

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

Methods

toParam :: Proxy t -> DocQueryParam

class ToCapture c where

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"

Methods

toCapture :: Proxy c -> DocCapture

markdown :: API -> String

Generate documentation in Markdown format for the given API.

Instances