Recently, there was a question on Stack Overflow on how Servant actually works. Others were quick to suggest the Servant paper as a thorough explanation of the approach and the implementation.

As a co-author, I’m obviously happy if the paper is being read, but it’s also 12 pages long in two-column ACM style. And while it explains the implementation, it does not necessarily make it easier to start playing with the code yourself, because it only shows excerpts, and code snippets in a paper are not easily runnable.

At the same time, whenever I want to demonstrate a new concept in the Servant context, or play with new ideas, I find myself not impementing it in the main Servant code base, but rather to create a small library that is “like Servant”, built on the same principles, but much simpler, so that I have less work to do and can evaluate the ideas more quickly. I’ve talked to some other contributors, and at least some of them are doing the same. So I thought it might be useful to develop and present the code of “TinyServant”, which is not exactly tiny, but still small compared to the full Servant code base, strips away a lot of duplication and unessential extras, but is still complete enough so that we can observe how Servant works. Obviously, this still won’t explain everything that one might want to know about the implementation of Servant, but I hope that it will serve as a useful ingredient in that process.

This blog post is a somewhat revised and expanded version of my Stack Overflow answer.

This is not a general tutorial on Servant and using Servant. For learning how to use Servant, the official Servant tutorial or the general documentation section of the Servant home page are better starting points.

The code

The full code that is discussed in this post is 81 lines of Haskell and available separately.

An overview

I’m going to show the following things:

  1. How to define the web API specification language that Servant offers. We are going to define as few constructs as possible: we are not going to worry about content types (just plain text), we are not going to worry about different HTTP methods (just GET), and the only special thing we can do in routes will be that we can capture components of the path. Still, this is enough to show all relevant ideas of the Servant implementation.

  2. How to define an interpretation of the specification language. The point of Servant is that we can define many of these: an API can be interpreted as a web server (for various web backends), a web client (for various frontend languages, such as Haskell or JavaScript), a mock server, as documentation (in various formats) and more. Here, I’m going to implement an interpretation as a simplified Haskell function that can be seen as simulating a primitive web server, but without incurring any actual web dependencies.

  3. How to use TinyServant on an example. We are going to take the very first example of the Servant homepage and adapt it for our examples.

Preparations

To start, here are the language extensions we’ll need:

{-# LANGUAGE DataKinds, PolyKinds, TypeOperators #-}
{-# LANGUAGE TypeFamilies, FlexibleInstances, ScopedTypeVariables #-}
{-# LANGUAGE InstanceSigs #-}

The first three are needed for the definition of the type-level DSL itself. The DSL makes use of type-level strings (DataKinds) and also uses kind polymorphism (PolyKinds). The use of the type-level infix operators such as :<|> and :> requires the TypeOperators extension.

The second three are needed for the definition of the interpretation. For this, we need type-level functions (TypeFamilies), some type class programming which will require FlexibleInstances, and some type annotations to guide the type checker which require ScopedTypeVariables.

Purely for documentation purposes, we also use InstanceSigs.

Here’s our module header:

module TinyServant where

import Control.Applicative
import GHC.TypeLits
import Text.Read
import Data.Time

The import of Data.Time is just for our example.

API specifications

The first ingredient is to define the datatypes that are being used for the API specifications.

data Get (a :: *)

data a :<|> b = a :<|> b
infixr 8 :<|>

data (a :: k) :> (b :: *)
infixr 9 :>

data Capture (a :: *)

As I’ve said before, we define only four constructs in our simplified language:

  1. A Get a represents an endpoint of type a (of kind *). In comparison with full Servant, we ignore content types here. We need the datatype only for the API specifications. There are no directly corresponding values, and hence there is no constructor for Get.

  2. With a :<|> b, we represent the choice between two routes. Again, we wouldn’t need a constructor, but it will turn out to be useful later when we define handlers.

  3. With item :> rest, we represent nested routes, where item is the first path component and rest are the remaining components. In our simplified DSL, there are just two possibilities for item: a type-level string, or a Capture. Because type-level strings are of kind Symbol, but a Capture, defined below is of kind *, we make the first argument of :> kind-polymorphic, so that both options are accepted by the Haskell kind system. So in particular, we will be able to write both

"person" :> Get Person

and

Capture Currency :> Get Amount

and it will be well-kinded.

  1. A Capture a represents a route component that is captured, parsed and then exposed to the handler as a parameter of type a. In full Servant, Capture has an additional string as a parameter that is used for documentation generation. We omit the string here.

Example API

We can now write down a version of the API specification from the Servant home page, adapted to our simplified DSL, and replacing the datatypes used there by actual datatypes that occur in the Data.Time library:

type MyAPI = "date" :> Get Day
        :<|> "time" :> Capture TimeZone :> Get ZonedTime

Interpretation as server

The most interesting aspect is of course what we can do with the API. Servant defines several interpretations, but they all follow a similar pattern. We’ll define only one here, which is inspired by the interpretation as a web server.

In Servant, the serve function has the following type:

serve :: HasServer layout
      => Proxy layout -> Server layout -> Application

It takes a proxy for the API type (we’ll get back to that in a moment), and a handler matching the API type (of type Server layout) to an Application. The Application type comes from the excellent WAI library that Servant uses as its default backend.

Even though WAI is very simple, it is too complicated for the purposes of this post, so we’ll assume a “simulated server” of type

[String] -> IO String

This server is supposed to receive a request that is just a sequence of path components ([String]). We do not care about request methods or the request body or anything like that. And the response it just a message of type String. We ignore status codes, headers and anything else. The underlying idea is still the same though than that of the Application type used in the actual Servant implementation.

So our serve function has type

serve :: HasServer layout
      => Proxy layout -> Server layout -> [String] -> IO String

The HasServer class, which we’ll define below, has instances for all the different constructs of the type-level DSL and therefore encodes what it means for a Haskell type layout to be interpretable as an API type of a server.

The Proxy type is defined as follows: It’s defined as

    data Proxy a = Proxy

Its only purpose is to help the GHC type checker. By passing an explicitly typed proxy such as Proxy :: Proxy MyAPI to serve, we can explicitly instantiate the serve function to a particular API type. Without the Proxy, the only occurrences of the layout parameter would be in the HasServer class constraint and as an argument of Server, which is a type family. GHC is not clever enough to infer the desired value of layout from these occurrences.

The Server argument is the handler for the API. As just stated, Server itself is a type family (i.e., a type-level function), and computes from the API type the type that the handler(s) must have. This is one core ingredient of what makes Servant work correctly.

From these inputs, we then compute the output function of type [String] -> IO String as explained above.

The Server type family

We define Server as a type family first. (Again, this is somewhat simplified compared to Servant, which defines a monad transformer type family called ServerT as part of the HasServer class and then a top-level type synonym Server in terms of ServerT.)

type family Server layout :: *

The handler for a Get a endpoint is simply an IO action producing an a. (Once again, in the full Servant code, we have slightly more options, such as producing an error with a choice of status codes.)

type instance Server (Get a) = IO a

The handler for a :<|> b is a pair of handlers, so we could just define

type instance Server (a :<|> b) = (Server a, Server b) -- preliminary

But with this definition, nested occurrences of :<|> in the API would lead to nested pairs of handlers, so we’d have to write code like

(handler1, (handler2, handler3))

which looks a bit ugly. Instead, we’re going to make :<|> equivalent to Haskell’s pair type, but with an infix constructor called :<|>, so that we can write

handler1 :<|> handler2 :<|> handler3

for a nested pair. The actual definition of Server for :<|> is then

type instance Server (a :<|> b) = Server a :<|> Server b

It remains to explain how each of the path components is handled.

Literal strings in the routes do not affect the type of the handler:

type instance Server ((s :: Symbol) :> r) = Server r

A capture, however, means that the handler expects an additional argument of the type being captured:

type instance Server (Capture a :> r) = a -> Server r

Computing the handler type of the example API

If we expand Server MyAPI, we obtain

   Server MyAPI

~  Server (     "date" :> Get Day
           :<|> "time" :> Capture TimeZone :> Get ZonedTime
          )

~       Server ("date" :> Get Day)
   :<|> Server ("time" :> Capture TimeZone :> Get ZonedTime)

~       Server (Get Day)
   :<|> Server ("time" :> Capture TimeZone :> Get ZonedTime)

~       IO Day
   :<|> Server ("time" :> Capture TimeZone :> Get ZonedTime)

~       IO Day
   :<|> Server (Capture TimeZone :> Get ZonedTime)

~       IO Day
   :<|> TimeZone -> Server (Get ZonedTime)

~       IO Day
   :<|> TimeZone -> IO ZonedTime

where ~ is GHC’s syntax for type equality.

Recall that :<|> as defined is equivalent to a pair. So as intended, the server for our API requires a pair of handlers, one that provides a date of type Day, and one that, given a time zone, provides a time (of type ZonedTime). We can define the handler(s) right now:

handleDate :: IO Day
handleDate = utctDay <$> getCurrentTime

handleTime :: TimeZone -> IO ZonedTime
handleTime tz = utcToZonedTime tz <$> getCurrentTime

handleMyAPI :: Server MyAPI
handleMyAPI = handleDate :<|> handleTime

The HasServer class

We still have to implement the HasServer class, which looks as follows:

class HasServer layout where
  route :: Proxy layout -> Server layout -> [String] -> Maybe (IO String)

The task of the function route is almost like serve. Internally, we have to dispatch an incoming request to the right router. In the case of :<|>, this means we have to make a choice between two handlers. How do we make this choice? A simple option is to allow route to fail, by returning a Maybe. Then in a choice we can just try the first option, and if it returns Nothing, try the second. (Again, full Servant is somewhat more sophisticated here, and version 0.5 will have a much improved routing strategy, which probably at some point in the future deserves to be the topic of its own blog post.)

Once we have route defined, we can easily define serve in terms of route:

serve :: HasServer layout
      => Proxy layout -> Server layout -> [String] -> IO String
serve p h xs = case route p h xs of
  Nothing -> ioError (userError "404")
  Just m  -> m

If none of the routes match, we fail with a (simulated) 404. Otherwise, we return the result.

The HasServer instances

For a Get endpoint, we defined

type instance Server (Get a) = IO a

so the handler is an IO action producing an a, which we have to turn into a String. We use show for this purpose. In the actual Servant implementation, this conversion is handled by the content types machinery, and will typically involve encoding to JSON or HTML.

instance Show a => HasServer (Get a) where
  route :: Proxy (Get a)
        -> IO a -> [String] -> Maybe (IO String)
  route _ handler [] = Just (show <$> handler)
  route _ _       _  = Nothing

Since we’re matching an endpoint only, the require the request to be empty at this point. If it isn’t, this route does not match and we return Nothing.

Let’s look at choice next:

instance (HasServer a, HasServer b) => HasServer (a :<|> b) where
  route :: Proxy (a :<|> b)
        -> (Server a :<|> Server b) -> [String] -> Maybe (IO String)
  route _ (handlera :<|> handlerb) xs =
        route (Proxy :: Proxy a) handlera xs
    <|> route (Proxy :: Proxy b) handlerb xs

Here, we get a pair of handlers, and we use <|> for Maybe to try both, preferring the first if it matches.

What happens for a literal string?

instance (KnownSymbol s, HasServer r) => HasServer ((s :: Symbol) :> r) where
  route :: Proxy (s :> r)
        -> Server r -> [String] -> Maybe (IO String)
  route _ handler (x : xs)
    | symbolVal (Proxy :: Proxy s) == x = route (Proxy :: Proxy r) handler xs
  route _ _       _                     = Nothing

The handler for s :> r is of the same type as the handler for r. We require the request to be non-empty and the first component to match the value-level counterpart of the type-level string. We obtain the value-level string corresponding to the type-level string literal by applying symbolVal. For this, we need a KnownSymbol constraint on the type-level string literal, but all concrete literals in GHC are automatically an instance of KnownSymbol.

The final case is for captures:

instance (Read a, HasServer r) => HasServer (Capture a :> r) where
  route :: Proxy (Capture a :> r)
        -> (a -> Server r) -> [String] -> Maybe (IO String)
  route _ handler (x : xs) = do
    a <- readMaybe x
    route (Proxy :: Proxy r) (handler a) xs
  route _ _       _        = Nothing

In this case, we can assume that our handler is actually a function that expects an a. We require the first component of the request to be parseable as an a. Here, we use the Read class, whereas in Servant, we use a special-purpose class called FromText (or FromHttpApiData in version 0.5). If reading fails, we consider the request not to match. Otherwise, we can feed it to the handler and continue.

Testing everything

Now we’re done.

We can confirm that everything works in GHCi:

GHCi> serve (Proxy :: Proxy MyAPI) handleMyAPI ["time", "CET"]
"2015-11-01 20:25:04.594003 CET"
GHCi> serve (Proxy :: Proxy MyAPI) handleMyAPI ["time", "12"]
*** Exception: user error (404)
GHCi> serve (Proxy :: Proxy MyAPI) handleMyAPI ["date"]
"2015-11-01"
GHCi> serve (Proxy :: Proxy MyAPI) handleMyAPI []
*** Exception: user error (404)

We now have a system that we can play with an extend and modify easily. We can for example extend the specification language by a new construct and see what we have to change. We can also make the simulation more faithful (e.g. include request bodies or query parameters). Or we can define a completely different interpretation (e.g. as a client) by following the same scheme.