#5152: GHC generates poor code for large 64-bit literals
---------------------------------+------------------------------------------
Reporter: bos | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.0.3 | Keywords:
Testcase: | Blockedby:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: Runtime performance bug
---------------------------------+------------------------------------------
I have a very simple test module:
{{{
module Word64 where
import Data.Word (Word64)
a :: Word64
a = 0x9ddfea08eb382d69
}}}
If I compile this module with a 64-bit version of GHC, I find that GHC is
actually generating for {{{a}}} an {{{Integer}}} like so:
{{{
a2 :: Integer
a2 = S# 2152696470933351786
a1 :: Integer
a1 = S# 9223372036854775807
a :: Word64
a =
case plusInteger a2 a1 of _ {
S# i_atz ->
W64# (int2Word# i_atz);
J# s_au0 d_au1 ->
case integer2Word# s_au0 d_au1
of ww_au3 { __DEFAULT ->
W64# ww_au3
}
}
}}}
This is bad because it means that {{{a}}} is always boxed.
If I attempt to manually inline such a definition, the code gets
dramatically worse:
{{{
b :: Word64
b = 0xc3a5c85c97cb3127
{-# INLINE b #-}
}}}
Here's some generated core from a hot inner loop of a 64-bit hash
function:
{{{
case lvl3_r1aA of _ {
Type.S# i_aVp ->
W64#
(xor#
(timesWord#
(or#
(uncheckedShiftL# ww10_aUE 22)
(uncheckedShiftRL# ww10_aUE 42))
(int2Word# i_aVp))
ww5_s17Y);
Type.J# s_aVO d_aVP ->
case GMP.Internals.integer2Word# s_aVO d_aVP
of ww11_aVR { __DEFAULT ->
W64#
(xor#
(timesWord#
(or#
(uncheckedShiftL# ww10_aUE 22)
(uncheckedShiftRL# ww10_aUE 42))
ww11_aVR)
ww5_s17Y)
}
} } in
}}}
We can see that GHC does case inspection on an {{{Integer}}}, then some
casting and boxing on the result. This destroys performance of code that
otherwise ought to be able to run from registers without any allocation at
all.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5152>
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