[GHC] #7582: Created thunk gets immediately evaluated
GHC
cvs-ghc at haskell.org
Tue Jan 15 06:31:20 CET 2013
#7582: Created thunk gets immediately evaluated
-----------------------------+----------------------------------------------
Reporter: tibbe | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.6.1 | Keywords:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
Failure: None/Unknown | Blockedby:
Blocking: | Related:
-----------------------------+----------------------------------------------
The following function, taken from the unordered-containers package, is
obviously strict in `go`:
{{{
lookup :: (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
lookup k0 = go h0 k0 0
where
h0 = hash k0
go !_ !_ !_ Empty = Nothing
go h k _ (Leaf hx (L kx x))
| h == hx && k == kx = Just x -- TODO: Split test in two
| otherwise = Nothing
go h k s (BitmapIndexed b v)
| b .&. m == 0 = Nothing
| otherwise = go h k (s+bitsPerSubkey) (A.index v (sparseIndex
b m))
where m = mask h s
go h k s (Full v) = go h k (s+bitsPerSubkey) (A.index v (index h s))
go h k _ (Collision hx v)
| h == hx = lookupInArray k v
| otherwise = Nothing
{-# INLINABLE lookup #-}
}}}
Here's a small test program that uses `lookup`:
{{{
module Test (test) where
import qualified Data.HashMap.Strict as HM
test :: Int -> HM.HashMap Int Int -> Maybe Int
test k m = HM.lookup k m
}}}
And here's part of the Core:
{{{
$slookup :: forall v_aBR. Int -> HashMap Int v_aBR -> Maybe v_aBR
$slookup =
\ (@ v_XBT) (k0_aBU :: Int) ->
let {
w_sM9 :: Hash
w_sM9 =
case defaultSalt of _ { I# x#_aJq ->
case k0_aBU of _ { I# i_aJv ->
case {__pkg_ccall hashable-1.2.0.5 hashable_wang_64 Word#
-> State# RealWorld -> (#
State# RealWorld, Word# #)}_aJu
(xor# (int2Word# x#_aJq) (int2Word# i_aJv)) realWorld#
of _ { (# _, ds1_aJA #) ->
W# ds1_aJA
}
}
} } in
\ (w1_sMl :: HashMap Int v_XBT) ->
case w_sM9 of _ { W# ww_sMb ->
case k0_aBU of _ { I# ww1_sMf ->
$wpoly_go @ v_XBT ww_sMb ww1_sMf 0 w1_sMl
}
}
test :: Int -> HashMap Int Int -> Maybe Int
test =
\ (k_asN :: Int) (m_asO :: HashMap Int Int) ->
$slookup @ Int k_asN m_asO
}}}
Note how `w_sM9`, corresponding to `h0` in the source program, has wedged
itself in-between two lambdas, causing unnecessary allocation. If we put a
bang on `h0` in the definition of `lookup`, we get this much better
looking Core:
{{{
$w$slookup
:: forall v_aBQ. Int# -> HashMap Int v_aBQ -> Maybe v_aBQ
$w$slookup =
\ (@ v_aBQ) (ww_sMt :: Int#) ->
case defaultSalt of _ { I# x#_aJt ->
case {__pkg_ccall hashable-1.2.0.5 hashable_wang_64 Word#
-> State# RealWorld -> (#
State# RealWorld, Word# #)}_aJx
(xor# (int2Word# x#_aJt) (int2Word# ww_sMt)) realWorld#
of _ { (# _, ds1_aJD #) ->
\ (w_sMo :: HashMap Int v_aBQ) ->
$wpoly_go @ v_aBQ ds1_aJD ww_sMt 0 w_sMo
}
}
$slookup :: forall v_aBQ. Int -> HashMap Int v_aBQ -> Maybe v_aBQ
$slookup =
\ (@ v_aBQ) (w_sMr :: Int) ->
case w_sMr of _ { I# ww_sMt -> $w$slookup @ v_aBQ ww_sMt }
test :: Int -> HashMap Int Int -> Maybe Int
test =
\ (k_asM :: Int) (m_asN :: HashMap Int Int) ->
case k_asM of _ { I# ww_sMt -> $w$slookup @ Int ww_sMt m_asN }
}}}
This bothers me. `h0` gets immediately passed to `go`, which is strict.
Why does it get boxed? Why does the extra bang make a difference?
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7582>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list