servant-pandoc-0.5.0.0: Use Pandoc to render servant API documentation

Safe HaskellNone
LanguageHaskell2010

Servant.Docs.Pandoc

Description

There are two ways in which to use this module.

The first is to use the renderer directly with the pandoc API. A very simple program to render the API documentation as a mediawiki document might look as follows.

import Text.Pandoc
import Servant.Docs.Pandoc
import Servant.Docs
import Data.Default (def)

myApi :: Proxy MyAPI
myApi = Proxy

writeDocs :: API -> IO ()
writeDocs api = writeFile "api.mw" (writeMediaWiki def (pandoc api))

The second approach is to use makeFilter to make a filter which can be used directly with pandoc from the command line. This filter will just append the API documentation to the end of the document. Example usage

-- api.hs
main :: IO ()
main = makeFilter (docs myApi)
> pandoc -o api.pdf --filter=api.hs manual.md

A more sophisticated filter can be used to actually convert introduction and note bodies into Markdown for pandoc to be able to process:

import Data.Monoid         (mconcat, (<>))
import Servant.Docs.Pandoc (pandoc)
import Text.Pandoc         (readMarkdown)
import Text.Pandoc.JSON    (Block(Para, Plain), Inline(Str), Pandoc(Pandoc),
                            toJSONFilter)
import Text.Pandoc.Options (def)
import Text.Pandoc.Walk    (walkM)

main :: IO ()
main = toJSONFilter append
  where
    append :: Pandoc -> Pandoc
    append = (<> mconcat (walkM parseMarkdown (pandoc myApi)))

parseMarkdown :: Block -> [Block]
parseMarkdown bl = case bl of
                     Para  [Str str] -> toMarkdown str
                     Plain [Str str] -> toMarkdown str
                     _               -> [bl]
  where
    toMarkdown = either (const [bl]) unPandoc . readMarkdown def

    unPandoc (Pandoc _ bls) = bls

Synopsis

Documentation

pandoc :: API -> Pandoc Source #

Generate a Pandoc representation of a given API.

This is equivalent to pandocWith defRenderingOptions.

pandocWith :: RenderingOptions -> API -> Pandoc Source #

Generate a Pandoc representation of a 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.
  • Whether all notes should be grouped together under a common heading with notesHeading.

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

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

Since: 0.5.0.0

makeFilter :: API -> IO () Source #

Helper function which can be used to make a pandoc filter which appends the generate docs to the end of the document.

This function is exposed for convenience. More experienced authors can of course define a more complicated filter to inject the API documentation.