Haskell is a marvellous language, but there are some things I don’t like about it. My least favorite: Haskell has no fewer than 8 different APIs for reporting errors.

To make a bad situation worse, the choice of API varies between popular libraries. To give a particularly unfortunate example, Network.URI.parseURI and Network.HTTP.simpleHTTP report errors in entirely different ways, turning a “download this URL” program into a page of code, nearly half of which is devoted to dealing with various kinds of errors. (The rest is boilerplate that could be refactored into a nice wrapper.)

Let’s begin with a toy function, the simplest possible program that could actually fail:

myDiv x y = x / y

As every algebra student knows, we can’t divide by zero. Using this function as our example, let’s take a look at all the different ways we can implement error-reporting in Haskell.

1. Use error

The most popular way to report errors in Haskell is error, which works as follows:

myDiv1 :: Float -> Float -> Float
myDiv1 x 0 = error "Division by zero"
myDiv1 x y = x / y

(This is similar to the error-reporting that’s built into integer division, actually.) We can catch the error using Control.Exception.catch:

import qualified Control.Exception as E

example1 :: Float -> Float -> IO ()
example1 x y =
  E.catch (putStrLn (show (myDiv1 x y)))
          (\err -> putStrLn (show err))

There are two limitations here: Our error is a free-form string, and we can only catch errors from within the IO monad. So this only works for smaller, informal programs.

2. Use Maybe a

What if we don’t have access to the IO monad? Well, we can always use Haskell’s Maybe type to represent a computation that might fail:

myDiv2 :: Float -> Float -> Maybe Float
myDiv2 x 0 = Nothing
myDiv2 x y = Just (x / y)

example2 x y =
  case myDiv2 x y of
    Nothing -> putStrLn "Division by zero"
    Just q  -> putStrLn (show q)

And thanks to the magic of monads, we can actually string together calls to myDiv2 quite nicely:

divSum2 :: Float -> Float -> Float ->
           Maybe Float
divSum2 x y z = do
  xdy <- myDiv2 x y
  xdz <- myDiv2 x z
  return (xdy + xdz)

This approach to error-reporting is used by Network.URI.parseURI, which is included with most Haskell compilers.

3. Use Either String a

But what if we want to have different error messages for different errors? In that case, we can use Either to represent computations which might return either an error message or a value:

myDiv3 :: Float -> Float ->
          Either String Float
myDiv3 x 0 = Left "Divison by zero"
myDiv3 x y = Right (x / y)

example3 x y =
  case myDiv3 x y of
    Left msg -> putStrLn msg
    Right q  -> putStrLn (show q)

Once again, we can treat Either String as a monad, allowing us to combine these computations with a minimum of fuss:

divSum3 :: Float -> Float -> Float ->
           Either String Float
divSum3 x y z = do
  xdy <- myDiv3 x y
  xdz <- myDiv3 x z
  return (xdy + xdz)

This approach is used by many small programs that need to recover from multiple kinds of non-IO errors, but I don’t think it appears in the standard Haskell libraries.

4. Use Monad and fail to generalize 1–3

But what if we don’t care what monad our caller is using? In that case, we can rewrite our code to work in any monad m, and use fail to report the error.

myDiv4 :: (Monad m) => Float -> Float ->
          m Float
myDiv4 x 0 = fail "Divison by zero"
myDiv4 x y = return (x / y)

This will do the right thing if our caller is expecting Maybe or Either:

example4a x y =
  case myDiv4 x y of
    Nothing -> putStrLn "Division by zero"
    Just q  -> putStrLn (show q)

example4b x y =
  case myDiv4 x y of
    Left msg -> putStrLn msg
    Right q  -> putStrLn (show q)

You can even use it with the IO monad!

example4c x y =
  E.catch (do q <- myDiv4 x y
              putStrLn (show q))
          (\err -> putStrLn (show err))

This style of error-reporting is used widely in the standard libraries, because it’s so flexible. You can find several examples in Data.Map.

If you’re writing new Haskell libraries for public consumption, and all your errors are strings, please consider using this error-reporting method.

5. Use MonadError and a custom error type

What if we want to keep track of specific types of errors? In that case, we could use the error Error type class:

import Control.Monad.Error

data CustomError = DivByZero
                 | OutOfCheese
                 | MiscError String

instance Show CustomError where
  show DivByZero = "Division by zero"
  show OutOfCheese = "Out of cheese"
  show (MiscError str) = str

instance Error CustomError where
  noMsg = MiscError "Unknown error"
  strMsg str = MiscError str

This works like the fail example, but instead of using error messages, we use error values:

myDiv5 :: (MonadError CustomError m) =>
          Float -> Float -> m Float
myDiv5 x 0 = throwError DivByZero
myDiv5 x y = return (x / y)

example5 :: Float -> Float ->
            Either CustomError String
example5 x y =
  catchError (do q <- myDiv5 x y
                 return (show q))
             (\err -> return (show err))

Note that this approach will work in almost any monad except the IO monad. This approach will also fail if we start mixing libraries, because each library will define its own set of errors, and we’ll need to write code which converts them all to our preferred error type.

This approach is used by many popular libraries, including parsec. An unusual variant of this approach is used by Network.HTTP, which returns values of type IO (Either ConnError a), but doesn’t make ConnError an instance of Error.

6. Use throwDyn in the IO monad

We can also use our custom error type in the IO monad, thanks to throwDyn and catchDyn from Control.Exception.

import Data.Typeable

data CustomError = DivByZero
                 | OutOfCheese
                 | MiscError String
  deriving (Typeable)

myDiv6 :: Float -> Float -> IO Float
myDiv6 x 0 = E.throwDyn DivByZero
myDiv6 x y = return (x / y)

example6 x y =
  E.catchDyn (do q <- myDiv6 x y
                 putStrLn (show q))
             handler
  where handler :: CustomError -> IO ()
        handler err = putStrLn (show err)

This relies on the fact that Exception is extensible, thanks to its DynException constructor. If you’re working in the IO monad, this approach is almost ideal for production code: You get support for custom exception types, it’s easy to make libraries compatible, and it’s compatible will all the other IO-based examples we’ve seen.

Note that this very flexible approach could generalized to non-IO monads by making Exception an instance of Error, and writing appropriate versions of throwDyn and catchDyn for MonadError. This would actually be very convenient for people who have to work with many libraries at once. But I’ll refrain from actually providing code, because there’s too many error-reporting conventions already!

7. Use ioError and catch

This is a close cousin to the throwDyn example above. It also relies on Exception.

myDiv7 :: Float -> Float -> IO Float
myDiv7 x 0 = ioError (userError "Division by zero")
myDiv7 x y = return (x / y)

example7 :: Float -> Float -> IO ()
example7 x y =
  catch (do q <- myDiv7 x y
            putStrLn (show q))
        (\err -> putStrLn (show err))

This one is pretty rare, as far as I can tell.

8. Go nuts with monad transformers

Several of the error-reporting approaches we’ve seen are based on non-IO monads. Most of these can can be generalized to the equivalent monad transformers. For example, Either CustomError a becomes:

type ErrIO = ErrorT CustomError IO

myDiv8 :: Float -> Float -> ErrIO Float
myDiv8 x 0 = throwError DivByZero
myDiv8 x y = return (x / y)

example8 x y = do
  result <- runErrorT (myDiv8 x y)
  case result of
    Left err -> putStrLn (show err)
    Right q  -> putStrLn (show q)

In the IO monad, this is usually a bad idea (though, again, I’ve seen it). Instead, consider using throwDyn. But if you’re working with a base monad other than IO, this can occasionally be useful.

A plea for consistency

Several of these error-reporting approaches offer interesting insights into Haskell. And most of them have legitimate uses.

But I’d be just as happy if we could standardize on two or three of the above whenever possible!

Update: Don Stewart has started a thread about Haskell error-handling conventions on the Haskell library list.