#2581: Record selectors not being inlined
-----------------------------------------+----------------------------------
Reporter: simonpj | Owner: simonpj
Type: run-time performance bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 6.8.3
Severity: normal | Keywords:
Difficulty: Unknown | Testcase:
Architecture: Unknown | Os: Unknown
-----------------------------------------+----------------------------------
Bryan O'Sullivan write: This comes from the bloomfilter package on
Hackage.
{{{
type Hash = Word32
data MBloom s a = MB {
hashMB :: {-# UNPACK #-} !(a -> [Hash])
, shiftMB :: {-# UNPACK #-} !Int
, maskMB :: {-# UNPACK #-} !Int
, bitArrayMB :: {-# UNPACK #-} !(STUArray s Int Hash)
}
insertMB :: MBloom s a -> a -> ST s ()
{-# SPECIALIZE insertMB
:: MBloom s SB.ByteString -> SB.ByteString -> ST s () #-}
insertMB mb elt = do
let mu = bitArrayMB mb
forM_ (hashesM mb elt) $ \(word :* bit) -> do
old <- unsafeRead mu word
unsafeWrite mu word (old .|. (1 `shiftL` bit))
}}}
If I look at the Core generated for any version of `insertMB`, specialised
or not, I see the following. Note the non-inlined uses of `maskMB` and
`bitArrayMB`. (I export `bitArrayMB` from the module, but not `maskMB`.)
{{{
Data.BloomFilter.insertMB =
\ (@ s_a2ta)
(@ a_a2tb)
(mb_X2n2 :: Data.BloomFilter.MBloom s_a2ta a_a2tb)
(elt_X2n4 :: a_a2tb) ->
__letrec {
a2_s3g9 :: [Word32]
-> State# s_a2ta
-> (# State# s_a2ta, () #)
[Arity 2
a2_s3g9 =
\ (ds_a2S9 :: [Word32]) (eta_s37Y :: State# s_a2ta) ->
case ds_a2S9 of wild_a2Sa {
[] -> (# eta_s37Y, () #);
: y_a2Se ys_a2Sf ->
case y_a2Se of wild1_a2Io { W32# x#_a2Iq ->
case Data.BloomFilter.maskMB @ s_a2ta @ a_a2tb mb_X2n2
of wild11_a2T0 { I# y#_a2T2 ->
case Data.BloomFilter.bitArrayMB @ s_a2ta @ a_a2tb mb_X2n2
of wild2_a2P0
{ Data.Array.Base.STUArray ds2_a2P2 ds3_a2P3 ds4_a2P4
marr#_a2P5 -> [......]
}}}
If I switch to non-record syntax, the inliner does the right thing.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2581>
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