
#15619: List comprehension seems to prevent some rewrite rules to fire -------------------------------------+------------------------------------- Reporter: nobrakal | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Other Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Hi, Consider {{{#!hs module Test (problem, noProblem) where data Relation = Relation Int vertex :: Int -> Relation vertex = Relation {-# NOINLINE vertex #-} star :: Int -> [Int] -> Relation star x [] = vertex x star x xs = vertex x {-# INLINE star #-} transpose :: Relation -> Relation transpose (Relation e) = Relation (-e) {-# NOINLINE transpose #-} {-# RULES "transpose/vertex" forall x. transpose (vertex x) = vertex x #-} -- The "transpose/vertex" rule does not fire here problem :: Relation problem = transpose $ star 0 [1..2] -- The "transpose/vertex" rule does fire here noProblem :: Relation noProblem = transpose $ star 0 [1,2] }}} `problem` and `noProblem` seems equivalents, but in the first the rewrite rule does not fire. * Commenting `noProblem` and compiling with "-ddump-rule-firings" gives: {{{ [1 of 1] Compiling Test ( Test.hs, Test.o ) Rule fired: Class op negate (BUILTIN) Rule fired: Class op enumFromTo (BUILTIN) Rule fired: eftIntList (GHC.Enum) }}} * Commenting `problem` and compiling with "-ddump-rule-firings" gives: {{{ [1 of 1] Compiling Test ( Test.hs, Test.o ) Rule fired: Class op negate (BUILTIN) Rule fired: transpose/vertex (Test) }}} It is a very "borderline" example (refined from a more complex one): * changing the `data` to a `newtype` solves the problem * removing the dumb pattern-match on the list in `star` also solves the problem I suspect the list comprehension to be the problem, but I am not sure at all (I am not sure if the whole thing is a real bug indeed). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15619 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler