#2823: Another arity expansion bug
---------------------------------------+------------------------------------
Reporter: simonpj | Owner:
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
---------------------------------------+------------------------------------
Roman reports: I've finally tracked down one big optimisation problem (at
least, I
think it is big). Here is a small example:
{{{
foo :: Eq a => a -> a
{-# NOINLINE foo #-}
foo x = x
bar :: Eq a => a -> a
{-# INLINE [1] bar #-}
bar x = let p = foo (x,x)
q = foo (p,p) in fst (fst q)
}}}
For some reason, bar's arity is 1 which is wrong. If we replace `(fst (fst
q))` by `(fst p)`, it gets the correct arity of 2.
The problem is that because of the arity, `(bar $dEq)` is then floated
out as far as possible which breaks fusion if we have RULES for bar.
In case you are interested, this affects `splitSD` in `dph-prim-par/Data/
Array/Parallel/Unlifted/Distributed/Arrays.hs`. I haven't noticed this
previously because we didn't use segmented arrays as much.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2823>
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