Awesome FOSS Logo
Discover awesome open source software
Launched 🚀🧑‍🚀

A Servant API Testing Example From the Wild

Categories
Haskell logo

tl;dr - I share some code snippets to test endpoints on a servant-powered API I work on. The servant tutorial (and the code on the servant-client hackage page) is better but this code might be a tad more realistic.

I’m a pretty verbal supporter of Haskell and when I write APIs in Haskell I exclusively use Servant – it’s a fantastic example of how well-crafted types and use of Haskell’s advanced type system can lead to code that is correct, beautiful, and performant (depends what you compare it to, of course). There are lots of ways to write large systems in haskell (monad transformers, mtl, free monads, etc), but regardless of how your system needs to talk to HTTP clients, Servant is a good “adapter” to use to do it (surely you’re using Domain Driven Design in a non-dogmatic way right??).

Of course, if you want to write good code, you’re going to want to test some of that code eventually – the Servant cookbook section is fantastic and has a great section on testing that is worth a read. It got me most of the way to what I ended up with, but I needed to do a little bit more work, and while some of it is specific to my setup/preferences I think some of it should be somewhat usable by others so I’m posting it.

Before I just dump a bunch of code on you, I should note that I use (and thoroughly enjoy) hspec. While I’m not a very dogmatic follower of Test Driven Development (AKA “TDD”) or it’s close cousin Behavior Driven Development (AKA “BDD”), I do appreciate the syntax and focus on testing they brought about. Somewhat counter to that, one of my favorite things about Haskell is that if you trust in and use the type system appropriately, generally “if it compiles, it works”. I also heavily relied on the hackage documentation for hspec which helped me get up and running quickly.

As much praise as testing deserves, I have to admit I write fewer tests (and feel less bad about it) for many of my Haskell projects, though I end up writing tests anyway for most levels, I focus on E2E tests that offer me the most value. You should never have to write a x < 0 type bounds-checking test in Haskell that might be considered a decent test in a dynamic language – that should be impossible at the type level (i.e. use Natural instead of Integer – if you have to write that you’re doing it wrong (there’s also generative testing a la QuickCheck so you’d be doubly wrong).

Before I get into the code, please note that I prefer explicit bind (>>=) over do notation, so the code might look terrible to you. The code also represents quite possibly the simplest, easiest and very-likely dumbest way to do everything since that’s the code future me is going to like debugging the most.

Code: Testing a random endpoint

Here’s a basic test for an unauthenticated endpoint – I’ll include snippets of the route, handler, and resulting test and any relevant utility code.

src/api/V1/Tags.hs

-- | Tag API routes
type Routes = "tags" :> QueryParam "pageSize" Limit :> QueryParam "offset" Offset :> Get '[JSON] (EnvelopedResponse (PaginatedList (ModelWithID Tag)))
    :<|> -- ... combined (via :<|>) more endpoints ...

-- | Tag API server
server :: ( HasDBBackend m db
          , HasCacheBackend m c
          , HasSearchBackend m s
          , MonadError ServerError m
          , TagStore db m
          ) => ServerT Routes m
server = listTags
         :<|> ... combined with more handlers to match endpoints ...

-- | List tags
listTags :: ( HasDBBackend m db
            , HasCacheBackend m c
            , MonadError ServerError m
            , TagStore db m
            ) => Maybe Limit -> Maybe Offset -> m (EnvelopedResponse (PaginatedList (ModelWithID Tag)))
listTags limit offset = getDBBackend
                        >>= \db -> getCacheBackend
                        >>= \cache -> getCachedTagListing db cache
                        >>= ifLeftEnvelopeAndThrow Err.failedToFindEntities
                        >>= pure . EnvelopedResponse "success" "Successfully retrieved tags"
    where
      cacheKey = TagListing limit offset

      lookup = getTagListing cacheKey
      compute db = getAllTags db limit offset
      updateCache = insertTagListing cacheKey

      getCachedTagListing db cache = lookupOrComputeAndSaveEither (lookup cache) (compute db) (updateCache cache)

If you’re not familiar with Servant and are very confused at what’s happening in the code above, I would suggest reading up on Servant – this post will be here when you get back.

Now that we’ve taken a whilwind tour through the code to enable the listTags endpoint (accessible @ GET /tags?[pageSize=?][offset=?]), which returns a EnvelopedResponse (PaginatedList (ModelWithID Tag)) (nice and legible types!) let’s get a look at what writing a test for this looks like:

test/e2e/TagSpec.hs


import           TestUtil (withAppInstance, shouldBeRight, TestAppInstanceInfo)
import           Servant.Client (client, Client, ClientEnv, parseBaseUrl, runClientM, ClientM)

-- | Generated client functions for the Tags API
-- NOTE: we have to specify the type of listTags so the proxy can resolve properly
-- Normally more endpoints would be here (to match more signatures above), but they've been removed, IIRC you need to add all of them, even if you don't provide the signatures for everything
listTags :: Maybe Limit -> Maybe Offset -> ClientM (EnvelopedResponse (PaginatedList (ModelWithID Tag)))
( listTags :<|> ... a name for every handler ... ) = client (Proxy :: Proxy TagsAPI.Routes)

-- End to end tests are for the whole application
spec :: Spec
spec = around (withAppInstance defaultTestConfig) tests
    where
      tests = tagListingTests
              >> -- normally more tests would be here --

-- Tag listing tests

tagListingTests :: SpecWith TestAppInstanceInfo
tagListingTests = describe "Tag listing" simpleTagList

simpleTagList :: SpecWith TestAppInstanceInfo
simpleTagList = it "should work" runTest
    where
      runTest (port, _, _) = buildClientEnv port
                             -- | Get the available tags
                             >>= \env -> runClientM (listTags Nothing Nothing) env
                             >>= shouldBeRight
                             >>= \response -> status response `shouldBe` "success"

runClientM come from servant-client, and that’s where the magic happens (automatic genreation of a client that knows how to hit your API), so that’s a great place to start (there’s a fully worked example ther too). There are a few custom helpers I wrote that might be interesting – withAppInstance, TestAppInstanceInfo and buildClientEnv:

test/util/TestUtil.hs

type TestAppInstanceInfo = (Port, FilePath, ThreadId)

appPortRangeStart :: Int
appPortRangeStart = 5102

appPortRangeEnd :: Int
appPortRangeEnd = appPortRangeStart + 100

getRandomPortInRange :: String -> Int -> Int -> IO Int
getRandomPortInRange _ start end = getStdRandom (randomR (start,end))

getRandomPortForApp :: IO Int
getRandomPortForApp = getRandomPortInRange "App" appPortRangeStart appPortRangeEnd

startAppForTest :: AppConfig -> IO TestAppInstanceInfo
startAppForTest c = getRandomPortForApp
                    -- | Build DB file
                    >>= \port -> emptySystemTempFile testDBFileTemplate
                    -- | Replace the DB paths in the AppConfig
                    >>= \dbPath -> pure (replaceDBPaths c dbPath)
                    -- | Start the app
                    >>= \cfg -> forkIO (startApp (cfg { appPort=port }))
                    -- | Wait for app to start up (1 second)... yuck
                    >>= \tid -> threadDelay 1000000
                    >> return (port, dbPath, tid)


withAppInstance :: AppConfig -> (TestAppInstanceInfo -> IO ()) -> IO ()
withAppInstance = flip bracket cleanup . startAppForTest
    where
      cleanup (port, dbPath, tid)  = killThread tid

test/util/ServantTestUtil.hs

import           Servant.Client (client, mkClientEnv, Client, ClientEnv, parseBaseUrl, runClientM, ClientM)
import qualified Network.HTTP.Client as HTTPClient

-- | Build client env for the app on a given (assumed localhost server) port
buildClientEnv :: Port -> IO ClientEnv
buildClientEnv port = parseBaseUrl ("http://localhost:" <> show port <> "/api/v1")
                      >>= \baseUrl -> HTTPClient.newManager HTTPClient.defaultManagerSettings
                      >>= \manager -> pure (mkClientEnv manager baseUrl)

All these functions come together to make the simpleTagList test work. Going through the motions with the code your head:

  1. The hspec specs are wrapped with withAppInstance which means that they will run while there is an active app instance to access.
  2. (inside withAppInstance) startAppForTest ensures a random port is chosen, configuration is set (the app uses SQLite so only need a single temp file for a whole new DB), and the app is forked & started, returning the port, path to the database and thread ID (i.e. a TestAppInstanceInfo value)
  3. spec’s tests binding is a >>-chained list of tests, all of the type SpecWith TestAppInstanceInfo. This means the tests must be given a TestAppInstanceInfo value (like the one created in step #2).
  4. The individual tagListingTest a simple call of hspec’s describe function (which produces a SpecWith), which runs a test simpleTagList (basically a spec that runs multiple specs)
  5. simpleTagList is also a SpecWith, but is of a different type – it’s a single test and uses hspec’s it
  6. (inside simpleTagList’s runTest) To run the actual test, first we build a client environment using the port we know the API is operating on
  7. (inside simpleTagList’s runTest) After building the client env, we can run the servant-client-provided automatically generated client for listTags (in this case, with no Offset and no Limit aka “pageSize”)
  8. (inside simpleTagList’s runTest) Once we get a response back, we ensure that it’s a Right value constructor with the utility function shouldBeRight
  9. (inside simpleTagList’s runTest) Now that we’ve got a response (or the test failed), we can check that the status of the response is "success", which is something provided by the EnvelopedResponse value.

Code: A fuller example, testing an authenticated endpoint

Code for testing an authenticated endpoint is actually really similar, thanks to how >>= binding, it’s just a few extra lines and forces us to write the functionality in a really composable way:

test/e2e/TagSpec.hs

-- Tag import tests

tagImportTests :: SpecWith TestAppInstanceInfo
tagImportTests = describe "Tag importing" simpleTagImport

simpleTagImport :: SpecWith TestAppInstanceInfo
simpleTagImport = it "should work" runTest
    where
      runTest (port, _, _) = buildClientEnv port
                             -- | Do login and get the cookie for the admin user
                             >>= \clientEnv -> doUserLogin clientEnv adminUserAndPassword
                             >>= \authenticatedReq -> pure ()
                             -- | Get the available tags
                             >> runClientM (listTags Nothing Nothing) clientEnv
                             >>= shouldBeRight
                             >>= \originalListResp -> when (status originalListResp /= "success") (error "Tag listing failed")
                             -- | Import a list of tags that don't exist yet (in the test DB)
                             >> runClientM (importTags authenticatedReq [testTag]) clientEnv
                             >>= shouldBeRight
                             >>= \tagImportResp -> when (status tagImportResp /= "success") (error "Failed to import tags")
                             -- | Retrieve all tags again
                             >> runClientM (listTags Nothing Nothing) clientEnv
                             >>= shouldBeRight
                             >>= \updatedListResp -> when (status updatedListResp /= "success") (error "Post-import tag listing failed")
                             -- | Ensure exactly one tag was added
                             >> let totalAfterUpdate = total $ respData updatedListResp
                                    originalTotal    = total $ respData originalListResp
                                in totalAfterUpdate `shouldBe` (originalTotal + 1)

So the big new thing here is doUserLogin – the code that makes this possible is a bit hairy, but is tucked away in ServantTestUtil – don’t worry, it’s similar to what we’ve seen so far, basically a procedure in that we just want to call it very easily from other places.

test/util/ServantTestUtil

import           Servant.API
import           Servant.Client.Core.Auth (AuthClientData, mkAuthenticatedRequest, AuthenticatedRequest)

-- The Headers type comes from Servant.API
-- (https://hackage.haskell.org/package/servant-0.16.2/docs/Servant-API.html#t:Headers)

-- | Used for authenticating with servant-client
type instance AuthClientData (AuthProtect "cookie-auth") = String

-- | Generated client functions for the Auth API
login :: UserEmailAndPassword -> ClientM (Headers '[Header "Set-Cookie" DT.Text] (EnvelopedResponse SessionInfo))
( login :<|> ... other handlers for the endpoints ... ) = client (Proxy :: Proxy AuthAPI.Routes)


-- | Used with mkAuthenticateRequest to make an authenticated cookie auth request
cookieAuthRequest :: String -> Request -> Request
cookieAuthRequest c = Servant.Client.Core.Request.addHeader hCookie (B8.unpack authCookieName <> "=" <> c)

-- | Do login and get the cookie for a given user, collecting the cookie to use for authenticated requests in the future
doUserLogin :: ClientEnv -> UserEmailAndPassword -> IO (AuthenticatedRequest (AuthProtect "cookie-auth"))
doUserLogin clientEnv emailAndPass = runClientM (login adminUserAndPassword) clientEnv
                                     >>= shouldBeRight
                                     >>= \loginResp -> pure (lookupResponseHeader loginResp :: ResponseHeader "Set-Cookie" DT.Text)
                                     >>= \case
                                         Header h -> pure $ B8.unpack $ setCookieValue $ parseSetCookie $ encodeUtf8 h
                                         _        -> error "login failed"
                                     -- | Repackage the auth cookie into a usable authenticated request
                                     >>= \authCookie -> pure (mkAuthenticatedRequest authCookie cookieAuthRequest)

I happen to be using a custom Authentication combinator called CookieAuth that I wrote way back before servant had good add-on libraries for authentication. Rather than post that code here, I’d advise everyone to adapt this code (if you’re basing yours on it) to be used by servant-auth-cookie. Also check out the servant tutorial section on Authentication – if you’re really stuck, send me an email and I’ll update the blog post to share my implementation (which you probably shouldn’t use).

As you might expect, this code does an actual log in (via runClientM) and then looks in the headres to pull ou tthe authenticated cookie. I won’t go into a full breakdown but hopefully the code is hopefully clear enough!

Gotchas

Here are a few gotchas I noted back when I wrote the outline for this post:

  • You’re possibly going to need ToJSON isntances if you didn’t have them before (aeson is one of the most useful libraries in the entire ecosystem, the maintainers and author are saints).
  • You may want to delete the temp files (I’m not doing that here), though your system should take care of it after a while (that’s what /tmp is for)

Another thing I found somewhat perplexing was how difficult it was to set up my <project>.cabal file to match the testing strucure I wanted. here’s what the tree looks like:

$ tree test
test
├── e2e
│   ├── JobsSpec.hs
│   ├── ... other spec files ...
│   └── Spec.hs.hs
├── integration
│   ├── DatabaseBackendSpec.hs
│   ├── ... other spec files ...
│   └── Spec.hs
├── Spec.hs
├── unit
│   ├── SQLiteTypesSpec.hs
│   └── Spec.hs
└── util
    ├── assets
    │   ├── logo-flipped-vert.jpeg.b64
    │   └── logo.jpeg.b64
    ├── ServantTestUtil.hs
    ├── TestFixtures.hs
    └── TestUtil.hs

The Spec.hs files are all empty except for the the magic incantation for hspec-discover:

{-# OPTIONS_GHC -F -pgmF hspec-discover #-}

To get this to work properly my test section looks like this:

test-suite unit
  type:                exitcode-stdio-1.0
  hs-source-dirs:      test/unit
                     , test/util
  other-modules:       SQLiteTypesSpec
  main-is:             Spec.hs
  build-depends:       base
                     , <project lib>
                     , hspec
                     , sqlite-simple
  ghc-options:         -threaded -rtsopts -with-rtsopts=-N -with-rtsopts=-A128m -with-rtsopts=-xc
  default-language:    Haskell2010

As you might imagine, integration tests are similar

test-suite int
  type:                exitcode-stdio-1.0
  hs-source-dirs:      test/integration
                     , test/util
  main-is:             Spec.hs
  other-modules:       CacheBackendSpec
                     , ... lots more specs ..
                     , TestFixtures
                     , TestUtil
  build-depends:       base
                     , <project lib>
                     , ... lots of dependencies ...
  ghc-options:         -threaded -rtsopts -with-rtsopts=-N -with-rtsopts=-A128m -with-rtsopts=-xc
  default-language:    Haskell2010

I’ll leave what the E2E tests looks like as an exercise for the reader.

Wrapup

Hopefully this code was a bit instructive and somewhat of a worked example of what testing could look like for a servant-based haskell project, thanks for reading.