
#8832: Constant-folding regression wrt `clearBit (bit 0) 0 ` ------------------------------+-------------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.8.1-rc2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Runtime performance bug Unknown/Multiple | Test Case: Difficulty: Unknown | Blocking: Blocked By: | Related Tickets: | ------------------------------+-------------------------------------------- While implementing `zeroBits` (see [83bd2f5fc7e/base]) I noticed that constant folding of the expression `clearBit (bit 0) 0` regressed (and improved at the same time) from GHC 7.6.3 to GHC 7.8.1, specifically, the following module {{{#!haskell {-# LANGUAGE CPP #-} module M where import Data.Bits import Data.Int import Data.Word #define T(s,T) \ s :: T ; \ s = clearBit (bit 0) 0 ; \ T(i,Int) T(i8,Int8) T(i16,Int16) T(i32,Int32) T(i64,Int64) T(w,Word) T(w8,Word8) T(w16,Word16) T(w32,Word32) T(w64,Word64) T(z,Integer) }}} compiled with GHC 7.8.1RC2 results in the following Core output: {{{#!haskell -- GHC 7.8.1RC2 i = I# (andI# 1 (notI# 1)) i8 = I8# 0 i16 = I16# 0 i32 = I32# 0 i64 = I64# 0 w = W# (__word 0) w8 = W8# (__word 0) w16 = W16# (__word 0) w32 = W32# (__word 0) w64 = W64# (__word 0) z2 = $w$cbit 0 z1 = complementInteger z2 z = andInteger z2 z1 }}} Thus, `i` and `z` are not properly constant-folded in GHC 7.8.1RC2. With GHC 7.6.3, however, `i` and `z` were properly folded to `0`: {{{#!haskell -- GHC 7.6.3 i = I# 0 i8 = case $fBitsInt8_$cbit i of _ { I8# x#_aDf -> case $fBitsInt8_$cbit i of _ { I8# x#1_aDr -> I8# (word2Int# (and# (int2Word# x#_aDf) (xor# (int2Word# x#1_aDr) (__word 18446744073709551615)))) } } i16,i32,i64 -- equivalent to i8 w = W# (__word 0) w8 = case $fBitsWord8_$cbit i of _ { W8# x#_aEV -> case $fBitsWord8_$cbit i of _ { W8# x#1_aF5 -> W8# (and# x#_aEV (xor# x#1_aF5 (__word 255))) } } w16,w32,w64 -- equivalent to w8 z = __integer 0 }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8832 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler