[Haskell-cafe] Just 3 >>= (1+)?
Neil Brown
nccb2 at kent.ac.uk
Sat May 9 16:24:19 EDT 2009
Hi,
(1+) :: Num a => a -> a
For the bind operator, you need something of type a -> Maybe b on the
RHS, not simply a -> a. You want one of these instead:
fmap (1+) (Just 3)
liftM (1+) (Just 3)
Alternatively, you may find it useful to define something like:
(>>*) = flip liftM
so that you can write:
Just 3 >>* (1+)
which bears a closer resemblance to the bind notation.
Thanks,
Neil.
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