
#8766: length [Integer] is twice as slow but length [Int] is 10 times faster --------------------------------------------+------------------------------ Reporter: George | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime performance bug | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Comment (by nomeata): hvr, your analysis is a bit misleading: In GHC 7.6.3 we have {{{#!haskell intlen1 :: [Integer] intlen1 = enumDeltaToInteger intlen4 intlen4 intlen2 intlen :: Int intlen = case $wlen @ Integer intlen1 0 of ww { __DEFAULT -> I# ww } }}} and in 7.9 we have {{{#!haskell intlen1 :: Int# -> Int intlen1 = enumDeltaToIntegerFB @ (Int# -> Int) (incLen @ Integer) I# intlen4 intlen4 intlen2 intlen :: Int intlen = intlen1 0 }}} Note how the `intlen1` do not directly correspond to each other. So we have a case of successful list fusion that does ''not'' speed up the program. The two `enumDeltaToInteger...` functions (at the end of source:base/GHC/Enum.lhs) are almost the same; both call auxiliary functions, the only difference is whether `:` is used, or an explicitly passed `c`. I believe the problem is that we are using `enumDeltaToIntegerFB` in a higher order way (note the `Int# -> Int`), which allocates partial function applications – basically the same that happens when `foldl` is implemented with `foldr` (#7994). The fix for that would to make sure that stuff is inlined far enough for the `go` from `up_fb` can be visible (as it is for `Int` in comment:1). It could be related to this comment with `Int` (or not, because inlining does not even go that far): {{{#!haskell {-# INLINE [0] eftIntFB #-} eftIntFB :: (Int -> r -> r) -> r -> Int# -> Int# -> r eftIntFB c n x0 y | isTrue# (x0 ># y) = n | otherwise = go x0 where go x = I# x `c` if isTrue# (x ==# y) then n else go (x +# 1#) -- Watch out for y=maxBound; hence ==, not > -- Be very careful not to have more than one "c" -- so that when eftInfFB is inlined we can inline -- whatever is bound to "c" }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8766#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler