summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSebastian Graf <sebastian.graf@kit.edu>2021-10-27 17:18:51 +0200
committerMarge Bot <ben+marge-bot@smart-cactus.org>2021-10-29 05:02:25 -0400
commit7170052651ff02bfcf1e9611f0813dd20a7c8558 (patch)
tree19f4b1baa46eb0158f0e929117f86182ec07638d
parent522eab3f056905db47110c73dac1833f4a2880f2 (diff)
downloadhaskell-7170052651ff02bfcf1e9611f0813dd20a7c8558.tar.gz
Add more INLINABLE and INLINE pragmas to `Enum Int*` instances
Otherwise the instances aren't good list producers. See Note [Stable Unfolding for list producers].
-rw-r--r--libraries/base/GHC/Int.hs24
-rw-r--r--libraries/base/GHC/Real.hs8
-rw-r--r--libraries/base/GHC/Word.hs36
3 files changed, 64 insertions, 4 deletions
diff --git a/libraries/base/GHC/Int.hs b/libraries/base/GHC/Int.hs
index 4e10e0ca41..df25e1cbe4 100644
--- a/libraries/base/GHC/Int.hs
+++ b/libraries/base/GHC/Int.hs
@@ -129,7 +129,11 @@ instance Enum Int8 where
= I8# (intToInt8# i#)
| otherwise = toEnumError "Int8" i (minBound::Int8, maxBound::Int8)
fromEnum (I8# x#) = I# (int8ToInt# x#)
+ -- See Note [Stable Unfolding for list producers] in GHC.Enum
+ {-# INLINE enumFrom #-}
enumFrom = boundedEnumFrom
+ -- See Note [Stable Unfolding for list producers] in GHC.Enum
+ {-# INLINE enumFromThen #-}
enumFromThen = boundedEnumFromThen
-- | @since 2.01
@@ -336,7 +340,11 @@ instance Enum Int16 where
= I16# (intToInt16# i#)
| otherwise = toEnumError "Int16" i (minBound::Int16, maxBound::Int16)
fromEnum (I16# x#) = I# (int16ToInt# x#)
+ -- See Note [Stable Unfolding for list producers] in GHC.Enum
+ {-# INLINE enumFrom #-}
enumFrom = boundedEnumFrom
+ -- See Note [Stable Unfolding for list producers] in GHC.Enum
+ {-# INLINE enumFromThen #-}
enumFromThen = boundedEnumFromThen
-- | @since 2.01
@@ -540,7 +548,11 @@ instance Enum Int32 where
| otherwise = toEnumError "Int32" i (minBound::Int32, maxBound::Int32)
#endif
fromEnum (I32# x#) = I# (int32ToInt# x#)
+ -- See Note [Stable Unfolding for list producers] in GHC.Enum
+ {-# INLINE enumFrom #-}
enumFrom = boundedEnumFrom
+ -- See Note [Stable Unfolding for list producers] in GHC.Enum
+ {-# INLINE enumFromThen #-}
enumFromThen = boundedEnumFromThen
-- | @since 2.01
@@ -747,9 +759,17 @@ instance Enum Int64 where
| x >= fromIntegral (minBound::Int) && x <= fromIntegral (maxBound::Int)
= I# (int64ToInt# x#)
| otherwise = fromEnumError "Int64" x
+ -- See Note [Stable Unfolding for list producers] in GHC.Enum
+ {-# INLINE enumFrom #-}
enumFrom = integralEnumFrom
+ -- See Note [Stable Unfolding for list producers] in GHC.Enum
+ {-# INLINE enumFromThen #-}
enumFromThen = integralEnumFromThen
+ -- See Note [Stable Unfolding for list producers] in GHC.Enum
+ {-# INLINE enumFromTo #-}
enumFromTo = integralEnumFromTo
+ -- See Note [Stable Unfolding for list producers] in GHC.Enum
+ {-# INLINE enumFromThenTo #-}
enumFromThenTo = integralEnumFromThenTo
-- | @since 2.01
@@ -941,7 +961,11 @@ instance Enum Int64 where
| otherwise = predError "Int64"
toEnum (I# i#) = I64# i#
fromEnum (I64# x#) = I# x#
+ -- See Note [Stable Unfolding for list producers] in GHC.Enum
+ {-# INLINE enumFrom #-}
enumFrom = boundedEnumFrom
+ -- See Note [Stable Unfolding for list producers] in GHC.Enum
+ {-# INLINE enumFromThen #-}
enumFromThen = boundedEnumFromThen
-- | @since 2.01
diff --git a/libraries/base/GHC/Real.hs b/libraries/base/GHC/Real.hs
index e71a91007e..a4d97b0497 100644
--- a/libraries/base/GHC/Real.hs
+++ b/libraries/base/GHC/Real.hs
@@ -813,9 +813,13 @@ lcm x y = abs ((x `quot` (gcd x y)) * y)
"gcd/Word->Word->Word" gcd = gcdWord
#-}
+-- See Note [Stable Unfolding for list producers] in GHC.Enum
+{-# INLINABLE integralEnumFrom #-}
integralEnumFrom :: (Integral a, Bounded a) => a -> [a]
integralEnumFrom n = map fromInteger [toInteger n .. toInteger (maxBound `asTypeOf` n)]
+-- See Note [Stable Unfolding for list producers] in GHC.Enum
+{-# INLINABLE integralEnumFromThen #-}
integralEnumFromThen :: (Integral a, Bounded a) => a -> a -> [a]
integralEnumFromThen n1 n2
| i_n2 >= i_n1 = map fromInteger [i_n1, i_n2 .. toInteger (maxBound `asTypeOf` n1)]
@@ -824,9 +828,13 @@ integralEnumFromThen n1 n2
i_n1 = toInteger n1
i_n2 = toInteger n2
+-- See Note [Stable Unfolding for list producers] in GHC.Enum
+{-# INLINABLE integralEnumFromTo #-}
integralEnumFromTo :: Integral a => a -> a -> [a]
integralEnumFromTo n m = map fromInteger [toInteger n .. toInteger m]
+-- See Note [Stable Unfolding for list producers] in GHC.Enum
+{-# INLINABLE integralEnumFromThenTo #-}
integralEnumFromThenTo :: Integral a => a -> a -> a -> [a]
integralEnumFromThenTo n1 n2 m
= map fromInteger [toInteger n1, toInteger n2 .. toInteger m]
diff --git a/libraries/base/GHC/Word.hs b/libraries/base/GHC/Word.hs
index dd803c55b4..be44bfd541 100644
--- a/libraries/base/GHC/Word.hs
+++ b/libraries/base/GHC/Word.hs
@@ -136,7 +136,11 @@ instance Enum Word8 where
= W8# (wordToWord8# (int2Word# i#))
| otherwise = toEnumError "Word8" i (minBound::Word8, maxBound::Word8)
fromEnum (W8# x#) = I# (word2Int# (word8ToWord# x#))
+ -- See Note [Stable Unfolding for list producers] in GHC.Enum
+ {-# INLINE enumFrom #-}
enumFrom = boundedEnumFrom
+ -- See Note [Stable Unfolding for list producers] in GHC.Enum
+ {-# INLINE enumFromThen #-}
enumFromThen = boundedEnumFromThen
-- | @since 2.01
@@ -322,7 +326,11 @@ instance Enum Word16 where
= W16# (wordToWord16# (int2Word# i#))
| otherwise = toEnumError "Word16" i (minBound::Word16, maxBound::Word16)
fromEnum (W16# x#) = I# (word2Int# (word16ToWord# x#))
+ -- See Note [Stable Unfolding for list producers] in GHC.Enum
+ {-# INLINE enumFrom #-}
enumFrom = boundedEnumFrom
+ -- See Note [Stable Unfolding for list producers] in GHC.Enum
+ {-# INLINE enumFromThen #-}
enumFromThen = boundedEnumFromThen
-- | @since 2.01
@@ -555,7 +563,11 @@ instance Enum Word32 where
enumFromThenTo = integralEnumFromThenTo
#else
fromEnum (W32# x#) = I# (word2Int# (word32ToWord# x#))
+ -- See Note [Stable Unfolding for list producers] in GHC.Enum
+ {-# INLINE enumFrom #-}
enumFrom = boundedEnumFrom
+ -- See Note [Stable Unfolding for list producers] in GHC.Enum
+ {-# INLINE enumFromThen #-}
enumFromThen = boundedEnumFromThen
#endif
@@ -724,9 +736,17 @@ instance Enum Word64 where
| x <= fromIntegral (maxBound::Int)
= I# (word2Int# (word64ToWord# x#))
| otherwise = fromEnumError "Word64" x
+ -- See Note [Stable Unfolding for list producers] in GHC.Enum
+ {-# INLINE enumFrom #-}
enumFrom = integralEnumFrom
+ -- See Note [Stable Unfolding for list producers] in GHC.Enum
+ {-# INLINE enumFromThen #-}
enumFromThen = integralEnumFromThen
+ -- See Note [Stable Unfolding for list producers] in GHC.Enum
+ {-# INLINE enumFromTo #-}
enumFromTo = integralEnumFromTo
+ -- See Note [Stable Unfolding for list producers] in GHC.Enum
+ {-# INLINE enumFromThenTo #-}
enumFromThenTo = integralEnumFromThenTo
-- | @since 2.01
@@ -869,10 +889,18 @@ instance Enum Word64 where
| otherwise = fromEnumError "Word64" x
#if WORD_SIZE_IN_BITS < 64
- enumFrom = integralEnumFrom
- enumFromThen = integralEnumFromThen
- enumFromTo = integralEnumFromTo
- enumFromThenTo = integralEnumFromThenTo
+ -- See Note [Stable Unfolding for list producers] in GHC.Enum
+ {-# INLINE enumFrom #-}
+ enumFrom = integralEnumFrom
+ -- See Note [Stable Unfolding for list producers] in GHC.Enum
+ {-# INLINE enumFromThen #-}
+ enumFromThen = integralEnumFromThen
+ -- See Note [Stable Unfolding for list producers] in GHC.Enum
+ {-# INLINE enumFromTo #-}
+ enumFromTo = integralEnumFromTo
+ -- See Note [Stable Unfolding for list producers] in GHC.Enum
+ {-# INLINE enumFromThenTo #-}
+ enumFromThenTo = integralEnumFromThenTo
#else
-- See Note [Stable Unfolding for list producers] in GHC.Enum
{-# INLINABLE enumFrom #-}