Testable IO in Haskell

By Andy Friesen

At IMVU, we write a lot of tests. Ideally, we write tests for every feature and bugfix we write. The problem we run into is one of scale: if each of IMVU’s tests were 99.9% reliable, 1 out of every 5 runs would result in an intermittent failure.

Tests erroneously fail for lots of reasons: the test could be running in the midst of the “extra” daylight-savings hour or a leap day (or a leap second!). The database could have been left corrupted by another test. CPU scheduling could prioritize one process over another. Maybe the random number generator just so happened to produce two zeroes in a row.

All of these things boil down to the same root cause: nondeterminism within the test.

We’ve done a lot of work at IMVU to isolate and control nondeterminism in our test frameworks. One of my favourite techniques is the way we make our Haskell tests provably perfectly deterministic.

Here’s how it works.

This post is Literate Haskell, which basically means you can point GHC at it directly and run it. You can download it here.

We’ll start with some boilerplate.

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NamedFieldPuns #-}

module Main where

import Control.Monad.State.Lazy as S

What we’re looking to achieve here is a syntax-lightweight way of writing side effectful logic in a way that permits easy unit testing.

In particular, a property we’d very much like to have is the ability to deny our actions access to IO when they are running in a unit test.

For this example, we’ll posit that the very important business action we wish to test is to prompt the user for their name, then say hello:

importantBusinessAction = do
    writeLine "Please enter your name: "
    name <- readLine
    if "" == name
      then do
        writeLine "I really really need a name!"
        importantBusinessAction
      else
        writeLine $ "Hello, " ++ name ++ "!"

We’ll achieve this by defining a class of monad in which testable side effects can occur. We’ll name this class World.

class Monad m => World m where
    writeLine :: String -> m ()
    readLine :: m String

We can now write the type of our importantBusinessAction:

importantBusinessAction :: World m => m ()

The name of this type can be read as “an action producing unit for some monad m in World.”

When our application is running in production, we don’t require anything except IO to run, so it’s perfectly sensible for IO to be a context in which World actions can be run. The Haskell Prelude already offers the exact functions we need, so this instance is completely trivial:

instance World IO where
    writeLine = putStrLn
    readLine = getLine

In unit tests, we specifically want to deny access to any kind of nondeterminism, so we’ll use the State monad. State provides the illusion of a mutable piece of data through a pure computation. We’ll pack the state of our application up in a record.

type FakeIO = S.State FakeState

(I’ll get to FakeState in a second)

Aside from reliability, this design has another very useful property: It is impossible for tests to interfere with one another even if many tests share the same state. This means that “test fixtures” can trivially be effected by simply running an action and using the resulting state in as many tests as desired.

The state record FakeState itself essentially captures the full state of the fake application at any one moment.

The writeLine implementation is very easy: We just need to accumulate a list of lines that were printed. We can carry that directly in our state record.

The readLine action is a bit more complicated. We’re going to write all kinds of tests for our application, and we really don’t want to burn any one particular behaviour into the framework. We want to parameterize this on a per-test basis.

We’ll solve this by embedding an action directly into our state record.

data FakeState = FS
    { fsWrittenLines :: [String]
    , fsReadLine     :: FakeIO String
    }

def :: FakeState
def = FS
    { fsWrittenLines = []
    , fsReadLine = return ""
    }

Now, given this record, we can declare that FakeIO is also a valid World Monad, and provide implementations for our platform when run under unit test.

instance World (S.State FakeState) where
    writeLine s = do
        st <- S.get
        let oldLines = fsWrittenLines st
        S.put st { fsWrittenLines = s:oldLines }

    readLine = do
        st <- S.get
        let readLineAction = fsReadLine st
        readLineAction

We also write a small helper function to make unit tests read a bit more naturally:

runFakeWorld :: b -> State b a -> (a, b)
runFakeWorld = flip S.runState

Now, let’s write our first unit test.

We wish to test that our application rejects the empty string as a name. When the user does this, we wish to verify that the customer sees an error message and is asked again for their name.

First, we’ll craft a readLine implementation that produces the empty string once, then the string “Joe.”

Making this function more natural without compromising extensibility is left as an exercise to the reader. 🙂

Note that by providing the type FakeIO String, we have effectively authored an action that can only be used in a unit test. The build will fail if production code tries to use this action.

main :: IO ()
main = do
    let readLine_for_test :: FakeIO String
        readLine_for_test = do
            S.modify $
                \s ->
                    s {fsReadLine=return "Joe"})
            return ""

Now that we have that, we can create a FakeState that represents the scenario we wish to test.

    let initState = def
            { fsReadLine = readLine_for_test }

And go!

    let ((), endState) =
            runFakeWorld
                initState importantBusinessAction

Note that runFakeWorld produces a pair of the result of the action and the final state. We can inspect this record freely:

    forM_ (reverse $ fsWrittenLines endState) $
        \line ->
            print line

That’s it!

In a real application, your FakeState analogue will be much more complex, potentially including things like a clock, a pseudo-random number generator, and potentially state for a pure database of some sort. Some of these things are themselves complex to build out, but, as long as those implementations are pure, everything snaps together neatly.

If complete isolation from IO is impractical, this technique could also be adjusted to run atop a StateT rather than pure State. This allows for imperfect side-effect isolation where necessary.

Happy testing!

Source Code.

What it’s like to use Haskell

By Andy Friesen

Since early 2013, we at IMVU have used Haskell to build several of the REST APIs that power our service.

When the company started, we chose PHP as our application server language, in part, because the founders expected the website to only be a small part of the business!  IMVU was primarily about a downloadable 3D client.  We needed “a website or something” to give users a place to download our client from, but didn’t expect it would have to be much more than that. This shows that predicting the future is hard.
Years later, we have quite a lot of customers, and we primarily use PHP to serve them.  We’re big enough that we run multiple subteams on separate initiatives at the same time.  Performance is becoming important to us not just because it matters to our customers, but because it can easily make the difference between buying 4 servers and buying 40 servers to support some new feature.

So, early in 2012, we found ourselves ready to look for an alternative that would help us be more rigorous.  In particular, we were ready for the idea that sacrificing a tiny bit of short term, straight-line time to market might actually speed us up in the long run.

How We Got Here

I started learning Haskell in my spare time in part because Haskell seems like the exact opposite of PHP: Natively compiled, statically typed, and very principled.

My initial exploration left me interested in evaluating Haskell at real scale.  A year later, we did a live-fire test in which we taught multiple teammates Haskell while delivering an important new feature under a deadline.

Today, a lot of our backend code is still driven by PHP, but we have a growing amount of Haskell that powers newer features. The process has been exciting not only because we got to actually answer a lot of the questions that keep many people from choosing not to try Haskell, but also because it’s simply a better solution.

The experiment to start developing in Haskell took a lot of internal courage and dedication, and we had to overcome a number of, quite rational, concerns related to adopting a whole new language. Here are the main ones and how they worked out for us:

Scalability

The first thing we did was to replace a single service with a Haskell implementation.  We picked a service that was high-volume but was not mission critical.

We didn’t do any particular optimization of this new service, but it nevertheless showed excellent performance characteristics in the field.  Our little Haskell server was running on a pair of spare servers that were otherwise set for retirement, and despite this, each machine was handling about 20x as many requests as one of our high-spec PHP servers could manage.

Reliability

The second thing we did was to take our hands off the Haskell service and leave it running until it fell over.  It ran for months without intervention.

Training

After the reliability test, we were ready to try a live fire exercise, but we had to wait a bit for the right project.  We got our chance in early 2013.

The rules of the experiment were simple: Train 3 engineers to write the backend for an important new project and keep up with a separate frontend team.  Most of the code was to be new, so there was relatively little room for legacy complications.

We very quickly learned that we had also signed up for a lot of catch-up work to bring the Haskell infrastructure inline with what we’ve had for years in PHP.  We were very busy for awhile, but once we got this infrastructure out of the way, the tables turned and the front-end team became the limiting factor.

Today, training an engineer to be productive in our Haskell code is not much harder than training someone to be productive in our PHP environment.  People who have prior functional programming knowledge seem to find their stride in just a few days.

Testing

Correctness is becoming very important for us because we sometimes have to change code that predates every current developer.  We have enough users that mistakes become very costly, very quickly.  Solving these sorts of issues in PHP is sometimes achievable but always difficult.  We usually solve them with unit tests and production alerts, but these approaches aren’t sufficient for all cases.

Unit tests are incredible and great, but you’re always at the mercy of the level of discipline of every engineer at every moment. It’s easy to tell your teammates to write tests for everything, but this basically boils down to asking everyone to be at their very best every day.  People make mistakes and things slip through the cracks.

When using Haskell, we actually remove an entire class of defects that we have to write tests for. Thus, the number of tests we have to write is smaller, and thus there are fewer cases we can forget to write tests for.

We like unit testing and test-driven development (TDD) at IMVU and we’ve found that Haskell is better with TDD, but also that TDD is better with Haskell.  It takes fewer tests to get the same degree of reliability out of Haskell.  The static verification takes care of quite a lot of error checking that has to be manually implemented (or forgotten) in PHP.  The Haskell QuickCheck tool is also a wonderful help for developers.
The way Haskell separates pure computations from side effects let us build something that isn’t practical with other languages: We built a custom monad that lets us “switch off” side effects in our tests.  This is incredible because it means that trying to escape the testing sandbox breaks compilation. While we have had to fight intermittent test failures for eight years in PHP (and at times have had multiple engineers simultaneously dedicated to the problem of test intermittency,) our unit tests in Haskell cannot intermittently fail.

Deployment

Deployment is great. At IMVU, we do continuous deployment, and Haskell is no exception. We build our application as a statically linked executable, and rsync it out to our servers. We can also keep old versions around, so we can switch back, should a deployment result in unexpected errors.

I wouldn’t write an OS kernel in it, but Haskell is way better than PHP as a systems language. We needed a Memcached client for our Haskell code, and rather than try to talk to a C implementation, we just wrote one in Haskell.  It took about a half day to write and performs really well. And, as a side effect, if we ever read back some data we don’t expect from memcached (say, because of an unexpected version change) then Haskell will automatically detect and reject this data.

We’ve consistently found that we unmake whole classes of bugs by defining new data types for concepts to wrap primitive types like integers and strings.  For instance, we have two lines of code that say that “customer IDs” and “product IDs” are represented to the hardware as numbers, but they are not mutually convertible.  Setting up these new types doesn’t take very much work and it makes the type checker a LOT more helpful. PHP, and other popular dynamic server languages like Javascript or Ruby, make doing the same very hard.

Refactoring is a breeze.  We just write the change we want and follow the compile errors.  If it builds, it almost certainly also passes tests.

Not All Sunshine and Rainbows

Resource leaks in Haskell are nasty.  We once had a bug where an unevaluated dictionary was the source of a space leak that would eventually take our servers down.  We also ran into an issue where an upstream library opened /dev/urandom for randomness, but never closed the file handle.  These issues don’t happen in PHP, with its process-per-request model, and they were more difficult to track down and resolve than they would have been in C++.

The Haskell package manager, Cabal, ended up getting in the way of our development. It lets you specify version ranges of particular packages you want, but it’s important for everyone on the team to have exactly the same versions of every package.  That means controlling transitive dependencies, and Cabal doesn’t really offer a way to handle this precisely. For a language that is so very principled on type algebra, it’s surprising that the package manager doesn’t follow suit regarding package versioning. Instead, we use Cabal for basic package installation, and a custom build tool (written in Haskell.)

Hiring

I’ll admit that I was very worried that we wouldn’t be able to hire great people if our criteria was expertise in an uncommon language without a comparatively sparse industrial track record, but the honest truth is that we found a great Haskell hacker in the Bay area after about 4 days of looking.

We had a chance to hire him because we were using Haskell, not in spite of it.

Final Thoughts

While it’s usually difficult to objectively measure things like choice of programming language or softwarestack, we’re now seeing fantastic, obvious productivity and efficiency gains.  Even a year later, all the Haskell code we have runs on just a tiny number of servers and, when we have to make changes to the code, we can do so quickly and confidently.