#5615: ghc produces poor code for `div` with constant powers of 2.
---------------------------------+------------------------------------------
Reporter: Lennart | Owner: daniel.is.fischer
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.2.1
Keywords: | Testcase:
Blockedby: | Difficulty:
Os: Unknown/Multiple | Blocking:
Architecture: x86 | Failure: None/Unknown
---------------------------------+------------------------------------------
Comment(by simonmar):
From this input:
{{{
module Foo where
foo :: Int -> Int
foo x = x `div` 64
}}}
With -O2 we get as far as a call to `GHC.Base.divInt#`:
{{{
Foo.foo =
\ (x_abl :: GHC.Types.Int) ->
case x_abl of _ { GHC.Types.I# ww_awV ->
case GHC.Base.divInt# ww_awV 64 of ww1_ax3 { __DEFAULT ->
GHC.Types.I# ww1_ax3
}
}
}}}
but `divInt#` wasn't inlined:
{{{
Considering inlining: GHC.Base.divInt#
arg infos [TrivArg, ValueArg]
uf arity 2
interesting continuation ArgCtxt False
some_benefit True
is exp: True
is cheap: True
guidance IF_ARGS [0 0] 139 0
discounted size = 109
ANSWER = NO
}}}
And `divInt#` has this unfolding:
{{{
435aa24ba2ad252f2b1992da3e8faa90
divInt# :: GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int#
{- Arity: 2, HasNoCafRefs, Strictness: LL,
Unfolding: (\ x# :: GHC.Prim.Int# y# :: GHC.Prim.Int# ->
case GHC.Prim.># x# 0 of wild {
GHC.Types.False
-> case GHC.Prim.<# x# 0 of wild1 {
GHC.Types.False -> GHC.Prim.quotInt# x# y#
GHC.Types.True
-> case GHC.Prim.># y# 0 of wild2 {
GHC.Types.False -> GHC.Prim.quotInt# x# y#
GHC.Types.True
-> case GHC.Prim.quotInt#
(GHC.Prim.+# x# 1)
y# of wild3 { DEFAULT ->
GHC.Prim.-# wild3 1 } } }
GHC.Types.True
-> case GHC.Prim.<# y# 0 of wild1 {
GHC.Types.False
-> case GHC.Prim.<# x# 0 of wild2 {
GHC.Types.False -> GHC.Prim.quotInt# x# y#
GHC.Types.True
-> case GHC.Prim.># y# 0 of wild3 {
GHC.Types.False -> GHC.Prim.quotInt#
x# y#
GHC.Types.True
-> case GHC.Prim.quotInt#
(GHC.Prim.+# x# 1)
y# of wild4 { DEFAULT ->
GHC.Prim.-# wild4 1 } } }
GHC.Types.True
-> case GHC.Prim.quotInt#
(GHC.Prim.-# x# 1)
y# of wild2 { DEFAULT ->
GHC.Prim.-# wild2 1 } } }) -}
}}}
I'm rather surprised it has such a large size, since it is mostly primops
and inline cases. I suspect we're counting too much for those cases, they
ought to look cheap because they're inline (not evals). And there ought
to be a big discount for that constant argument.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5615#comment:4>
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