#1544: Derived Read instances for recursive datatypes with infix constructors
are
too inefficient
-------------------------------------+--------------------------------------
Reporter: [EMAIL PROTECTED] | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 6.8 branch
Component: Compiler | Version: 6.6.1
Severity: normal | Resolution:
Keywords: | Difficulty: Unknown
Os: Unknown | Testcase:
Architecture: Unknown |
-------------------------------------+--------------------------------------
Comment (by simonpj):
From Koen:
It was as I feared: Even the backtracking parser from the Haskell98
report has the exponential behavior you describe!
I took the code from Figure 8 here:
http://haskell.org/onlinereport/derived.html
And copied the relevant bits into a file:
{{{
infixr 5 :^:
data Tree a = Leaf a | Tree a :^: Tree a
deriving ( Eq, Ord, Show )
instance (Read a) => Read (Tree a) where
readsPrec d r = readParen (d > up_prec)
(\r -> [(u:^:v,w) |
(u,s) <- readsPrec (up_prec+1) r,
(":^:",t) <- lex s,
(v,w) <- readsPrec (up_prec+1) t]) r
++ readParen (d > app_prec)
(\r -> [(Leaf m,t) |
("Leaf",s) <- lex r,
(m,t) <- readsPrec (app_prec+1) s]) r
up_prec = 5 :: Int -- Precedence of :^:
app_prec = 10 :: Int -- Application has precedence one more than
-- the most tightly-binding operator
}}}
And then added the following:
{{{
main = print (read s :: Tree Int)
where
s = "(((((((((((((((((((((((((((((((((Leaf 3"
++ ")))))))))))))))))))))))))))))))))"
}}}
Neither Hugs nor GHC can evaluate this expression in reasonable time.
And (probably) neither would the old GHC without my ReadP/ReadPrec
stuff.
Conclusion: We need to be smarter when generating parsers for
datatypes with infix operators, ''independent of'' the underlying
parsing technology. In order to make an efficient parser for a grammar
with binary operators, one ''must'' massage the grammar to remove
left-recursion from the grammar.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/1544>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs