servant-docs-0.2.1: 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 generate an API from the type that represents your API using docs:

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

You can then call markdown on it:

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.

Here's a little (but complete) example that you can run to see the markdown pretty printer in action:

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}

import Data.Proxy
import Data.Text
import Servant

-- our type for a Greeting message
data Greet = Greet { _msg :: Text }
  deriving (Generic, Show)

-- we get our JSON serialization for free
instance FromJSON Greet
instance ToJSON Greet

-- we provide a sample value for the 'Greet' type
instance ToSample Greet where
  toSample = Just g

    where g = Greet "Hello, haskeller!"

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

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

instance ToCapture (Capture "greetid" Text) where
  toCapture _ = DocCapture "greetid" "identifier of the greet msg to remove"

-- API specification
type TestApi =
       "hello" :> Capture "name" Text :> QueryParam "capital" Bool :> Get Greet
  :<|> "greet" :> RQBody Greet :> Post Greet
  :<|> "delete" :> Capture "greetid" Text :> Delete

testApi :: Proxy TestApi
testApi = Proxy

-- Generate the Documentation's ADT
greetDocs :: API
greetDocs = docs testApi

main :: IO ()
main = putStrLn $ markdown greetDocs

Synopsis

HasDocs class and key functions

class HasDocs layout where Source

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

Methods

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

Instances

HasDocs Delete 
HasDocs Raw 
ToSample a => HasDocs (Get a) 
ToSample a => HasDocs (Post a) 
ToSample a => HasDocs (Put a) 
(HasDocs layout1, HasDocs layout2) => HasDocs ((:<|>) layout1 layout2)

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

(KnownSymbol sym, ToCapture (Capture Symbol * sym a), HasDocs sublayout) => HasDocs ((:>) * (Capture Symbol * sym a) sublayout)

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

(KnownSymbol sym, HasDocs sublayout) => HasDocs ((:>) * (Header Symbol * sym a) sublayout) 
(KnownSymbol sym, ToParam (QueryParam Symbol * sym a), HasDocs sublayout) => HasDocs ((:>) * (QueryParam Symbol * sym a) sublayout) 
(KnownSymbol sym, ToParam (QueryParams Symbol * sym a), HasDocs sublayout) => HasDocs ((:>) * (QueryParams Symbol * sym a) sublayout) 
(KnownSymbol sym, ToParam (QueryFlag Symbol sym), HasDocs sublayout) => HasDocs ((:>) * (QueryFlag Symbol sym) sublayout) 
(ToSample a, HasDocs sublayout) => HasDocs ((:>) * (ReqBody * a) sublayout) 
(KnownSymbol path, HasDocs sublayout) => HasDocs ((:>) Symbol path sublayout) 

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

Generate the docs for a given API that implements HasDocs.

markdown :: API -> String Source

Generate documentation in Markdown format for the given API.

Classes you need to implement for your types

class ToJSON a => ToSample a where Source

The class that lets us display a sample JSON input or output 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
  toSample = Just g

    where g = Greet "Hello, haskeller!"

Methods

toSample :: Maybe a Source

Instances

class ToParam t where Source

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."

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"

ADTs to represent an API

data Method Source

Supported HTTP request methods

Constructors

DocDELETE

the DELETE method

DocGET

the GET method

DocPOST

the POST method

DocPUT

the PUT method

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

defEndpoint :: Endpoint Source

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

type API = HashMap Endpoint Action Source

Our API type, a good old hashmap from Endpoint to Action

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 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 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 Source

A type to represent an HTTP response. Has an Int status and a 'Maybe ByteString' response body. Tweak defResponse using the respStatus 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 some JSON in the response.

Can be tweaked with two lenses.

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

Instances

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 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.

Instances

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 <>.

Useful modules when defining your doc printers