[Haskell-cafe] Just 3 >>= (1+)?

Alexander Dunlap alexander.dunlap at gmail.com
Sat May 9 16:42:29 EDT 2009


On Sat, May 9, 2009 at 12:31 PM, michael rice <nowgate at yahoo.com> wrote:
> Why doesn't this work?
>
> Michael
>
> ================
>
> data Maybe a = Nothing | Just a
>
> instance Monad Maybe where
>     return         = Just
>     fail           = Nothing
>     Nothing  >>= f = Nothing
>     (Just x) >>= f = f x
>
> instance MonadPlus Maybe where
>     mzero             = Nothing
>     Nothing `mplus` x = x
>     x `mplus` _       = x
>
> ================
>
> [michael at localhost ~]$ ghci
> GHCi, version 6.10.1: http://www.haskell.org/ghc/  :? for help
> Loading package ghc-prim ... linking ... done.
> Loading package integer ... linking ... done.
> Loading package base ... linking ... done.
> Prelude> Just 3 >>= (1+)
>
> <interactive>:1:0:
>     No instance for (Num (Maybe b))
>       arising from a use of `it' at <interactive>:1:0-14
>     Possible fix: add an instance declaration for (Num (Maybe b))
>     In the first argument of `print', namely `it'
>     In a stmt of a 'do' expression: print it
> Prelude>
>

The type of (>>=) is

(>>=) :: m a -> (a -> m b) -> m b

For the Maybe monad, that specializes to

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

But when you say

Just 3 >>= (+1)

this desugars to

(>>=) (Just 3) (\x -> x + 1)

but the second argument to (>>=) that you have given has the type (\x
-> x + 1) :: Num a => a -> a, whereas it needs to return a type of
Maybe a to fit the type signature.

What you probably want is

Just 3 >>= (Just . (+1))

so the second function returns a Maybe value. A nicer way of writing this is

fmap (+1) (Just 3), which uses the Functor class. Intuitively, the
fmap function applies a function to the inside of a container. All
monads can be defined as Functors as well; all Monads in the standard
libraries have their functor instances defined.

Hope that helps you.

Alex


More information about the Haskell-Cafe mailing list