> However, I note that Maybe is an instance of Monad.  What for?  
> ... Could somebody please post a relatively down-to-earth piece 
> of code where Maybe is used monadically - or explain its 
> usefulness in prose?

Sure.  Below is a short excerpt from my forthcoming book.

  -Paul 

--------------------------------------------------------------------

\subsection{Other Instances of Monad}
\label{monad-instances}

\paragraph*{\hs{Maybe}}
\indexhs{Maybe}

In addition to \hs{IO}, the Standard Prelude's \hs{Maybe} data type is
a predefined instance of \hs{Monad}:

> instance  Monad Maybe  where
>     Just x  >>= k   =  k x
>     Nothing >>= k   =  Nothing
>     return          =  Just
>     fail s          =  Nothing

When used with this instance, the types of the monad operators are:

| (>>=)  :: Maybe a -> (a -> Maybe b) -> Maybe b
| return :: a -> Maybe a

I will leave as an exercise the task of proving that this instance is
law-abiding.

To see how this might be used, consider a computation involving
functions \hs{f :: Int -> Int}, \hs{g :: Int -> Int}, and 
\hs{x :: Int}:

| g (f x)

Now suppose that each of the calculations using \hs{f} and \hs{g}
could in fact be erroneous, and thus the results are encoded using the
\hs{Maybe} data type.  Unfortunately this can become rather tedious to
program, since each result that might be an error must be checked
manually, as in:

| case (f x) of 
|   Nothing -> Nothing
|   Just y  -> case (g y) of
|                Nothing -> Nothing
|                Just z  -> z

Alternatively, you could take advantage of \hs{Maybe}'s membership in
the \hs{Monad} class, and convert this into monadic form:

| f x >>= \y ->
| g y >>= \z ->
| return z

Or, using the more familiar \hs{do} notation:

| do y <- f x
|    z <- g y
|    return z

Thus the tedium of the error check is ``hidden'' within the monad.  In
this sense monads are a good example of the abstraction principle in
action (pardon the pun)!

It is also worth noting the following simplification:

| f x >>= \y ->
| g y >>= \z ->
| return z
| ==> { currying simplification }
| f x >>= \y ->
| g y >>= return 
| ==> { monad law for return }
| f x >>= \y ->
| g y
| ==> { currying simplification }
| f x >>= g

So we started with \hs{g (f x)} and ended with \hs{f x >>= g}; this is
not too bad considering the alternative that we started with!

For an even more pleasing result, we can define a monadic composition
operator:

> composeM :: Monad m => (b -> m c) -> (a -> m b) -> (a -> m c)
> (g `composeM` f) x = f x >>= g

in which case we started with \hs{(g . f) x} and ended with 
\hs{(g `composeM` f) x}.



Reply via email to