summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSylvain Henry <sylvain@haskus.fr>2021-05-31 15:47:56 +0200
committerBen Gamari <ben@smart-cactus.org>2021-08-05 21:19:13 -0400
commit4d2bbd676e8f9c6b19f8b2dc94b54096f3e4f777 (patch)
tree93bc2ae19a7bf5b029a8ba10f7f7bb0423372627
parenta24044dcb0df17fb10d3f4bd4d9d75df79cfe06f (diff)
downloadhaskell-4d2bbd676e8f9c6b19f8b2dc94b54096f3e4f777.tar.gz
Remove ad-hoc fromIntegral rules
fromIntegral is defined as: {-# NOINLINE [1] fromIntegral #-} fromIntegral :: (Integral a, Num b) => a -> b fromIntegral = fromInteger . toInteger Before this patch, we had a lot of rewrite rules for fromIntegral, to avoid passing through Integer when there is a faster way, e.g.: "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 Since we have added sized types and primops (Word8#, Int16#, etc.) and Natural, this approach didn't really scale as there is a combinatorial explosion of types. In addition, we really want these conversions to be optimized for all these types and in every case (not only when fromIntegral is explicitly used). This patch removes all those ad-hoc fromIntegral rules. Instead we rely on inlining and built-in constant-folding rules. There are not too many native conversions between Integer/Natural and fixed size types, so we can handle them all explicitly. Foreign.C.Types was using rules to ensure that fromIntegral rules "sees" through the newtype wrappers,e.g.: {-# RULES "fromIntegral/a->CSize" fromIntegral = \x -> CSize (fromIntegral x) "fromIntegral/CSize->a" fromIntegral = \(CSize x) -> fromIntegral x #-} But they aren't necessary because coercions due to newtype deriving are pushed out of the way. So this patch removes these rules (as fromIntegral is now inlined, they won't match anymore anyway). Summary: * INLINE `fromIntegral` * Add some missing constant-folding rules * Remove every fromIntegral ad-hoc rules (fix #19907) Fix #20062 (missing fromIntegral rules for sized primitives) Performance: - T12545 wiggles (tracked by #19414) Metric Decrease: T12545 T10359 Metric Increase: T12545 (cherry picked from commit 145a356606db754ac39e095338f00b98e013c7f2)
-rw-r--r--compiler/GHC/Core/Opt/ConstantFold.hs289
-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.hs51
-rw-r--r--libraries/base/GHC/Word.hs82
-rw-r--r--testsuite/tests/numeric/should_compile/T20062.hs1008
-rw-r--r--testsuite/tests/numeric/should_compile/all.T1
9 files changed, 1254 insertions, 311 deletions
diff --git a/compiler/GHC/Core/Opt/ConstantFold.hs b/compiler/GHC/Core/Opt/ConstantFold.hs
index eba36f0902..645329703d 100644
--- a/compiler/GHC/Core/Opt/ConstantFold.hs
+++ b/compiler/GHC/Core/Opt/ConstantFold.hs
@@ -1374,10 +1374,13 @@ instance Alternative RuleM where
instance MonadPlus RuleM
getPlatform :: RuleM Platform
-getPlatform = roPlatform <$> getEnv
+getPlatform = roPlatform <$> getRuleOpts
-getEnv :: RuleM RuleOpts
-getEnv = RuleM $ \env _ _ _ -> Just env
+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
@@ -1411,6 +1414,20 @@ 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
@@ -1452,13 +1469,13 @@ getLiteral n = RuleM $ \_ _ _ exprs -> case drop n exprs of
unaryLit :: (RuleOpts -> Literal -> Maybe CoreExpr) -> RuleM CoreExpr
unaryLit op = do
- env <- getEnv
+ env <- getRuleOpts
[Lit l] <- getArgs
liftMaybe $ op env (convFloating env l)
binaryLit :: (RuleOpts -> Literal -> Literal -> Maybe CoreExpr) -> RuleM CoreExpr
binaryLit op = do
- env <- getEnv
+ env <- getRuleOpts
[Lit l1, Lit l2] <- getArgs
liftMaybe $ op env (convFloating env l1) (convFloating env l2)
@@ -1987,62 +2004,91 @@ builtinBignumRules =
, bignum_popcount "integerPopCount" integerPopCountName mkLitIntWrap
, bignum_popcount "naturalPopCount" naturalPopCountName mkLitWordWrap
- -- identity passthrough
- , id_passthrough "Int# -> Integer -> Int#"
- integerToIntName integerISName
- , id_passthrough "Word# -> Integer -> Word#"
- integerToWordName integerFromWordName
- , id_passthrough "Int64# -> Integer -> Int64#"
- integerToInt64Name integerFromInt64Name
- , id_passthrough "Word64# -> Integer -> Word64#"
- integerToWord64Name integerFromWord64Name
- , id_passthrough "Natural -> Integer -> Natural (wrap)"
- integerToNaturalName integerFromNaturalName
- , id_passthrough "Natural -> Integer -> Natural (throw)"
- integerToNaturalThrowName integerFromNaturalName
- , id_passthrough "Natural -> Integer -> Natural (clamp)"
- integerToNaturalClampName integerFromNaturalName
- , id_passthrough "Word# -> Natural -> Word#"
- naturalToWordName naturalNSName
- , id_passthrough "Word# -> Natural -> Word# (clamp)"
- naturalToWordClampName naturalNSName
-
- -- passthrough bignum small constructors with a conversion that can be done
- -- directly instead
-
- , small_passthrough "Int# -> Integer -> Word#"
+ ------------------------------------------------------------
+ -- The following `small_passthough_*` rules are used to optimise conversions
+ -- between numeric types by avoiding passing through "small" constructors of
+ -- Integer and Natural.
+ --
+ -- 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 "Int# -> Integer -> Float#"
+ , small_passthrough_app "Int# -> Integer -> Float#"
integerISName integerToFloatName (mkPrimOpId IntToFloatOp)
- , small_passthrough "Int# -> Integer -> Double#"
+ , small_passthrough_app "Int# -> Integer -> Double#"
integerISName integerToDoubleName (mkPrimOpId IntToDoubleOp)
- , small_passthrough "Word# -> Integer -> Float#"
+
+ , small_passthrough_app "Word# -> Integer -> Int#"
+ integerFromWordName integerToIntName (mkPrimOpId WordToIntOp)
+ , small_passthrough_app "Word# -> Integer -> Float#"
integerFromWordName integerToFloatName (mkPrimOpId WordToFloatOp)
- , small_passthrough "Word# -> Integer -> Double#"
+ , small_passthrough_app "Word# -> Integer -> Double#"
integerFromWordName integerToDoubleName (mkPrimOpId WordToDoubleOp)
- , small_passthrough "Word# -> Natural -> Float#"
+ , 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 "Word# -> Natural -> Double#"
+ , small_passthrough_app "Word# -> Natural -> Double#"
naturalNSName naturalToDoubleName (mkPrimOpId WordToDoubleOp)
+
#if WORD_SIZE_IN_BITS < 64
- , id_passthrough "Int64# -> Integer -> Int64#"
- integerToInt64Name integerFromInt64Name
- , id_passthrough "Word64# -> Integer -> Word64#"
- integerToWord64Name integerFromWord64Name
+ , small_passthrough_id "Int64# -> Integer -> Int64#"
+ integerFromInt64Name integerToInt64Name
+ , small_passthrough_id "Word64# -> Integer -> Word64#"
+ integerFromWord64Name integerToWord64Name
- , small_passthrough "Int64# -> Integer -> Word64#"
+ , small_passthrough_app "Int64# -> Integer -> Word64#"
integerFromInt64Name integerToWord64Name (mkPrimOpId Int64ToWord64Op)
- , small_passthrough "Word64# -> Integer -> Int64#"
+ , small_passthrough_app "Word64# -> Integer -> Int64#"
integerFromWord64Name integerToInt64Name (mkPrimOpId Word64ToInt64Op)
- , small_passthrough "Word# -> Integer -> Word64#"
+ , small_passthrough_app "Word# -> Integer -> Word64#"
integerFromWordName integerToWord64Name (mkPrimOpId WordToWord64Op)
- , small_passthrough "Word64# -> Integer -> Word#"
+ , small_passthrough_app "Word64# -> Integer -> Word#"
integerFromWord64Name integerToWordName (mkPrimOpId Word64ToWordOp)
- , small_passthrough "Int# -> Integer -> Int64#"
+ , small_passthrough_app "Int# -> Integer -> Int64#"
integerISName integerToInt64Name (mkPrimOpId IntToInt64Op)
- , small_passthrough "Int64# -> Integer -> Int#"
+ , 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))
#endif
-- Bits.bit
@@ -2096,15 +2142,17 @@ builtinBignumRules =
-- The data constructor may or may not have a wrapper, but if not
-- dataConWrapId will return the worker
--
- integerISName = idName (dataConWrapId integerISDataCon)
- naturalNSName = idName (dataConWrapId naturalNSDataCon)
+ 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
, ru_nargs = nargs
, ru_try = runRuleM $ do
- env <- getEnv
+ env <- getRuleOpts
guard (roBignumRules env)
f
}
@@ -2206,15 +2254,18 @@ builtinBignumRules =
x <- isNumberLiteral a0
pure $ Lit (mk_lit platform (fromIntegral (popCount x)))
- id_passthrough str to_x from_x = mkRule str to_x 1 $ do
- [App (Var f) x] <- getArgs
- guard (idName f == from_x)
- pure 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 str from_x to_y x_to_y = mkRule str to_y 1 $ do
- [App (Var f) x] <- getArgs
+ 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 $ App (Var x_to_y) x
+ pure $ x_to_y x
bignum_bit str name mk_lit = mkRule str name 1 $ do
[a0] <- getArgs
@@ -2542,7 +2593,7 @@ match_magicDict _ = Nothing
addFoldingRules :: PrimOp -> NumOps -> RuleM CoreExpr
addFoldingRules op num_ops = do
ASSERT(op == numAdd num_ops) return ()
- env <- getEnv
+ env <- getRuleOpts
guard (roNumConstantFolding env)
[arg1,arg2] <- getArgs
platform <- getPlatform
@@ -2554,7 +2605,7 @@ addFoldingRules op num_ops = do
subFoldingRules :: PrimOp -> NumOps -> RuleM CoreExpr
subFoldingRules op num_ops = do
ASSERT(op == numSub num_ops) return ()
- env <- getEnv
+ env <- getRuleOpts
guard (roNumConstantFolding env)
[arg1,arg2] <- getArgs
platform <- getPlatform
@@ -2563,7 +2614,7 @@ subFoldingRules op num_ops = do
mulFoldingRules :: PrimOp -> NumOps -> RuleM CoreExpr
mulFoldingRules op num_ops = do
ASSERT(op == numMul num_ops) return ()
- env <- getEnv
+ env <- getRuleOpts
guard (roNumConstantFolding env)
[arg1,arg2] <- getArgs
platform <- getPlatform
@@ -3147,4 +3198,126 @@ 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/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 4bb4169a9f..8ca903d9fe 100644
--- a/libraries/base/GHC/Float.hs
+++ b/libraries/base/GHC/Float.hs
@@ -1356,10 +1356,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 b9dea130c8..c8a0312d64 100644
--- a/libraries/base/GHC/Int.hs
+++ b/libraries/base/GHC/Int.hs
@@ -49,7 +49,6 @@ import GHC.Num
import GHC.Real
import GHC.Read
import GHC.Arr
-import GHC.Word hiding (uncheckedShiftL64#, uncheckedShiftRL64#)
import GHC.Show
------------------------------------------------------------------------
@@ -234,12 +233,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 {
@@ -451,14 +444,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 {
@@ -657,16 +642,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 {
@@ -906,16 +881,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
@@ -1071,11 +1036,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 {
@@ -1142,35 +1102,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 4b57f8a746..5121741cf7 100644
--- a/libraries/base/GHC/Real.hs
+++ b/libraries/base/GHC/Real.hs
@@ -455,7 +455,7 @@ instance Integral Integer where
-- | @since 4.8.0.0
instance Integral Natural where
- toInteger = integerFromNatural
+ toInteger x = integerFromNatural x
{-# INLINE quot #-}
_ `quot` 0 = divZeroError
@@ -565,54 +565,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 a5c9759c4e..5f8a4d206d 100644
--- a/libraries/base/GHC/Word.hs
+++ b/libraries/base/GHC/Word.hs
@@ -218,13 +218,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 {
@@ -415,14 +408,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 {
@@ -591,15 +576,7 @@ instance Integral Word32 where
| y /= 0 = (W32# (wordToWord32# ((word32ToWord# x#) `quotWord#` (word32ToWord# y#)))
,W32# (wordToWord32# ((word32ToWord# x#) `remWord#` (word32ToWord# y#))))
| otherwise = divZeroError
- 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
@@ -645,15 +622,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
@@ -823,14 +791,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.
@@ -956,11 +916,7 @@ instance Integral Word64 where
divMod (W64# x#) y@(W64# y#)
| y /= 0 = (W64# (x# `quotWord#` y#), W64# (x# `remWord#` y#))
| otherwise = divZeroError
- 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
@@ -997,11 +953,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#
@@ -1077,32 +1028,3 @@ bitReverse64 :: Word64 -> Word64
bitReverse64 (W64# w#) = W64# (bitReverse# w#)
#endif
--------------------------------------------------------------------------------
-
-{-# 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
diff --git a/testsuite/tests/numeric/should_compile/T20062.hs b/testsuite/tests/numeric/should_compile/T20062.hs
new file mode 100644
index 0000000000..f4c5024313
--- /dev/null
+++ b/testsuite/tests/numeric/should_compile/T20062.hs
@@ -0,0 +1,1008 @@
+module T20062 where
+
+import GHC.Int
+import GHC.Word
+import Data.Char
+import Control.Monad
+import Foreign.C.Types
+
+---------------------------------------------------------------
+-- This is used to generate the code that is copy-pasted below
+---------------------------------------------------------------
+
+types :: [String]
+types = [ "Word64", "Word32", "Word16", "Word8"
+ , "Int64" , "Int32" , "Int16" , "Int8"
+ , "CChar" , "CUShort", "CUInt", "CULong", "CULLong"
+ , "CSChar", "CShort" , "CInt" , "CLong" , "CLLong"
+ ]
+
+main :: IO ()
+main = do
+ forM_ types $ \t1 ->
+ forM_ types $ \t2 -> do
+ let n = fmap toLower t1++"_to_"++fmap toLower t2
+ let t = ":: "++t1++" -> "++t2
+ putStrLn $ mconcat
+ [ n, t, "\n"
+ , n, " = fromIntegral\n"
+ ]
+
+---------------------------------------------------------------
+-- End of generator
+--
+-- Copy-paste of generated code:
+---------------------------------------------------------------
+
+word64_to_word64:: Word64 -> Word64
+word64_to_word64 = fromIntegral
+
+word64_to_word32:: Word64 -> Word32
+word64_to_word32 = fromIntegral
+
+word64_to_word16:: Word64 -> Word16
+word64_to_word16 = fromIntegral
+
+word64_to_word8:: Word64 -> Word8
+word64_to_word8 = fromIntegral
+
+word64_to_int64:: Word64 -> Int64
+word64_to_int64 = fromIntegral
+
+word64_to_int32:: Word64 -> Int32
+word64_to_int32 = fromIntegral
+
+word64_to_int16:: Word64 -> Int16
+word64_to_int16 = fromIntegral
+
+word64_to_int8:: Word64 -> Int8
+word64_to_int8 = fromIntegral
+
+word64_to_cchar:: Word64 -> CChar
+word64_to_cchar = fromIntegral
+
+word64_to_cushort:: Word64 -> CUShort
+word64_to_cushort = fromIntegral
+
+word64_to_cuint:: Word64 -> CUInt
+word64_to_cuint = fromIntegral
+
+word64_to_culong:: Word64 -> CULong
+word64_to_culong = fromIntegral
+
+word64_to_cullong:: Word64 -> CULLong
+word64_to_cullong = fromIntegral
+
+word64_to_cschar:: Word64 -> CSChar
+word64_to_cschar = fromIntegral
+
+word64_to_cshort:: Word64 -> CShort
+word64_to_cshort = fromIntegral
+
+word64_to_cint:: Word64 -> CInt
+word64_to_cint = fromIntegral
+
+word64_to_clong:: Word64 -> CLong
+word64_to_clong = fromIntegral
+
+word64_to_cllong:: Word64 -> CLLong
+word64_to_cllong = fromIntegral
+
+word32_to_word64:: Word32 -> Word64
+word32_to_word64 = fromIntegral
+
+word32_to_word32:: Word32 -> Word32
+word32_to_word32 = fromIntegral
+
+word32_to_word16:: Word32 -> Word16
+word32_to_word16 = fromIntegral
+
+word32_to_word8:: Word32 -> Word8
+word32_to_word8 = fromIntegral
+
+word32_to_int64:: Word32 -> Int64
+word32_to_int64 = fromIntegral
+
+word32_to_int32:: Word32 -> Int32
+word32_to_int32 = fromIntegral
+
+word32_to_int16:: Word32 -> Int16
+word32_to_int16 = fromIntegral
+
+word32_to_int8:: Word32 -> Int8
+word32_to_int8 = fromIntegral
+
+word32_to_cchar:: Word32 -> CChar
+word32_to_cchar = fromIntegral
+
+word32_to_cushort:: Word32 -> CUShort
+word32_to_cushort = fromIntegral
+
+word32_to_cuint:: Word32 -> CUInt
+word32_to_cuint = fromIntegral
+
+word32_to_culong:: Word32 -> CULong
+word32_to_culong = fromIntegral
+
+word32_to_cullong:: Word32 -> CULLong
+word32_to_cullong = fromIntegral
+
+word32_to_cschar:: Word32 -> CSChar
+word32_to_cschar = fromIntegral
+
+word32_to_cshort:: Word32 -> CShort
+word32_to_cshort = fromIntegral
+
+word32_to_cint:: Word32 -> CInt
+word32_to_cint = fromIntegral
+
+word32_to_clong:: Word32 -> CLong
+word32_to_clong = fromIntegral
+
+word32_to_cllong:: Word32 -> CLLong
+word32_to_cllong = fromIntegral
+
+word16_to_word64:: Word16 -> Word64
+word16_to_word64 = fromIntegral
+
+word16_to_word32:: Word16 -> Word32
+word16_to_word32 = fromIntegral
+
+word16_to_word16:: Word16 -> Word16
+word16_to_word16 = fromIntegral
+
+word16_to_word8:: Word16 -> Word8
+word16_to_word8 = fromIntegral
+
+word16_to_int64:: Word16 -> Int64
+word16_to_int64 = fromIntegral
+
+word16_to_int32:: Word16 -> Int32
+word16_to_int32 = fromIntegral
+
+word16_to_int16:: Word16 -> Int16
+word16_to_int16 = fromIntegral
+
+word16_to_int8:: Word16 -> Int8
+word16_to_int8 = fromIntegral
+
+word16_to_cchar:: Word16 -> CChar
+word16_to_cchar = fromIntegral
+
+word16_to_cushort:: Word16 -> CUShort
+word16_to_cushort = fromIntegral
+
+word16_to_cuint:: Word16 -> CUInt
+word16_to_cuint = fromIntegral
+
+word16_to_culong:: Word16 -> CULong
+word16_to_culong = fromIntegral
+
+word16_to_cullong:: Word16 -> CULLong
+word16_to_cullong = fromIntegral
+
+word16_to_cschar:: Word16 -> CSChar
+word16_to_cschar = fromIntegral
+
+word16_to_cshort:: Word16 -> CShort
+word16_to_cshort = fromIntegral
+
+word16_to_cint:: Word16 -> CInt
+word16_to_cint = fromIntegral
+
+word16_to_clong:: Word16 -> CLong
+word16_to_clong = fromIntegral
+
+word16_to_cllong:: Word16 -> CLLong
+word16_to_cllong = fromIntegral
+
+word8_to_word64:: Word8 -> Word64
+word8_to_word64 = fromIntegral
+
+word8_to_word32:: Word8 -> Word32
+word8_to_word32 = fromIntegral
+
+word8_to_word16:: Word8 -> Word16
+word8_to_word16 = fromIntegral
+
+word8_to_word8:: Word8 -> Word8
+word8_to_word8 = fromIntegral
+
+word8_to_int64:: Word8 -> Int64
+word8_to_int64 = fromIntegral
+
+word8_to_int32:: Word8 -> Int32
+word8_to_int32 = fromIntegral
+
+word8_to_int16:: Word8 -> Int16
+word8_to_int16 = fromIntegral
+
+word8_to_int8:: Word8 -> Int8
+word8_to_int8 = fromIntegral
+
+word8_to_cchar:: Word8 -> CChar
+word8_to_cchar = fromIntegral
+
+word8_to_cushort:: Word8 -> CUShort
+word8_to_cushort = fromIntegral
+
+word8_to_cuint:: Word8 -> CUInt
+word8_to_cuint = fromIntegral
+
+word8_to_culong:: Word8 -> CULong
+word8_to_culong = fromIntegral
+
+word8_to_cullong:: Word8 -> CULLong
+word8_to_cullong = fromIntegral
+
+word8_to_cschar:: Word8 -> CSChar
+word8_to_cschar = fromIntegral
+
+word8_to_cshort:: Word8 -> CShort
+word8_to_cshort = fromIntegral
+
+word8_to_cint:: Word8 -> CInt
+word8_to_cint = fromIntegral
+
+word8_to_clong:: Word8 -> CLong
+word8_to_clong = fromIntegral
+
+word8_to_cllong:: Word8 -> CLLong
+word8_to_cllong = fromIntegral
+
+int64_to_word64:: Int64 -> Word64
+int64_to_word64 = fromIntegral
+
+int64_to_word32:: Int64 -> Word32
+int64_to_word32 = fromIntegral
+
+int64_to_word16:: Int64 -> Word16
+int64_to_word16 = fromIntegral
+
+int64_to_word8:: Int64 -> Word8
+int64_to_word8 = fromIntegral
+
+int64_to_int64:: Int64 -> Int64
+int64_to_int64 = fromIntegral
+
+int64_to_int32:: Int64 -> Int32
+int64_to_int32 = fromIntegral
+
+int64_to_int16:: Int64 -> Int16
+int64_to_int16 = fromIntegral
+
+int64_to_int8:: Int64 -> Int8
+int64_to_int8 = fromIntegral
+
+int64_to_cchar:: Int64 -> CChar
+int64_to_cchar = fromIntegral
+
+int64_to_cushort:: Int64 -> CUShort
+int64_to_cushort = fromIntegral
+
+int64_to_cuint:: Int64 -> CUInt
+int64_to_cuint = fromIntegral
+
+int64_to_culong:: Int64 -> CULong
+int64_to_culong = fromIntegral
+
+int64_to_cullong:: Int64 -> CULLong
+int64_to_cullong = fromIntegral
+
+int64_to_cschar:: Int64 -> CSChar
+int64_to_cschar = fromIntegral
+
+int64_to_cshort:: Int64 -> CShort
+int64_to_cshort = fromIntegral
+
+int64_to_cint:: Int64 -> CInt
+int64_to_cint = fromIntegral
+
+int64_to_clong:: Int64 -> CLong
+int64_to_clong = fromIntegral
+
+int64_to_cllong:: Int64 -> CLLong
+int64_to_cllong = fromIntegral
+
+int32_to_word64:: Int32 -> Word64
+int32_to_word64 = fromIntegral
+
+int32_to_word32:: Int32 -> Word32
+int32_to_word32 = fromIntegral
+
+int32_to_word16:: Int32 -> Word16
+int32_to_word16 = fromIntegral
+
+int32_to_word8:: Int32 -> Word8
+int32_to_word8 = fromIntegral
+
+int32_to_int64:: Int32 -> Int64
+int32_to_int64 = fromIntegral
+
+int32_to_int32:: Int32 -> Int32
+int32_to_int32 = fromIntegral
+
+int32_to_int16:: Int32 -> Int16
+int32_to_int16 = fromIntegral
+
+int32_to_int8:: Int32 -> Int8
+int32_to_int8 = fromIntegral
+
+int32_to_cchar:: Int32 -> CChar
+int32_to_cchar = fromIntegral
+
+int32_to_cushort:: Int32 -> CUShort
+int32_to_cushort = fromIntegral
+
+int32_to_cuint:: Int32 -> CUInt
+int32_to_cuint = fromIntegral
+
+int32_to_culong:: Int32 -> CULong
+int32_to_culong = fromIntegral
+
+int32_to_cullong:: Int32 -> CULLong
+int32_to_cullong = fromIntegral
+
+int32_to_cschar:: Int32 -> CSChar
+int32_to_cschar = fromIntegral
+
+int32_to_cshort:: Int32 -> CShort
+int32_to_cshort = fromIntegral
+
+int32_to_cint:: Int32 -> CInt
+int32_to_cint = fromIntegral
+
+int32_to_clong:: Int32 -> CLong
+int32_to_clong = fromIntegral
+
+int32_to_cllong:: Int32 -> CLLong
+int32_to_cllong = fromIntegral
+
+int16_to_word64:: Int16 -> Word64
+int16_to_word64 = fromIntegral
+
+int16_to_word32:: Int16 -> Word32
+int16_to_word32 = fromIntegral
+
+int16_to_word16:: Int16 -> Word16
+int16_to_word16 = fromIntegral
+
+int16_to_word8:: Int16 -> Word8
+int16_to_word8 = fromIntegral
+
+int16_to_int64:: Int16 -> Int64
+int16_to_int64 = fromIntegral
+
+int16_to_int32:: Int16 -> Int32
+int16_to_int32 = fromIntegral
+
+int16_to_int16:: Int16 -> Int16
+int16_to_int16 = fromIntegral
+
+int16_to_int8:: Int16 -> Int8
+int16_to_int8 = fromIntegral
+
+int16_to_cchar:: Int16 -> CChar
+int16_to_cchar = fromIntegral
+
+int16_to_cushort:: Int16 -> CUShort
+int16_to_cushort = fromIntegral
+
+int16_to_cuint:: Int16 -> CUInt
+int16_to_cuint = fromIntegral
+
+int16_to_culong:: Int16 -> CULong
+int16_to_culong = fromIntegral
+
+int16_to_cullong:: Int16 -> CULLong
+int16_to_cullong = fromIntegral
+
+int16_to_cschar:: Int16 -> CSChar
+int16_to_cschar = fromIntegral
+
+int16_to_cshort:: Int16 -> CShort
+int16_to_cshort = fromIntegral
+
+int16_to_cint:: Int16 -> CInt
+int16_to_cint = fromIntegral
+
+int16_to_clong:: Int16 -> CLong
+int16_to_clong = fromIntegral
+
+int16_to_cllong:: Int16 -> CLLong
+int16_to_cllong = fromIntegral
+
+int8_to_word64:: Int8 -> Word64
+int8_to_word64 = fromIntegral
+
+int8_to_word32:: Int8 -> Word32
+int8_to_word32 = fromIntegral
+
+int8_to_word16:: Int8 -> Word16
+int8_to_word16 = fromIntegral
+
+int8_to_word8:: Int8 -> Word8
+int8_to_word8 = fromIntegral
+
+int8_to_int64:: Int8 -> Int64
+int8_to_int64 = fromIntegral
+
+int8_to_int32:: Int8 -> Int32
+int8_to_int32 = fromIntegral
+
+int8_to_int16:: Int8 -> Int16
+int8_to_int16 = fromIntegral
+
+int8_to_int8:: Int8 -> Int8
+int8_to_int8 = fromIntegral
+
+int8_to_cchar:: Int8 -> CChar
+int8_to_cchar = fromIntegral
+
+int8_to_cushort:: Int8 -> CUShort
+int8_to_cushort = fromIntegral
+
+int8_to_cuint:: Int8 -> CUInt
+int8_to_cuint = fromIntegral
+
+int8_to_culong:: Int8 -> CULong
+int8_to_culong = fromIntegral
+
+int8_to_cullong:: Int8 -> CULLong
+int8_to_cullong = fromIntegral
+
+int8_to_cschar:: Int8 -> CSChar
+int8_to_cschar = fromIntegral
+
+int8_to_cshort:: Int8 -> CShort
+int8_to_cshort = fromIntegral
+
+int8_to_cint:: Int8 -> CInt
+int8_to_cint = fromIntegral
+
+int8_to_clong:: Int8 -> CLong
+int8_to_clong = fromIntegral
+
+int8_to_cllong:: Int8 -> CLLong
+int8_to_cllong = fromIntegral
+
+cchar_to_word64:: CChar -> Word64
+cchar_to_word64 = fromIntegral
+
+cchar_to_word32:: CChar -> Word32
+cchar_to_word32 = fromIntegral
+
+cchar_to_word16:: CChar -> Word16
+cchar_to_word16 = fromIntegral
+
+cchar_to_word8:: CChar -> Word8
+cchar_to_word8 = fromIntegral
+
+cchar_to_int64:: CChar -> Int64
+cchar_to_int64 = fromIntegral
+
+cchar_to_int32:: CChar -> Int32
+cchar_to_int32 = fromIntegral
+
+cchar_to_int16:: CChar -> Int16
+cchar_to_int16 = fromIntegral
+
+cchar_to_int8:: CChar -> Int8
+cchar_to_int8 = fromIntegral
+
+cchar_to_cchar:: CChar -> CChar
+cchar_to_cchar = fromIntegral
+
+cchar_to_cushort:: CChar -> CUShort
+cchar_to_cushort = fromIntegral
+
+cchar_to_cuint:: CChar -> CUInt
+cchar_to_cuint = fromIntegral
+
+cchar_to_culong:: CChar -> CULong
+cchar_to_culong = fromIntegral
+
+cchar_to_cullong:: CChar -> CULLong
+cchar_to_cullong = fromIntegral
+
+cchar_to_cschar:: CChar -> CSChar
+cchar_to_cschar = fromIntegral
+
+cchar_to_cshort:: CChar -> CShort
+cchar_to_cshort = fromIntegral
+
+cchar_to_cint:: CChar -> CInt
+cchar_to_cint = fromIntegral
+
+cchar_to_clong:: CChar -> CLong
+cchar_to_clong = fromIntegral
+
+cchar_to_cllong:: CChar -> CLLong
+cchar_to_cllong = fromIntegral
+
+cushort_to_word64:: CUShort -> Word64
+cushort_to_word64 = fromIntegral
+
+cushort_to_word32:: CUShort -> Word32
+cushort_to_word32 = fromIntegral
+
+cushort_to_word16:: CUShort -> Word16
+cushort_to_word16 = fromIntegral
+
+cushort_to_word8:: CUShort -> Word8
+cushort_to_word8 = fromIntegral
+
+cushort_to_int64:: CUShort -> Int64
+cushort_to_int64 = fromIntegral
+
+cushort_to_int32:: CUShort -> Int32
+cushort_to_int32 = fromIntegral
+
+cushort_to_int16:: CUShort -> Int16
+cushort_to_int16 = fromIntegral
+
+cushort_to_int8:: CUShort -> Int8
+cushort_to_int8 = fromIntegral
+
+cushort_to_cchar:: CUShort -> CChar
+cushort_to_cchar = fromIntegral
+
+cushort_to_cushort:: CUShort -> CUShort
+cushort_to_cushort = fromIntegral
+
+cushort_to_cuint:: CUShort -> CUInt
+cushort_to_cuint = fromIntegral
+
+cushort_to_culong:: CUShort -> CULong
+cushort_to_culong = fromIntegral
+
+cushort_to_cullong:: CUShort -> CULLong
+cushort_to_cullong = fromIntegral
+
+cushort_to_cschar:: CUShort -> CSChar
+cushort_to_cschar = fromIntegral
+
+cushort_to_cshort:: CUShort -> CShort
+cushort_to_cshort = fromIntegral
+
+cushort_to_cint:: CUShort -> CInt
+cushort_to_cint = fromIntegral
+
+cushort_to_clong:: CUShort -> CLong
+cushort_to_clong = fromIntegral
+
+cushort_to_cllong:: CUShort -> CLLong
+cushort_to_cllong = fromIntegral
+
+cuint_to_word64:: CUInt -> Word64
+cuint_to_word64 = fromIntegral
+
+cuint_to_word32:: CUInt -> Word32
+cuint_to_word32 = fromIntegral
+
+cuint_to_word16:: CUInt -> Word16
+cuint_to_word16 = fromIntegral
+
+cuint_to_word8:: CUInt -> Word8
+cuint_to_word8 = fromIntegral
+
+cuint_to_int64:: CUInt -> Int64
+cuint_to_int64 = fromIntegral
+
+cuint_to_int32:: CUInt -> Int32
+cuint_to_int32 = fromIntegral
+
+cuint_to_int16:: CUInt -> Int16
+cuint_to_int16 = fromIntegral
+
+cuint_to_int8:: CUInt -> Int8
+cuint_to_int8 = fromIntegral
+
+cuint_to_cchar:: CUInt -> CChar
+cuint_to_cchar = fromIntegral
+
+cuint_to_cushort:: CUInt -> CUShort
+cuint_to_cushort = fromIntegral
+
+cuint_to_cuint:: CUInt -> CUInt
+cuint_to_cuint = fromIntegral
+
+cuint_to_culong:: CUInt -> CULong
+cuint_to_culong = fromIntegral
+
+cuint_to_cullong:: CUInt -> CULLong
+cuint_to_cullong = fromIntegral
+
+cuint_to_cschar:: CUInt -> CSChar
+cuint_to_cschar = fromIntegral
+
+cuint_to_cshort:: CUInt -> CShort
+cuint_to_cshort = fromIntegral
+
+cuint_to_cint:: CUInt -> CInt
+cuint_to_cint = fromIntegral
+
+cuint_to_clong:: CUInt -> CLong
+cuint_to_clong = fromIntegral
+
+cuint_to_cllong:: CUInt -> CLLong
+cuint_to_cllong = fromIntegral
+
+culong_to_word64:: CULong -> Word64
+culong_to_word64 = fromIntegral
+
+culong_to_word32:: CULong -> Word32
+culong_to_word32 = fromIntegral
+
+culong_to_word16:: CULong -> Word16
+culong_to_word16 = fromIntegral
+
+culong_to_word8:: CULong -> Word8
+culong_to_word8 = fromIntegral
+
+culong_to_int64:: CULong -> Int64
+culong_to_int64 = fromIntegral
+
+culong_to_int32:: CULong -> Int32
+culong_to_int32 = fromIntegral
+
+culong_to_int16:: CULong -> Int16
+culong_to_int16 = fromIntegral
+
+culong_to_int8:: CULong -> Int8
+culong_to_int8 = fromIntegral
+
+culong_to_cchar:: CULong -> CChar
+culong_to_cchar = fromIntegral
+
+culong_to_cushort:: CULong -> CUShort
+culong_to_cushort = fromIntegral
+
+culong_to_cuint:: CULong -> CUInt
+culong_to_cuint = fromIntegral
+
+culong_to_culong:: CULong -> CULong
+culong_to_culong = fromIntegral
+
+culong_to_cullong:: CULong -> CULLong
+culong_to_cullong = fromIntegral
+
+culong_to_cschar:: CULong -> CSChar
+culong_to_cschar = fromIntegral
+
+culong_to_cshort:: CULong -> CShort
+culong_to_cshort = fromIntegral
+
+culong_to_cint:: CULong -> CInt
+culong_to_cint = fromIntegral
+
+culong_to_clong:: CULong -> CLong
+culong_to_clong = fromIntegral
+
+culong_to_cllong:: CULong -> CLLong
+culong_to_cllong = fromIntegral
+
+cullong_to_word64:: CULLong -> Word64
+cullong_to_word64 = fromIntegral
+
+cullong_to_word32:: CULLong -> Word32
+cullong_to_word32 = fromIntegral
+
+cullong_to_word16:: CULLong -> Word16
+cullong_to_word16 = fromIntegral
+
+cullong_to_word8:: CULLong -> Word8
+cullong_to_word8 = fromIntegral
+
+cullong_to_int64:: CULLong -> Int64
+cullong_to_int64 = fromIntegral
+
+cullong_to_int32:: CULLong -> Int32
+cullong_to_int32 = fromIntegral
+
+cullong_to_int16:: CULLong -> Int16
+cullong_to_int16 = fromIntegral
+
+cullong_to_int8:: CULLong -> Int8
+cullong_to_int8 = fromIntegral
+
+cullong_to_cchar:: CULLong -> CChar
+cullong_to_cchar = fromIntegral
+
+cullong_to_cushort:: CULLong -> CUShort
+cullong_to_cushort = fromIntegral
+
+cullong_to_cuint:: CULLong -> CUInt
+cullong_to_cuint = fromIntegral
+
+cullong_to_culong:: CULLong -> CULong
+cullong_to_culong = fromIntegral
+
+cullong_to_cullong:: CULLong -> CULLong
+cullong_to_cullong = fromIntegral
+
+cullong_to_cschar:: CULLong -> CSChar
+cullong_to_cschar = fromIntegral
+
+cullong_to_cshort:: CULLong -> CShort
+cullong_to_cshort = fromIntegral
+
+cullong_to_cint:: CULLong -> CInt
+cullong_to_cint = fromIntegral
+
+cullong_to_clong:: CULLong -> CLong
+cullong_to_clong = fromIntegral
+
+cullong_to_cllong:: CULLong -> CLLong
+cullong_to_cllong = fromIntegral
+
+cschar_to_word64:: CSChar -> Word64
+cschar_to_word64 = fromIntegral
+
+cschar_to_word32:: CSChar -> Word32
+cschar_to_word32 = fromIntegral
+
+cschar_to_word16:: CSChar -> Word16
+cschar_to_word16 = fromIntegral
+
+cschar_to_word8:: CSChar -> Word8
+cschar_to_word8 = fromIntegral
+
+cschar_to_int64:: CSChar -> Int64
+cschar_to_int64 = fromIntegral
+
+cschar_to_int32:: CSChar -> Int32
+cschar_to_int32 = fromIntegral
+
+cschar_to_int16:: CSChar -> Int16
+cschar_to_int16 = fromIntegral
+
+cschar_to_int8:: CSChar -> Int8
+cschar_to_int8 = fromIntegral
+
+cschar_to_cchar:: CSChar -> CChar
+cschar_to_cchar = fromIntegral
+
+cschar_to_cushort:: CSChar -> CUShort
+cschar_to_cushort = fromIntegral
+
+cschar_to_cuint:: CSChar -> CUInt
+cschar_to_cuint = fromIntegral
+
+cschar_to_culong:: CSChar -> CULong
+cschar_to_culong = fromIntegral
+
+cschar_to_cullong:: CSChar -> CULLong
+cschar_to_cullong = fromIntegral
+
+cschar_to_cschar:: CSChar -> CSChar
+cschar_to_cschar = fromIntegral
+
+cschar_to_cshort:: CSChar -> CShort
+cschar_to_cshort = fromIntegral
+
+cschar_to_cint:: CSChar -> CInt
+cschar_to_cint = fromIntegral
+
+cschar_to_clong:: CSChar -> CLong
+cschar_to_clong = fromIntegral
+
+cschar_to_cllong:: CSChar -> CLLong
+cschar_to_cllong = fromIntegral
+
+cshort_to_word64:: CShort -> Word64
+cshort_to_word64 = fromIntegral
+
+cshort_to_word32:: CShort -> Word32
+cshort_to_word32 = fromIntegral
+
+cshort_to_word16:: CShort -> Word16
+cshort_to_word16 = fromIntegral
+
+cshort_to_word8:: CShort -> Word8
+cshort_to_word8 = fromIntegral
+
+cshort_to_int64:: CShort -> Int64
+cshort_to_int64 = fromIntegral
+
+cshort_to_int32:: CShort -> Int32
+cshort_to_int32 = fromIntegral
+
+cshort_to_int16:: CShort -> Int16
+cshort_to_int16 = fromIntegral
+
+cshort_to_int8:: CShort -> Int8
+cshort_to_int8 = fromIntegral
+
+cshort_to_cchar:: CShort -> CChar
+cshort_to_cchar = fromIntegral
+
+cshort_to_cushort:: CShort -> CUShort
+cshort_to_cushort = fromIntegral
+
+cshort_to_cuint:: CShort -> CUInt
+cshort_to_cuint = fromIntegral
+
+cshort_to_culong:: CShort -> CULong
+cshort_to_culong = fromIntegral
+
+cshort_to_cullong:: CShort -> CULLong
+cshort_to_cullong = fromIntegral
+
+cshort_to_cschar:: CShort -> CSChar
+cshort_to_cschar = fromIntegral
+
+cshort_to_cshort:: CShort -> CShort
+cshort_to_cshort = fromIntegral
+
+cshort_to_cint:: CShort -> CInt
+cshort_to_cint = fromIntegral
+
+cshort_to_clong:: CShort -> CLong
+cshort_to_clong = fromIntegral
+
+cshort_to_cllong:: CShort -> CLLong
+cshort_to_cllong = fromIntegral
+
+cint_to_word64:: CInt -> Word64
+cint_to_word64 = fromIntegral
+
+cint_to_word32:: CInt -> Word32
+cint_to_word32 = fromIntegral
+
+cint_to_word16:: CInt -> Word16
+cint_to_word16 = fromIntegral
+
+cint_to_word8:: CInt -> Word8
+cint_to_word8 = fromIntegral
+
+cint_to_int64:: CInt -> Int64
+cint_to_int64 = fromIntegral
+
+cint_to_int32:: CInt -> Int32
+cint_to_int32 = fromIntegral
+
+cint_to_int16:: CInt -> Int16
+cint_to_int16 = fromIntegral
+
+cint_to_int8:: CInt -> Int8
+cint_to_int8 = fromIntegral
+
+cint_to_cchar:: CInt -> CChar
+cint_to_cchar = fromIntegral
+
+cint_to_cushort:: CInt -> CUShort
+cint_to_cushort = fromIntegral
+
+cint_to_cuint:: CInt -> CUInt
+cint_to_cuint = fromIntegral
+
+cint_to_culong:: CInt -> CULong
+cint_to_culong = fromIntegral
+
+cint_to_cullong:: CInt -> CULLong
+cint_to_cullong = fromIntegral
+
+cint_to_cschar:: CInt -> CSChar
+cint_to_cschar = fromIntegral
+
+cint_to_cshort:: CInt -> CShort
+cint_to_cshort = fromIntegral
+
+cint_to_cint:: CInt -> CInt
+cint_to_cint = fromIntegral
+
+cint_to_clong:: CInt -> CLong
+cint_to_clong = fromIntegral
+
+cint_to_cllong:: CInt -> CLLong
+cint_to_cllong = fromIntegral
+
+clong_to_word64:: CLong -> Word64
+clong_to_word64 = fromIntegral
+
+clong_to_word32:: CLong -> Word32
+clong_to_word32 = fromIntegral
+
+clong_to_word16:: CLong -> Word16
+clong_to_word16 = fromIntegral
+
+clong_to_word8:: CLong -> Word8
+clong_to_word8 = fromIntegral
+
+clong_to_int64:: CLong -> Int64
+clong_to_int64 = fromIntegral
+
+clong_to_int32:: CLong -> Int32
+clong_to_int32 = fromIntegral
+
+clong_to_int16:: CLong -> Int16
+clong_to_int16 = fromIntegral
+
+clong_to_int8:: CLong -> Int8
+clong_to_int8 = fromIntegral
+
+clong_to_cchar:: CLong -> CChar
+clong_to_cchar = fromIntegral
+
+clong_to_cushort:: CLong -> CUShort
+clong_to_cushort = fromIntegral
+
+clong_to_cuint:: CLong -> CUInt
+clong_to_cuint = fromIntegral
+
+clong_to_culong:: CLong -> CULong
+clong_to_culong = fromIntegral
+
+clong_to_cullong:: CLong -> CULLong
+clong_to_cullong = fromIntegral
+
+clong_to_cschar:: CLong -> CSChar
+clong_to_cschar = fromIntegral
+
+clong_to_cshort:: CLong -> CShort
+clong_to_cshort = fromIntegral
+
+clong_to_cint:: CLong -> CInt
+clong_to_cint = fromIntegral
+
+clong_to_clong:: CLong -> CLong
+clong_to_clong = fromIntegral
+
+clong_to_cllong:: CLong -> CLLong
+clong_to_cllong = fromIntegral
+
+cllong_to_word64:: CLLong -> Word64
+cllong_to_word64 = fromIntegral
+
+cllong_to_word32:: CLLong -> Word32
+cllong_to_word32 = fromIntegral
+
+cllong_to_word16:: CLLong -> Word16
+cllong_to_word16 = fromIntegral
+
+cllong_to_word8:: CLLong -> Word8
+cllong_to_word8 = fromIntegral
+
+cllong_to_int64:: CLLong -> Int64
+cllong_to_int64 = fromIntegral
+
+cllong_to_int32:: CLLong -> Int32
+cllong_to_int32 = fromIntegral
+
+cllong_to_int16:: CLLong -> Int16
+cllong_to_int16 = fromIntegral
+
+cllong_to_int8:: CLLong -> Int8
+cllong_to_int8 = fromIntegral
+
+cllong_to_cchar:: CLLong -> CChar
+cllong_to_cchar = fromIntegral
+
+cllong_to_cushort:: CLLong -> CUShort
+cllong_to_cushort = fromIntegral
+
+cllong_to_cuint:: CLLong -> CUInt
+cllong_to_cuint = fromIntegral
+
+cllong_to_culong:: CLLong -> CULong
+cllong_to_culong = fromIntegral
+
+cllong_to_cullong:: CLLong -> CULLong
+cllong_to_cullong = fromIntegral
+
+cllong_to_cschar:: CLLong -> CSChar
+cllong_to_cschar = fromIntegral
+
+cllong_to_cshort:: CLLong -> CShort
+cllong_to_cshort = fromIntegral
+
+cllong_to_cint:: CLLong -> CInt
+cllong_to_cint = fromIntegral
+
+cllong_to_clong:: CLLong -> CLong
+cllong_to_clong = fromIntegral
+
+cllong_to_cllong:: CLLong -> CLLong
+cllong_to_cllong = fromIntegral
+
diff --git a/testsuite/tests/numeric/should_compile/all.T b/testsuite/tests/numeric/should_compile/all.T
index 766dda4814..425d0dbd85 100644
--- a/testsuite/tests/numeric/should_compile/all.T
+++ b/testsuite/tests/numeric/should_compile/all.T
@@ -10,3 +10,4 @@ test('T8542', omit_ways(['hpc']), compile, [''])
test('T10929', normal, compile, [''])
test('T16402', [ grep_errmsg(r'and'), when(wordsize(32), expect_broken(19024)) ], compile, [''])
test('T19892', normal, compile, ['-O -ddump-rule-firings'])
+test('T20062', [ grep_errmsg(r'integer') ], compile, ['-ddump-simpl -O -dsuppress-all'])