Yet Another Monad Tutorial (part 6: more on error-handling monads)

Aug 16, 2010 19:52


In the previous article we discussed error-handling strategies in Haskell and derived the Either e monad for structured error handling. In this article we'll continue our discussion of error handling by introducing some new type classes that will enable us to write code which recovers from errors in a selective way (which is called exception handling in most computer languages). Interestingly, exception handling doesn't have to be built-in in Haskell; you get it for free once you have monads!

I also promise (threaten?) that there will be one absolutely jaw-droppingly awful pun in what follows. You have been warned.


The MonadError type class

In the Control.Monad.Error module, there is a type class called MonadError with the following definition:

class Monad m => MonadError e m | m -> e where throwError :: e -> m a catchError :: m a -> (e -> m a) -> m a
There is a lot to discuss here. First off, notice that (unlike the type classes we've seen so far, which all had one type parameter) the MonadError type class is a two-parameter type class. (Don't confuse this with a two-parameter type constructor like Either - they're completely different things.) The parameters are e, the error type, and m, a (unary) type constructor representing a monad. The Monad m => part is a context; it says that the type constructor m must be an instance of the Monad type class, as we want. The | m -> e part is a functional dependency, which I'll get back to below.

The purpose of the MonadError type class is to allow us to define what exception handling means for a particular kind of error (say, ArithmeticError) and a particular kind of error-handling monad (say, the Either ArithmeticError monad). The exception-handling functions are the usual "throw"- and "catch"-type functions, here called throwError and catchError.

Side note: In most languages, "throw" and "catch" are built-in features, but in Haskell they are just methods of a type class. This is a good thing because it gives you the ability to define exactly what they mean for any given monad. Put differently, you can have an arbitrary number of different "throw" and "catch" functions, and defining "throw" and "catch" with special behaviors for a particular monad requires nothing more than defining a new instance of MonadError.

It will be easier to understand these functions in terms of a specific example, so let's see what this looks like in the context of the Either ArithmeticError monad used in the previous article. (Note that the Either ArithmeticError monad is just a more specific version of the Either e monad; the same Monad instance definition is used for both.) We'll also assume that the type a is always Int. We will assume that we have defined an instance of the MonadError type class for the Either ArithmeticError monad.

instance MonadError ArithmeticError (Either ArithmeticError) where -- throwError :: ArithmeticError -> Either ArithmeticError Int throwError err = {- to be defined -} -- catchError :: Either ArithmeticError Int -> -- (ArithmeticError -> Either ArithmeticError Int) -- -> Either ArithmeticError Int catchError mval handler = {- to be defined -}
What throwError does is to "lift" an error (here, of type ArithmeticError) into an error-handling monadic value (here, of type Either ArithmeticError Int) that represents the error. So if a computation in the Either ArithmeticError monad is happening and the throwError function is called, that causes the entire computation to fail with the specified error value. This is pretty much the same thing that "throw" does in most computer languages that have exception handling built in.

For instance, using throwError, our safe_divide function from last time can be rewritten as:

safe_divide :: Int -> Int -> Either ArithmeticError Int safe_divide _ 0 = throwError DivideByZero -- use throwError instead of Left safe_divide i j | i `mod` j /= 0 = throwError NotDivisible safe_divide i j = Right (i `div` j)
For this to mean the same thing as the previous version, throwError must be the same as Left, which gives us part of our instance definition:

instance MonadError ArithmeticError (Either ArithmeticError) where throwError err = Left err catchError mval handler = {- to be defined -}
We can write this even more simply by leaving off the err argument in throwError:

instance MonadError ArithmeticError (Either ArithmeticError) where throwError = Left catchError mval handler = {- to be defined -}
We can improve safe_divide still further by noting that return in our monad is just Right. This leads to this definition:

safe_divide :: Int -> Int -> Either ArithmeticError Int safe_divide _ 0 = throwError DivideByZero safe_divide i j | i `mod` j /= 0 = throwError NotDivisible safe_divide i j = return (i `div` j)
Why is this an improvement? Our function now doesn't contain any Left or Right constructors; we've completely abstracted away from the concrete details of our error-handling type (other than in the type signature). Now our function says, in effect, that in the first two cases we "throw" an exception, while in the third (non-exceptional) case we just "return" the correct value. We could conceivably change our error-handling strategy completely (using a different monad) and the only thing we'd have to change in this function is the type signature. And we could even abstract that away:

safe_divide :: MonadError ArithmeticError m => Int -> Int -> m Int safe_divide _ 0 = throwError DivideByZero safe_divide i j | i `mod` j /= 0 = throwError NotDivisible safe_divide i j = return (i `div` j)
Now, even if we change the error-handling monad we don't have to change this code, assuming that the correct instance for MonadError ArithmeticError m has been defined for the monad m. This is pretty darned generic code - the kind Haskell programmers love to write. (Despite this, we'll stick to the version with m as Either ArithmeticError for the rest of the examples to keep things simple.)

You might wonder why this version of safe_divide isn't written as:

safe_divide :: (Monad m, MonadError ArithmeticError m) => Int -> Int -> m Int safe_divide _ 0 = throwError DivideByZero safe_divide i j | i `mod` j /= 0 = throwError NotDivisible safe_divide i j = return (i `div` j)
Although this would be a perfectly valid definition, it isn't necessary. For MonadError ArithmeticError m to be a valid instance, m must be an instance of Monad, so there is no need to repeat the constraint.

If we can "throw" errors, it makes sense that we should be able to "catch" them somehow, and that's what catchError is for. Specifically, what catchError does is take a monadic value mval of type m a (for some error-handling monad m and any type a) and "handle" the errors (monadic values which represent errors) using the handler function, which has the type e -> m a where e and m are (together) an instance of the MonadError type class.

Let's look at what catchError does step by step using the types in our specific example (ArithmeticError, Either ArithmeticError Int), instead of the most general types (e, m a). The first argument to our catchError function will be a monadic value of type Either ArithmeticError Int. This will generally be the result of some error-handling computation, and can either be

  1. Left err with err being an error value of type ArithmeticError (if an error occurred), or

  2. Right val with val being a non-error value of type Int (if no error occurred).

If no error occurs, the handler function isn't called, and the first argument is also the result of catchError. If an error does occur, then the error value of type ArithmeticError is unpacked from the Left err value and passed as the argument to handler. The handler function has the specific type ArithmeticError -> Either ArithmeticError Int, and when passed the error value of type ArithmeticError it will compute the return value of catchError, which (as in the non-error case) will have the type Either ArithmeticError Int. This means that, depending on what the handler function does with particular errors, errors that occur in a computation can either be passed through or replaced with values of type Int. Typically the handler function will handle some errors and let others pass through.

Surprisingly, the last paragraph gives us the definition of catchError we'll need for our Either ArithmeticError monad:

-- catchError :: Either ArithmeticError Int -> -- (ArithmeticError -> Either ArithmeticError Int) -- -> Either ArithmeticError Int catchError (Right val) _ = Right val -- pass through catchError (Left err) h = h err -- handle error
That's pretty simple. Who says exception handling has to be complicated? ;-)

Of course, what's really happening is that all the hard stuff is being done by the handler function h. As we've defined it above, an ArithmeticError can either be DivideByZero or NotDivisible. Let's say we wanted to catch NotDivisible errors and divide them (throwing away the remainder, like in the divide function from last time), but pass through DivideByZero errors (since there really isn't any reasonable value we can give in that case). Our first try looks like this:

arithmeticErrorHandler :: ArithmeticError -> Either ArithmeticError Int arithmeticErrorHandler DivideByZero = Left DivideByZero arithmeticErrorHandler NotDivisible = Right ???
Before we finish this, let's improve it by replacing the Left/Right constructors with throwError and return (we saw this trick previously with safe_divide):

arithmeticErrorHandler :: ArithmeticError -> Either ArithmeticError Int arithmeticErrorHandler DivideByZero = throwError DivideByZero arithmeticErrorHandler NotDivisible = return ???
In words, we are re-throwing DivideByZero errors because we can't handle them, but since we can handle NotDivisible errors we are (hopefully) "returning" a useful value in that case.

At this point, we realize that if we want to do anything useful with the NotDivisible error, we need to pass more information in the error value. So we have to change our original definition of ArithmeticError from:

data ArithmeticError = DivideByZero | NotDivisible deriving Show
to:

data ArithmeticError = DivideByZero | NotDivisible Int Int -- save the indivisible values deriving Show
Furthermore, we change the definition of safe_divide yet again to:

safe_divide :: Int -> Int -> Either ArithmeticError Int safe_divide _ 0 = throwError DivideByZero safe_divide i j | i `mod` j /= 0 = throwError (NotDivisible i j) safe_divide i j = return (i `div` j)
Now, when we throw a NotDivisible error, we pass along the values that we couldn't divide evenly. With this done, we can write our arithmeticErrorHandler function as:

arithmeticErrorHandler :: ArithmeticError -> Either ArithmeticError Int arithmeticErrorHandler DivideByZero = throwError DivideByZero arithmeticErrorHandler (NotDivisible i j) = return (i `div` j)
And now we can rewrite the divide function as:

divide :: Int -> Int -> Either ArithmeticError Int divide i j = catchError (i `safe_divide` j) arithmeticErrorHandler
Notice that the first argument to catchError is i `safe_divide` j, which has the type Either ArithmeticError Int (i.e. it is a monadic value in the Either ArithmeticError monad). The second argument is the error handler, which must have the type ArithmeticError -> Either ArithmeticError Int, and does.

This looks nicer if we write catchError as an operator:

divide :: Int -> Int -> Either ArithmeticError Int divide i j = (i `safe_divide` j) `catchError` arithmeticErrorHandler
Now we have a clean separation between the error-handling code (in arithmeticErrorHandler) and the non-error-handling code (i `safe_divide` j). We can improve this in two more ways. First, since it's likely that the error handling in this function will be specific to this function only, we can make the arithmeticErrorHandler function local to divide:

divide :: Int -> Int -> Either ArithmeticError Int divide i j = (i `safe_divide` j) `catchError` handler where handler :: ArithmeticError -> Either ArithmeticError Int handler DivideByZero = throwError DivideByZero handler (NotDivisible i j) = return (i `div` j)
Second, we can get rid of the name handler altogether and just use an anonymous function (lambda expression) together with a case statement:

divide :: Int -> Int -> Either ArithmeticError Int divide i j = (i `safe_divide` j) `catchError` \e -> case e of DivideByZero -> throwError DivideByZero NotDivisible i j -> return (i `div` j)
At this point I want to contrast this with the way exception-handling code would be written in a more conventional language like Java. It would look something like this (I think; it's been a while since I programmed in Java):

public static int divide(int i, int j) throws DivideByZeroException, NotDivisibleException { try { return safe_divide(i, j); } catch (DivideByZeroException e) { throw (DivideByZeroException e); } catch (NotDivisibleException e) { return (i / j); } }
(You could of course get rid of the explicit re-throwing by removing the first catch block.) The interesting this about this is that the Java version and the Haskell version are essentially the same except for (a) the obvious differences in syntax, and (b) the different type declarations. Syntactically, in the Haskell version multiple catch blocks are replaced by a single handler function which pattern-matches on the error to give multiple cases, so there is no essential difference (there is one Haskell case per one Java catch block). The try block is not needed at all; if the computation that corresponds to what would be inside the try block in Java is of an error-handling monadic type in Haskell, that's all that's needed.

NOTE: This is a very simple example. Most of the time, the main computation would consist of more than just one expression. Typically you'd have a bunch of expressions in a do statement, something like this:

foo :: Int -> Int -> Either ArithmeticError Int foo i j = do k <- i `safe_divide` j l <- return (i + j) return (k + 2 * l) `catchError` \e -> case e of DivideByZero -> throwError DivideByZero NotDivisible i j -> return (i `div` j)
Of course, if you wanted to, you could use the >>= operator explicitly instead of using the do notation:

foo :: Int -> Int -> Either ArithmeticError Int foo i j = (i `safe_divide` j >>= \k -> return (i + j) >>= \l -> return (k + 2 * l)) `catchError` \e -> case e of DivideByZero -> throwError DivideByZero NotDivisible i j -> return (i `div` j)
In each case the monadic code (inside the do expression, or not) takes the place of what would be inside a try block in Java. Or, as Yoda would put it: "do or do not, there is no try" :-)

By the way, this example is somewhat contrived (in order to get to the pun!). The NotDivisible i j case just causes the entire computation to return i `div` j, wrapped up in a Right constructor, which is not really the answer we want. It would be better if we could restart the computation at the point where it failed. One way to do this is to have a catchError statement immediately surrounding the i `safe_divide` j code (before the result gets bound to k). I'll leave this as an exercise for the reader. That would still be a bit ugly, though. What would really be nice is if, from the catchError clause in the code example (which sits outside of the do block), you could catch the NotDivisible error and restart the computation inside the do block at the point at which it failed, with the value of i `div` j bound to k. This turns out to be beyond the capabilities of simple error-handling monads, but there is a very cool monad called the continuation monad which can accomplish this kind of magic, and which I hope to get to eventually.

To end this section, let's recall the MonadError type class definition:

class Monad m => MonadError e m | m -> e where throwError :: e -> m a catchError :: m a -> (e -> m a) -> m a
I promised I'd explain the mysterious | m -> e part of the first line, and so I will. This is a functional dependency; it states that the error type e in some way "depends" upon the monad m. Recall that in our example, m is Either ArithmeticError and e is ArithmeticError. It should be plausible that this example wouldn't work if m was Either ArithmeticError and e was (say) String, because the methods of this class would then be expecting error values of type String which would be different from the error values of type ArithmeticError used in the monad. In general, for any instance of MonadError e m where m is Either e, the error type e in the Either e monad should be the same e as the e in MonadError e m. So we can have instances like

-- error type: ArithmeticError instance MonadError ArithmeticError (Either ArithmeticError) where ... -- error type: String instance MonadError String (Either String) where ... -- error type: Foobar (for some hypothetical type Foobar) instance MonadError Foobar (Either Foobar) where ...
but not e.g.

instance MonadError ArithmeticError (Either String) where ... instance MonadError String (Either Foobar) where ... instance MonadError Foobar (Either ArithmeticError) where ...
This kind of invariant is hard to enforce, because MonadError can be used with monads that are not of the form Either e. What we can enforce is that the monad m determines the error type e, and that's what the functional dependency m -> e does. The way this works is that the first time Haskell sees an instance declaration of the form

instance MonadError ArithmeticError (Either ArithmeticError) where ...
it says "OK, from now on, the only error type that I will allow with the monad Either ArithmeticError is ArithmeticError. If later you try to add another instance declaration using the Either ArithmeticError monad, for instance:

instance MonadError Foobar (Either ArithmeticError) where ...
the compiler will reject it, because it already has an error type for the Either ArithmeticError monad. This is called a "functional dependency" because the error type is a function of the monad type (one monad type yields one and only one error type). Note, however, that there is nothing to require you to define sensible instances; you could, for instance, start off by defining

instance MonadError Foobar (Either ArithmeticError) where ...
and then you wouldn't be allowed to later define the more sensible instance:

instance MonadError ArithmeticError (Either ArithmeticError) where ...
It's up to you to make sure that your first instance is the correct one. (This is reminiscent of the way Haskell doesn't enforce the monad laws but requires you to make sure that your monad definitions don't violate them; if not, your code won't work the way you want it to.)

Functional dependencies are considered to be a moderately advanced aspect of Haskell's type system, but there's not really much to them. All they do is prevent you from defining useless instances of type classes.
The Error type class

Recall the monad definition for (Either e) we derived previously:

instance Monad (Either e) where return x = Right x (Left x) >>= f = Left x (Right x) >>= f = f x
Simplifying this a bit and removing unnecessary parentheses gives:

instance Monad (Either e) where return = Right Left x >>= _ = Left x Right x >>= f = f x
Recall the MonadError instance definition for the Either ArithmeticError monad and the ArithmeticError error type we derived above:

instance MonadError ArithmeticError (Either ArithmeticError) where throwError = Left catchError (Right val) _ = Right val catchError (Left err) h = h err
This definition doesn't depend on the details of the ArithmeticError error type, so it can be generalized to:

instance MonadError e (Either e) where throwError = Left catchError (Right val) _ = Right val catchError (Left err) h = h err
These instance definitions (Monad (Either e) and MonadError e (Either e)) are so generally useful that you would probably expect them to be part of the Haskell libraries. And they are, almost. In the module Control.Monad.Error we have these definitions:

instance (Error e) => Monad (Either e) where return = Right Left x >>= _ = Left x Right x >>= f = f x fail msg = Left (strMsg msg)
and:

instance (Error e) => MonadError e (Either e) where throwError = Left catchError (Right val) _ = Right val catchError (Left err) h = h err
The variable names have been changed slightly to agree with the previous definitions, and catchError is written as a function instead of as an operator, but otherwise these are the same definitions GHC uses.

The differences between the versions we derived above and the library versions are:

  1. Both instances require the error type e to be an instance of a type class called Error, which we haven't discussed yet.

  2. The Monad instance for Either e also includes a custom definition for the fail function.

These two differences are related. To understand them we first have to delve a little more deeply into what the fail function is for and how it works.
Digression: the fail function

fail is a method of the Monad type class which I glossed over in part 3. I did mention that it was called on a pattern-match failure and had the type:

fail :: String -> a
fail is called with an error message as an argument. In addition to being automatically invoked upon a pattern-match failure, fail can also be called explicitly by user code if desired, though this is rare. fail has the default definition:

fail s = error s
How can a pattern-match failure occur so that fail gets called in the first place? Recall how the >>= operator is used:

mx >>= (\x -> ...)
where mx is some monadic value. The monadic value gets "unpacked" in some monad-specific way into x and then the code to the right of the -> is evaluated with the new binding for x. The version using the do-notation is:

do x <- mx ...
but the meaning is the same.

In fact, as long as the right argument of the >>= operator is a lambda expression of the form \x -> ..., there won't be a pattern-match error. The operator will always extract a value from the monadic value mx and bind the entire value to the name x. However, lambda expressions can do destructuring during binding. For instance, consider this type:

data Foobar = Foo Int | Bar String
Using this type, we can write this function:

getFoo :: Foobar -> Int getFoo (Foo i) = i
What's wrong with this function? It's not a total function! If you give the function an argument of the form Bar s where s is some String, it will be type-correct but will fail at run time with a pattern-matching error (since the pattern Bar s can't match anything). For instance:

ghci> getFoo (Foo 10) 10 ghci> getFoo (Bar "xxx") *** Exception: Non-exhaustive patterns in function getFoo
Now let's rewrite getFoo in a slightly different (but equivalent) way:

getFoo :: Foobar -> Int getFoo x = case x of Foo i -> i
This is what the GHC compiler converts the original form into; all the definitional equations of a particular function get turned into a single case statement. Here there is only one case, but usually there are more.

We can rewrite it in an even more primitive form using a lambda expression:

getFoo :: Foobar -> Int getFoo = \x -> case x of Foo i -> i
We can also push the case stuff into the lambda expression as follows:

getFoo :: Foobar -> Int getFoo = \(Foo i) -> i
This means the same thing as the previous definition.

Now let's look at monads again. Say you had a monadic computation that involved monadic values of the type m Foobar for some monad m. (For instance, it could be IO Foobar in the IO monad, Maybe Foobar in the Maybe monad, etc.). Some uses of the >>= operator might then have the specialized type:

(>>=) :: m Foobar -> (Foobar -> m Int) -> m Int
and there might be computations like this:

return (Foo 42) >>= \(Foo i) -> return i
This will work fine, since the Foo 42 value will be unpacked into the Foo i pattern, binding i to the number 42. But what if this happened?

return (Bar "xxx") >>= \(Foo i) -> return i
We would have a pattern-match error, because there is no way to match a pattern of the form Foo i with a value of the form Bar "xxx". The error we would get is:

*** Exception: Non-exhaustive patterns in lambda
This shouldn't be surprising. Now imagine that we re-wrote this using the do-notation based on the desugaring we've defined previously. It would look like this:

do (Foo i) <- return (Bar "xxx") return i
You'd expect that running this would give the exact same error message. In fact, it doesn't, and what happens depends on the monad, or specifically, on the definition of the fail function for the monad. In the IO monad, we have:

testIO :: IO Int testIO = do (Foo i) <- return (Bar "xxx") return i ghci> testIO *** Exception: user error (Pattern match failure in do expression)
In the Maybe monad, we have:

testMaybe :: Maybe Int testMaybe = do (Foo i) <- return (Bar "xxx") return i ghci> testMaybe Nothing
Weird! But perhaps not so weird if we look at the definition of the fail function for both monads. For Maybe it is:

fail _ = Nothing
So a pattern-match failure just causes the entire computation to fail. For IO we have (in GHC, anyway):

fail s = GHC.IO.failIO s
which will give rise to the "user error" error message shown above.

The point of all this is to show that the fail function, which is not a fundamental method of the Monad type class, is still important and is somehow called when a pattern-matching error occurs inside a do-expression. But how does this work?

The desugaring of a do-expression I showed you before was this:

do x <- mx ... -- desugars to: mx >>= \x -> ...
But that's not true if x has internal structure (e.g. if x is something like (Foo i) as shown above). In that case, the desugaring is:

do (Foo i) <- mx ... -- desugars to: mx >>= \x -> case x of Foo i -> ... _ -> fail "Pattern match failure in do expression"
(Actually, the error message also has some file name and line number information as well, but I've ignored that to keep things simple.) Since Haskell doesn't know what you're going to put on the left-hand side of the arrows (<-) in a do-expression, it's important to define the fail function for a monad in an appropriate way. If you don't care, you can just use the default definition of fail, which is:

fail s = error s
This is suitable for many monads, but not for error-handling monads. In an error-handling monad, a pattern-match error is just one more error that can occur, and it should yield a well-defined error value. And this is what the Error class is all about.
From fail to Error

Recall the library definition of the Either e monad mentioned above:

instance (Error e) => Monad (Either e) where return = Right Left x >>= _ = Left x Right x >>= f = f x fail msg = Left (strMsg msg)
We derived the definitions for return and >>= in the previous article. Let's look at the definition of fail. As I just mentioned, it's not appropriate in an error-handling monad to use the default definition of fail (which means to just call the error function) because the expectation is that any error will become a value of the error type e. And that's exactly what this definition of fail does: it takes the error message msg, turns it into a value of the error type e using the strMsg function (which I'll explain shortly) and uses the Left constructor to inject it into a value of type Either e a where type a is whatever is being returned as the normal return value.

The strMsg function is a method of the Error type class, which is defined in the module Control.Monad.Error as follows:

class Error a where noMsg :: a strMsg :: String -> a -- default definitions: noMsg = strMsg "" strMsg _ = noMsg
Essentially, what the Error type class defines is what an error type (such as ArithmeticError) has to be able to do in order to be usable with the fail function in an error-handling monad. It has two methods: noMsg and strMsg, and the default definitions mean that either can be defined in terms of the other. However, at least one of the two has to be defined for each instance. noMsg is intended to be used for errors for which the error message is irrelevant, and strMsg is for errors in which the error message is relevant. We'll just define strMsg in what follows and use the default definition of noMsg.

Let's see how we can start to define ArithmeticError as an instance of the Error class:

instance Error ArithmeticError where strMsg msg = {- to be filled in -}
The type signature of strMsg states that the return value of the function has to be of type a, which in this instance is ArithmeticError. This leads us to an interesting dilemma. The definition of ArithmeticError we've been using is:

data ArithmeticError = DivideByZero | NotDivisible Int Int deriving Show
Somehow, whatever strMsg msg returns must have this type. But since we know that it will get invoked on a pattern match error, it doesn't make much sense to return DivideByZero or NotDivisible errors, which aren't relevant. Furthermore, it would be nice to be able to incorporate the msg string into the error value. Finally, fail can be called in ordinary user code, again with an error message. The best thing we can do is to add another constructor to ArithmeticError specifically for use with strMsg (and thus, with fail). This leads to this revised definition:

data ArithmeticError = DivideByZero | NotDivisible Int Int | OtherError String -- for Error instance deriving Show
The OtherError constructor is a catch-all constructor that can be used to put an arbitrary error message string into a value of the ArithmeticError type. With this new definition it's easy to define the Error instance for ArithmeticError:

instance Error ArithmeticError where strMsg msg = OtherError msg
We can simplify this definition a tiny bit by leaving off msg from both sides to get:

instance Error ArithmeticError where strMsg = OtherError
And that's all we need to do with the Error class.

You might ask what this buys you. It's simple: if you define this trivial instance of the Error class, you no longer have to define the MonadError instance at all, because it's defined automatically for all Either e monads where e is an instance of the Error class! That's what this code was all about:

instance (Error e) => MonadError e (Either e) where throwError = Left catchError (Right val) _ = Right val catchError (Left err) h = h err
So that's a chunk of code you don't have to write. Of course, you do have to import the Control.Monad.Error module where this definition comes from. When you do that, you also get this:

instance (Error e) => Monad (Either e) where return = Right Left x >>= _ = Left x Right x >>= f = f x fail msg = Left (strMsg msg)
which is yet another chunk of code you don't have to write.

To summarize:

  1. We imported the Control.Monad.Error module.

  2. We defined the error type ArithmeticError, with constructors corresponding to the kinds of errors that could occur in your computations, as well as the catch-all OtherError constructor which takes an error message as its argument.

  3. We defined the instance of the Error type class for ArithmeticErrors.

And that's it. We get the Monad instance definition for the Either e monad and the MonadError instance definition for the ArithmeticError error type and the Either ArithmeticError monad defined for us automatically. Then we can write all the error-handling functions we wrote above.

Here's the final version of the code:

import Control.Monad.Error data ArithmeticError = DivideByZero | NotDivisible Int Int | OtherError String deriving Show instance Error ArithmeticError where strMsg = OtherError -- Division that checks for divide-by-zero and not-divisible errors. safe_divide :: Int -> Int -> Either ArithmeticError Int safe_divide _ 0 = throwError DivideByZero safe_divide i j | i `mod` j /= 0 = throwError (NotDivisible i j) safe_divide i j = return (i `div` j) -- Division that checks for divide-by-zero errors but that -- allows not-divisible conditions (throwing away the remainder). divide :: Int -> Int -> Either ArithmeticError Int divide i j = (i `safe_divide` j) `catchError` \e -> case e of -- Note: OtherErrors are just re-thrown. OtherError s -> throwError (OtherError s) DivideByZero -> throwError DivideByZero NotDivisible i j -> return (i `div` j)
This is all we need to do in order to use the Either e monad with a custom error type. And we get "throw" and "catch" for free due to the MonadError definition. Monads have allowed us to take something that is built-in and mysterious in other languages (exception handling) and write it as a normal library in Haskell. This is just another example of the great power of the monad abstraction.
Getting this code to work

Some of the features I've described above are not (yet) standard Haskell features, and as such require you to enable certain GHC optional extensions for them to work. There are three ways to do this:

  1. Compile your code (or run ghci with the -fglasgow-exts command-line option. This is the simplest way.

  2. Use the command-line options -XFlexibleContexts and -XMultiParamTypeClasses. Actually, only the first is absolutely required, but I like to enable them both because it's obvious that we're actually using multi-parameter type classes. (I think that enabling -XFlexibleContexts automatically enables -XMultiParamTypeClasses but I haven't been able to confirm this yet.)

  3. Don't use command-line options, but instead add this comment at the beginning of the Haskell module containing your code:

    {-# LANGUAGE FlexibleContexts, MultiParamTypeClasses #-}

I don't want to spend time explaining why this is necessary; see the GHC documentation for a thorough discussion.
Next time

In the next installment I'll look at state monads, which are a way to simulate some aspects of imperative programming in a functional context.
Previous post Next post
Up