servant-docs-simple-0.4.0.0: Generate endpoints overview for Servant API
Safe HaskellNone
LanguageHaskell2010

Servant.Docs.Simple

Description

Parse and render an API type, write documentation to file, stdout

Example script

Writing documentation to file

With the following language extensions

DataKinds
TypeApplications
TypeOperators

Using this script

module Main where

import Servant.API ((:>), Post, ReqBody)
import Servant.Docs.Simple (writeDocsJson, writeDocsPlainText)

-- Our API type
type API = "hello" :> "world" :> Request :> Response
type Request = ReqBody '[()] ()
type Response = Post '[()] ()

main :: IO ()
main = do
  -- Writes to the file $PWD/docs.json
  writeDocsJson @API "docs.json"

  -- Writes to the file $PWD/docs.txt
  writeDocsPlainText @API "docs.txt"

Expected Output

Files should be generated relative to $PWD

$ ls | grep docs
docs.json
docs.txt

docs.json

{
    "/hello/world": {
        "Response": {
            "Format": "[()]",
            "ContentType": "()"
        },
        "RequestType": "'POST",
        "RequestBody": {
            "Format": "[()]",
            "ContentType": "()"
        }
    }
}

docs.txt

/hello/world:
RequestBody:
    Format: [()]
    ContentType: ()
RequestType: 'POST
Response:
    Format: [()]
    ContentType: ()
Synopsis

Documentation

document :: forall api. HasParsableApi api => PlainText Source #

Convert API type into PlainText format

documentWith :: forall api a. (HasParsableApi api, Renderable a) => a Source #

Convert API type into specified formats

stdoutJson :: forall api. HasParsableApi api => IO () Source #

Write documentation as JSON to stdout

stdoutMarkdown :: forall api. HasParsableApi api => IO () Source #

Write documentation as Markdown to stdout

stdoutPlainText :: forall api. HasParsableApi api => IO () Source #

Write documentation as PlainText to stdout

writeDocsJson :: forall api. HasParsableApi api => FilePath -> IO () Source #

Write documentation as JSON to file

writeDocsMarkdown :: forall api. HasParsableApi api => FilePath -> IO () Source #

Write documentation as Markdown to file

writeDocsPlainText :: forall api. HasParsableApi api => FilePath -> IO () Source #

Write documentation as PlainText to file