X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=GHC%2FWord.hs;h=9d3e1a6ae717ff90f8c0f15d5fdd27fdaba68fd7;hb=41e8fba828acbae1751628af50849f5352b27873;hp=99b25ba19229d80adbfbcab464f67600613276f5;hpb=258f37c7ef4af4c1ac1e9bf6dfedb53dd8a4c0e9;p=ghc-base.git diff --git a/GHC/Word.hs b/GHC/Word.hs index 99b25ba..9d3e1a6 100644 --- a/GHC/Word.hs +++ b/GHC/Word.hs @@ -1,5 +1,6 @@ -{-# OPTIONS_GHC -XNoImplicitPrelude #-} +{-# LANGUAGE CPP, NoImplicitPrelude, BangPatterns, MagicHash #-} {-# OPTIONS_HADDOCK hide #-} + ----------------------------------------------------------------------------- -- | -- Module : GHC.Word @@ -41,6 +42,8 @@ import GHC.Real import GHC.Read import GHC.Arr import GHC.Show +import GHC.Err +import GHC.Float () -- for RealFrac methods ------------------------------------------------------------------------ -- Helper functions @@ -115,29 +118,29 @@ instance Enum Word where enumFromThenTo = integralEnumFromThenTo instance Integral Word where - quot x@(W# x#) y@(W# y#) + quot (W# x#) y@(W# y#) | y /= 0 = W# (x# `quotWord#` y#) | otherwise = divZeroError - rem x@(W# x#) y@(W# y#) + rem (W# x#) y@(W# y#) | y /= 0 = W# (x# `remWord#` y#) | otherwise = divZeroError - div x@(W# x#) y@(W# y#) + div (W# x#) y@(W# y#) | y /= 0 = W# (x# `quotWord#` y#) | otherwise = divZeroError - mod x@(W# x#) y@(W# y#) + mod (W# x#) y@(W# y#) | y /= 0 = W# (x# `remWord#` y#) | otherwise = divZeroError - quotRem x@(W# x#) y@(W# y#) + quotRem (W# x#) y@(W# y#) | y /= 0 = (W# (x# `quotWord#` y#), W# (x# `remWord#` y#)) | otherwise = divZeroError - divMod x@(W# x#) y@(W# y#) + divMod (W# x#) y@(W# y#) | y /= 0 = (W# (x# `quotWord#` y#), W# (x# `remWord#` y#)) | otherwise = divZeroError toInteger (W# x#) | i# >=# 0# = smallInteger i# | otherwise = wordToInteger x# where - i# = word2Int# x# + !i# = word2Int# x# instance Bounded Word where minBound = 0 @@ -153,9 +156,9 @@ instance Bounded Word where #endif instance Ix Word where - range (m,n) = [m..n] - unsafeIndex b@(m,_) i = fromIntegral (i - m) - inRange (m,n) i = m <= i && i <= n + range (m,n) = [m..n] + unsafeIndex (m,_) i = fromIntegral (i - m) + inRange (m,n) i = m <= i && i <= n instance Read Word where readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s] @@ -166,7 +169,8 @@ instance Bits Word where (W# x#) .&. (W# y#) = W# (x# `and#` y#) (W# x#) .|. (W# y#) = W# (x# `or#` y#) (W# x#) `xor` (W# y#) = W# (x# `xor#` y#) - complement (W# x#) = W# (x# `xor#` mb#) where W# mb# = maxBound + complement (W# x#) = W# (x# `xor#` mb#) + where !(W# mb#) = maxBound (W# x#) `shift` (I# i#) | i# >=# 0# = W# (x# `shiftL#` i#) | otherwise = W# (x# `shiftRL#` negateInt# i#) @@ -174,21 +178,21 @@ instance Bits Word where | i'# ==# 0# = W# x# | otherwise = W# ((x# `uncheckedShiftL#` i'#) `or#` (x# `uncheckedShiftRL#` (wsib -# i'#))) where - i'# = word2Int# (int2Word# i# `and#` int2Word# (wsib -# 1#)) - wsib = WORD_SIZE_IN_BITS# {- work around preprocessor problem (??) -} + !i'# = word2Int# (int2Word# i# `and#` int2Word# (wsib -# 1#)) + !wsib = WORD_SIZE_IN_BITS# {- work around preprocessor problem (??) -} bitSize _ = WORD_SIZE_IN_BITS isSigned _ = False - {-# INLINE shiftR #-} - -- same as the default definition, but we want it inlined (#2376) - x `shiftR` i = x `shift` (-i) - {-# RULES "fromIntegral/Int->Word" fromIntegral = \(I# x#) -> W# (int2Word# x#) "fromIntegral/Word->Int" fromIntegral = \(W# x#) -> I# (word2Int# x#) "fromIntegral/Word->Word" fromIntegral = id :: Word -> Word #-} +-- No RULES for RealFrac unfortunately. +-- Going through Int isn't possible because Word's range is not +-- included in Int's, going through Integer may or may not be slower. + ------------------------------------------------------------------------ -- type Word8 ------------------------------------------------------------------------ @@ -231,22 +235,22 @@ instance Enum Word8 where enumFromThen = boundedEnumFromThen instance Integral Word8 where - quot x@(W8# x#) y@(W8# y#) + quot (W8# x#) y@(W8# y#) | y /= 0 = W8# (x# `quotWord#` y#) | otherwise = divZeroError - rem x@(W8# x#) y@(W8# y#) + rem (W8# x#) y@(W8# y#) | y /= 0 = W8# (x# `remWord#` y#) | otherwise = divZeroError - div x@(W8# x#) y@(W8# y#) + div (W8# x#) y@(W8# y#) | y /= 0 = W8# (x# `quotWord#` y#) | otherwise = divZeroError - mod x@(W8# x#) y@(W8# y#) + mod (W8# x#) y@(W8# y#) | y /= 0 = W8# (x# `remWord#` y#) | otherwise = divZeroError - quotRem x@(W8# x#) y@(W8# y#) + quotRem (W8# x#) y@(W8# y#) | y /= 0 = (W8# (x# `quotWord#` y#), W8# (x# `remWord#` y#)) | otherwise = divZeroError - divMod x@(W8# x#) y@(W8# y#) + divMod (W8# x#) y@(W8# y#) | y /= 0 = (W8# (x# `quotWord#` y#), W8# (x# `remWord#` y#)) | otherwise = divZeroError toInteger (W8# x#) = smallInteger (word2Int# x#) @@ -256,9 +260,9 @@ instance Bounded Word8 where maxBound = 0xFF instance Ix Word8 where - range (m,n) = [m..n] - unsafeIndex b@(m,_) i = fromIntegral (i - m) - inRange (m,n) i = m <= i && i <= n + range (m,n) = [m..n] + unsafeIndex (m,_) i = fromIntegral (i - m) + inRange (m,n) i = m <= i && i <= n instance Read Word8 where readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s] @@ -269,7 +273,8 @@ instance Bits Word8 where (W8# x#) .&. (W8# y#) = W8# (x# `and#` y#) (W8# x#) .|. (W8# y#) = W8# (x# `or#` y#) (W8# x#) `xor` (W8# y#) = W8# (x# `xor#` y#) - complement (W8# x#) = W8# (x# `xor#` mb#) where W8# mb# = maxBound + complement (W8# x#) = W8# (x# `xor#` mb#) + where !(W8# mb#) = maxBound (W8# x#) `shift` (I# i#) | i# >=# 0# = W8# (narrow8Word# (x# `shiftL#` i#)) | otherwise = W8# (x# `shiftRL#` negateInt# i#) @@ -278,14 +283,10 @@ instance Bits Word8 where | otherwise = W8# (narrow8Word# ((x# `uncheckedShiftL#` i'#) `or#` (x# `uncheckedShiftRL#` (8# -# i'#)))) where - i'# = word2Int# (int2Word# i# `and#` int2Word# 7#) + !i'# = word2Int# (int2Word# i# `and#` int2Word# 7#) bitSize _ = 8 isSigned _ = False - {-# INLINE shiftR #-} - -- same as the default definition, but we want it inlined (#2376) - x `shiftR` i = x `shift` (-i) - {-# RULES "fromIntegral/Word8->Word8" fromIntegral = id :: Word8 -> Word8 "fromIntegral/Word8->Integer" fromIntegral = toInteger :: Word8 -> Integer @@ -293,6 +294,36 @@ instance Bits Word8 where "fromIntegral/Word8->a" fromIntegral = \(W8# x#) -> fromIntegral (W# x#) #-} +{-# RULES +"properFraction/Float->(Word8,Float)" + forall x. properFraction (x :: Float) = + case properFraction x of { + (n, y) -> ((fromIntegral :: Int -> Word8) n, y) } +"truncate/Float->Word8" + forall x. truncate (x :: Float) = (fromIntegral :: Int -> Word8) (truncate x) +"floor/Float->Word8" + forall x. floor (x :: Float) = (fromIntegral :: Int -> Word8) (floor x) +"ceiling/Float->Word8" + forall x. ceiling (x :: Float) = (fromIntegral :: Int -> Word8) (ceiling x) +"round/Float->Word8" + forall x. round (x :: Float) = (fromIntegral :: Int -> Word8) (round x) + #-} + +{-# RULES +"properFraction/Double->(Word8,Double)" + forall x. properFraction (x :: Double) = + case properFraction x of { + (n, y) -> ((fromIntegral :: Int -> Word8) n, y) } +"truncate/Double->Word8" + forall x. truncate (x :: Double) = (fromIntegral :: Int -> Word8) (truncate x) +"floor/Double->Word8" + forall x. floor (x :: Double) = (fromIntegral :: Int -> Word8) (floor x) +"ceiling/Double->Word8" + forall x. ceiling (x :: Double) = (fromIntegral :: Int -> Word8) (ceiling x) +"round/Double->Word8" + forall x. round (x :: Double) = (fromIntegral :: Int -> Word8) (round x) + #-} + ------------------------------------------------------------------------ -- type Word16 ------------------------------------------------------------------------ @@ -335,22 +366,22 @@ instance Enum Word16 where enumFromThen = boundedEnumFromThen instance Integral Word16 where - quot x@(W16# x#) y@(W16# y#) + quot (W16# x#) y@(W16# y#) | y /= 0 = W16# (x# `quotWord#` y#) | otherwise = divZeroError - rem x@(W16# x#) y@(W16# y#) + rem (W16# x#) y@(W16# y#) | y /= 0 = W16# (x# `remWord#` y#) | otherwise = divZeroError - div x@(W16# x#) y@(W16# y#) + div (W16# x#) y@(W16# y#) | y /= 0 = W16# (x# `quotWord#` y#) | otherwise = divZeroError - mod x@(W16# x#) y@(W16# y#) + mod (W16# x#) y@(W16# y#) | y /= 0 = W16# (x# `remWord#` y#) | otherwise = divZeroError - quotRem x@(W16# x#) y@(W16# y#) + quotRem (W16# x#) y@(W16# y#) | y /= 0 = (W16# (x# `quotWord#` y#), W16# (x# `remWord#` y#)) | otherwise = divZeroError - divMod x@(W16# x#) y@(W16# y#) + divMod (W16# x#) y@(W16# y#) | y /= 0 = (W16# (x# `quotWord#` y#), W16# (x# `remWord#` y#)) | otherwise = divZeroError toInteger (W16# x#) = smallInteger (word2Int# x#) @@ -360,9 +391,9 @@ instance Bounded Word16 where maxBound = 0xFFFF instance Ix Word16 where - range (m,n) = [m..n] - unsafeIndex b@(m,_) i = fromIntegral (i - m) - inRange (m,n) i = m <= i && i <= n + range (m,n) = [m..n] + unsafeIndex (m,_) i = fromIntegral (i - m) + inRange (m,n) i = m <= i && i <= n instance Read Word16 where readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s] @@ -373,7 +404,8 @@ instance Bits Word16 where (W16# x#) .&. (W16# y#) = W16# (x# `and#` y#) (W16# x#) .|. (W16# y#) = W16# (x# `or#` y#) (W16# x#) `xor` (W16# y#) = W16# (x# `xor#` y#) - complement (W16# x#) = W16# (x# `xor#` mb#) where W16# mb# = maxBound + complement (W16# x#) = W16# (x# `xor#` mb#) + where !(W16# mb#) = maxBound (W16# x#) `shift` (I# i#) | i# >=# 0# = W16# (narrow16Word# (x# `shiftL#` i#)) | otherwise = W16# (x# `shiftRL#` negateInt# i#) @@ -382,14 +414,10 @@ instance Bits Word16 where | otherwise = W16# (narrow16Word# ((x# `uncheckedShiftL#` i'#) `or#` (x# `uncheckedShiftRL#` (16# -# i'#)))) where - i'# = word2Int# (int2Word# i# `and#` int2Word# 15#) + !i'# = word2Int# (int2Word# i# `and#` int2Word# 15#) bitSize _ = 16 isSigned _ = False - {-# INLINE shiftR #-} - -- same as the default definition, but we want it inlined (#2376) - x `shiftR` i = x `shift` (-i) - {-# RULES "fromIntegral/Word8->Word16" fromIntegral = \(W8# x#) -> W16# x# "fromIntegral/Word16->Word16" fromIntegral = id :: Word16 -> Word16 @@ -398,6 +426,36 @@ instance Bits Word16 where "fromIntegral/Word16->a" fromIntegral = \(W16# x#) -> fromIntegral (W# x#) #-} +{-# RULES +"properFraction/Float->(Word16,Float)" + forall x. properFraction (x :: Float) = + case properFraction x of { + (n, y) -> ((fromIntegral :: Int -> Word16) n, y) } +"truncate/Float->Word16" + forall x. truncate (x :: Float) = (fromIntegral :: Int -> Word16) (truncate x) +"floor/Float->Word16" + forall x. floor (x :: Float) = (fromIntegral :: Int -> Word16) (floor x) +"ceiling/Float->Word16" + forall x. ceiling (x :: Float) = (fromIntegral :: Int -> Word16) (ceiling x) +"round/Float->Word16" + forall x. round (x :: Float) = (fromIntegral :: Int -> Word16) (round x) + #-} + +{-# RULES +"properFraction/Double->(Word16,Double)" + forall x. properFraction (x :: Double) = + case properFraction x of { + (n, y) -> ((fromIntegral :: Int -> Word16) n, y) } +"truncate/Double->Word16" + forall x. truncate (x :: Double) = (fromIntegral :: Int -> Word16) (truncate x) +"floor/Double->Word16" + forall x. floor (x :: Double) = (fromIntegral :: Int -> Word16) (floor x) +"ceiling/Double->Word16" + forall x. ceiling (x :: Double) = (fromIntegral :: Int -> Word16) (ceiling x) +"round/Double->Word16" + forall x. round (x :: Double) = (fromIntegral :: Int -> Word16) (round x) + #-} + ------------------------------------------------------------------------ -- type Word32 ------------------------------------------------------------------------ @@ -489,10 +547,6 @@ instance Bits Word32 where bitSize _ = 32 isSigned _ = False - {-# INLINE shiftR #-} - -- same as the default definition, but we want it inlined (#2376) - x `shiftR` i = x `shift` (-i) - {-# RULES "fromIntegral/Int->Word32" fromIntegral = \(I# x#) -> W32# (int32ToWord32# (intToInt32# x#)) "fromIntegral/Word->Word32" fromIntegral = \(W# x#) -> W32# (wordToWord32# x#) @@ -507,6 +561,39 @@ instance Bits Word32 where #if WORD_SIZE_IN_BITS > 32 -- Operations may assume and must ensure that it holds only values -- from its logical range. + +-- We can use rewrite rules for the RealFrac methods + +{-# RULES +"properFraction/Float->(Word32,Float)" + forall x. properFraction (x :: Float) = + case properFraction x of { + (n, y) -> ((fromIntegral :: Int -> Word32) n, y) } +"truncate/Float->Word32" + forall x. truncate (x :: Float) = (fromIntegral :: Int -> Word32) (truncate x) +"floor/Float->Word32" + forall x. floor (x :: Float) = (fromIntegral :: Int -> Word32) (floor x) +"ceiling/Float->Word32" + forall x. ceiling (x :: Float) = (fromIntegral :: Int -> Word32) (ceiling x) +"round/Float->Word32" + forall x. round (x :: Float) = (fromIntegral :: Int -> Word32) (round x) + #-} + +{-# RULES +"properFraction/Double->(Word32,Double)" + forall x. properFraction (x :: Double) = + case properFraction x of { + (n, y) -> ((fromIntegral :: Int -> Word32) n, y) } +"truncate/Double->Word32" + forall x. truncate (x :: Double) = (fromIntegral :: Int -> Word32) (truncate x) +"floor/Double->Word32" + forall x. floor (x :: Double) = (fromIntegral :: Int -> Word32) (floor x) +"ceiling/Double->Word32" + forall x. ceiling (x :: Double) = (fromIntegral :: Int -> Word32) (ceiling x) +"round/Double->Word32" + forall x. round (x :: Double) = (fromIntegral :: Int -> Word32) (round x) + #-} + #endif data Word32 = W32# Word# deriving (Eq, Ord) @@ -552,22 +639,22 @@ instance Enum Word32 where #endif instance Integral Word32 where - quot x@(W32# x#) y@(W32# y#) + quot (W32# x#) y@(W32# y#) | y /= 0 = W32# (x# `quotWord#` y#) | otherwise = divZeroError - rem x@(W32# x#) y@(W32# y#) + rem (W32# x#) y@(W32# y#) | y /= 0 = W32# (x# `remWord#` y#) | otherwise = divZeroError - div x@(W32# x#) y@(W32# y#) + div (W32# x#) y@(W32# y#) | y /= 0 = W32# (x# `quotWord#` y#) | otherwise = divZeroError - mod x@(W32# x#) y@(W32# y#) + mod (W32# x#) y@(W32# y#) | y /= 0 = W32# (x# `remWord#` y#) | otherwise = divZeroError - quotRem x@(W32# x#) y@(W32# y#) + quotRem (W32# x#) y@(W32# y#) | y /= 0 = (W32# (x# `quotWord#` y#), W32# (x# `remWord#` y#)) | otherwise = divZeroError - divMod x@(W32# x#) y@(W32# y#) + divMod (W32# x#) y@(W32# y#) | y /= 0 = (W32# (x# `quotWord#` y#), W32# (x# `remWord#` y#)) | otherwise = divZeroError toInteger (W32# x#) @@ -575,7 +662,7 @@ instance Integral Word32 where | i# >=# 0# = smallInteger i# | otherwise = wordToInteger x# where - i# = word2Int# x# + !i# = word2Int# x# #else = smallInteger (word2Int# x#) #endif @@ -586,7 +673,8 @@ instance Bits Word32 where (W32# x#) .&. (W32# y#) = W32# (x# `and#` y#) (W32# x#) .|. (W32# y#) = W32# (x# `or#` y#) (W32# x#) `xor` (W32# y#) = W32# (x# `xor#` y#) - complement (W32# x#) = W32# (x# `xor#` mb#) where W32# mb# = maxBound + complement (W32# x#) = W32# (x# `xor#` mb#) + where !(W32# mb#) = maxBound (W32# x#) `shift` (I# i#) | i# >=# 0# = W32# (narrow32Word# (x# `shiftL#` i#)) | otherwise = W32# (x# `shiftRL#` negateInt# i#) @@ -595,14 +683,10 @@ instance Bits Word32 where | otherwise = W32# (narrow32Word# ((x# `uncheckedShiftL#` i'#) `or#` (x# `uncheckedShiftRL#` (32# -# i'#)))) where - i'# = word2Int# (int2Word# i# `and#` int2Word# 31#) + !i'# = word2Int# (int2Word# i# `and#` int2Word# 31#) bitSize _ = 32 isSigned _ = False - {-# INLINE shiftR #-} - -- same as the default definition, but we want it inlined (#2376) - x `shiftR` i = x `shift` (-i) - {-# RULES "fromIntegral/Word8->Word32" fromIntegral = \(W8# x#) -> W32# x# "fromIntegral/Word16->Word32" fromIntegral = \(W16# x#) -> W32# x# @@ -630,9 +714,9 @@ instance Bounded Word32 where maxBound = 0xFFFFFFFF instance Ix Word32 where - range (m,n) = [m..n] - unsafeIndex b@(m,_) i = fromIntegral (i - m) - inRange (m,n) i = m <= i && i <= n + range (m,n) = [m..n] + unsafeIndex (m,_) i = fromIntegral (i - m) + inRange (m,n) i = m <= i && i <= n instance Read Word32 where #if WORD_SIZE_IN_BITS < 33 @@ -690,22 +774,22 @@ instance Enum Word64 where enumFromThenTo = integralEnumFromThenTo instance Integral Word64 where - quot x@(W64# x#) y@(W64# y#) + quot (W64# x#) y@(W64# y#) | y /= 0 = W64# (x# `quotWord64#` y#) | otherwise = divZeroError - rem x@(W64# x#) y@(W64# y#) + rem (W64# x#) y@(W64# y#) | y /= 0 = W64# (x# `remWord64#` y#) | otherwise = divZeroError - div x@(W64# x#) y@(W64# y#) + div (W64# x#) y@(W64# y#) | y /= 0 = W64# (x# `quotWord64#` y#) | otherwise = divZeroError - mod x@(W64# x#) y@(W64# y#) + mod (W64# x#) y@(W64# y#) | y /= 0 = W64# (x# `remWord64#` y#) | otherwise = divZeroError - quotRem x@(W64# x#) y@(W64# y#) + quotRem (W64# x#) y@(W64# y#) | y /= 0 = (W64# (x# `quotWord64#` y#), W64# (x# `remWord64#` y#)) | otherwise = divZeroError - divMod x@(W64# x#) y@(W64# y#) + divMod (W64# x#) y@(W64# y#) | y /= 0 = (W64# (x# `quotWord64#` y#), W64# (x# `remWord64#` y#)) | otherwise = divZeroError toInteger (W64# x#) = word64ToInteger x# @@ -725,14 +809,10 @@ instance Bits Word64 where | otherwise = W64# ((x# `uncheckedShiftL64#` i'#) `or64#` (x# `uncheckedShiftRL64#` (64# -# i'#))) where - i'# = word2Int# (int2Word# i# `and#` int2Word# 63#) + !i'# = word2Int# (int2Word# i# `and#` int2Word# 63#) bitSize _ = 64 isSigned _ = False - {-# INLINE shiftR #-} - -- same as the default definition, but we want it inlined (#2376) - x `shiftR` i = x `shift` (-i) - -- give the 64-bit shift operations the same treatment as the 32-bit -- ones (see GHC.Base), namely we wrap them in tests to catch the -- cases when we're shifting more than 64 bits to avoid unspecified @@ -793,29 +873,29 @@ instance Enum Word64 where enumFromThenTo = integralEnumFromThenTo instance Integral Word64 where - quot x@(W64# x#) y@(W64# y#) + quot (W64# x#) y@(W64# y#) | y /= 0 = W64# (x# `quotWord#` y#) | otherwise = divZeroError - rem x@(W64# x#) y@(W64# y#) + rem (W64# x#) y@(W64# y#) | y /= 0 = W64# (x# `remWord#` y#) | otherwise = divZeroError - div x@(W64# x#) y@(W64# y#) + div (W64# x#) y@(W64# y#) | y /= 0 = W64# (x# `quotWord#` y#) | otherwise = divZeroError - mod x@(W64# x#) y@(W64# y#) + mod (W64# x#) y@(W64# y#) | y /= 0 = W64# (x# `remWord#` y#) | otherwise = divZeroError - quotRem x@(W64# x#) y@(W64# y#) + quotRem (W64# x#) y@(W64# y#) | y /= 0 = (W64# (x# `quotWord#` y#), W64# (x# `remWord#` y#)) | otherwise = divZeroError - divMod x@(W64# x#) y@(W64# y#) + divMod (W64# x#) y@(W64# y#) | y /= 0 = (W64# (x# `quotWord#` y#), W64# (x# `remWord#` y#)) | otherwise = divZeroError toInteger (W64# x#) | i# >=# 0# = smallInteger i# | otherwise = wordToInteger x# where - i# = word2Int# x# + !i# = word2Int# x# instance Bits Word64 where {-# INLINE shift #-} @@ -823,7 +903,8 @@ instance Bits Word64 where (W64# x#) .&. (W64# y#) = W64# (x# `and#` y#) (W64# x#) .|. (W64# y#) = W64# (x# `or#` y#) (W64# x#) `xor` (W64# y#) = W64# (x# `xor#` y#) - complement (W64# x#) = W64# (x# `xor#` mb#) where W64# mb# = maxBound + complement (W64# x#) = W64# (x# `xor#` mb#) + where !(W64# mb#) = maxBound (W64# x#) `shift` (I# i#) | i# >=# 0# = W64# (x# `shiftL#` i#) | otherwise = W64# (x# `shiftRL#` negateInt# i#) @@ -832,20 +913,19 @@ instance Bits Word64 where | otherwise = W64# ((x# `uncheckedShiftL#` i'#) `or#` (x# `uncheckedShiftRL#` (64# -# i'#))) where - i'# = word2Int# (int2Word# i# `and#` int2Word# 63#) + !i'# = word2Int# (int2Word# i# `and#` int2Word# 63#) bitSize _ = 64 isSigned _ = False - {-# INLINE shiftR #-} - -- same as the default definition, but we want it inlined (#2376) - x `shiftR` i = x `shift` (-i) - {-# RULES "fromIntegral/a->Word64" fromIntegral = \x -> case fromIntegral x of W# x# -> W64# x# "fromIntegral/Word64->a" fromIntegral = \(W64# x#) -> fromIntegral (W# x#) #-} +uncheckedShiftL64# :: Word# -> Int# -> Word# uncheckedShiftL64# = uncheckedShiftL# + +uncheckedShiftRL64# :: Word# -> Int# -> Word# uncheckedShiftRL64# = uncheckedShiftRL# #endif @@ -861,9 +941,9 @@ instance Bounded Word64 where maxBound = 0xFFFFFFFFFFFFFFFF instance Ix Word64 where - range (m,n) = [m..n] - unsafeIndex b@(m,_) i = fromIntegral (i - m) - inRange (m,n) i = m <= i && i <= n + range (m,n) = [m..n] + unsafeIndex (m,_) i = fromIntegral (i - m) + inRange (m,n) i = m <= i && i <= n instance Read Word64 where readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]