
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@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>

Because you're looking for:
Just 3 >>= return . (+1)
or more simply
Just 3 >>= Just . (+1)
or more generally:
return 3 >>= return . (+1)
The second argument of (>>=) is supposed to be of type (Monad m => a
-> m b) but (+1) ishe of type (Num a => a -> a). Wre is the monad in
that?
Thomas
On Sat, May 9, 2009 at 12:31 PM, michael rice
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@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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I think you're looking for fmap/liftM here. The type of >>= is:
(>>=) :: (Monad m) => m a -> (a -> m b) -> m b
so it's trying to make your function (1+) return m b, which in this
case should be a Maybe. Clearly, (1+) doesn't return a Maybe, so it
breaks. Another options is to do return . (1+) to lift the function
into Maybe, but that might be a little much.
On Sat, May 9, 2009 at 3:31 PM, michael rice
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@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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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@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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On May 9, 2009, at 15:31 , michael rice wrote:
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>
(>>=) must be applied to a function that produces a result in the same monad: (>>=) :: Monad m => m a -> (a -> m b) -> m b That (a -> m b) in the middle is what's failing to typecheck. The error is a bit obtuse because ghci is trying hard to find a way to do what you want, so it assumes "m" is "(-> r)" (the functor/monad representing functions, also known as the Reader monad) which means "b" must be "Maybe x" for some x, but there are no instances of Maybe that are also instances of Num. If ghci had started by fixing m as Maybe (via the "Just 3") the types in the error message would have made more sensen; fixing m is more restrictive The function you're actually looking for is liftm or fmap: liftm :: Monad m => m a -> (a -> b) -> m b fmap :: Functor f => f a -> (a -> b) -> f b which "lifts" the (1+) up inside the monad/functor (which in this case is Maybe, as per the above). -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On 10 May 2009, at 00:30, Brandon S. Allbery KF8NH wrote:
On May 9, 2009, at 15:31 , michael rice wrote:
Prelude> Just 3 >>= (1+)
That (a -> m b) in the middle is what's failing to typecheck. The error is a bit obtuse because ghci is trying hard to find a way to do what you want, so it assumes "m" is "(-> r)" (the functor/monad representing functions, also known as the Reader monad)
Ehm? What? I haven't seen the (-> r) monad anywhere near this code.

On May 9, 2009, at 18:03 , Miguel Mitrofanov wrote:
On 10 May 2009, at 00:30, Brandon S. Allbery KF8NH wrote:
On May 9, 2009, at 15:31 , michael rice wrote:
Prelude> Just 3 >>= (1+)
That (a -> m b) in the middle is what's failing to typecheck. The error is a bit obtuse because ghci is trying hard to find a way to do what you want, so it assumes "m" is "(-> r)" (the functor/monad representing functions, also known as the Reader monad)
Ehm? What? I haven't seen the (-> r) monad anywhere near this code.
That's the only way I can get the error he got; if it uses Maybe as the monad then why is the Maybe on the *inside* in the error message? Clearly it bound m to something else, and ((->) r) is the only other one I can think of applying there. (Hm, I suppose it could be IO forced by the ghci context, but I didn't think it worked that way.) -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On May 9, 2009, at 18:16 , Brandon S. Allbery KF8NH wrote:
That's the only way I can get the error he got; if it uses Maybe as the monad then why is the Maybe on the *inside* in the error message? Clearly it bound m to something else, and ((->) r) is the only other one I can think of applying there. (Hm, I suppose it could be IO forced by the ghci context, but I didn't think it worked that way.)
Er, clarifying: it's looking for Num (Maybe a), but the context where Num applies is inside the scope where the Maybe applies (a -> m b has been fixed at Num n => n -> m n). But the error message says ghc is trying to make *n* an instance of Num. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

michael rice wrote:
Prelude> Just 3 >>= (1+)
Let's check the types. Prelude> :t (>>=) (>>=) :: (Monad m) => m a -> (a -> m b) -> m b Prelude> :t Just 3 Just 3 :: (Num t) => Maybe t Prelude> :t (1 +) (1 +) :: (Num a) => a -> a Renaming the variables in the type of (1 +) gives: (1 +) :: (Num c) => c -> c Since (Just 3) is the first argument of (>>=), we have to unify the types (Maybe t) and (m a). This leads to: m = Maybe t = a Since (1 +) is the second argument of (>>=), we have to unify the types (c -> c) and (a -> m b). This leads to: c = a = m b Since we haven't found any inconsistencies, typechecking succeeded, and we instantiate the types of Just 3, (>>=) and (1 +) to the following types by applying the substituations we found. Just 3 :: Num (Maybe b) => Maybe (Maybe b) (1 +) :: Num (Maybe b) => Maybe b -> Maybe b (>>=) :: Monad Maybe => Maybe (Maybe b) -> (Maybe b -> Maybe b) -> Maybe b And the type of the whole expression is accordingly: Just 3 >>= (1 +) :: (Monad Maybe, Num (Maybe b)) => Maybe b Now ghc looks at the constraints, figures out that Monad Maybe is fine, and complains about Num (Maybe b). Try the fmap function instead, it has the following type: Prelude> :t fmap fmap :: (Functor f) => (a -> b) -> f a -> f b Since every self-respecting Monad is also a Functor, you can use fmap (1 +) (Just 3). Now (a -> b) is unified with (Num a => a -> a), so that the overall type of the function is (Num a => Maybe a) as you would expect. Tillmann

Hi,
Haskell expects the function with type (a -> m b) in the right side of
(>>=),
but you put there function with type (a -> a):
try:
:t (Just 3 >>=)
(Just 3 >>=) :: (Num a) => (a -> Maybe b) -> Maybe b
and:
:t (1+)
(1+) :: (Num a) => a -> a
You should put (1+) into Maybe monad, just do return.(1+), so
Just 3 >>= return . (1+)
will return `Just 4`
--
Best regards,
Vasyl Pasternak
2009/5/9 michael rice
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@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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sat, May 9, 2009 at 12:31 PM, michael rice
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@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

Hey Michael,
If you would look at the type of >>=, it would give
(>>=) :: (Monad m) => m a -> (a -> m b) -> m b
and specifically in your case:
(>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b
You are applying Just 3 as first argument, which is correct, but then supply
a partially applied function (1+) which is of type Num a => a -> a, while
it should be
a -> Maybe b.
What are you expecting as result? You cannot pull something out of a monad
using a bind operator. Maybe you meant something like this?
(Just 3) >>= \x -> return (x + 1)
Notice how Just 3 is just the Maybe a argument, and \x -> return (x + 1) is
the (a -> Maybe b) argument, finally delivering a Just 4 (of type Maybe b).
(This is the same as do x <- Just 3
return (x + 1)
)
Oh and btw, fail should take an argument (the error string).
Good luck,
Bas van Gijzel
On Sat, May 9, 2009 at 9:31 PM, michael rice
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@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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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@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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Excerpts from michael rice's message of Sat May 09 14:31:20 -0500 2009:
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@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>
Look at the types: Prelude> :t (>>=) (>>=) :: (Monad m) => m a -> (a -> m b) -> m b Prelude> :t (+1) (+1) :: (Num a) => a -> a Prelude> The return type of '(+1)' in this case should be 'm b' but it instead only returns 'b'. If we tag a return on there, it will work fine: Prelude> Just 3 >>= return . (+1) Just 4 Prelude> Austin

Am Samstag 09 Mai 2009 21:31:20 schrieb michael rice:
Why doesn't this work?
Michael [michael@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 Monad m => m a -> (a -> m b) -> m b, the type of (1 +) is Num n => n -> n. Using (1 +) as the second argument of (>>=), you must unify Num n => n -> n with Monad m => a -> m b the types of the arguments and results must match, so a = n m b = n = a , giving the type (Monad m, Num (m b)) => m b -> m b The first argument of (>>=) is Just 3 :: Num k => Maybe k. That must be unified with m a, giving m = Maybe and a = k. On the other hand we previously found a = m b, so in Just 3 >>= (1 +) the (1 +) has type Num (Maybe b) => Maybe b -> Maybe b and Just 3 has type Num (Maybe b) => Maybe (Maybe b). But ghci can't find an instance Num (Maybe b). You probably wanted fmap (1 +) (Just 3) ~> Just 4

... There have been 12 replies to this question, all of which say the same thing. I'm glad we're so happy to help, but does Just 3 >>= return . (+1) Need to be explained by 12 different people? fmap ("trying to"++) $ Just "help" -- :D Cory
Why doesn't this work?
Michael [michael@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>

On 10 May 2009, at 04:00, Cory Knapp wrote:
... There have been 12 replies to this question, all of which say the same thing.
Brandon's one was different. And incorrect, which shows that this question isn't completely obvious.
I'm glad we're so happy to help, but does
Just 3 >>= return . (+1)
Need to be explained by 12 different people?
1) That's how mail lists work. 2) We are just happy that Michael finally managed to present code which passes the syntax checker. To Michael: no sarcasm here.
fmap ("trying to"++) $ Just "help" -- :D
Cory
Why doesn't this work?
Michael [michael@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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Cory, Cory Knapp wrote:
... There have been 12 replies to this question, all of which say the same thing. I'm glad we're so happy to help, but does
Just 3 >>= return . (+1)
Need to be explained by 12 different people?
maybe eleven others have already pointed that out by now, but as far as I know, there is no way to see whether someone else is concurrently answering the same question. And I don't think that all answers were equivalent. Some answer pointed out how to correct the error, while others focused on explaining why the error arises. One answer was wrong. Tillmann

Am Sonntag 10 Mai 2009 02:00:29 schrieb Cory Knapp:
... There have been 12 replies to this question, all of which say the same thing. I'm glad we're so happy to help, but does
Just 3 >>= return . (+1)
Need to be explained by 12 different people?
fmap ("trying to"++) $ Just "help" -- :D
Cory
I guess it's because almost nobody saw any reply to it when writing their own, the mail server seems to be slooow on weekends. The first reply appeared in my mailbox some two hours after I posted mine. I wonder how many people have already answered your post :)
participants (14)
-
Alexander Dunlap
-
Austin Seipp
-
Bas van Gijzel
-
Brandon S. Allbery KF8NH
-
Cory Knapp
-
Daniel Fischer
-
Daniel Peebles
-
Henning Thielemann
-
michael rice
-
Miguel Mitrofanov
-
Neil Brown
-
Thomas DuBuisson
-
Tillmann Rendel
-
Vasyl Pasternak