Another monad question...

Hi everyone, I've been playing with the parsers decribed in "Monadic Parser Combinators" (http://www.cs.nott.ac.uk/~gmh/bib.html#monparsing) and I've gotten stumped. I'm trying to get comfortable working monadically, so please excuse my ignorance. Here's the relevant portions of my code: data Parser a = Parser { parse :: (String -> [(a, String)]) } instance Monad Parser where return v = Parser (\inp -> [(v, inp)]) par@(Parser p) >>= f = Parser (\inp -> concat [parse (f v) out | (v, out) <- p inp]) instance MonadPlus Parser where mzero = Parser (\inp -> []) p `mplus` q = Parser (\inp -> (parse p inp ++ parse q inp)) item :: Parser Char item = Parser (\inp -> case inp of [] -> [] (x:xs) -> [(x, xs)]) sat :: (Char -> Bool) -> Parser Char sat p = Parser (\inp -> [ (v, out) | (v, out) <- parse item inp, p v]) lower :: Parser Char lower = Parser (\inp -> parse (sat (\x -> 'a' <= x && x <= 'z')) inp) upper :: Parser Char upper = Parser (\inp -> parse (sat (\x -> 'A' <= x && x <= 'Z')) inp) letter :: Parser Char letter = lower `mplus` upper -- word parses everything as [] word :: Parser String word = mzero `mplus` do x <- letter; xs <- word; return (x:xs) As I noted in the code, no matter what inputs I give it,
parse word "blah blah" always returns []. Any ideas where where my misunderstanding is?
David

On Sat, Jul 14, 2007 at 11:26:56PM -0400, David LaPalomento wrote:
I've been playing with the parsers decribed in "Monadic Parser Combinators" (http://www.cs.nott.ac.uk/~gmh/bib.html#monparsing) and I've gotten stumped. I'm trying to get comfortable working monadically, so please excuse my ignorance. Here's the relevant portions of my code:
You don't need to excuse yourself. If you *ever* feel as though you might regret a question, we have failed. The point of this list is for newbies to ask questions and learn!
[reordered]
-- word parses everything as [] word :: Parser String word = mzero `mplus` do x <- letter; xs <- word; return (x:xs)
As I noted in the code, no matter what inputs I give it,
parse word "blah blah" always returns []. Any ideas where where my misunderstanding is?
Your base case is subtly wrong - it should be return [], not mzero. Mzero always fails - mzero `mplus` x = x, by one of the MonadPlus laws.
sat :: (Char -> Bool) -> Parser Char sat p = Parser (\inp -> [ (v, out) | (v, out) <- parse item inp, p v])
lower :: Parser Char lower = Parser (\inp -> parse (sat (\x -> 'a' <= x && x <= 'z')) inp)
upper :: Parser Char upper = Parser (\inp -> parse (sat (\x -> 'A' <= x && x <= 'Z')) inp)
These definitions aren't in the best style; while they are correct, I would prefer to write them as: sat :: (Char -> Bool) -> Parser Char sat p = do { ch <- item ; guard (p ch) ; return ch } lower :: Parser Char lower = sat isLower upper :: Parser Char upper = sat isUpper Stefan

On 7/14/07, Stefan O'Rear
On Sat, Jul 14, 2007 at 11:26:56PM -0400, David LaPalomento wrote:
I've been playing with the parsers decribed in "Monadic Parser Combinators" (http://www.cs.nott.ac.uk/~gmh/bib.html#monparsing) and I've gotten stumped. I'm trying to get comfortable working monadically, so please excuse my ignorance. Here's the relevant portions of my code:
You don't need to excuse yourself. If you *ever* feel as though you might regret a question, we have failed. The point of this list is for newbies to ask questions and learn!
[reordered]
-- word parses everything as [] word :: Parser String word = mzero `mplus` do x <- letter; xs <- word; return (x:xs)
As I noted in the code, no matter what inputs I give it,
parse word "blah blah" always returns []. Any ideas where where my misunderstanding is?
Your base case is subtly wrong - it should be return [], not mzero. Mzero always fails - mzero `mplus` x = x, by one of the MonadPlus laws.
Ah! So here's another quick question: if mzero is the identity element, why isn't it part of the Monad class? Correct me if I'm wrong but aren't Monads (in the mathematical sense) required an identity element by definition?
sat :: (Char -> Bool) -> Parser Char
sat p = Parser (\inp -> [ (v, out) | (v, out) <- parse item inp, p v])
lower :: Parser Char lower = Parser (\inp -> parse (sat (\x -> 'a' <= x && x <= 'z')) inp)
upper :: Parser Char upper = Parser (\inp -> parse (sat (\x -> 'A' <= x && x <= 'Z')) inp)
These definitions aren't in the best style; while they are correct, I would prefer to write them as:
sat :: (Char -> Bool) -> Parser Char sat p = do { ch <- item ; guard (p ch) ; return ch }
lower :: Parser Char lower = sat isLower
upper :: Parser Char upper = sat isUpper
Thanks for the style tips. Your definition is much clearer (as well as more succinct). Stefan Thanks again! David

On Sun, Jul 15, 2007 at 12:03:06AM -0400, David LaPalomento wrote:
On 7/14/07, Stefan O'Rear
wrote: Your base case is subtly wrong - it should be return [], not mzero. Mzero always fails - mzero `mplus` x = x, by one of the MonadPlus laws.
Ah! So here's another quick question: if mzero is the identity element, why isn't it part of the Monad class? Correct me if I'm wrong but aren't Monads (in the mathematical sense) required an identity element by definition?
You're probably confusing Monads with Monoids. Monoid: * Concept from abstract algebra * A set Ty, a distinguished element mempty :: Ty, and a binary operator mappend :: Ty -> Ty -> Ty * mempty `mappend` x = x * x `mappend` mempty = x * a `mappend` (b `mappend` c) = (a `mappend` b) `mappend` c Monad: * Concept from category theory * A category C (assumed to be Haskell objects in the type class) * A functor F :: C -> C * Two natural transformations η :: F^0 -> F^1, μ :: F^2 -> F^1 * the monad laws MonadPlus: * Monads that are also monoids * mappend, mempty named mplus, mzero to avoid conflicts * (OK it was the other way around, monadplus came first) I've heard that Monads are in some way like Monoids, hence the name. But I don't understand the explanation yet myself :( Stefan

On Saturday 14 July 2007, Stefan O'Rear wrote:
On Sun, Jul 15, 2007 at 12:03:06AM -0400, David LaPalomento wrote:
On 7/14/07, Stefan O'Rear
wrote: Your base case is subtly wrong - it should be return [], not mzero. Mzero always fails - mzero `mplus` x = x, by one of the MonadPlus laws.
Ah! So here's another quick question: if mzero is the identity element, why isn't it part of the Monad class? Correct me if I'm wrong but aren't Monads (in the mathematical sense) required an identity element by definition?
You're probably confusing Monads with Monoids.
Monoid: * Concept from abstract algebra * A set Ty, a distinguished element mempty :: Ty, and a binary operator mappend :: Ty -> Ty -> Ty * mempty `mappend` x = x * x `mappend` mempty = x * a `mappend` (b `mappend` c) = (a `mappend` b) `mappend` c
Monad: * Concept from category theory * A category C (assumed to be Haskell objects in the type class) * A functor F :: C -> C * Two natural transformations η :: F^0 -> F^1, μ :: F^2 -> F^1 * the monad laws
MonadPlus: * Monads that are also monoids * mappend, mempty named mplus, mzero to avoid conflicts * (OK it was the other way around, monadplus came first)
I've heard that Monads are in some way like Monoids, hence the name. But I don't understand the explanation yet myself :(
A regular algebra monoid (in the context of category theory) is a triple (M, e : 1 -> M, * : M * M -> M), where 1 is an arbitrary one-element set and M * M is the regular cartesian product, satisfying certain laws. Categorical monoids generalize this in two ways: first, the category chosen doesn't have to be Set, and second the product operator doesn't have to be the cartesian product, but can be an arbitrary bifunctor, as long as that bifunctor is itself a monoid. So, if C is a category, the functor category C^C is a monoidal category with the identity functor in for the terminal object operator and composition in for the product, and a monoid in that category is a monad in C. Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs

SOR> I've heard that Monads are in some way like Monoids, hence the SOR> name. But I don't understand the explanation yet myself :( Just compare: Monoid: a set M with maps ident: M^0 -> M and product: M^2 -> M (here M^0 is a one-element set) Monad: a functor M with natural transformations return: M^0 -> M and join: M^2 -> M (here M^0 is an identity functor) If you extend the definition of monoid to arbitrary "monoidal category", which means, arbitrary category with identity object I and bifunctor "\times", such that I \times X ~ X \times I ~ X and (X \times Y) \times Z ~ X \times (Y \times Z), and then apply it to the category of endofunctors with identity functor as I and composition as \times, then you get a monad.

On 7/15/07, Miguel Mitrofanov
SOR> I've heard that Monads are in some way like Monoids, hence the SOR> name. But I don't understand the explanation yet myself :(
Just compare:
Monoid: a set M with maps ident: M^0 -> M and product: M^2 -> M
(here M^0 is a one-element set)
Monad: a functor M with natural transformations return: M^0 -> M and join: M^2 -> M
(here M^0 is an identity functor)
I had forgotten that the identity element was from M^0 -> M. In my gut I always feel it should be something more like M -> M, though I realize (as Stefan pointed out) I'm thinking too much in set-terms and not in category-terms. David

DL> Ah! So here's another quick question: if mzero is the identity DL> element, why isn't it part of the Monad class? Correct me if I'm DL> wrong but aren't Monads (in the mathematical sense) required an DL> identity element by definition? Yes, they do. And this identity element is called "return" in Haskell, not "mzero". Consider, for example, the monad (_,M), which maps each object X to the product of X and M, with M being some chosen monoid. In this case, "return" is a map from X to (X,M), and return(a) = (a,e), where e is the identity element of M. In fact, this monad is called "Writer" in Haskell.
participants (4)
-
David LaPalomento
-
Jonathan Cast
-
Miguel Mitrofanov
-
Stefan O'Rear