[GHC] #12354: Word foldl' isn't optimized as well as Int foldl'
GHC
ghc-devs at haskell.org
Fri Jul 1 07:46:40 UTC 2016
#12354: Word foldl' isn't optimized as well as Int foldl'
-------------------------------------+-------------------------------------
Reporter: kjslag | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by nomeata):
As pointed out by dfeuer on stackexchange, the `Enum` instance for `Int`
is better than the one for `Word`:
`Int`:
{{{
instance Enum Int where
{-# INLINE enumFromTo #-}
enumFromTo (I# x) (I# y) = eftInt x y
{-# RULES
"eftInt" [~1] forall x y. eftInt x y = build (\ c n -> eftIntFB c n
x y)
"eftIntList" [1] eftIntFB (:) [] = eftInt
#-}
{- Note [How the Enum rules work]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
* Phase 2: eftInt ---> build . eftIntFB
* Phase 1: inline build; eftIntFB (:) --> eftInt
* Phase 0: optionally inline eftInt
-}
{-# NOINLINE [1] eftInt #-}
eftInt :: Int# -> Int# -> [Int]
-- [x1..x2]
eftInt x0 y | isTrue# (x0 ># y) = []
| otherwise = go x0
where
go x = I# x : if isTrue# (x ==# y)
then []
else go (x +# 1#)
{-# 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"
}}}
Now `Word` actually uses the implementation for `Integer`
{{{
enumFromTo n1 n2 = map integerToWordX [wordToIntegerX n1 ..
wordToIntegerX n2]
}}}
which uses
{{{
instance Enum Integer where
enumFromTo x lim = enumDeltaToInteger x 1 lim
}}}
Now `enumDeltaToInteger` has rewrite rules set up, but it turns out that
`Word`’s `enumFromTo` is never inlined, so this setup has no chance of
fusing here.
Inlining this function into my test code causes `fold/build` to fire,
cutting down allocation severely, but the conversion from and to `Integer`
remains.
One could of course write similar hand-written code such as for `Int` also
for `Word`. But what about `Word8`, `Word16`, `Word32` and `Word64` then?
Where does it stop?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12354#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list