servant-docs-simple-0.1.0.0: Generate documentation via TypeRep 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

Using this script

With the following language extensions

DataKinds
TypeApplications
TypeOperators
module Main where

import Data.Aeson (Value)
import Data.Text (Text)

import Servant.API ((:>), Post, ReqBody)
import Servant.Docs.Simple (document, documentWith, stdoutJson, stdoutPlainText, writeDocsJson,
                            writeDocsPlainText)
import Servant.Docs.Simple.Render (Json (..), PlainText (..))

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

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

  -- Writes to the file $PWD/docsPlainText
  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. HasParsable api => PlainText Source #

Convert API type into PlainText format

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

Convert API type into specified formats

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

Write documentation as JSON to stdout

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

Write documentation as PlainText to stdout

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

Write documentation as JSON to file

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

Write documentation as PlainText to file