Disclaimer: This post assumes a minimal understanding of the Haskell programming language. Some of the code presented will not compile, either because it is already implemented in Haskell itself, or because you might have to add the {-# LANGUAGE InstanceSigs #-}
tag to the top of the source file..
Welcome to an alternative monad tutorial. Monads are notoriously difficult to explain. It is said that there is a curse on them.
Once you understand what monads are, and why they exist, you lose the ability to explain it to anybody. -- Douglas Crockford
Monads were originally developed in category theory, one of the highest and most abstract branches of mathematics, but they are used in functional programming too. To understand monads yourself, you could jump into category theory and you might even want to do so (I know I did!), but for most programmers there has to be a better way.
Most of the programmers I know, have learned to program, not in a classroom or from a book, but from a lot of examples from different sources. Programmers have gotten really good at (silently) abstracting examples to implement exactly what they were looking for while ignoring most of the surrounding explanation.
I think that most monad tutorials explain monads the wrong way around. They start by defining a monad, and then explain why the concept of a monad could be useful. The 'inventors' of monads started out by seeing a repetitive pattern and abstracting that.
That is why I have opted to show you a few examples of monads, and finish by showing you the abstract definition. I will not try to explain monads at all, there are enough bad tutorials to be found online already. You will have to look for the pattern yourself.
Just to make sure you don't want to learn category theory.
A monad is just a monoid in the category of endofunctors, what's the problem?
If you understood that, you can go read something else, you're done. The theory behind this is really mind blowingly beautiful once you understand it. I just want to make sure that you're not interested, because a well founded understanding of monads from category theory will be much more usefull to a programmer than simply knowing how to use them.
Let's get started!
A list is a monad.
instance Monad [] where
return :: a -> [a]
return x = [x]
(>>=) :: [a] -> (a -> [b]) -> [b]
>>= f = concat (map f xs) xs
Remember: A list is used as a container.
Maybe is a monad
instance Monad Maybe where
return :: a -> Maybe a
return x = Just x
(>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b
Nothing >>= f = Nothing
Just x >>= f = f x
Maybe is used to give context to values that are the result of some procedure that could go wrong.
Even this useless thing is a monad!
data Useless a = Thing a
instance Monad Useless where
return :: a -> Useless a
return x = Thing x
(>>=) :: Useless a -> (a -> Useless b) -> Useless b
Thing a >>= f = f a
Granted, this monad has no use other than giving you another example. You could see it as a 'Useless' example.
And now for a more practical example: Debuggable
data Debuggable a = Debug a String
deriving (Eq, Show)
instance Monad Debuggable where
return a = Debug a ""
Debug a str) >>= f
(= Debug b (str ++ s)
where (Debug b s) = f a
Now, here we define some functions that produce a debuggable result. Debuggable gives a context as well as a 'side effect' to a computation.
-- Square of an integer.
f :: Integer -> Double
= sqrt . fromInteger
f
-- Check whether a double is an integer.
g :: Double -> Bool
= a == (fromInteger $ round a)
g a
fM :: Integer -> Debuggable Double
= Debug (f a) "f was called. "
fM a
gM :: Double -> Debuggable Bool
= Debug (g a) "g was called. " gM a
Now we can use the bind (>>=)
(or (=<<)
) function to compose these functions instead of the normal function composition (.)
(or $
).
*Main> (g . f) x
True
*Main> return 4 >>= fM >>= gM
Debug True "f was called. g was called. "
*Main> g $ f $ 4
True
*Main> gM =<< fM =<< return 4
Debug True "f was called. g was called. "
The most confusing one: IO
IO is also a monad, but we cannot look at the definition, because that part can't be written in native Haskell. It is, however, another good example of a monad because it adds side effects to computation. I write 'add', because there are no other ways to introduce side effects into a program other than the IO monad.
The abstract monad
To conclude this tutorial, here is the abstract definition of a monad. You should be comfortable with both the return and the bind function by now, and the abstract definition should come as no surprise. The other two functions (>>)
and fail
are not mentioned in this post.
class Monad m where
return :: a -> m a
(>>=) :: m a -> (a -> m b) -> m b
(>>) :: m a -> m b -> m b
fail :: String -> m a
>> k = m >>= \_ -> k
m fail s = error s
Your turn!
You've seen a few examples of monads, now it's up to you to write one! I encourage you to write a monad that does nothing but abide by the monad laws. Something like the Useless
monad maybe? Next, I would like for you to try using one monad you haven't used before (so not the IO monad).
The random monad: introduce randomness into Haskell.
The state monad: introduce statefulness into Haskell.
Xmonad: an awesome tiling window manager that uses Haskell for its configuration.
Some good monad tutorials
Of course, if you didn't understand monads before this post, you won't understand them now. Here are some more monad tutorials. Some of them are not necessarily the first to be found, but all of these are good monad tutorials.