Most servant examples online are for older versions of servant and incompatible with the modern Haskell ecosystem. This post is built against stackage LTS 11.15, and servant 0.13. Certain aspects have been simplified, and certain things made incompatible.

servant

In this version we are going to use the Reader IO pattern in a custom monad, and provide basic database integration that supports the new UnliftIO changes.

Requirements

Start with dependencies

servant, servant-server, exceptions, persistent, mtl, wai, warp, monad-logger, persistent-postgresql, unliftio-core

Language extensions

{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE TypeOperators              #-}
{-# LANGUAGE OverloadedStrings          #-}
{-# LANGUAGE FlexibleContexts           #-}

If you are using stack you may want to build against LTS 11.15, but future versions will probably work.

Environment

Import servant, persistent, and miscellaneous required dependencies.

import Servant
import Database.Persist.Sql (ConnectionPool, runSqlPool)
import Control.Exception (try)
import Control.Monad.Catch (MonadThrow, throwM)
import Control.Monad.Except (ExceptT(..))
import Control.Monad.IO.Class (MonadIO)
import Control.Monad.Reader (MonadReader, ReaderT(..), runReaderT, ask)
import Network.Wai.Handler.Warp (run)
import Control.Monad.Logger (runStdoutLoggingT)
import Database.Persist.Postgresql (createPostgresqlPool)
import Control.Monad.IO.Unlift (MonadUnliftIO)

Custom Monad

If you are building a real application with Servant you are probably going to want to use a custom reader monad so you don’t have to manually thread a context through to every API endpoint.

Here we define our reader environment type. Right now it only contains a database pool. AppMonad is just a wrapper around a reader with our environment.

data Env = Env
  { pool :: ConnectionPool
  }

newtype AppMonad a = AppMonad { unAppMonad :: ReaderT Env IO a } deriving
  (Functor, Applicative, Monad, MonadThrow, MonadIO, MonadUnliftIO, MonadReader Env)

Note that this time around we have added MonadUnliftIO to our list of derived instances. A decent portion of the Haskell ecosystem has migrated to using this class and it’s going to be a requirement for our database access.

Utilities

This is just a simple database utility to fetch our pool from the reader environment and then run a query with it.

runDB query = do
  env <- ask
  runSqlPool query $ pool env

API

The actual API implementation should look about the same as with previous versions. Here are 3 standard endpoints in our custom monad.

type API =
       "a" :> Get '[JSON] String
  :<|> "b" :> Get '[JSON] Int
  :<|> "c" :> Get '[JSON] String

server :: ServerT API AppMonad
server = endpoint1 :<|> endpoint2 :<|> endpoint3

-- vanilla example
endpoint1 :: AppMonad String
endpoint1 = return "hello world!"

-- error example
endpoint2 :: AppMonad Int
endpoint2 = do
  throwM err400
  return 3

-- db example
endpoint3:: AppMonad String
endpoint3 = do
  runDB $ return ()
  return "my db"

The DB example here does not actually do anything with the connection. Notice that I have used throwM, instead of throwError. We we have defined our custom Monad over IO instead of servant’s standard ExceptT IO. In this instance throwM will be throwing an IO exception.

The current UnliftIO system does not nicely integrate with ExceptT. Many articles have been written at this point speaking out against ExceptT over IO. ExceptT being the core of servant makes this situation somewhat problematic. To deal with this we just made the core of our monad IO instead of ExceptT IO, and deal with the conversion in the hoist phase.

The persistent database library (and by extension Esqueleto) is an example of something made incompatible with the core servant ExceptT IO pattern.

Hoisting

This part of using a custom monad has become easier with recent versions. Now servant has the hoistServer function. Our hoistAppServer function converts our API to a form usable by servant.

proxyAPI :: Proxy API
proxyAPI = Proxy

hoistAppServer :: Env -> Server API
hoistAppServer config = hoistServer proxyAPI (nt config) server where
  nt :: Env -> AppMonad a -> Handler a
  nt env m = Handler $ ExceptT $ try $ runReaderT (unAppMonad m) env

We pass in our environment, run the reader, catch IO exceptions, then integrate them with servants error system.

Wrap Up

All that’s left to do is prepare our database connection and launch the webserver.

main :: IO ()
main = do
  newpool <- runStdoutLoggingT $ createPostgresqlPool "my conn" 2
  run 3001 $ serve proxyAPI $ hoistAppServer $ Env newpool

You will have to provide the specifics of your db connection string.