summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSylvain Henry <sylvain@haskus.fr>2021-08-11 16:20:53 +0200
committerMarge Bot <ben+marge-bot@smart-cactus.org>2021-09-07 08:02:28 -0400
commitf72aa31d36f4fbab0258cae1c94ac0cc24682ab9 (patch)
treebfdd65d170c425272f066a851b26bec3bdf34d96
parent3fb1afea019422292954785575902c62473e93e3 (diff)
downloadhaskell-f72aa31d36f4fbab0258cae1c94ac0cc24682ab9.tar.gz
Bignum: refactor conversion rules
* make "passthrough" rules non built-in: they don't need to * enhance note about efficient conversions between numeric types * make integerFromNatural a little more efficient * fix noinline pragma for naturalToWordClamp# (at least with non built-in rules, we get warnings in cases like this)
-rw-r--r--compiler/GHC/Core/Opt/ConstantFold.hs258
-rw-r--r--libraries/base/GHC/Float.hs26
-rw-r--r--libraries/ghc-bignum/src/GHC/Num/Integer.hs269
-rw-r--r--libraries/ghc-bignum/src/GHC/Num/Natural.hs19
-rw-r--r--testsuite/tests/numeric/should_compile/T14465.stdout8
-rw-r--r--testsuite/tests/numeric/should_compile/T19892.stderr6
6 files changed, 319 insertions, 267 deletions
diff --git a/compiler/GHC/Core/Opt/ConstantFold.hs b/compiler/GHC/Core/Opt/ConstantFold.hs
index e4d04c3548..df7e9b0782 100644
--- a/compiler/GHC/Core/Opt/ConstantFold.hs
+++ b/compiler/GHC/Core/Opt/ConstantFold.hs
@@ -1413,9 +1413,6 @@ getPlatform = roPlatform <$> getRuleOpts
getRuleOpts :: RuleM RuleOpts
getRuleOpts = RuleM $ \rule_opts _ _ _ -> Just rule_opts
-getEnv :: RuleM InScopeEnv
-getEnv = RuleM $ \_ env _ _ -> Just env
-
liftMaybe :: Maybe a -> RuleM a
liftMaybe Nothing = mzero
liftMaybe (Just x) = return x
@@ -1448,20 +1445,6 @@ getInScopeEnv = RuleM $ \_ iu _ _ -> Just iu
getFunction :: RuleM Id
getFunction = RuleM $ \_ _ fn _ -> Just fn
-exprIsVarApp_maybe :: InScopeEnv -> CoreExpr -> Maybe (Id,CoreArg)
-exprIsVarApp_maybe env@(_, id_unf) e = case e of
- App (Var f) a -> Just (f, a)
- Var v
- | Just rhs <- expandUnfolding_maybe (id_unf v)
- -> exprIsVarApp_maybe env rhs
- _ -> Nothing
-
--- | Looks into the expression or its unfolding to find "App (Var f) x"
-isVarApp :: InScopeEnv -> CoreExpr -> RuleM (Id,CoreArg)
-isVarApp env e = case exprIsVarApp_maybe env e of
- Nothing -> mzero
- Just r -> pure r
-
isLiteral :: CoreExpr -> RuleM Literal
isLiteral e = do
env <- getInScopeEnv
@@ -1970,7 +1953,6 @@ builtinBignumRules =
, integer_to_natural "Integer -> Natural (wrap)" integerToNaturalName False False
, integer_to_natural "Integer -> Natural (throw)" integerToNaturalThrowName True False
- , lit_to_natural "Word# -> Natural" naturalNSName
, natural_to_word "Natural -> Word# (wrap)" naturalToWordName False
, natural_to_word "Natural -> Word# (clamp)" naturalToWordClampName True
@@ -2050,83 +2032,6 @@ builtinBignumRules =
-- See Note [Optimising conversions between numeric types]
--
- , small_passthrough_id "Word# -> Natural -> Word#"
- naturalNSName naturalToWordName
- , small_passthrough_id "Word# -> Natural -> Word# (clamp)"
- naturalNSName naturalToWordClampName
-
- , small_passthrough_id "Int# -> Integer -> Int#"
- integerISName integerToIntName
- , small_passthrough_id "Word# -> Integer -> Word#"
- integerFromWordName integerToWordName
- , small_passthrough_id "Int64# -> Integer -> Int64#"
- integerFromInt64Name integerToInt64Name
- , small_passthrough_id "Word64# -> Integer -> Word64#"
- integerFromWord64Name integerToWord64Name
- , small_passthrough_id "Natural -> Integer -> Natural (wrap)"
- integerFromNaturalName integerToNaturalName
- , small_passthrough_id "Natural -> Integer -> Natural (throw)"
- integerFromNaturalName integerToNaturalThrowName
- , small_passthrough_id "Natural -> Integer -> Natural (clamp)"
- integerFromNaturalName integerToNaturalClampName
-
- , small_passthrough_app "Int# -> Integer -> Word#"
- integerISName integerToWordName (mkPrimOpId IntToWordOp)
- , small_passthrough_app "Int# -> Integer -> Float#"
- integerISName integerToFloatName (mkPrimOpId IntToFloatOp)
- , small_passthrough_app "Int# -> Integer -> Double#"
- integerISName integerToDoubleName (mkPrimOpId IntToDoubleOp)
-
- , small_passthrough_app "Word# -> Integer -> Int#"
- integerFromWordName integerToIntName (mkPrimOpId WordToIntOp)
- , small_passthrough_app "Word# -> Integer -> Float#"
- integerFromWordName integerToFloatName (mkPrimOpId WordToFloatOp)
- , small_passthrough_app "Word# -> Integer -> Double#"
- integerFromWordName integerToDoubleName (mkPrimOpId WordToDoubleOp)
- , small_passthrough_app "Word# -> Integer -> Natural (wrap)"
- integerFromWordName integerToNaturalName naturalNSId
- , small_passthrough_app "Word# -> Integer -> Natural (throw)"
- integerFromWordName integerToNaturalThrowName naturalNSId
- , small_passthrough_app "Word# -> Integer -> Natural (clamp)"
- integerFromWordName integerToNaturalClampName naturalNSId
-
- , small_passthrough_app "Word# -> Natural -> Float#"
- naturalNSName naturalToFloatName (mkPrimOpId WordToFloatOp)
- , small_passthrough_app "Word# -> Natural -> Double#"
- naturalNSName naturalToDoubleName (mkPrimOpId WordToDoubleOp)
-
- , small_passthrough_id "Int64# -> Integer -> Int64#"
- integerFromInt64Name integerToInt64Name
- , small_passthrough_id "Word64# -> Integer -> Word64#"
- integerFromWord64Name integerToWord64Name
-
- , small_passthrough_app "Int64# -> Integer -> Word64#"
- integerFromInt64Name integerToWord64Name (mkPrimOpId Int64ToWord64Op)
- , small_passthrough_app "Word64# -> Integer -> Int64#"
- integerFromWord64Name integerToInt64Name (mkPrimOpId Word64ToInt64Op)
-
- , small_passthrough_app "Word# -> Integer -> Word64#"
- integerFromWordName integerToWord64Name (mkPrimOpId WordToWord64Op)
- , small_passthrough_app "Word64# -> Integer -> Word#"
- integerFromWord64Name integerToWordName (mkPrimOpId Word64ToWordOp)
- , small_passthrough_app "Int# -> Integer -> Int64#"
- integerISName integerToInt64Name (mkPrimOpId IntToInt64Op)
- , small_passthrough_app "Int64# -> Integer -> Int#"
- integerFromInt64Name integerToIntName (mkPrimOpId Int64ToIntOp)
-
- , small_passthrough_custom "Int# -> Integer -> Word64#"
- integerISName integerToWord64Name
- (\x -> Var (mkPrimOpId Int64ToWord64Op) `App` (Var (mkPrimOpId IntToInt64Op) `App` x))
- , small_passthrough_custom "Word64# -> Integer -> Int#"
- integerFromWord64Name integerToIntName
- (\x -> Var (mkPrimOpId WordToIntOp) `App` (Var (mkPrimOpId Word64ToWordOp) `App` x))
- , small_passthrough_custom "Word# -> Integer -> Int64#"
- integerFromWordName integerToInt64Name
- (\x -> Var (mkPrimOpId Word64ToInt64Op) `App` (Var (mkPrimOpId WordToWord64Op) `App` x))
- , small_passthrough_custom "Int64# -> Integer -> Word#"
- integerFromInt64Name integerToWordName
- (\x -> Var (mkPrimOpId IntToWordOp) `App` (Var (mkPrimOpId Int64ToIntOp) `App` x))
-
-- Bits.bit
, bignum_bit "integerBit" integerBitName mkLitInteger
, bignum_bit "naturalBit" naturalBitName mkLitNatural
@@ -2162,27 +2067,6 @@ builtinBignumRules =
, integer_encode_float "integerEncodeDouble" integerEncodeDoubleName mkDoubleLitDouble
]
where
- -- The rule is matching against an occurrence of a data constructor in a
- -- Core expression. It must match either its worker name or its wrapper
- -- name, /not/ the DataCon name itself, which is different.
- -- See Note [Data Constructor Naming] in GHC.Core.DataCon and #19892
- --
- -- But data constructor wrappers deliberately inline late; See Note
- -- [Activation for data constructor wrappers] in GHC.Types.Id.Make.
- -- Suppose there is a wrapper and the rule matches on the worker: the
- -- wrapper won't be inlined until rules have finished firing and the rule
- -- will never fire.
- --
- -- Hence the rule must match on the wrapper, if there is one, otherwise on
- -- the worker. That is exactly the dataConWrapId for the data constructor.
- -- The data constructor may or may not have a wrapper, but if not
- -- dataConWrapId will return the worker
- --
- integerISId = dataConWrapId integerISDataCon
- naturalNSId = dataConWrapId naturalNSDataCon
- integerISName = idName integerISId
- naturalNSName = idName naturalNSId
-
mkRule str name nargs f = BuiltinRule
{ ru_name = fsLit str
, ru_fn = name
@@ -2222,13 +2106,6 @@ builtinBignumRules =
LitNumber _ i -> pure (Lit (mkLitInteger i))
_ -> mzero
- lit_to_natural str name = mkRule str name 1 $ do
- [a0] <- getArgs
- isLiteral a0 >>= \case
- -- convert any *positive* numeric literal into a Natural literal
- LitNumber _ i | i >= 0 -> pure (Lit (mkLitNatural i))
- _ -> mzero
-
integer_binop str name op = mkRule str name 2 $ do
[a0,a1] <- getArgs
x <- isIntegerLiteral a0
@@ -2290,19 +2167,6 @@ builtinBignumRules =
x <- isNumberLiteral a0
pure $ Lit (mk_lit platform (fromIntegral (popCount x)))
- small_passthrough_id str from_x to_x =
- small_passthrough_custom str from_x to_x id
-
- small_passthrough_app str from_x to_y x_to_y =
- small_passthrough_custom str from_x to_y (App (Var x_to_y))
-
- small_passthrough_custom str from_x to_y x_to_y = mkRule str to_y 1 $ do
- [a0] <- getArgs
- env <- getEnv
- (f,x) <- isVarApp env a0
- guard (idName f == from_x)
- pure $ x_to_y x
-
bignum_bit str name mk_lit = mkRule str name 1 $ do
[a0] <- getArgs
platform <- getPlatform
@@ -3267,126 +3131,4 @@ Hence caseRules returns (AltCon -> Maybe AltCon), with Nothing indicating
an alternative that is unreachable.
You may wonder how this can happen: check out #15436.
-
-
-Note [Optimising conversions between numeric types]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Converting between numeric types is very common in Haskell codes. Suppose that
-we have N inter-convertible numeric types (Word, Word8, Int, Integer, etc.).
-
-- We don't want to have to use one conversion function per pair of types as that
-would require N^2 functions: wordToWord8, wordToInt, wordToInteger...
-
-- The following kind of class would allow us to have a single conversion
-function at the price of N^2 instances and of the use of MultiParamTypeClasses
-extension.
-
- class Convert a b where
- convert :: a -> b
-
-What we do instead is that we use the Integer type (signed, unbounded) as a
-passthrough type to perform every conversion. Hence we only need to define two
-functions per numeric type:
-
- class Integral a where
- toInteger :: a -> Integer
-
- class Num a where
- fromInteger :: Integer -> a
-
-These classes have a single parameter and can be derived automatically (e.g. for
-newtypes). So we don't even have to define 2*N instances.
-
-fromIntegral
-------------
-
-We can now define a generic conversion function:
-
- -- in the Prelude
- fromIntegral :: (Integral a, Num b) => a -> b
- fromIntegral = fromInteger . toInteger
-
-The trouble with this approach is that performance might be terrible. E.g.
-converting an Int into a Word, which is a no-op at the machine level, becomes
-costly when performed via `fromIntegral` because an Integer has to be allocated.
-
-To alleviate this:
-
-- first `fromIntegral` was specialized (SPECIALIZE pragma). However it would
-need N^2 pragmas to cover every case and it wouldn't cover user defined numeric
-types which don't belong to base.
-
-- while writing this note I discovered that we have a `-fwarn-identities` warning
-to detect useless conversions (since 0656c72a8f):
-
- > fromIntegral (1 :: Int) :: Int
-
- <interactive>:3:21: warning: [-Widentities]
- Call of fromIntegral :: Int -> Int
- can probably be omitted
-
-- but more importantly, many rules were added (e.g. in e0c787c10f):
-
- "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# x#)
-
- The idea was to ensure that only cheap conversions ended up being used. E.g.:
-
- foo :: Int8 --> {- Integer -> -} -> Word8
- foo = fromIntegral
-
- ====> {Some fromIntegral rule for Int8}
-
- foo :: Int8 -> {- Int -> Integer -} -> Word8
- foo = fromIntegral . int8ToInt
-
- ====> {Some fromIntegral rule for Word8}
-
- foo :: Int8 -> {- Int -> Integer -> Word -} -> Word8
- foo = wordToWord8 . fromIntegral . int8ToInt
-
- ====> {Some fromIntegral rule for Int/Word}
-
- foo :: Int8 -> {- Int -> Word -} -> Word8
- foo = wordToWord8 . intToWord . int8ToInt
- -- not passing through Integer anymore!
-
-
-It worked but there were still some issues with this approach:
-
-1. These rules only work for `fromIntegral`. If we wanted to define our own
- similar function (e.g. using other type-classes), we would also have to redefine
- all the rules to get similar performance.
-
-2. `fromIntegral` had to be marked `NOINLINE [1]`:
- - NOINLINE to allow rules to match
- - [1] to allow inlining in later phases to avoid incurring a function call
- overhead for such a trivial operation
-
- Users of the function had to be careful because a simple helper without an
- INLINE pragma like:
-
- toInt :: Integral a => a -> Int
- toInt = fromIntegral
-
- has the following unfolding:
-
- toInt = integerToInt . toInteger
-
- which doesn't mention `fromIntegral` anymore. Hence `fromIntegral` rules
- wouldn't be triggered for any user of `toInt`. For this reason, we also have
- a bunch of rules for bignum primitives such as `integerToInt`.
-
-3. These rewrite rules are tedious to write and error-prone (cf #19345).
-
-
-For these reasons, it is simpler to only rely on built-in rewrite rules for
-bignum primitives. There aren't so many conversion primitives:
- - Natural <-> Word
- - Integer <-> Int/Word/Natural (+ Int64/Word64 on 32-bit arch)
-
-All the built-in "small_passthrough_*" rules are used to avoid passing through
-Integer/Natural. We now always inline `fromIntegral`.
-
-}
diff --git a/libraries/base/GHC/Float.hs b/libraries/base/GHC/Float.hs
index da4d14a669..743da55df8 100644
--- a/libraries/base/GHC/Float.hs
+++ b/libraries/base/GHC/Float.hs
@@ -1587,3 +1587,29 @@ foreign import prim "stg_doubleToWord64zh"
#else
stgDoubleToWord64 :: Double# -> Word64#
#endif
+
+
+
+-- See Note [Optimising conversions between numeric types]
+-- in GHC.Num.Integer
+{-# RULES
+
+"Int# -> Integer -> Float#"
+ forall x. integerToFloat# (IS x) = int2Float# x
+
+"Int# -> Integer -> Double#"
+ forall x. integerToDouble# (IS x) = int2Double# x
+
+"Word# -> Integer -> Float#"
+ forall x. integerToFloat# (integerFromWord# x) = word2Float# x
+
+"Word# -> Integer -> Double#"
+ forall x. integerToDouble# (integerFromWord# x) = word2Double# x
+
+"Word# -> Natural -> Float#"
+ forall x. naturalToFloat# (NS x) = word2Float# x
+
+"Word# -> Natural -> Double#"
+ forall x. naturalToDouble# (NS x) = word2Double# x
+
+#-}
diff --git a/libraries/ghc-bignum/src/GHC/Num/Integer.hs b/libraries/ghc-bignum/src/GHC/Num/Integer.hs
index 2dd2185592..f0cfcb81b0 100644
--- a/libraries/ghc-bignum/src/GHC/Num/Integer.hs
+++ b/libraries/ghc-bignum/src/GHC/Num/Integer.hs
@@ -194,7 +194,7 @@ integerToWord !i = W# (integerToWord# i)
integerFromNatural :: Natural -> Integer
{-# NOINLINE integerFromNatural #-}
integerFromNatural (NS x) = integerFromWord# x
-integerFromNatural (NB x) = integerFromBigNat# x
+integerFromNatural (NB x) = IP x
-- | Convert a list of Word into an Integer
integerFromWordList :: Bool -> [Word] -> Integer
@@ -1269,3 +1269,270 @@ integerPowMod# !b !e !m
-- e > 0 by cases above
| True = (# Backend.integer_powmod b (integerToNatural e) m | #)
+
+
+{-
+Note [Optimising conversions between numeric types]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Converting between numeric types is very common in Haskell codes. Suppose that
+we have N inter-convertible numeric types (Word, Word8, Word32, Int, etc.).
+
+- We don't want to have to use one conversion function per pair of types as that
+would require N^2 functions: wordToWord8, wordToInt, word8ToWord32...
+
+- The following kind of class would allow us to have a single conversion
+function but at the price of N^2 instances and of the use of
+MultiParamTypeClasses extension.
+
+ class Convert a b where
+ convert :: a -> b
+
+So what we do instead is that we use the Integer type (signed, unbounded) as a
+passthrough type to perform every conversion. Hence we only need to define two
+functions per numeric type:
+
+ class Integral a where
+ toInteger :: a -> Integer
+
+ class Num a where
+ fromInteger :: Integer -> a
+
+These classes have a single parameter and can be derived automatically (e.g. for
+newtypes). So we don't even have to define 2*N instances. For example, all the
+instances for the types in Foreign.C.Types (CChar, CShort, CInt, CUInt, etc.)
+are automatically derived from the instances for Word, Int, Word8, Word16, etc.
+
+Finally we can define a generic conversion function:
+
+ -- in the Prelude
+ fromIntegral :: (Integral a, Num b) => a -> b
+ fromIntegral = fromInteger . toInteger
+
+Efficient conversions
+~~~~~~~~~~~~~~~~~~~~~
+
+An issue with this approach is that performance might be terrible. E.g.
+converting an Int into a Word, which is a no-op at the machine level, becomes
+costly when performed via `fromIntegral` or any similar function because an
+intermediate Integer has to be allocated in the heap to perform the conversion.
+
+A solution is to bless one particular `fromIntegral`-like function and to use
+rewrite rules to replace it with a more efficient function when both types are
+known. This is what was done in the past, see next section. We use another
+approach nowadays:
+
+Notice that the set of primitive operations to convert from and to Integer and
+Natural is pretty small:
+
+ - Natural <-> Word#/BigNat#
+ - Integer <-> Int#/Word#/Natural/BigNat# (+ Int64#/Word64# on 32-bit arch)
+
+For example, we have the following primitives:
+ - integerToWord# :: Integer -> Word#
+ - integerFromWord# :: Word# -> Integer
+ - integerToInt# :: Integer -> Int#
+ - ...
+
+Compared to optimising `fromIntegral :: (Integral a, Num b) => a -> b` where `a`
+and `b` are arbitrary, we only have to write rewrite rules for the concrete
+types that can be converted from and to Natural/Integer. All the other ones
+necessarily pass through these concrete types!
+
+For example we have the following rules:
+ integerToWord# (integerFromWord# x) ===> x
+ integerToInt# (integerFromWord# x) ===> word2Int# x
+
+But we don't need rules to handle conversion from/to e.g. Word32# because there
+is no Word32#-to-Integer primitive: Word32# must be converted into something
+else first (e.g. Word#) for which we have rules.
+
+We rely on inlining of fromInteger/toInteger and on other transformations (e.g.
+float-in) to make these rules likely to fire. It seems to work well in practice.
+
+Example 1: converting an Int into a Word
+
+ fromIntegral @Int @Word x
+
+ ===> {inline fromIntegral}
+ fromInteger @Word (toInteger @Int x)
+
+ ===> {inline fromInteger and toInteger}
+ W# (integerToWord# (case x of { I# x# -> IS x# }))
+
+ ===> {float-in}
+ case x of { I# x# -> W# (integerToWord# (IS x#)) }
+
+ ===> {rewrite rule for "integerToWord# . IS"}
+ case x of { I# x# -> W# (int2Word# x#) }
+
+
+Example 2: converting an Int8 into a Word32
+
+ fromIntegral @Int8 @Word32 x
+
+ ===> {inline fromIntegral}
+ fromInteger @Word32 (toInteger @Int8 x)
+
+ ===> {inline fromInteger and toInteger}
+ W32# (wordToWord32# (integerToWord# (case x of { I8# x# -> IS (int8ToInt# x#) })))
+
+ ===> {float-in}
+ case x of { I8# x# -> W32# (wordToWord32# (integerToWord# (IS (int8ToInt# x#)))) }
+
+ ===> {rewrite rule for "integerToWord# . IS"}
+ case x of { I8# x# -> W32# (wordToWord32# (int2Word# (int8ToInt# x#))) }
+
+ Notice that in the resulting expression the value passes through types Int#
+ and Word# with native machine word size: it is first sign-extended from Int8#
+ to Int#, then cast into Word#, and finally truncated into Word32#. These are
+ all very cheap operations that are performed in registers without allocating
+ anything in the heap.
+
+
+
+Historical fromIntegral optimisations
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+In the past, `fromIntegral` function in the Prelude was special because many
+rewrite rules were mentioning it explicitly. For example to replace a call to
+`fromIntegral :: Int -> Word`, which allocates an intermediate Integer, with a
+call to `intToWord`, which is a no-op when compiled into machine code. Nowadays
+`fromIntegral` isn't a special function anymore and we just INLINE it (see above).
+
+- first `fromIntegral` was specialized (SPECIALIZE pragma). However it would
+need N^2 pragmas to cover every case and it wouldn't cover user defined numeric
+types which don't belong to base.
+
+- `-fwarn-identities` enables a warning to detect useless conversions via
+fromIntegral (since 0656c72a8f):
+
+ > fromIntegral (1 :: Int) :: Int
+
+ <interactive>:3:21: warning: [-Widentities]
+ Call of fromIntegral :: Int -> Int
+ can probably be omitted
+
+
+- many rules were added (e.g. in e0c787c10f) to perform float-in transformations
+explicitly (to allow more fromIntegral rules to fire) and to replace some
+fromIntegral calls with faster operations:
+
+ "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# x#)
+
+It worked but there were still some issues with this approach:
+
+1. These rules only work for `fromIntegral`. If we wanted to define our own
+ similar function (e.g. using other type-classes), we would also have to redefine
+ all the rules to get similar performance.
+
+2. `fromIntegral` had to be marked `NOINLINE [1]`:
+ - NOINLINE to allow rules to match
+ - [1] to allow inlining in later phases to avoid incurring a function call
+ overhead for such a trivial operation
+
+ Users of the function had to be careful because a simple helper without an
+ INLINE pragma like:
+
+ toInt :: Integral a => a -> Int
+ toInt = fromIntegral
+
+ had the following unfolding:
+
+ toInt = integerToInt . toInteger
+
+ which doesn't mention `fromIntegral` anymore. Hence `fromIntegral` rules
+ wouldn't fire for codes using `toInt` while they would if they had used
+ `fromIntegral` directly!
+ For this reason, a bunch of rules for bignum primitives as we have now were
+ already present to handle these cases.
+
+3. These rewrite rules were tedious to write and error-prone (cf #19345).
+
+For these reasons, it is simpler to not consider fromIntegral special at all and
+to only rely on rewrite rules for bignum functions.
+
+-}
+
+-- See Note [Optimising conversions between numeric types]
+{-# RULES
+"Word# -> Natural -> Integer"
+ forall x. integerFromNatural (NS x) = integerFromWord# x
+
+"BigNat# -> Natural -> Integer"
+ forall x. integerFromNatural (NB x) = IP x
+
+"Int# -> Integer -> Int#"
+ forall x. integerToInt# (IS x) = x
+
+"Word# -> Integer -> Word#"
+ forall x. integerToWord# (integerFromWord# x) = x
+
+"Natural -> Integer -> Natural (wrap)"
+ forall x. integerToNatural (integerFromNatural x) = x
+
+"Natural -> Integer -> Natural (throw)"
+ forall x. integerToNaturalThrow (integerFromNatural x) = x
+
+"Natural -> Integer -> Natural (clamp)"
+ forall x. integerToNaturalClamp (integerFromNatural x) = x
+
+"Int# -> Integer -> Word#"
+ forall x. integerToWord# (IS x) = int2Word# x
+
+"Word# -> Integer -> Int#"
+ forall x. integerToInt# (integerFromWord# x) = word2Int# x
+
+"Word# -> Integer -> Natural (wrap)"
+ forall x. integerToNatural (integerFromWord# x) = NS x
+
+"Word# -> Integer -> Natural (throw)"
+ forall x. integerToNaturalThrow (integerFromWord# x) = NS x
+
+"Word# -> Integer -> Natural (clamp)"
+ forall x. integerToNaturalClamp (integerFromWord# x) = NS x
+
+#-}
+
+#if WORD_SIZE_IN_BITS == 32
+{-# RULES
+
+"Int64# -> Integer -> Int64#"
+ forall x. integerToInt64# (integerFromInt64# x) = x
+
+"Word64# -> Integer -> Word64#"
+ forall x. integerToWord64# (integerFromWord64# x) = x
+
+"Int64# -> Integer -> Word64#"
+ forall x. integerToWord64# (integerFromInt64# x) = int64ToWord64# x
+
+"Word64# -> Integer -> Int64#"
+ forall x. integerToInt64# (integerFromWord64# x) = word64ToInt64# x
+
+"Word# -> Integer -> Word64#"
+ forall x. integerToWord64# (integerFromWord# x) = wordToWord64# x
+
+"Word64# -> Integer -> Word#"
+ forall x. integerToWord# (integerFromWord64# x) = word64ToWord# x
+
+"Int# -> Integer -> Int64#"
+ forall x. integerToInt64# (IS x) = intToInt64# x
+
+"Int64# -> Integer -> Int#"
+ forall x. integerToInt# (integerFromInt64# x) = int64ToInt# x
+
+"Int# -> Integer -> Word64#"
+ forall x. integerToWord64# (IS x) = int64ToWord64# (intToInt64# x)
+
+"Int64# -> Integer -> Word#"
+ forall x. integerToWord# (integerFromInt64# x) = int2Word# (int64ToInt# x)
+
+"Word# -> Integer -> Int64#"
+ forall x. integerToInt64# (integerFromWord# x) = word64ToInt64# (wordToWord64# x)
+
+"Word64# -> Integer -> Int#"
+ forall x. integerToInt# (integerFromWord64# x) = word2Int# (word64ToWord# x)
+
+#-}
+#endif
diff --git a/libraries/ghc-bignum/src/GHC/Num/Natural.hs b/libraries/ghc-bignum/src/GHC/Num/Natural.hs
index 38a20f5169..9f950a843c 100644
--- a/libraries/ghc-bignum/src/GHC/Num/Natural.hs
+++ b/libraries/ghc-bignum/src/GHC/Num/Natural.hs
@@ -72,6 +72,7 @@ naturalIsPowerOf2# (NB w) = bigNatIsPowerOf2# w
-- | Create a Natural from a BigNat# (respect the invariants)
naturalFromBigNat# :: BigNat# -> Natural
+{-# NOINLINE naturalFromBigNat# #-}
naturalFromBigNat# x = case bigNatSize# x of
0# -> naturalZero
1# -> NS (bigNatIndex# x 0#)
@@ -79,6 +80,7 @@ naturalFromBigNat# x = case bigNatSize# x of
-- | Convert a Natural into a BigNat#
naturalToBigNat# :: Natural -> BigNat#
+{-# NOINLINE naturalToBigNat# #-}
naturalToBigNat# (NS w) = bigNatFromWord# w
naturalToBigNat# (NB bn) = bn
@@ -112,7 +114,7 @@ naturalToWord !n = W# (naturalToWord# n)
-- | Convert a Natural into a Word# clamping to (maxBound :: Word#).
naturalToWordClamp# :: Natural -> Word#
-{-# NOINLINE naturalToWordClamp #-}
+{-# NOINLINE naturalToWordClamp# #-}
naturalToWordClamp# (NS x) = x
naturalToWordClamp# (NB _) = WORD_MAXBOUND##
@@ -585,3 +587,18 @@ naturalFromByteArray# :: Word# -> ByteArray# -> Word# -> Bool# -> State# s -> (#
{-# NOINLINE naturalFromByteArray# #-}
naturalFromByteArray# sz ba off e s = case bigNatFromByteArray# sz ba off e s of
(# s', a #) -> (# s', naturalFromBigNat# a #)
+
+
+
+-- See Note [Optimising conversions between numeric types]
+-- in GHC.Num.Integer
+{-# RULES
+"Word# -> Natural -> Word#"
+ forall x. naturalToWord# (NS x) = x
+
+"Word# -> Natural -> Word# (clamp)"
+ forall x. naturalToWordClamp# (NS x) = x
+
+"BigNat# -> Natural -> BigNat#"
+ forall x. naturalToBigNat# (naturalFromBigNat# x) = x
+#-}
diff --git a/testsuite/tests/numeric/should_compile/T14465.stdout b/testsuite/tests/numeric/should_compile/T14465.stdout
index 7c2e846101..d640a017cc 100644
--- a/testsuite/tests/numeric/should_compile/T14465.stdout
+++ b/testsuite/tests/numeric/should_compile/T14465.stdout
@@ -1,14 +1,14 @@
==================== Tidy Core ====================
Result size of Tidy Core
- = {terms: 34, types: 14, coercions: 0, joins: 0/0}
+ = {terms: 35, types: 14, coercions: 0, joins: 0/0}
--- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
ten :: Natural
[GblId,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
- WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 100 0}]
-ten = 10
+ WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}]
+ten = GHC.Num.Natural.NS 10##
-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
M.$trModule4 :: GHC.Prim.Addr#
diff --git a/testsuite/tests/numeric/should_compile/T19892.stderr b/testsuite/tests/numeric/should_compile/T19892.stderr
index 89411a6df9..a82ea9d9d2 100644
--- a/testsuite/tests/numeric/should_compile/T19892.stderr
+++ b/testsuite/tests/numeric/should_compile/T19892.stderr
@@ -1,4 +1,4 @@
-Rule fired: Int# -> Integer -> Word# (BUILTIN)
+Rule fired: Int# -> Integer -> Word# (GHC.Num.Integer)
Rule fired: int2Word# (BUILTIN)
-Rule fired: Int# -> Integer -> Int# (BUILTIN)
-Rule fired: Word# -> Natural -> Word# (BUILTIN)
+Rule fired: Int# -> Integer -> Int# (GHC.Num.Integer)
+Rule fired: Word# -> Natural -> Word# (GHC.Num.Natural)