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

Miguel Mitrofanov miguelimo38 at yandex.ru
Sat May 9 16:54:30 EDT 2009


Types.

(>>=) :: Monad m => m a -> (a -> m b) -> m b
(1+)  :: Num a => a -> a

So, the typechecker deduces that 1) "a" is the same as "m b", and 2)  
"a" (and "m b", therefore) must be of class "Num"

Now,

Just 3 :: Num t => Maybe t

and the typechecker learns from that that "m a" must be the same as  
"Maybe t", with "t" being of class "Num". This leads to two  
observations: 3) "m" is "Maybe", and 4) "a" is of class "Num" - the  
same as (2) above

Now, from (1) and (3) it follows that "a" is the same as "Maybe b".  
(2) lead than to "Maybe b" being of class "Num" - but GHCi doesn't  
have this instance, and complains.

What you've probably meant is something like

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

or, equivalently,

liftM (+1) $ Just 3

On 9 May 2009, at 23:31, michael rice 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>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list