[commit: packages/base] ghc-7.8: Workaround failed constant-folding for zeroBits (591142f)
git at git.haskell.org
git at git.haskell.org
Sat Mar 1 13:53:21 UTC 2014
Repository : ssh://git@git.haskell.org/base
On branch : ghc-7.8
Link : http://ghc.haskell.org/trac/ghc/changeset/591142f8aead4c28bdaa5656d79e6dc38273e685/base
>---------------------------------------------------------------
commit 591142f8aead4c28bdaa5656d79e6dc38273e685
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date: Sat Mar 1 14:45:48 2014 +0100
Workaround failed constant-folding for zeroBits
For some reason GHC fails to constant fold `zeroBits :: Int` and
`zeroBits :: Integer`; `ghc -show-iface` shows
$fBitsInt_$czeroBits :: GHC.Types.Int
{- Strictness: m,
Unfolding: (GHC.Types.I# (GHC.Prim.andI# 1 (GHC.Prim.notI# 1))) -}
Otoh, constant-folding works as expected, reducing `zeroBits` to 0 constant
for the other integer-types (= {Word,Int}{8,16,32,64}` and `Word`). So this
quickfix is actually just treating the symptom rather than the cause.
Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org>
(cherry picked from commit 2dbfcd70e53845d9119389cecc88411b47b70644)
>---------------------------------------------------------------
591142f8aead4c28bdaa5656d79e6dc38273e685
Data/Bits.hs | 3 +++
1 file changed, 3 insertions(+)
diff --git a/Data/Bits.hs b/Data/Bits.hs
index e771624..28cd024 100644
--- a/Data/Bits.hs
+++ b/Data/Bits.hs
@@ -363,6 +363,8 @@ instance Bits Int where
{-# INLINE bit #-}
{-# INLINE testBit #-}
+ zeroBits = 0
+
bit = bitDefault
testBit = testBitDefault
@@ -437,6 +439,7 @@ instance Bits Integer where
| otherwise = shiftRInteger x (negateInt# i#)
testBit x (I# i) = testBitInteger x i
+ zeroBits = 0
bit = bitDefault
popCount = popCountDefault
More information about the ghc-commits
mailing list