
You have "unguarded" recursion between expr and parseAdd. When you try to
parse an expression, one option is to parse an addition. When you go to do
that, you look to parse an expression followed by other stuff. Thanks to
the structure of ReadP, I *believe* this will actually work ... if you just
take the first result. But if you keep going, you will definitely find
yourself stuck.
On Wed, Sep 25, 2019, 10:56 AM Henry Laxen
Dear Haskell gurus,
There has to be something very simple that I am misunderstanding here. I have tried sticking in trace statement, using the ghci debugger, but it just makes no sense to me. Please tell me what I am missing.
Best wishes, Henry Laxen
--------------------------------------------------------------------------------
module S where
import Text.ParserCombinators.ReadP import Data.Char
data Exp = Num Int | Add Exp Exp deriving (Eq, Show)
expr :: ReadP Exp expr = do e <- (parseNumber +++ parseAdd) return e
parseAdd :: ReadP Exp parseAdd = do e1 <- expr _ <- char '+' e2 <- expr return (Add e1 e2)
parseNumber :: ReadP Exp parseNumber = do ds <- (munch1 isDigit) return . Num . read $ ds
parse s = let parses = (readP_to_S expr) s in case parses of (p : _) -> fst (last parses) _ -> error "parse error" main = do print $ parse "1"
λ> main *** Exception: stack overflow λ> parse "1+2" *** Exception: stack overflow
--------------------------------------------------------------------------------
-- Nadine and Henry Laxen The rest is silence Villa Alta #6 Calle Gaviota #10 Never try to teach a pig to sing Chapala It wastes your time +52 (376) 765-3181 And it annoys the pig _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.