
#7596: Opportunity to improve CSE -------------------------------------+------------------------------------ Reporter: simonpj | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by nomeata): As suggested, I made CSE much more aggressive by floating out much more expressions, so that `Just x` is CSE’ed in {{{#!haskell module T7596 where f :: Maybe Int -> (Bool, Bool) f Nothing = (True, True) f _ = (False, True) {-# NOINLINE f #-} g :: Maybe Int -> (Bool, Bool) g Nothing = (True, True) g _ = (False, True) {-# NOINLINE g #-} foo :: Int -> Bool foo x = case f (Just x) of (a, b) -> case g (Just x) of (p,q) -> a && b && p && q }}} It hardy helps, though: {{{ Min -0.6% -14.1% -33.0% -33.9% -20.0% Max +0.6% +178.2% +85.2% +86.1% +50.0% Geometric Mean -0.2% +14.1% +13.1% +12.5% +0.8% }}} But that is no surprise; it CSE’s dictionary access functions like `lvl1 = GHC.Classes.<= @ a sc` – not much to win here. Preventing aggresive floating of partial applications... slightly better, but still horrible: {{{ Min -0.7% -14.1% -53.0% -55.4% -20.0% Max +0.5% +178.2% +25.9% +25.9% +50.0% Geometric Mean -0.4% +13.6% -16.8% -18.1% +0.6% }}} For example `spectral/sorting`: `+123.1%` increase, due to the expression `reverse rev` shared in this code {{{#!haskell insertSort [] = [] insertSort (x:xs) = trins [] [x] xs where trins :: Ord a => [a] -> [a] -> [a] -> [a] trins rev [] (y:ys) = trins [] ((reverse rev) ++ [y]) ys trins rev xs [] = (reverse rev) ++ xs trins rev (x:xs) (y:ys) | x < y = trins (x:rev) xs (y:ys) | True = trins [] (reverse rev ++ (y:x:xs)) ys }}} Clearly CSE’ing something from different branches can never be a win (besides potentially code size). But that is something the current CSE code cannot check, right? And even in the example from the ticket description, it is not stupid not to do CSE: With some luck the first `I#` allocated will be free before the next GC run, causing no copying. After CSE it stays alive for longer, causing more work. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/7596#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler