[GHC] #8508: Inlining Unsaturated Function Applications

#8508: Inlining Unsaturated Function Applications ------------------------------+-------------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.2 Keywords: | Operating System: Linux Architecture: x86_64 | Type of failure: Runtime performance bug (amd64) | Test Case: Difficulty: Unknown | Blocking: Blocked By: | Related Tickets: | ------------------------------+-------------------------------------------- After trying a simple test, I noticed some strange performance results from stylistic changes to the code. For example, {{{#!haskell import qualified Data.Vector.Unboxed as U {-# INLINE f #-} f :: U.Vector Int -> U.Vector Int -> U.Vector Int f = U.zipWith (+) -- version 1 --f x = U.zipWith (+) x -- version 2 --f x = (U.zipWith (+) x) . id -- version 3 --f x y = U.zipWith (+) x y -- version 4 main = do let iters = 100 dim = 221184 y = U.replicate dim 0 :: U.Vector Int let ans = iterate (f y) y !! iters putStr $ (show $ U.foldl1' (+) ans) }}} Versions 1 and 2 of `f` run in 1.6 seconds, while versions 3 and 4 run in 0.09 seconds (with vector-0.10.9.1 and GHC 7.6.2, compiling with -O2). According to an answer on the Vector trac (link below), this problem is because GHC only inlines on saturated function applications. Is there any way to expand the cases when GHC inlines to avoid having coding style affect performance? * [https://github.com/haskell/vector/issues/4 Vector Trac] -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8508 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8508: Inlining Unsaturated Function Applications --------------------------------------------+------------------------------ Reporter: crockeea | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.6.2 Resolution: duplicate | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Runtime performance bug | (amd64) Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Changes (by simonpj): * status: new => closed * resolution: => duplicate Comment: Dup of #8508. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8508#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC