#4463: CORE notes break optimisation
---------------------------------+------------------------------------------
Reporter: rl | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.1 | Keywords:
Testcase: | Blockedby:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: Runtime performance bug
---------------------------------+------------------------------------------
I think at some point we decided that Core notes shouldn't affect
optimisation. Here is a case where they do:
{{{
module Foo where
foo :: Int -> Int
{-# INLINE [1] foo #-}
foo x = x+1
{-# RULES "foo/foo" forall x. foo (foo x) = x #-}
}}}
{{{
module Bar where
import Foo
bar :: Int -> Int -> Int
bar x y = foo ({-# CORE "note" #-} x `seq` foo y)
}}}
When compiled with -O2, the rule doesn't fire with the note but does fire
without it. This is the Core with the note:
{{{
Bar.bar =
\ (x_aaw :: GHC.Types.Int) (y_aax :: GHC.Types.Int) ->
Foo.foo
(__core_note "note"
(case x_aaw of _ { GHC.Types.I# _ -> Foo.foo y_aax }))
}}}
For the rule to fire, GHC must move the seq to the outside but because of
the note, it doesn't.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4463>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs