[Haskell-cafe] Another monad question...
David LaPalomento
dlapalomento at gmail.com
Sat Jul 14 23:26:56 EDT 2007
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
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20070714/13573641/attachment.htm
More information about the Haskell-Cafe
mailing list