summaryrefslogtreecommitdiff
path: root/libraries/base
diff options
context:
space:
mode:
Diffstat (limited to 'libraries/base')
-rw-r--r--libraries/base/Foreign/C/Types.hs46
-rw-r--r--libraries/base/GHC/Float.hs4
-rw-r--r--libraries/base/GHC/Int.hs69
-rw-r--r--libraries/base/GHC/Num.hs15
-rw-r--r--libraries/base/GHC/Real.hs55
-rw-r--r--libraries/base/GHC/Word.hs81
6 files changed, 16 insertions, 254 deletions
diff --git a/libraries/base/Foreign/C/Types.hs b/libraries/base/Foreign/C/Types.hs
index e2907ca2d8..05295a819f 100644
--- a/libraries/base/Foreign/C/Types.hs
+++ b/libraries/base/Foreign/C/Types.hs
@@ -146,33 +146,6 @@ INTEGRAL_TYPE(CULLong,HTYPE_UNSIGNED_LONG_LONG)
-- @since 4.10.0.0
INTEGRAL_TYPE_WITH_CTYPE(CBool,bool,HTYPE_BOOL)
-{-# RULES
-"fromIntegral/a->CChar" fromIntegral = \x -> CChar (fromIntegral x)
-"fromIntegral/a->CSChar" fromIntegral = \x -> CSChar (fromIntegral x)
-"fromIntegral/a->CUChar" fromIntegral = \x -> CUChar (fromIntegral x)
-"fromIntegral/a->CShort" fromIntegral = \x -> CShort (fromIntegral x)
-"fromIntegral/a->CUShort" fromIntegral = \x -> CUShort (fromIntegral x)
-"fromIntegral/a->CInt" fromIntegral = \x -> CInt (fromIntegral x)
-"fromIntegral/a->CUInt" fromIntegral = \x -> CUInt (fromIntegral x)
-"fromIntegral/a->CLong" fromIntegral = \x -> CLong (fromIntegral x)
-"fromIntegral/a->CULong" fromIntegral = \x -> CULong (fromIntegral x)
-"fromIntegral/a->CLLong" fromIntegral = \x -> CLLong (fromIntegral x)
-"fromIntegral/a->CULLong" fromIntegral = \x -> CULLong (fromIntegral x)
-
-"fromIntegral/CChar->a" fromIntegral = \(CChar x) -> fromIntegral x
-"fromIntegral/CSChar->a" fromIntegral = \(CSChar x) -> fromIntegral x
-"fromIntegral/CUChar->a" fromIntegral = \(CUChar x) -> fromIntegral x
-"fromIntegral/CShort->a" fromIntegral = \(CShort x) -> fromIntegral x
-"fromIntegral/CUShort->a" fromIntegral = \(CUShort x) -> fromIntegral x
-"fromIntegral/CInt->a" fromIntegral = \(CInt x) -> fromIntegral x
-"fromIntegral/CUInt->a" fromIntegral = \(CUInt x) -> fromIntegral x
-"fromIntegral/CLong->a" fromIntegral = \(CLong x) -> fromIntegral x
-"fromIntegral/CULong->a" fromIntegral = \(CULong x) -> fromIntegral x
-"fromIntegral/CLLong->a" fromIntegral = \(CLLong x) -> fromIntegral x
-"fromIntegral/CULLong->a" fromIntegral = \(CULLong x) -> fromIntegral x
-"fromIntegral/CBool->a" fromIntegral = \(CBool x) -> fromIntegral x
- #-}
-
-- | Haskell type representing the C @float@ type.
-- /(The concrete types of "Foreign.C.Types#platform" are platform-specific.)/
FLOATING_TYPE(CFloat,HTYPE_FLOAT)
@@ -206,18 +179,6 @@ INTEGRAL_TYPE(CWchar,HTYPE_WCHAR_T)
-- /(The concrete types of "Foreign.C.Types#platform" are platform-specific.)/
INTEGRAL_TYPE(CSigAtomic,HTYPE_SIG_ATOMIC_T)
-{-# RULES
-"fromIntegral/a->CPtrdiff" fromIntegral = \x -> CPtrdiff (fromIntegral x)
-"fromIntegral/a->CSize" fromIntegral = \x -> CSize (fromIntegral x)
-"fromIntegral/a->CWchar" fromIntegral = \x -> CWchar (fromIntegral x)
-"fromIntegral/a->CSigAtomic" fromIntegral = \x -> CSigAtomic (fromIntegral x)
-
-"fromIntegral/CPtrdiff->a" fromIntegral = \(CPtrdiff x) -> fromIntegral x
-"fromIntegral/CSize->a" fromIntegral = \(CSize x) -> fromIntegral x
-"fromIntegral/CWchar->a" fromIntegral = \(CWchar x) -> fromIntegral x
-"fromIntegral/CSigAtomic->a" fromIntegral = \(CSigAtomic x) -> fromIntegral x
- #-}
-
-- | Haskell type representing the C @clock_t@ type.
-- /(The concrete types of "Foreign.C.Types#platform" are platform-specific.)/
ARITHMETIC_TYPE(CClock,HTYPE_CLOCK_T)
@@ -252,13 +213,6 @@ INTEGRAL_TYPE(CUIntPtr,HTYPE_UINTPTR_T)
INTEGRAL_TYPE(CIntMax,HTYPE_INTMAX_T)
INTEGRAL_TYPE(CUIntMax,HTYPE_UINTMAX_T)
-{-# RULES
-"fromIntegral/a->CIntPtr" fromIntegral = \x -> CIntPtr (fromIntegral x)
-"fromIntegral/a->CUIntPtr" fromIntegral = \x -> CUIntPtr (fromIntegral x)
-"fromIntegral/a->CIntMax" fromIntegral = \x -> CIntMax (fromIntegral x)
-"fromIntegral/a->CUIntMax" fromIntegral = \x -> CUIntMax (fromIntegral x)
- #-}
-
-- C99 types which are still missing include:
-- wint_t, wctrans_t, wctype_t
diff --git a/libraries/base/GHC/Float.hs b/libraries/base/GHC/Float.hs
index e1dbe03010..da4d14a669 100644
--- a/libraries/base/GHC/Float.hs
+++ b/libraries/base/GHC/Float.hs
@@ -1436,10 +1436,6 @@ word2Float :: Word -> Float
word2Float (W# w) = F# (word2Float# w)
{-# RULES
-"fromIntegral/Int->Float" fromIntegral = int2Float
-"fromIntegral/Int->Double" fromIntegral = int2Double
-"fromIntegral/Word->Float" fromIntegral = word2Float
-"fromIntegral/Word->Double" fromIntegral = word2Double
"realToFrac/Float->Float" realToFrac = id :: Float -> Float
"realToFrac/Float->Double" realToFrac = float2Double
"realToFrac/Double->Float" realToFrac = double2Float
diff --git a/libraries/base/GHC/Int.hs b/libraries/base/GHC/Int.hs
index c52ea6e25d..d8ecc7dc4e 100644
--- a/libraries/base/GHC/Int.hs
+++ b/libraries/base/GHC/Int.hs
@@ -52,7 +52,6 @@ import GHC.Num
import GHC.Real
import GHC.Read
import GHC.Arr
-import GHC.Word hiding (uncheckedShiftL64#, uncheckedShiftRL64#)
import GHC.Show
------------------------------------------------------------------------
@@ -233,12 +232,6 @@ instance FiniteBits Int8 where
countTrailingZeros (I8# x#) = I# (word2Int# (ctz8# (int2Word# (int8ToInt# x#))))
{-# RULES
-"fromIntegral/Int8->Int8" fromIntegral = id :: Int8 -> Int8
-"fromIntegral/a->Int8" fromIntegral = \x -> case fromIntegral x of I# x# -> I8# (intToInt8# x#)
-"fromIntegral/Int8->a" fromIntegral = \(I8# x#) -> fromIntegral (I# (int8ToInt# x#))
- #-}
-
-{-# RULES
"properFraction/Float->(Int8,Float)"
properFraction = \x ->
case properFraction x of {
@@ -446,14 +439,6 @@ instance FiniteBits Int16 where
countTrailingZeros (I16# x#) = I# (word2Int# (ctz16# (int2Word# (int16ToInt# x#))))
{-# RULES
-"fromIntegral/Word8->Int16" fromIntegral = \(W8# x#) -> I16# (intToInt16# (word2Int# (word8ToWord# x#)))
-"fromIntegral/Int8->Int16" fromIntegral = \(I8# x#) -> I16# (intToInt16# (int8ToInt# x#))
-"fromIntegral/Int16->Int16" fromIntegral = id :: Int16 -> Int16
-"fromIntegral/a->Int16" fromIntegral = \x -> case fromIntegral x of I# x# -> I16# (intToInt16# x#)
-"fromIntegral/Int16->a" fromIntegral = \(I16# x#) -> fromIntegral (I# (int16ToInt# x#))
- #-}
-
-{-# RULES
"properFraction/Float->(Int16,Float)"
properFraction = \x ->
case properFraction x of {
@@ -648,16 +633,6 @@ instance FiniteBits Int32 where
countTrailingZeros (I32# x#) = I# (word2Int# (ctz32# (int2Word# (int32ToInt# x#))))
{-# RULES
-"fromIntegral/Word8->Int32" fromIntegral = \(W8# x#) -> I32# (intToInt32# (word2Int# (word8ToWord# x#)))
-"fromIntegral/Word16->Int32" fromIntegral = \(W16# x#) -> I32# (intToInt32# (word2Int# (word16ToWord# x#)))
-"fromIntegral/Int8->Int32" fromIntegral = \(I8# x#) -> I32# (intToInt32# (int8ToInt# x#))
-"fromIntegral/Int16->Int32" fromIntegral = \(I16# x#) -> I32# (intToInt32# (int16ToInt# x#))
-"fromIntegral/Int32->Int32" fromIntegral = id :: Int32 -> Int32
-"fromIntegral/a->Int32" fromIntegral = \x -> case fromIntegral x of I# x# -> I32# (intToInt32# x#)
-"fromIntegral/Int32->a" fromIntegral = \(I32# x#) -> fromIntegral (I# (int32ToInt# x#))
- #-}
-
-{-# RULES
"properFraction/Float->(Int32,Float)"
properFraction = \x ->
case properFraction x of {
@@ -897,16 +872,6 @@ a `iShiftRA64#` b | isTrue# (b >=# 64#) = if isTrue# (a `ltInt64#` (intToInt64#
else intToInt64# 0#
| otherwise = a `uncheckedIShiftRA64#` b
-{-# RULES
-"fromIntegral/Int->Int64" fromIntegral = \(I# x#) -> I64# (intToInt64# x#)
-"fromIntegral/Word->Int64" fromIntegral = \(W# x#) -> I64# (word64ToInt64# (wordToWord64# x#))
-"fromIntegral/Word64->Int64" fromIntegral = \(W64# x#) -> I64# (word64ToInt64# x#)
-"fromIntegral/Int64->Int" fromIntegral = \(I64# x#) -> I# (int64ToInt# x#)
-"fromIntegral/Int64->Word" fromIntegral = \(I64# x#) -> W# (int2Word# (int64ToInt# x#))
-"fromIntegral/Int64->Word64" fromIntegral = \(I64# x#) -> W64# (int64ToWord64# x#)
-"fromIntegral/Int64->Int64" fromIntegral = id :: Int64 -> Int64
- #-}
-
-- No RULES for RealFrac methods if Int is smaller than Int64, we can't
-- go through Int and whether going through Integer is faster is uncertain.
#else
@@ -1062,11 +1027,6 @@ instance Bits Int64 where
testBit = testBitDefault
{-# RULES
-"fromIntegral/a->Int64" fromIntegral = \x -> case fromIntegral x of I# x# -> I64# x#
-"fromIntegral/Int64->a" fromIntegral = \(I64# x#) -> fromIntegral (I# x#)
- #-}
-
-{-# RULES
"properFraction/Float->(Int64,Float)"
properFraction = \x ->
case properFraction x of {
@@ -1133,35 +1093,6 @@ instance Ix Int64 where
-------------------------------------------------------------------------------
-{-# RULES
-"fromIntegral/Natural->Int8"
- fromIntegral = (fromIntegral :: Int -> Int8) . fromIntegral . naturalToWord
-"fromIntegral/Natural->Int16"
- fromIntegral = (fromIntegral :: Int -> Int16) . fromIntegral . naturalToWord
-"fromIntegral/Natural->Int32"
- fromIntegral = (fromIntegral :: Int -> Int32) . fromIntegral . naturalToWord
- #-}
-
-{-# RULES
-"fromIntegral/Int8->Natural"
- fromIntegral = naturalFromWord . fromIntegral . (fromIntegral :: Int8 -> Int)
-"fromIntegral/Int16->Natural"
- fromIntegral = naturalFromWord . fromIntegral . (fromIntegral :: Int16 -> Int)
-"fromIntegral/Int32->Natural"
- fromIntegral = naturalFromWord . fromIntegral . (fromIntegral :: Int32 -> Int)
- #-}
-
-#if WORD_SIZE_IN_BITS == 64
--- these RULES are valid for Word==Word64 & Int==Int64
-{-# RULES
-"fromIntegral/Natural->Int64"
- fromIntegral = (fromIntegral :: Int -> Int64) . fromIntegral . naturalToWord
-"fromIntegral/Int64->Natural"
- fromIntegral = naturalFromWord . fromIntegral . (fromIntegral :: Int64 -> Int)
- #-}
-#endif
-
-
{- Note [Order of tests]
~~~~~~~~~~~~~~~~~~~~~~~~~
(See #3065, #5161.) Suppose we had a definition like:
diff --git a/libraries/base/GHC/Num.hs b/libraries/base/GHC/Num.hs
index 3d26d35a0d..c7d0425eab 100644
--- a/libraries/base/GHC/Num.hs
+++ b/libraries/base/GHC/Num.hs
@@ -97,7 +97,7 @@ subtract :: (Num a) => a -> a -> a
subtract x y = y - x
-- | @since 2.01
-instance Num Int where
+instance Num Int where
I# x + I# y = I# (x +# y)
I# x - I# y = I# (x -# y)
negate (I# x) = I# (negateInt# x)
@@ -108,8 +108,7 @@ instance Num Int where
| n `eqInt` 0 = 0
| otherwise = 1
- {-# INLINE fromInteger #-} -- Just to be sure!
- fromInteger i = integerToInt i
+ fromInteger i = I# (integerToInt# i)
-- | @since 2.01
instance Num Word where
@@ -120,15 +119,15 @@ instance Num Word where
abs x = x
signum 0 = 0
signum _ = 1
- fromInteger i = integerToWord i
+ fromInteger i = W# (integerToWord# i)
-- | @since 2.01
-instance Num Integer where
+instance Num Integer where
(+) = integerAdd
(-) = integerSub
(*) = integerMul
negate = integerNegate
- fromInteger x = x
+ fromInteger i = i
abs = integerAbs
signum = integerSignum
@@ -137,12 +136,12 @@ instance Num Integer where
-- additive inverse. It is a semiring though.
--
-- @since 4.8.0.0
-instance Num Natural where
+instance Num Natural where
(+) = naturalAdd
(-) = naturalSubThrow
(*) = naturalMul
negate = naturalNegate
- fromInteger = integerToNaturalThrow
+ fromInteger i = integerToNaturalThrow i
abs = id
signum = naturalSignum
diff --git a/libraries/base/GHC/Real.hs b/libraries/base/GHC/Real.hs
index 6c7ae43e5c..a265150171 100644
--- a/libraries/base/GHC/Real.hs
+++ b/libraries/base/GHC/Real.hs
@@ -323,7 +323,7 @@ instance Real Int where
toRational x = toInteger x :% 1
-- | @since 2.0.1
-instance Integral Int where
+instance Integral Int where
toInteger (I# i) = IS i
{-# INLINE quot #-} -- see Note [INLINE division wrappers] in GHC.Base
@@ -438,7 +438,7 @@ instance Real Natural where
-- | @since 2.0.1
-instance Integral Integer where
+instance Integral Integer where
-- see Note [INLINE division wrappers] in GHC.Base
{-# INLINE quot #-}
{-# INLINE rem #-}
@@ -477,7 +477,7 @@ instance Integral Natural where
{-# INLINE mod #-}
{-# INLINE divMod #-}
- toInteger = integerFromNatural
+ toInteger x = integerFromNatural x
!_ `quot` 0 = divZeroError
n `quot` d = n `naturalQuot` d
@@ -576,54 +576,13 @@ instance (Integral a) => Enum (Ratio a) where
--------------------------------------------------------------
-- | general coercion from integral types
-{-# NOINLINE [1] fromIntegral #-}
+{-# INLINE fromIntegral #-}
+ -- Inlined to allow built-in rules to match.
+ -- See Note [Optimising conversions between numeric types]
+ -- in GHC.Core.Opt.ConstantFold
fromIntegral :: (Integral a, Num b) => a -> b
fromIntegral = fromInteger . toInteger
-{-# RULES
-"fromIntegral/Int->Int" fromIntegral = id :: Int -> Int
- #-}
-
-{-# 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
- #-}
-
-{-# RULES
-"fromIntegral/Natural->Natural" fromIntegral = id :: Natural -> Natural
-"fromIntegral/Natural->Integer" fromIntegral = toInteger :: Natural -> Integer
-"fromIntegral/Natural->Word" fromIntegral = naturalToWord :: Natural -> Word
- #-}
-
--- Don't forget the type signatures in the following rules! Without a type
--- signature we ended up with the rule:
---
--- "fromIntegral/Int->Natural" forall a (d::Integral a).
--- fromIntegral @a @Natural = naturalFromWord . fromIntegral @a d
---
--- but this rule is certainly not valid for every Integral type a!
---
--- This rule wraps any Integral input into Word's range. As a consequence,
--- (2^64 :: Integer) was incorrectly wrapped to (0 :: Natural), see #19345.
---
--- A follow-up issue with this rule was that no underflow exception was raised
--- for negative Int values (see #20066). We now use a naturalFromInt helper
--- function to restore this behavior.
-
-{-# RULES
-"fromIntegral/Word->Natural" fromIntegral = naturalFromWord :: Word -> Natural
-"fromIntegral/Int->Natural" fromIntegral = naturalFromInt :: Int -> Natural
- #-}
-
--- | Convert an Int into a Natural, throwing an underflow exception for negative
--- values.
-naturalFromInt :: Int -> Natural
-{-# INLINE naturalFromInt #-}
-naturalFromInt x
- | x < 0 = underflowError
- | otherwise = naturalFromWord (fromIntegral x)
-
-- | general coercion to fractional types
realToFrac :: (Real a, Fractional b) => a -> b
{-# NOINLINE [1] realToFrac #-}
diff --git a/libraries/base/GHC/Word.hs b/libraries/base/GHC/Word.hs
index baa878763e..ec231de2b8 100644
--- a/libraries/base/GHC/Word.hs
+++ b/libraries/base/GHC/Word.hs
@@ -220,13 +220,6 @@ instance FiniteBits Word8 where
countTrailingZeros (W8# x#) = I# (word2Int# (ctz8# (word8ToWord# x#)))
{-# RULES
-"fromIntegral/Word8->Word8" fromIntegral = id :: Word8 -> Word8
-"fromIntegral/Word8->Integer" fromIntegral = toInteger :: Word8 -> Integer
-"fromIntegral/a->Word8" fromIntegral = \x -> case fromIntegral x of W# x# -> W8# (wordToWord8# x#)
-"fromIntegral/Word8->a" fromIntegral = \(W8# x#) -> fromIntegral (W# (word8ToWord# x#))
- #-}
-
-{-# RULES
"properFraction/Float->(Word8,Float)"
properFraction = \x ->
case properFraction x of {
@@ -419,14 +412,6 @@ byteSwap16 :: Word16 -> Word16
byteSwap16 (W16# w#) = W16# (wordToWord16# (byteSwap16# (word16ToWord# w#)))
{-# RULES
-"fromIntegral/Word8->Word16" fromIntegral = \(W8# x#) -> W16# (wordToWord16# (word8ToWord# x#))
-"fromIntegral/Word16->Word16" fromIntegral = id :: Word16 -> Word16
-"fromIntegral/Word16->Integer" fromIntegral = toInteger :: Word16 -> Integer
-"fromIntegral/a->Word16" fromIntegral = \x -> case fromIntegral x of W# x# -> W16# (wordToWord16# x#)
-"fromIntegral/Word16->a" fromIntegral = \(W16# x#) -> fromIntegral (W# (word16ToWord# x#))
- #-}
-
-{-# RULES
"properFraction/Float->(Word16,Float)"
properFraction = \x ->
case properFraction x of {
@@ -597,15 +582,7 @@ instance Integral Word32 where
mod x y = rem x y
divMod x y = quotRem x y
- toInteger (W32# x#)
-#if WORD_SIZE_IN_BITS == 32
- | isTrue# (i# >=# 0#) = IS i#
- | otherwise = integerFromWord# (word32ToWord# x#)
- where
- !i# = word2Int# (word32ToWord# x#)
-#else
- = IS (word2Int# (word32ToWord# x#))
-#endif
+ toInteger (W32# x#) = integerFromWord# (word32ToWord# x#)
-- | @since 2.01
instance Bits Word32 where
@@ -651,15 +628,6 @@ instance FiniteBits Word32 where
countLeadingZeros (W32# x#) = I# (word2Int# (clz32# (word32ToWord# x#)))
countTrailingZeros (W32# x#) = I# (word2Int# (ctz32# (word32ToWord# x#)))
-{-# RULES
-"fromIntegral/Word8->Word32" fromIntegral = \(W8# x#) -> W32# (wordToWord32# (word8ToWord# x#))
-"fromIntegral/Word16->Word32" fromIntegral = \(W16# x#) -> W32# (wordToWord32# (word16ToWord# x#))
-"fromIntegral/Word32->Word32" fromIntegral = id :: Word32 -> Word32
-"fromIntegral/Word32->Integer" fromIntegral = toInteger :: Word32 -> Integer
-"fromIntegral/a->Word32" fromIntegral = \x -> case fromIntegral x of W# x# -> W32# (wordToWord32# x#)
-"fromIntegral/Word32->a" fromIntegral = \(W32# x#) -> fromIntegral (W# (word32ToWord# x#))
- #-}
-
-- | @since 2.01
instance Show Word32 where
#if WORD_SIZE_IN_BITS < 33
@@ -833,14 +801,6 @@ a `shiftL64#` b | isTrue# (b >=# 64#) = wordToWord64# 0##
a `shiftRL64#` b | isTrue# (b >=# 64#) = wordToWord64# 0##
| otherwise = a `uncheckedShiftRL64#` b
-{-# RULES
-"fromIntegral/Int->Word64" fromIntegral = \(I# x#) -> W64# (int64ToWord64# (intToInt64# x#))
-"fromIntegral/Word->Word64" fromIntegral = \(W# x#) -> W64# (wordToWord64# x#)
-"fromIntegral/Word64->Int" fromIntegral = \(W64# x#) -> I# (word2Int# (word64ToWord# x#))
-"fromIntegral/Word64->Word" fromIntegral = \(W64# x#) -> W# (word64ToWord# x#)
-"fromIntegral/Word64->Word64" fromIntegral = id :: Word64 -> Word64
- #-}
-
#else
-- Word64 is represented in the same way as Word.
@@ -969,11 +929,7 @@ instance Integral Word64 where
mod x y = rem x y
divMod x y = quotRem x y
- toInteger (W64# x#)
- | isTrue# (i# >=# 0#) = IS i#
- | otherwise = integerFromWord# x#
- where
- !i# = word2Int# x#
+ toInteger (W64# x#) = integerFromWord# x#
-- | @since 2.01
instance Bits Word64 where
@@ -1010,11 +966,6 @@ instance Bits Word64 where
bit = bitDefault
testBit = testBitDefault
-{-# 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#
@@ -1092,34 +1043,6 @@ bitReverse64 (W64# w#) = W64# (bitReverse# w#)
-------------------------------------------------------------------------------
-{-# RULES
-"fromIntegral/Natural->Word8"
- fromIntegral = (fromIntegral :: Word -> Word8) . naturalToWord
-"fromIntegral/Natural->Word16"
- fromIntegral = (fromIntegral :: Word -> Word16) . naturalToWord
-"fromIntegral/Natural->Word32"
- fromIntegral = (fromIntegral :: Word -> Word32) . naturalToWord
- #-}
-
-{-# RULES
-"fromIntegral/Word8->Natural"
- fromIntegral = naturalFromWord . (fromIntegral :: Word8 -> Word)
-"fromIntegral/Word16->Natural"
- fromIntegral = naturalFromWord . (fromIntegral :: Word16 -> Word)
-"fromIntegral/Word32->Natural"
- fromIntegral = naturalFromWord . (fromIntegral :: Word32 -> Word)
- #-}
-
-#if WORD_SIZE_IN_BITS == 64
--- these RULES are valid for Word==Word64
-{-# RULES
-"fromIntegral/Natural->Word64"
- fromIntegral = (fromIntegral :: Word -> Word64) . naturalToWord
-"fromIntegral/Word64->Natural"
- fromIntegral = naturalFromWord . (fromIntegral :: Word64 -> Word)
- #-}
-#endif
-
shiftRLWord8# :: Word8# -> Int# -> Word8#
a `shiftRLWord8#` b | isTrue# (b >=# 8#) = wordToWord8# 0##
| otherwise = a `uncheckedShiftRLWord8#` b