Back to top
Mocking an Automotive Backend with Haskell and Servant: Episode 5

Generating documentation

Read Episode 1
Read Episode 2
Read Episode 3
Read Episode 4

Welcome to the fifth and final installment of this blog series. In this post, we’ll examine how we can take advantage of Servant’s ability to generate API documentation for us.

First, let’s consider why we might need Servant-generated documentation in the first place. After all, the premise of this blog series is that we are mocking our customer’s backend based on documentation that the customer has provided. Why would we need more documentation?

Well, we’ve found that the customer’s documentation often suffers from subtle ambiguities, a problem that may not be entirely evident at first. Consider the case when the customer furnishes informal, ad hoc specifications for calls that they have not yet developed. When the customer’s backend development lags behind our development of the front-end app, we’ll add the as-of-yet nonexistent calls to our mock backend and have our app hit the mock backend for those particular calls. This allows us to continue our app development unimpeded. When the customer finishes their development, we simply point our app to the real backend.

If the customer’s API specifications are entirely unequivocal, chances are good that the switch will go seamlessly. However, it is often the case that issues arise. For example, we may have assumed that for a given GET endpoint, when there is no data to return the server will respond with an empty JSON array. However, the backend developers might instead decide to return an error response. The customer’s API documentation was unclear or lacking in regards to this particular behavior.

At times like these, we’ve found that automatically generated documentation for the mock backend can be quite helpful when it is referenced during discussions with the customer. Automatically generated documentation tends to be thorough and very precise. When there are discrepancies between your mock backend (by extension, consequently, your front-end) and the customer’s real backend, it can help all parties to quickly reach a compromise regarding what the “correct” behavior is.

With a little effort on our part we can reap the benefits of automatically generated documentation. Servant needs our assistance to some degree, as it cannot deduce the steps we take in our handler functions.

First, let’s head over to our Types module and add some imports.

import Servant.Docs (DocCapture(..), DocQueryParam(..), ParamKind(..), ToCapture, ToParam, ToSample, toCapture, toParam, toSample)

We must provide Servant with information regarding the applied meaning of all our captures, query parameters, request bodies, and response bodies. This is accomplished by instantiating three typeclasses from Servant: ToCapture (instantiated by Captures), ToParam (instantiated by QueryParams), and ToSample (instantiated by those types used in ReqBodys and response bodies).

Here is what our typeclass instances look like:

type VehicleAPI =
       "vehicles" :> "all"                                       :> Get  '[JSON] [Vehicle]
  :<|> "vehicles" :> Capture "id" Int                            :> Get  '[JSON] Vehicle
  :<|> "vehicles" :>                     ReqBody '[JSON] Vehicle :> Post '[JSON] Vehicle
  :<|> "vehicles" :> Capture "id" Int :> ReqBody '[JSON] Vehicle :> Put  '[JSON] Vehicle
  -----
  :<|> "vehicles" :> "issues" :> Capture "id" Int :> QueryParam "sortBy" SortBy :> Get '[JSON] [Issue]
  :<|> "vehicles" :> "issues" :> Capture "id" Int :> ReqBody '[JSON] [Issue]    :> Put '[JSON] [Issue]

-- ...

-- Instantiate ToCapture to provide info regarding the meaning of a Capture.
instance ToCapture (Capture "id" Int) where
  toCapture _ = DocCapture "id"                    -- name
                           "(integer) Vehicle ID." -- description

-- Instantiate ToSample to provide sample data used in documentation.
instance ToSample Vehicle Vehicle where
  toSample _ = Just Vehicle { vin = "vin", year = 1985, model = "DeLorean", issues = issueList }

issueList :: [Issue]
issueList = [ Issue Battery High, Issue Brakes Low ]

instance ToSample [Vehicle] [Vehicle] where
  toSample _ = Just [ Vehicle { vin = "vin", year = 1985, model = "DeLorean", issues = issueList } ]

instance ToSample [Issue] [Issue] where
  toSample _ = Just [ Issue Battery High ]

-- Instantiate ToParam to provide info regarding the meaning of a QueryParam.
instance ToParam (QueryParam "sortBy" SortBy) where
  toParam _ = DocQueryParam "sortBy"                                        -- name
                            [ "ByType", "ByPriority" ]                      -- example values
                            "Criteria by which to sort the list of issues." -- description
                            Normal                                          -- "Normal", "List" or "Flag"
-- Note: Use "List" for GET parameters with multiple values. Use "Flag" for a "QueryFlag", i.e. a value-less GET parameter.

We have now provided all the information Servant needs to generate documentation for us. However, there is a problem. If you compile the code, you’ll get the following unfortunate warning:

Orphan instance: instance ToCapture (Capture "id" Int)
To avoid this
    move the instance declaration to the module of the class or of the type, or
    wrap the type with a newtype and declare the instance on the new type.

An “orphan instance” is created when a typeclass is instantiated by a type in a module in which neither the typeclass nor the type are declared. The culprits here are the ToCapture typeclass and the Int type: neither ToCapture nor Int are defined in our Types module.

To see why this would be a problem, consider the following contrived example. In module A we make Int a Monoid on addition. In module B we make Int a Monoid on multiplication. Both modules A and B will raise the orphan instance warning, but we choose to ignore it. In module C, we import the Monoid Int instances from both modules A and B. Now module C will fail to compile with a Duplicate instance declarations error, because Haskell cannot know which Monoid Int we prefer to use. You’d likely be rather exasperated if you were the author of module C while modules A and B were authored by others.

So, we now have two options: we can put {-# OPTIONS_GHC -fno-warn-orphans #-} at the top of our Types module so as to blatantly ignore the orphan instance warning, or do The Right Thing and forgo the use of Int in favor of a newtype that wraps Int. Let’s do The Right Thing!

newtype CaptureInt = CaptureInt { fromCaptureInt :: Int } deriving (Eq, FromText, Generic, Show, ToText)

To derive FromText and ToText for CaptureInt, we must turn on the GeneralizedNewtypeDeriving language extension:

{-# LANGUAGE DataKinds, DeriveGeneric, FlexibleInstances, GeneralizedNewtypeDeriving, MultiParamTypeClasses, OverloadedStrings, TypeOperators #-}

Now our code will compile without the orphan instance warning.

Let’s begin by writing a function that will output our documentation to a markdown file.

module Main ( main
            , writeMarkdownDoc ) where

-- ...

import Servant.Docs (API, docs, markdown)

-- ...

-- This binding encapsulates internal info about our API spec and forms the basis for the documentation we generate.
apiDocs :: API
apiDocs = docs vehicleAPI

writeMarkdownDoc :: IO ()
writeMarkdownDoc = writeFile "/Users/stolaruk/Desktop/doc.md" . markdown $ apiDocs

If we invoke the writeMarkdownDoc function from the REPL, a markdown file will be created for us.

Unfortunately, the code won’t work yet. We are now faced with the following error:

No instance for (Servant.Docs.Internal.ToCapture
                   (Servant.API.Capture.Capture "id" Int))
  arising from a use of ‘docs’
In the expression: docs vehicleAPI

Now that we’ve opted to use our CaptureInt newtype, we have to use it everywhere in place of the Int in Capture "id" Int. This requires refactoring three modules: Types, Server, and Client.

module Types where

-- ...

type VehicleAPI =
       "vehicles" :> "all"                                              :> Get  '[JSON] [Vehicle]
  :<|> "vehicles" :> Capture "id" CaptureInt                            :> Get  '[JSON] Vehicle
  :<|> "vehicles" :>                            ReqBody '[JSON] Vehicle :> Post '[JSON] Vehicle
  :<|> "vehicles" :> Capture "id" CaptureInt :> ReqBody '[JSON] Vehicle :> Put  '[JSON] Vehicle
  -----
  :<|> "vehicles" :> "issues" :> Capture "id" CaptureInt :> QueryParam "sortBy" SortBy :> Get '[JSON] [Issue]
  :<|> "vehicles" :> "issues" :> Capture "id" CaptureInt :> ReqBody '[JSON] [Issue]    :> Put '[JSON] [Issue]
module Server where

-- ...

    getVehicleById :: CaptureInt -> EitherT ServantErr IO Vehicle
    getVehicleById (CaptureInt i) = maybe notFound return =<< IM.lookup i <$> liftIO (readIORef ref)

-- ...

    putVehicle :: CaptureInt -> Vehicle -> EitherT ServantErr IO Vehicle
    putVehicle (CaptureInt i) v = putHelper f
      where
        f :: IM.IntMap Vehicle -> (IM.IntMap Vehicle, Maybe Vehicle)
        f tbl | i `IM.member` tbl = let tbl' = IM.insert i v tbl
                                    in (tbl', Just v)
              | otherwise         = (tbl, Nothing)


-- ...


    getIssuesById :: CaptureInt -> Maybe SortBy -> EitherT ServantErr IO [Issue]
    getIssuesById ci msb = do
        unsorted <- issues <$> getVehicleById ci
        return . maybe unsorted (sortIssues unsorted) $ msb

-- ...

    putIssues :: CaptureInt -> [Issue] -> EitherT ServantErr IO [Issue]
    putIssues (CaptureInt i) is = putHelper f
      where
        f :: IM.IntMap Vehicle -> (IM.IntMap Vehicle, Maybe [Issue])
        f tbl = maybe (tbl, Nothing) found $ IM.lookup i tbl
          where
            found :: Vehicle -> (IM.IntMap Vehicle, Maybe [Issue])
            found v = let v'   = v { issues = is }
                          tbl' = IM.insert i v' tbl
                      in (tbl', Just is)
module Client where

-- ...

getAllVehicles ::                               EitherT ServantError IO [Vehicle]
getVehicleById :: CaptureInt                 -> EitherT ServantError IO Vehicle
postVehicle    ::               Vehicle      -> EitherT ServantError IO Vehicle
putVehicle     :: CaptureInt -> Vehicle      -> EitherT ServantError IO Vehicle
-----
getIssuesById  :: CaptureInt -> Maybe SortBy -> EitherT ServantError IO [Issue]
putIssues      :: CaptureInt -> [Issue]      -> EitherT ServantError IO [Issue]

-- ...

tryGetVehicleById :: CaptureInt -> IO ()
tryGetVehicleById = tryEndpoint . getVehicleById

-- ...

tryPutVehicle :: CaptureInt -> Vehicle -> IO ()
tryPutVehicle ci = tryEndpoint . putVehicle ci

tryGetIssuesById :: CaptureInt -> Maybe SortBy -> IO ()
tryGetIssuesById ci = tryEndpoint . getIssuesById ci

tryPutIssues :: CaptureInt -> [Issue] -> IO ()
tryPutIssues ci = tryEndpoint . putIssues ci

Finally, the code will compile and we can invoke our new writeMarkdownDoc function. Here is a snippet of our rendered markdown:

Markdown is the format that Servant provides out of the box. If we leverage Pandoc and the servant-pandoc library, we can get other formats, too. Pandoc can convert markdown to HTML (along with numerous other formats), and vice versa.

Let’s write a new function that will output our documentation to an HTML file.

module Main ( main
            , writeHtmlDoc
            , writeMarkdownDoc ) where

-- ...

import Servant.Docs.Pandoc (pandoc)
import Text.Pandoc (writeHtmlString)
import Text.Pandoc.Options (def)

-- ...

writeHtmlDoc :: IO ()
writeHtmlDoc = writeFile "/Users/stolaruk/Desktop/doc.html" . writeHtmlString def . pandoc $ apiDocs

That was easy! Here is a snippet of our rendered HTML:

Finally, let’s take it one step further and have our server host our API documentation. We’ll do this by creating a new type named VehicleAPIWithDocs that builds upon our VehicleAPI type by adding a Raw endpoint from which the documentation will be served.

module Types where

-- ...

import Servant (Capture, FromText(..), Get, JSON, Post, Put, Raw, QueryParam, ReqBody, ToText(..), (:<|>), (:>))

-- ...

type VehicleAPIWithDocs = VehicleAPI :<|> Raw

Next we’ll add the following code to our Server module. While we’re at it, we’ll tack on a short introduction to the top of our documentation.

import Data.ByteString.Lazy (ByteString)
import Data.Text.Lazy.Encoding (encodeUtf8)
import Network.HTTP.Types (ok200)
import Network.Wai (responseLBS)
import qualified Data.Text.Lazy as T
import Servant.Docs (DocIntro(..), docsWithIntros)
import Servant.Docs.Pandoc (pandoc)
import Text.Pandoc (writeHtmlString)
import Text.Pandoc.Options (def)

-- ...

vehicleAPIWithDocs :: Proxy VehicleAPIWithDocs
vehicleAPIWithDocs = Proxy

serverWithDocs :: IORef (IM.IntMap Vehicle) -> Server VehicleAPIWithDocs
serverWithDocs ref = server ref :<|> serveDocs
  where
    serveDocs _ respond = respond . responseLBS ok200 [("Content-Type", "text/html")] $ docsBS

docsBS :: ByteString -- Raw endpoints must serve content in the lazy bytestring format.
docsBS = encodeUtf8 . T.pack . writeHtmlString def . pandoc . docsWithIntros [intro] $ vehicleAPI
  where
    intro = DocIntro "Welcome" [ "This is our mock auto API.", "Enjoy!" ]

Finally, in our Main module we’ll modify the app function so as to serve the new API which includes the Raw endpoint.

app :: IORef (IM.IntMap Vehicle) -> Application
app = serve vehicleAPIWithDocs . serverWithDocs

Our Raw endpoint – the final endpoint specified in our API – will automatically succeed when all others fail. This means the user will see our documentation should they attempt to access an endpoint that we haven’t defined. Nice!

Here is what it looks like in a browser:

That’s all for this blog series. Thank you for reading!

The complete code for the mock backend can be found here.

One final word of advice: when you have questions about Servant, consider asking the #servant channel on IRC. The kind folks there were quite helpful to me when I got stuck while writing the code for this blog.

Happy Haskell hacking!