Newbie qustion about monads

I have an extremely-newbie question about monads and how to interpret the monadic laws; I asked that same question yesterday on IRC and the answers were interesting but non-conclusive (to me anyway). I'm trying to learn monads by reading "All About Monads", version 1.0.2. I though of defining a monad like that: data Counted a = Ct Int a instance Monad (Counted) where return x = Ct 1 x Ct n x >>= f = let (Ct n' x') = f x in Ct (n+n') x' -- fail as default The intent is that Counted objects "count" the number of times an operation is applied to them. (For the purpose of the question, that's irrelevant anyway: the problem would be the same if I assigned a random number to the Int on each calling of >>=.) According to "All About Monads", the first monadic law says: (return x) >>= f == f x In my case, let's suppose I define: reverseCounted :: [a] -> Counted [a] reverseCounted x = return (reverse x) so I do: c1 = return "xxx" >>= reverseCounted -- c1 == Ct 2 "xxx" c2 = reverseCounted "xxx" -- c2 == Ct 1 "xxx" Now comes the question: In what sense should I interpret the "==" in the monadic law? Obviously, c1 and c2 are not structurally equal. If I can accept that two Counted things are "equal" even if they are not identical, is enough for me to define: instance Eq a => Eq (Counted a) where Ct _ x == Ct _ y = x == y to satisfy the first law? Yesterday I was said that it'd work if c1 and c2 are mutually substitutable. They are, for the purposes of equality, though evidently not for every purpose. A simple: count (Ct n _) = n allows me to distinguish between them. Juanma

W liście z czw, 02-10-2003, godz. 11:13, Juanma Barranquero pisze:
The intent is that Counted objects "count" the number of times an operation is applied to them.
As you discovered, there is no meaningful count of operations. If an operation doesn't do anything, do you count it? I suppose yes - but monad laws say that "return" *really* doesn't do anything, and you incremented the count for it. "return" should have the count of 0. Some other operations could have a positive count, there is no obvious choice which ones. -- __("< Marcin Kowalczyk \__/ qrczak@knm.org.pl ^^ http://qrnik.knm.org.pl/~qrczak/

On Thu, 02 Oct 2003 11:22:13 +0200
"Marcin 'Qrczak' Kowalczyk"
As you discovered, there is no meaningful count of operations. If an operation doesn't do anything, do you count it?
It's not about counting the operations (that's just an example), but accumulating any kind of state. For example: data Accum a = Ac [a] a instance Monad Accum where return x = Ac [x] x Ac _ x >>= f = let Ac l x' = f x in Ac (l ++ [x']) x' dupAcc x = Ac [x,x] x m1 = (return 'a') >>= dupAcc -- Ac "aaa" 'a' m2 = dupAcc 'a' -- Ac "aa" 'a'
but monad laws say that "return" *really* doesn't do anything
I don't see it. As I understand, the problem (if any) would be in my implementations of either >>= or f (dupAcc, in this case). I get the same values for m1 and m2 even if I define return x = Ac [] x. I'm not trying to create useful monads (I'm pretty sure they aren't :), but understanding the concepts. So, the question remains: when the monad laws say that (return x) >>= f == f x what is intended in that "=="? Eq."==" for instance Eq MyCustomMonad where x == y = whatever... or a more profound kind of equality? Juanma

So, the question remains: when the monad laws say that
(return x) >>= f == f x
what is intended in that "=="?
Observational equivalence. For monads like list and maybe, this boils down to the normal equality because the standard equality on these types is exactly observational equality. For monads like IO, you can't define an Eq instance so it comes down to what can the user of the program observe. They can observe the order you create files or write to files. They can even observe the order you open files. They can't observe 'internal' actions that don't have side effects and don't depend on the IO environment so 'return' should not be observable. In particular, they can't see any of the returns in this sequence: do return 1 return 2 return 3 print 42 Which is a good thing since the monad law you cite requires this to be equal to print 42 For monads like parser monads, there is usually a notion of encapsulation. That is, you're supposed to be able to observe the results of running the parser and you may also be able to observe how much input was examined but you probably can't directly observe the internal state of the parser. In that case, we'd consider two states to be equivalent if they lead to the same results being returned and the same input being examined. Since parsers are state transformers, we'd say that two parsers are equivalent if they preserve and reflect equivalence of states. (There's a little circularity there and I'm ignoring the exception part of parser monads but, hopefully, you get the idea.) -- Alastair Reid www.haskell-consulting.com

On Thu, 2 Oct 2003 12:30:54 +0100
Alastair Reid
Observational equivalence.
For monads like list and maybe, this boils down to the normal equality because the standard equality on these types is exactly observational equality.
For monads like IO, you can't define an Eq instance so it comes down to what can the user of the program observe.
OK. But in my examples, the difference is observable only if I do define a "count" or equivalent to show it. Otherwise, c1/c2 (or m1/m2) are indistinguishable.
(There's a little circularity there and I'm ignoring the exception part of parser monads but, hopefully, you get the idea.)
Yes, thanks a lot. Juanma

On Thu, 02 Oct 2003 12:59:25 +0200
Juanma Barranquero
On Thu, 02 Oct 2003 11:22:13 +0200 "Marcin 'Qrczak' Kowalczyk"
wrote: As you discovered, there is no meaningful count of operations. If an operation doesn't do anything, do you count it?
The Count monad with return defined as Count 0 a with >>= adding them is an instance of the Writer/Output monad. Using 1 and addition isn't. It's also a potentially useful monad. I've seen the equivalent called the Complexity monad before. Using that intuition, return a is something that has 0 complexity. What you needed to do was add primitives that have a complexity you want to measure. For example if you were considering space complexity, you might have a cons primitive defined as say, cons x xs = Count 2 (x:xs), but multiplication, say, would have zero complexity. In general you could use a HOF to add complexity annotations to functions or add a bump = Count 1 () to bump up the complexity of some computation, cons x xs = bump >> bump >> return (x:xs)
It's not about counting the operations (that's just an example), but accumulating any kind of state.
This isn't state, this is, again, a (broken) instance of the Writer/Output monad. The return should use the empty list and your >>= doesn't even make sense.
For example:
data Accum a = Ac [a] a
instance Monad Accum where return x = Ac [x] x Ac _ x >>= f = let Ac l x' = f x in Ac (l ++ [x']) x'
dupAcc x = Ac [x,x] x
m1 = (return 'a') >>= dupAcc -- Ac "aaa" 'a' m2 = dupAcc 'a' -- Ac "aa" 'a'
Which shows that your monad is broken. As Markus mentions, -you- have to make sure the monad laws hold, they don't come for free. If they don't hold, you don't have a monad.
but monad laws say that "return" *really* doesn't do anything
I don't see it. As I understand, the problem (if any) would be in my implementations of either >>= or f (dupAcc, in this case). I get the same values for m1 and m2 even if I define return x = Ac [] x.
As Marcin said, return doesn't do anything. In fact, I believe the monad laws together effectively state that both >>= and return are "pure" with respect to whatever computation is being modelled. So the associativity condition says that it doesn't matter which >>= is evaluated first. Another thing that should be noted, is that most monads are completely useless without "primitive" computations. I.e. using only >>= and return will get you nothing that couldn't have been done "purely". This can be seen by considering the similarity between monads and monoids. return corresponds to the neutral element of a monoid, while join m = m
= id is the multiplication. One example of a monoid is the natural numbers with 0 as the neutral element and + as the multiplication. If we only use 0 and + the result is rather boring, 0+0+0+0, 0+0. This is similar to only using return and >>=. If we use other elements (corresponding to primitive monadic computations) things are much more interesting, 4+90+0+2, 10+3.
So again, with Accum, you need a "primitive" computation that actually is effectful while return and >>= aren't, with the Writer monad this is tell :: [a] -> Writer() which is similar to putStr except it doesn't perform IO, it just collects up a list of "output". The Haskell wiki has implementations of various monads.
I'm not trying to create useful monads (I'm pretty sure they aren't :), but understanding the concepts. So, the question remains: when the monad laws say that
(return x) >>= f == f x
what is intended in that "=="? Eq."==" for
instance Eq MyCustomMonad where x == y = whatever...
or a more profound kind of equality?
A more profound kind, as it usually isn't possible to define a reasonable instance of Eq for monads. Anyways, these laws are the ones from the Category Theory definition of monads (slightly restructured), obviously they aren't talking about Haskell's Eq or even computable equality in general.

On Thu, 2 Oct 2003 08:08:16 -0400
Derek Elkins
The Count monad with return defined as Count 0 a with >>= adding them is an instance of the Writer/Output monad. Using 1 and addition isn't. It's also a potentially useful monad. I've seen the equivalent called the Complexity monad before.
Interesting.
This isn't state, this is, again, a (broken) instance of the Writer/Output monad. The return should use the empty list and your >>= doesn't even make sense.
Excuse me, but from my perspective is not a broken instance of Writer/Output because it didn't try to be an instance of anything... :) And I wasn't interested in making >>= "make sense" (I've said already that I don't think Counted or Accum where useful monads-to-be, just toys to help me learn Haskell) in any sense, *other than* the fact that they satisfy *or* not satisfy the 1st. monadic law. That's what I was trying to know. Even if my >>= is meaningless, mathematical- or computer science-wise, the question I asked is: Could I define >>= so, and == so, and the resulting type would satisfy 1st law?
m1 = (return 'a') >>= dupAcc -- Ac "aaa" 'a' m2 = dupAcc 'a' -- Ac "aa" 'a'
Which shows that your monad is broken. As Markus mentions, -you- have to make sure the monad laws hold, they don't come for free. If they don't hold, you don't have a monad.
Yeah. That's why I'm asking the limits of "hold". Observable behaviour, as Alastair said, is a nice explanation.
In fact, I believe the monad laws together effectively state that both >>= and return are "pure" with respect to whatever computation is being modelled. So the associativity condition says that it doesn't matter which >>= is evaluated first.
Yes. But if I do have a return function which turns on/off a LED outside my computer, and the state of this LED is irrelevant to my computation, is that "return" pure or not? :)
Another thing that should be noted, is that most monads are completely useless without "primitive" computations. [snip] So again, with Accum, you need a "primitive" computation that actually is effectful while return and >>= aren't
In Counted, reverseCounted did a "useful" (for some ad hoc definition of "useful") computation: it turned a list into a reverse list inside the monad. Unless I'm misunderstading my own examples, that is.
A more profound kind, as it usually isn't possible to define a reasonable instance of Eq for monads.
Which resolves into Alastair's definition.
Anyways, these laws are the ones from the Category Theory definition of monads (slightly restructured), obviously they aren't talking about Haskell's Eq or even computable equality in general.
Well, yeah, but this is Haskell and not Category Theory. If an instance of Monad satisfies a weaker 1st law that a mathematical monad should, but it is still useful and "acts like a Monad", I don't see the problem. Anyway, I think that I know understand what's "expected" from a Monad instance. Thanks for your comments (and everyone else's, of course). Juanma

From your examples and interpretations, it looks like you need to become more familiar and comfortable with -using- monads before you bother trying to write one. Then once you have that down, seeing how -correct- monads work would probably be the next most helpful thing. You'll have a very hard time thinking up correct monads if you don't have any intuition about how they are supposed to be used. In any case, knowing how to write an instance of Monad is probably the least useful thing to know about them in Haskell.

W liście z czw, 02-10-2003, godz. 12:59, Juanma Barranquero pisze:
It's not about counting the operations (that's just an example), but accumulating any kind of state. For example:
data Accum a = Ac [a] a
instance Monad Accum where return x = Ac [x] x Ac _ x >>= f = let Ac l x' = f x in Ac (l ++ [x']) x'
Accumulating state is fine. These definitions don't accumulate state: 'return' should yield a "neutral" state, and the above ">>=" ignores the state of the lhs. The type of Accum makes little sense. Each atomic operation can have a different result type, so in order to accumulate something the state can't depend on the type of the result. data Accum s a = Ac [s] a instance Monad (Accum s) where return x = Ac [] x Ac s1 x >>= f = let Ac s2 y = f x in Ac (s1++s2) y output :: a -> Accum a () output x = Ac [x] () -- __("< Marcin Kowalczyk \__/ qrczak@knm.org.pl ^^ http://qrnik.knm.org.pl/~qrczak/

On Thu, 02 Oct 2003 14:27:29 +0200
"Marcin 'Qrczak' Kowalczyk"
Accumulating state is fine. These definitions don't accumulate state: 'return' should yield a "neutral" state, and the above ">>=" ignores the state of the lhs.
You're right.
data Accum s a = Ac [s] a
instance Monad (Accum s) where return x = Ac [] x Ac s1 x >>= f = let Ac s2 y = f x in Ac (s1++s2) y
output :: a -> Accum a () output x = Ac [x] ()
Nice. Thanks! Juanma

On Thu, 02 Oct 2003 14:57:22 +0200, Juanma Barranquero
data Accum s a = Ac [s] a
instance Monad (Accum s) where return x = Ac [] x Ac s1 x >>= f = let Ac s2 y = f x in Ac (s1++s2) y
output :: a -> Accum a () output x = Ac [x] ()
After trying this one, and also output :: a -> Accum a a output x = Ac [x] x I though of doing: data Accum a = Ac [a] a because I was going to accumulate a's into the list. That didn't work; defining >>= gave an error about the inferred type being less polymorphic than expected ('a' and 'b' unified, etc.). After thinking a while, I sort of understood that >>= is really more polymorphic, i.e., even if it is constraining [s] to be a list (because it is using ++), it really is saying nothing about the contents of the list. It is "output" who's doing the constraint, but, with the very same monad, I could do: output :: [a] -> Accum Int [a] output x = Ac [length x] x or output :: a -> Accum [a] a output x = Ac [[x]] x or whatever. But then I wondered, is there any way to really define data Accum a = Ac [a] a i.e., constraining it to use a for both values, and make a monad from it? Curious, Juanma

Incidentally, it is quite common to define a Monad instance but no Eq instance. (e.g., the IO monad, most parser monads, most state transformer monads, etc.) So you should not interpret the '==' in the monad law as requiring you to define an Eq instance. If you do define an Eq instance, it ought to be reflexive, symmetric and transitive (i.e., an equivalence) if you want functions with Eq constraints to behave in a meaningful way. Also, although there's probably no necessity for your Eq instance to match your notion of equality between computations (i.e., the == used in the monad laws), I think you'll end up very confused if you define an Eq instance which doesn't match in the same way that having Eq on pairs ignore the 2nd field would confuse you. -- Alastair Reid www.haskell-consulting.com
So, the question remains: when the monad laws say that
(return x) >>= f == f x
what is intended in that "=="? Eq."==" for
instance Eq MyCustomMonad where x == y = whatever...
or a more profound kind of equality?

On Thu, 2 Oct 2003 16:09:11 +0100, Alastair Reid
So you should not interpret the '==' in the monad law as requiring you to define an Eq instance.
If you do define an Eq instance, it ought to be reflexive, symmetric and transitive (i.e., an equivalence) if you want functions with Eq constraints to behave in a meaningful way.
Thanks, I understand now. (Incidentally, the == I was defining was an equivalence, AFAICS.)
Also, although there's probably no necessity for your Eq instance to match your notion of equality between computations (i.e., the == used in the monad laws), I think you'll end up very confused if you define an Eq instance which doesn't match in the same way that having Eq on pairs ignore the 2nd field would confuse you.
Sure. I imagine only very specialized monads will need an Eq that doesn't match the equality implicit in the monad laws. As Derek has pointed out, I'm yet far from reaching a point where I should worry about that :) Thanks for your comments, Juanma

As Derek has pointed out, I'm yet far from reaching a point where I should worry about that :)
_If_ you understand Haskell but not monads, I think it is entirely legitimate to start with the implementation and then proceed to the uses. A bottom-up approach instead of a top-down approach. This is the approach of Will Partain's old 'country boys guide to monads' (which I can't find a copy of). He started with examples of non-monadic code where you couldn't see what was going on because of all the 'plumbing' required to make sure you had a supply of fresh names here and a current substitution there and showed how a monad could cleanup the plumbing. Of course, this only works if you've written enough of the right kind of code that the examples make sense... -- Alastair Reid www.haskell-consulting.com
participants (5)
-
Alastair Reid
-
Derek Elkins
-
Juanma Barranquero
-
Juanma Barranquero
-
Marcin 'Qrczak' Kowalczyk