servant-docs-simple
Introduction
This library uses Data.Typeable
to generate documentation for Servant API types.
It relies on the typeRep
of Servant's combinators and other datatypes used in
the API to generate the documentation.
Why do we need this?
-
We need the API Format types
inside the documentation. They can be used as keys
while querying an API endpoint, to look up examples, fields, and other
miscellaneous details.
-
We want to generate documentation from the information our API
type provides, without having to write instances.
In-depth explanation here
Functionality
Servant.Docs.Simple.Parse
Parses the API into a documentation friendly structure
API type
type API = "hello" :> "world" :> Request :> Response
type Request = ReqBody '[()] ()
type Response = Post '[()] ()
Intermediate structure
Endpoints [Node "/hello/world"
(Details [ Node "RequestBody" (Details [ Node "Format"
(Detail "': * () ('[] *)")
, Node "ContentType"
(Detail "()")
])
, Node "RequestType" (Detail "'POST")
, Node "Response" (Details [ Node "Format"
(Detail "': * () ('[] *)")
, Node "ContentType"
(Detail "()")
])
])]
Servant.Docs.Simple.Render
Renders the intermediate structure into common documentation formats
Intermediate structure
Endpoints [Node "/hello/world"
(Details [ Node "RequestBody" (Details [ Node "Format"
(Detail "': * () ('[] *)")
, Node "ContentType"
(Detail "()")
])
, Node "RequestType" (Detail "'POST")
, Node "Response" (Details [ Node "Format"
(Detail "': * () ('[] *)")
, Node "ContentType"
(Detail "()")
])
])]
JSON
{
"/hello/world": {
"Response": {
"Format": "': * () ('[] *)",
"ContentType": "()"
},
"RequestType": "'POST",
"RequestBody": {
"Format": "': * () ('[] *)",
"ContentType": "()"
}
}
}
Text
/hello/world:
RequestBody:
Format: ': * () ('[] *)
ContentType: ()
RequestType: 'POST
Response:
Format: ': * () ('[] *)
ContentType: ()
Servant.Docs.Simple
Provides functions to write rendered formats to file/stdout
Using this script
-- stack --system-ghc runghc --package servant-docs-simple
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE 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: ()
Tutorials
Click on these links for tutorials
Generating plaintext/JSON documentation from api types
Generating the intermediate documentation structure
Writing our own rendering format
To run tutorial scripts
# clone this repository
git clone git@github.com:Holmusk/servant-docs-simple.git
# run the examples
stack examples/<source file>
FAQ
What's the usecase for this?
-
Lightweight documentation solution.
-
Keeping documentation for types in one place
Suppose we have a library of format types. These are shared between different
languages and formats. If we centralize all the information in this
library, we have one source of truth.
-- --- Format Types ---
-- | |
-- v v
type singleAPI = "hello" :> ReqBody '[JSON] User :> POST '[JSON] Message
data User = User Name Password deriving Typeable
data Messsage = Message Id Content deriving Typeable
We use these format types in our API
as illustrated above.
Developers can use these format types to index the library, to find information
(examples, instances, ...) they need about the type.
What is required to achieve this?
-
We need documentation to be generated from the API type, without writing
extra instances for each format type we use.
We can do this with typeRep
from Data.Typeable
.
$ stack ghci
Prelude> import Data.Typeable
Prelude Data.Typeable> data Alignment = Good | Bad deriving Typeable
Prelude Data.Typeable> typeRep (Proxy :: Proxy Alignment)
Alignment
-
We need access to the API format types (Email
, Users
, ...) in documentation.
This is so we can index our library with these types to get the relevant
fields, examples for these.
Why don't we use Servant.Docs?
-
Servant.Docs
generates documentation only if Format Types
have
implemented the necessary instances.
-- Instances for format types; they provide examples for format types
instance ToSample User where
toSamples _ = <some example>
instance ToSample Message where
toSamples _ = <some example>
Hence, we cannot generate documentation solely from the Format Type
.
-
In documentation generated by Servant.Docs
, the format types mentioned above (User
,
Message
) are not included. This means we can't use them to index our library
to look for the relevant information.
What are the trade-offs?
-
Currently Servant.Docs.Simple
does not support as many formats as
Servant.Docs
(via Servant.Docs.Pandoc
).
-
Examples are not mandatory as you do not have to write instances for your format
types.
This means that if developers don't provide examples, the generated
documentation would be without them.
We can still provide these examples through: