#2940: Do CSE after CorePrep
---------------------------------------+------------------------------------
  Reporter:  simonpj                   |          Owner:  simonpj         
      Type:  run-time performance bug  |         Status:  new             
  Priority:  normal                    |      Milestone:                  
 Component:  Compiler                  |        Version:  6.10.1          
  Severity:  normal                    |       Keywords:                  
Difficulty:  Unknown                   |       Testcase:                  
        Os:  Unknown/Multiple          |   Architecture:  Unknown/Multiple
---------------------------------------+------------------------------------
 Common sub-expression analysis is deliberately conservative, but it's
 really ''too'' conservative: we are missing obvious opportunities.
 Consider
 {{{
 {-# OPTIONS_GHC -XBangPatterns -XMagicHash #-}

 module Foo where

 import GHC.Base

 -- CorePrep evaluates (reverse xs) twice
 f xs = let !v1 = reverse (reverse xs)
            !v2 = filter id (reverse xs)
        in (v1, v2)

 -- Even CSE inside CorePrep would not get this right;
 -- the strict evaluation of (reverse xs) doesn't scope
 -- over the non-strict version
 g xs = reverse (reverse xs) ++ filter id (reverse xs)


 -- Duplicate evaluation of (x +# 1#)
 h :: Int# -> ( Int, Int )
 h x = ( I# (x +# 1#), I# ((x +# 1#) *# 2#) )
 }}}
 If you compile this you'll see that there are obvious missed CSE
 opportunities in `f`, `g` and `h`; but they only show up after `CorePrep`.

 I guess the right thing is to CSE after `CorePrep`, but then CSE would
 have to maintain the `CorePrep` invariants, which isn't trivial.
 Something to think about.

 Simon

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2940>
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

Reply via email to