Hello Ian, Monday, October 9, 2006, 6:51:46 PM, you wrote:
> * Inline shift in GHC's Bits instances for {Int,Word}{,8,16,32,64} > M ./Data/Bits.hs +2 > M ./GHC/Int.hs +12 > M ./GHC/Word.hs +14 i think that it will be not enough for proper specialization of constant-width shifts. look for example at the following code: instance Bits Int8 where {-# INLINE shift #-} (I8# x#) `shift` (I# i#) | i# >=# 0# = I8# (narrow8Int# (x# `iShiftL#` i#)) | otherwise = I8# (x# `iShiftRA#` negateInt# i#) here we call iShiftL# and iShiftRA# operations. but they are not primitives! GHC.Base contains their definitions: iShiftL# :: Int# -> Int# -> Int# a `iShiftL#` b | b >=# WORD_SIZE_IN_BITS# = 0# | otherwise = a `uncheckedIShiftL#` b iShiftRA# :: Int# -> Int# -> Int# a `iShiftRA#` b | b >=# WORD_SIZE_IN_BITS# = if a <# 0# then (-1#) else 0# | otherwise = a `uncheckedIShiftRA#` b as you can see, these are not inlined, so we probably get the same problems. i think that we need to add inlining either to iShiftL#/iShiftRA# definitions or usage sites -- Best regards, Bulat mailto:[EMAIL PROTECTED] _______________________________________________ Cvs-libraries mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/cvs-libraries