summaryrefslogtreecommitdiff
path: root/libraries
diff options
context:
space:
mode:
authorSylvain Henry <sylvain@haskus.fr>2021-01-15 12:33:40 +0100
committerMarge Bot <ben+marge-bot@smart-cactus.org>2021-01-23 15:31:20 -0500
commit773e2828fde4d8f640082b6bded9945e7b9584e3 (patch)
tree735cc36bc1ce14820890f8734e68280521a6e2ce /libraries
parent97208613414106e493a586d295ca05393e136ba4 (diff)
downloadhaskell-773e2828fde4d8f640082b6bded9945e7b9584e3.tar.gz
Bignum: add Natural constant folding rules (#15821)
* Implement constant folding rules for Natural (similar to Integer ones) * Add mkCoreUbxSum helper in GHC.Core.Make * Remove naturalTo/FromInt We now only provide `naturalTo/FromWord` as the semantics is clear (truncate/zero-extend). For Int we have to deal with negative numbers (throw an exception? convert to Word beforehand?) so we leave the decision about what to do to the caller. Moreover, now that we have sized types (Int8#, Int16#, ..., Word8#, etc.) there is no reason to bless `Int#` more than `Int8#` or `Word8#` (for example). * Replaced a few `()` with `(# #)`
Diffstat (limited to 'libraries')
-rw-r--r--libraries/base/GHC/Enum.hs4
-rw-r--r--libraries/base/GHC/Float.hs6
-rw-r--r--libraries/base/GHC/Int.hs16
-rw-r--r--libraries/base/GHC/Natural.hs20
-rw-r--r--libraries/base/GHC/Num.hs12
-rw-r--r--libraries/base/GHC/Real.hs2
-rw-r--r--libraries/ghc-bignum/src/GHC/Num/BigNat.hs64
-rw-r--r--libraries/ghc-bignum/src/GHC/Num/Integer.hs14
-rw-r--r--libraries/ghc-bignum/src/GHC/Num/Natural.hs162
-rw-r--r--libraries/ghc-bignum/src/GHC/Num/Primitives.hs4
-rw-r--r--libraries/ghc-bignum/src/GHC/Num/WordArray.hs4
-rw-r--r--libraries/integer-gmp/src/GHC/Integer/GMP/Internals.hs8
12 files changed, 187 insertions, 129 deletions
diff --git a/libraries/base/GHC/Enum.hs b/libraries/base/GHC/Enum.hs
index 54d6c6b34a..d107c1eb12 100644
--- a/libraries/base/GHC/Enum.hs
+++ b/libraries/base/GHC/Enum.hs
@@ -963,8 +963,8 @@ dn_list x0 delta lim = go (x0 :: Integer)
instance Enum Natural where
succ n = n + 1
pred n = n - 1
- toEnum i
- | i >= 0 = naturalFromIntUnsafe i
+ toEnum i@(I# i#)
+ | i >= 0 = naturalFromWord# (int2Word# i#)
| otherwise = errorWithoutStackTrace "toEnum: unexpected negative Int"
fromEnum (NS w)
diff --git a/libraries/base/GHC/Float.hs b/libraries/base/GHC/Float.hs
index eae6edb253..cb1ef6044c 100644
--- a/libraries/base/GHC/Float.hs
+++ b/libraries/base/GHC/Float.hs
@@ -1099,9 +1099,9 @@ fromRat'' minEx@(I# me#) mantDigs@(I# md#) n d =
| isTrue# (ld'# ># (ln# +# 1#)) -> encodeFloat 0 0 -- result of shift < 0.5
| otherwise -> -- first bit of n shifted to 0.5 place
case integerIsPowerOf2# n of
- (# | _ #) -> encodeFloat 0 0 -- round to even
- (# () | #) -> encodeFloat 1 (minEx - mantDigs)
- (# () | #) ->
+ (# | _ #) -> encodeFloat 0 0 -- round to even
+ (# (# #) | #) -> encodeFloat 1 (minEx - mantDigs)
+ (# (# #) | #) ->
let ln = I# (word2Int# (integerLog2# n))
ld = I# (word2Int# (integerLog2# d))
-- 2^(ln-ld-1) < n/d < 2^(ln-ld+1)
diff --git a/libraries/base/GHC/Int.hs b/libraries/base/GHC/Int.hs
index 08827e92c4..2af0856bb7 100644
--- a/libraries/base/GHC/Int.hs
+++ b/libraries/base/GHC/Int.hs
@@ -1124,29 +1124,29 @@ instance Ix Int64 where
{-# RULES
"fromIntegral/Natural->Int8"
- fromIntegral = (fromIntegral :: Int -> Int8) . naturalToInt
+ fromIntegral = (fromIntegral :: Int -> Int8) . fromIntegral . naturalToWord
"fromIntegral/Natural->Int16"
- fromIntegral = (fromIntegral :: Int -> Int16) . naturalToInt
+ fromIntegral = (fromIntegral :: Int -> Int16) . fromIntegral . naturalToWord
"fromIntegral/Natural->Int32"
- fromIntegral = (fromIntegral :: Int -> Int32) . naturalToInt
+ fromIntegral = (fromIntegral :: Int -> Int32) . fromIntegral . naturalToWord
#-}
{-# RULES
"fromIntegral/Int8->Natural"
- fromIntegral = naturalFromIntUnsafe . (fromIntegral :: Int8 -> Int)
+ fromIntegral = naturalFromWord . fromIntegral . (fromIntegral :: Int8 -> Int)
"fromIntegral/Int16->Natural"
- fromIntegral = naturalFromIntUnsafe . (fromIntegral :: Int16 -> Int)
+ fromIntegral = naturalFromWord . fromIntegral . (fromIntegral :: Int16 -> Int)
"fromIntegral/Int32->Natural"
- fromIntegral = naturalFromIntUnsafe . (fromIntegral :: Int32 -> Int)
+ 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) . naturalToInt
+ fromIntegral = (fromIntegral :: Int -> Int64) . fromIntegral . naturalToWord
"fromIntegral/Int64->Natural"
- fromIntegral = naturalFromIntUnsafe . (fromIntegral :: Int64 -> Int)
+ fromIntegral = naturalFromWord . fromIntegral . (fromIntegral :: Int64 -> Int)
#-}
#endif
diff --git a/libraries/base/GHC/Natural.hs b/libraries/base/GHC/Natural.hs
index 29c3a4b55e..424b2e6eef 100644
--- a/libraries/base/GHC/Natural.hs
+++ b/libraries/base/GHC/Natural.hs
@@ -37,12 +37,10 @@ module GHC.Natural
-- * Conversions
, naturalToInteger
, naturalToWord
- , naturalToInt
- , naturalFromInteger
- , wordToNatural
- , intToNatural
, naturalToWordMaybe
+ , wordToNatural
, wordToNatural#
+ , naturalFromInteger
-- * Modular arithmetic
, powModNatural
)
@@ -100,8 +98,8 @@ minusNatural = N.naturalSubThrow
-- @since 4.8.0.0
minusNaturalMaybe :: Natural -> Natural -> Maybe Natural
minusNaturalMaybe x y = case N.naturalSub x y of
- (# () | #) -> Nothing
- (# | n #) -> Just n
+ (# (# #) | #) -> Nothing
+ (# | n #) -> Just n
-- | 'Natural' multiplication
timesNatural :: Natural -> Natural -> Natural
@@ -161,9 +159,6 @@ naturalToInteger = I.integerFromNatural
naturalToWord :: Natural -> Word
naturalToWord = N.naturalToWord
-naturalToInt :: Natural -> Int
-naturalToInt = N.naturalToInt
-
-- | @since 4.10.0.0
naturalFromInteger :: Integer -> Natural
naturalFromInteger = I.integerToNatural
@@ -174,17 +169,14 @@ naturalFromInteger = I.integerToNatural
wordToNatural :: Word -> Natural
wordToNatural = N.naturalFromWord
-intToNatural :: Int -> Natural
-intToNatural = N.naturalFromIntThrow
-
-- | Try downcasting 'Natural' to 'Word' value.
-- Returns 'Nothing' if value doesn't fit in 'Word'.
--
-- @since 4.8.0.0
naturalToWordMaybe :: Natural -> Maybe Word
naturalToWordMaybe n = case N.naturalToWordMaybe# n of
- (# w | #) -> Just (W# w)
- (# | () #) -> Nothing
+ (# | w #) -> Just (W# w)
+ (# (# #) | #) -> Nothing
wordToNatural# :: Word -> Natural
wordToNatural# = N.naturalFromWord
diff --git a/libraries/base/GHC/Num.hs b/libraries/base/GHC/Num.hs
index df0c66b7bd..3d26d35a0d 100644
--- a/libraries/base/GHC/Num.hs
+++ b/libraries/base/GHC/Num.hs
@@ -138,13 +138,13 @@ instance Num Integer where
--
-- @since 4.8.0.0
instance Num Natural where
- (+) = naturalAdd
- (-) = naturalSubThrow
- (*) = naturalMul
- negate = naturalNegate
+ (+) = naturalAdd
+ (-) = naturalSubThrow
+ (*) = naturalMul
+ negate = naturalNegate
fromInteger = integerToNaturalThrow
- abs = id
- signum = naturalSignum
+ abs = id
+ signum = naturalSignum
{-# DEPRECATED quotRemInteger "Use integerQuotRem# instead" #-}
quotRemInteger :: Integer -> Integer -> (# Integer, Integer #)
diff --git a/libraries/base/GHC/Real.hs b/libraries/base/GHC/Real.hs
index 4d0b05a5f9..ee61e34e70 100644
--- a/libraries/base/GHC/Real.hs
+++ b/libraries/base/GHC/Real.hs
@@ -587,7 +587,7 @@ fromIntegral = fromInteger . toInteger
{-# RULES
"fromIntegral/Word->Natural" fromIntegral = naturalFromWord
-"fromIntegral/Int->Natural" fromIntegral = naturalFromInt
+"fromIntegral/Int->Natural" fromIntegral = naturalFromWord . fromIntegral
#-}
-- | general coercion to fractional types
diff --git a/libraries/ghc-bignum/src/GHC/Num/BigNat.hs b/libraries/ghc-bignum/src/GHC/Num/BigNat.hs
index b0408bcfa6..bd3137a116 100644
--- a/libraries/ghc-bignum/src/GHC/Num/BigNat.hs
+++ b/libraries/ghc-bignum/src/GHC/Num/BigNat.hs
@@ -136,13 +136,13 @@ bigNatIsTwo# ba =
&&# indexWordArray# ba 0# `eqWord#` 2##
-- | Indicate if the value is a power of two and which one
-bigNatIsPowerOf2# :: BigNat# -> (# () | Word# #)
+bigNatIsPowerOf2# :: BigNat# -> (# (# #) | Word# #)
bigNatIsPowerOf2# a
- | bigNatIsZero a = (# () | #)
+ | bigNatIsZero a = (# (# #) | #)
| True = case wordIsPowerOf2# msw of
- (# () | #) -> (# () | #)
+ (# (# #) | #) -> (# (# #) | #)
(# | c #) -> case checkAllZeroes (imax -# 1#) of
- 0# -> (# () | #)
+ 0# -> (# (# #) | #)
_ -> (# | c `plusWord#`
(int2Word# imax `uncheckedShiftL#` WORD_SIZE_BITS_SHIFT#) #)
where
@@ -227,11 +227,11 @@ bigNatToWord# a
| True = bigNatIndex# a 0#
-- | Convert a BigNat into a Word# if it fits
-bigNatToWordMaybe# :: BigNat# -> (# Word# | () #)
+bigNatToWordMaybe# :: BigNat# -> (# (# #) | Word# #)
bigNatToWordMaybe# a
- | bigNatIsZero a = (# 0## | #)
- | isTrue# (bigNatSize# a ># 1#) = (# | () #)
- | True = (# bigNatIndex# a 0# | #)
+ | bigNatIsZero a = (# | 0## #)
+ | isTrue# (bigNatSize# a ># 1#) = (# (# #) | #)
+ | True = (# | bigNatIndex# a 0# #)
-- | Convert a BigNat into a Word
bigNatToWord :: BigNat# -> Word
@@ -359,8 +359,44 @@ bigNatCompare a b =
-- | Predicate: a < b
+bigNatLt# :: BigNat# -> BigNat# -> Bool#
+bigNatLt# a b
+ | LT <- bigNatCompare a b = 1#
+ | True = 0#
+
+-- | Predicate: a < b
bigNatLt :: BigNat# -> BigNat# -> Bool
-bigNatLt a b = bigNatCompare a b == LT
+bigNatLt a b = isTrue# (bigNatLt# a b)
+
+-- | Predicate: a <= b
+bigNatLe# :: BigNat# -> BigNat# -> Bool#
+bigNatLe# a b
+ | GT <- bigNatCompare a b = 0#
+ | True = 1#
+
+-- | Predicate: a <= b
+bigNatLe :: BigNat# -> BigNat# -> Bool
+bigNatLe a b = isTrue# (bigNatLe# a b)
+
+-- | Predicate: a > b
+bigNatGt# :: BigNat# -> BigNat# -> Bool#
+bigNatGt# a b
+ | GT <- bigNatCompare a b = 1#
+ | True = 0#
+
+-- | Predicate: a > b
+bigNatGt :: BigNat# -> BigNat# -> Bool
+bigNatGt a b = isTrue# (bigNatGt# a b)
+
+-- | Predicate: a >= b
+bigNatGe# :: BigNat# -> BigNat# -> Bool#
+bigNatGe# a b
+ | LT <- bigNatCompare a b = 0#
+ | True = 1#
+
+-- | Predicate: a >= b
+bigNatGe :: BigNat# -> BigNat# -> Bool
+bigNatGe a b = isTrue# (bigNatGe# a b)
-------------------------------------------------
-- Addition
@@ -474,10 +510,10 @@ bigNatSubWordUnsafe :: BigNat# -> Word -> BigNat#
bigNatSubWordUnsafe x (W# y) = bigNatSubWordUnsafe# x y
-- | Subtract a Word# from a BigNat
-bigNatSubWord# :: BigNat# -> Word# -> (# () | BigNat# #)
+bigNatSubWord# :: BigNat# -> Word# -> (# (# #) | BigNat# #)
bigNatSubWord# a b
| 0## <- b = (# | a #)
- | bigNatIsZero a = (# () | #)
+ | bigNatIsZero a = (# (# #) | #)
| True
= withNewWordArrayTrimedMaybe# (bigNatSize# a) \mwa s ->
inline bignat_sub_word mwa a b s
@@ -498,11 +534,11 @@ bigNatSubUnsafe a b
-- GHC.Num.Primitives
-- | Subtract two BigNat
-bigNatSub :: BigNat# -> BigNat# -> (# () | BigNat# #)
+bigNatSub :: BigNat# -> BigNat# -> (# (# #) | BigNat# #)
bigNatSub a b
| bigNatIsZero b = (# | a #)
| isTrue# (bigNatSize# a <# bigNatSize# b)
- = (# () | #)
+ = (# (# #) | #)
| True
= withNewWordArrayTrimedMaybe# (bigNatSize# a) \mwa s ->
@@ -1136,7 +1172,7 @@ bigNatPowModWord# b e m
-- exponent @/e/@ modulo @/m/@.
bigNatPowMod :: BigNat# -> BigNat# -> BigNat# -> BigNat#
bigNatPowMod !b !e !m
- | (# m' | #) <- bigNatToWordMaybe# m
+ | (# | m' #) <- bigNatToWordMaybe# m
= bigNatFromWord# (bigNatPowModWord# b e m')
| bigNatIsZero m = raiseDivZero_BigNat (# #)
| bigNatIsOne m = bigNatFromWord# 0##
diff --git a/libraries/ghc-bignum/src/GHC/Num/Integer.hs b/libraries/ghc-bignum/src/GHC/Num/Integer.hs
index 2e0327127d..35afa5d15a 100644
--- a/libraries/ghc-bignum/src/GHC/Num/Integer.hs
+++ b/libraries/ghc-bignum/src/GHC/Num/Integer.hs
@@ -205,7 +205,7 @@ integerFromWordList :: Bool -> [Word] -> Integer
integerFromWordList True ws = integerFromBigNatNeg# (bigNatFromWordList ws)
integerFromWordList False ws = integerFromBigNat# (bigNatFromWordList ws)
--- | Convert a Integer into a Natural
+-- | Convert an Integer into a Natural
--
-- Return 0 for negative Integers.
integerToNaturalClamp :: Integer -> Natural
@@ -216,7 +216,7 @@ integerToNaturalClamp (IS x)
integerToNaturalClamp (IP x) = naturalFromBigNat# x
integerToNaturalClamp (IN _) = naturalZero
--- | Convert a Integer into a Natural
+-- | Convert an Integer into a Natural
--
-- Return absolute value
integerToNatural :: Integer -> Natural
@@ -225,9 +225,9 @@ integerToNatural (IS x) = naturalFromWord# (wordFromAbsInt# x)
integerToNatural (IP x) = naturalFromBigNat# x
integerToNatural (IN x) = naturalFromBigNat# x
--- | Convert a Integer into a Natural
+-- | Convert an Integer into a Natural
--
--- Throw on underflow
+-- Throw an Underflow exception if input is negative.
integerToNaturalThrow :: Integer -> Natural
{-# NOINLINE integerToNaturalThrow #-}
integerToNaturalThrow (IS x)
@@ -1007,11 +1007,11 @@ integerLogBase :: Integer -> Integer -> Word
integerLogBase !base !i = W# (integerLogBase# base i)
-- | Indicate if the value is a power of two and which one
-integerIsPowerOf2# :: Integer -> (# () | Word# #)
+integerIsPowerOf2# :: Integer -> (# (# #) | Word# #)
integerIsPowerOf2# (IS i)
- | isTrue# (i <=# 0#) = (# () | #)
+ | isTrue# (i <=# 0#) = (# (# #) | #)
| True = wordIsPowerOf2# (int2Word# i)
-integerIsPowerOf2# (IN _) = (# () | #)
+integerIsPowerOf2# (IN _) = (# (# #) | #)
integerIsPowerOf2# (IP w) = bigNatIsPowerOf2# w
#if WORD_SIZE_IN_BITS == 32
diff --git a/libraries/ghc-bignum/src/GHC/Num/Natural.hs b/libraries/ghc-bignum/src/GHC/Num/Natural.hs
index d10a76165d..55aee2d2f7 100644
--- a/libraries/ghc-bignum/src/GHC/Num/Natural.hs
+++ b/libraries/ghc-bignum/src/GHC/Num/Natural.hs
@@ -32,6 +32,10 @@ instance Eq Natural where
instance Ord Natural where
compare = naturalCompare
+ (>) = naturalGt
+ (>=) = naturalGe
+ (<) = naturalLt
+ (<=) = naturalLe
-- | Check Natural invariants
@@ -62,7 +66,7 @@ naturalIsOne (NS 1##) = True
naturalIsOne _ = False
-- | Indicate if the value is a power of two and which one
-naturalIsPowerOf2# :: Natural -> (# () | Word# #)
+naturalIsPowerOf2# :: Natural -> (# (# #) | Word# #)
naturalIsPowerOf2# (NS w) = wordIsPowerOf2# w
naturalIsPowerOf2# (NB w) = bigNatIsPowerOf2# w
@@ -80,7 +84,6 @@ naturalToBigNat# (NB bn) = bn
-- | Create a Natural from a Word#
naturalFromWord# :: Word# -> Natural
-{-# NOINLINE naturalFromWord# #-}
naturalFromWord# x = NS x
-- | Convert two Word# (most-significant first) into a Natural
@@ -109,6 +112,7 @@ naturalToWord !n = W# (naturalToWord# n)
-- | Convert a Natural into a Word# clamping to (maxBound :: Word#).
naturalToWordClamp# :: Natural -> Word#
+{-# NOINLINE naturalToWordClamp #-}
naturalToWordClamp# (NS x) = x
naturalToWordClamp# (NB _) = WORD_MAXBOUND##
@@ -117,58 +121,10 @@ naturalToWordClamp :: Natural -> Word
naturalToWordClamp !n = W# (naturalToWordClamp# n)
-- | Try downcasting 'Natural' to 'Word' value.
--- Returns '()' if value doesn't fit in 'Word'.
-naturalToWordMaybe# :: Natural -> (# Word# | () #)
-naturalToWordMaybe# (NS w) = (# w | #)
-naturalToWordMaybe# _ = (# | () #)
-
--- | Create a Natural from an Int# (unsafe: silently converts negative values
--- into positive ones)
-naturalFromIntUnsafe# :: Int# -> Natural
-naturalFromIntUnsafe# !i = NS (int2Word# i)
-
--- | Create a Natural from an Int (unsafe: silently converts negative values
--- into positive ones)
-naturalFromIntUnsafe :: Int -> Natural
-naturalFromIntUnsafe (I# i) = naturalFromIntUnsafe# i
-
--- | Create a Natural from an Int#
---
--- Throws 'Control.Exception.Underflow' when passed a negative 'Int'.
-naturalFromIntThrow# :: Int# -> Natural
-naturalFromIntThrow# i
- | isTrue# (i <# 0#) = raiseUnderflow
- | True = naturalFromIntUnsafe# i
-
--- | Create a Natural from an Int
---
--- Throws 'Control.Exception.Underflow' when passed a negative 'Int'.
-naturalFromIntThrow :: Int -> Natural
-naturalFromIntThrow (I# i) = naturalFromIntThrow# i
-
--- | Create an Int# from a Natural (can overflow the int and give a negative
--- number)
-naturalToInt# :: Natural -> Int#
-naturalToInt# !n = word2Int# (naturalToWord# n)
-
--- | Create an Int# from a Natural (can overflow the int and give a negative
--- number)
-naturalToInt :: Natural -> Int
-naturalToInt !n = I# (naturalToInt# n)
-
--- | Create a Natural from an Int#
---
--- Underflow exception if Int# is negative
-naturalFromInt# :: Int# -> Natural
-naturalFromInt# !i
- | isTrue# (i >=# 0#) = NS (int2Word# i)
- | True = raiseUnderflow
-
--- | Create a Natural from an Int
---
--- Underflow exception if Int# is negative
-naturalFromInt :: Int -> Natural
-naturalFromInt (I# i) = naturalFromInt# i
+-- Returns '(##)' if value doesn't fit in 'Word'.
+naturalToWordMaybe# :: Natural -> (# (# #) | Word# #)
+naturalToWordMaybe# (NS w) = (# | w #)
+naturalToWordMaybe# _ = (# (# #) | #)
-- | Encode (# Natural mantissa, Int# exponent #) into a Double#
naturalEncodeDouble# :: Natural -> Int# -> Double#
@@ -180,7 +136,7 @@ naturalEncodeDouble# (NB b) e = bigNatEncodeDouble# b e
naturalToDouble# :: Natural -> Double#
naturalToDouble# !n = naturalEncodeDouble# n 0#
--- | Encode an Natural (mantissa) into a Float#
+-- | Encode a Natural (mantissa) into a Float#
naturalToFloat# :: Natural -> Float#
naturalToFloat# !i = naturalEncodeFloat# i 0#
@@ -193,6 +149,7 @@ naturalEncodeFloat# !m e = double2Float# (naturalEncodeDouble# m e)
-- | Equality test for Natural
naturalEq# :: Natural -> Natural -> Bool#
+{-# NOINLINE naturalEq# #-}
naturalEq# (NS x) (NS y) = x `eqWord#` y
naturalEq# (NB x) (NB y) = bigNatEq# x y
naturalEq# _ _ = 0#
@@ -203,6 +160,7 @@ naturalEq !x !y = isTrue# (naturalEq# x y)
-- | Inequality test for Natural
naturalNe# :: Natural -> Natural -> Bool#
+{-# NOINLINE naturalNe# #-}
naturalNe# (NS x) (NS y) = x `neWord#` y
naturalNe# (NB x) (NB y) = bigNatNe# x y
naturalNe# _ _ = 1#
@@ -211,15 +169,66 @@ naturalNe# _ _ = 1#
naturalNe :: Natural -> Natural -> Bool
naturalNe !x !y = isTrue# (naturalNe# x y)
+-- | Greater or equal test for Natural
+naturalGe# :: Natural -> Natural -> Bool#
+{-# NOINLINE naturalGe# #-}
+naturalGe# (NS x) (NS y) = x `geWord#` y
+naturalGe# (NS _) (NB _) = 0#
+naturalGe# (NB _) (NS _) = 1#
+naturalGe# (NB x) (NB y) = bigNatGe# x y
+
+-- | Greater or equal test for Natural
+naturalGe :: Natural -> Natural -> Bool
+naturalGe !x !y = isTrue# (naturalGe# x y)
+
+-- | Lower or equal test for Natural
+naturalLe# :: Natural -> Natural -> Bool#
+{-# NOINLINE naturalLe# #-}
+naturalLe# (NS x) (NS y) = x `leWord#` y
+naturalLe# (NS _) (NB _) = 1#
+naturalLe# (NB _) (NS _) = 0#
+naturalLe# (NB x) (NB y) = bigNatLe# x y
+
+-- | Lower or equal test for Natural
+naturalLe :: Natural -> Natural -> Bool
+naturalLe !x !y = isTrue# (naturalLe# x y)
+
+
+-- | Greater test for Natural
+naturalGt# :: Natural -> Natural -> Bool#
+{-# NOINLINE naturalGt# #-}
+naturalGt# (NS x) (NS y) = x `gtWord#` y
+naturalGt# (NS _) (NB _) = 0#
+naturalGt# (NB _) (NS _) = 1#
+naturalGt# (NB x) (NB y) = bigNatGt# x y
+
+-- | Greater test for Natural
+naturalGt :: Natural -> Natural -> Bool
+naturalGt !x !y = isTrue# (naturalGt# x y)
+
+-- | Lower test for Natural
+naturalLt# :: Natural -> Natural -> Bool#
+{-# NOINLINE naturalLt# #-}
+naturalLt# (NS x) (NS y) = x `ltWord#` y
+naturalLt# (NS _) (NB _) = 1#
+naturalLt# (NB _) (NS _) = 0#
+naturalLt# (NB x) (NB y) = bigNatLt# x y
+
+-- | Lower test for Natural
+naturalLt :: Natural -> Natural -> Bool
+naturalLt !x !y = isTrue# (naturalLt# x y)
+
-- | Compare two Natural
naturalCompare :: Natural -> Natural -> Ordering
-naturalCompare (NS x) (NS y) = compare (W# x) (W# y)
+{-# NOINLINE naturalCompare #-}
+naturalCompare (NS x) (NS y) = cmpW# x y
naturalCompare (NB x) (NB y) = bigNatCompare x y
naturalCompare (NS _) (NB _) = LT
naturalCompare (NB _) (NS _) = GT
-- | PopCount for Natural
naturalPopCount# :: Natural -> Word#
+{-# NOINLINE naturalPopCount# #-}
naturalPopCount# (NS x) = popCnt# x
naturalPopCount# (NB x) = bigNatPopCount# x
@@ -230,6 +239,7 @@ naturalPopCount (NB x) = bigNatPopCount x
-- | Right shift for Natural
naturalShiftR# :: Natural -> Word# -> Natural
+{-# NOINLINE naturalShiftR# #-}
naturalShiftR# (NS x) n = NS (x `shiftRW#` n)
naturalShiftR# (NB x) n = naturalFromBigNat# (x `bigNatShiftR#` n)
@@ -239,6 +249,7 @@ naturalShiftR x (W# n) = naturalShiftR# x n
-- | Left shift
naturalShiftL# :: Natural -> Word# -> Natural
+{-# NOINLINE naturalShiftL# #-}
naturalShiftL# v@(NS x) n
| 0## <- x = v
| isTrue# (clz# x `geWord#` n) = NS (x `uncheckedShiftL#` word2Int# n)
@@ -261,23 +272,24 @@ naturalAdd (NS x) (NS y) =
(# l,c #) -> NB (bigNatFromWord2# (int2Word# c) l)
-- | Sub two naturals
-naturalSub :: Natural -> Natural -> (# () | Natural #)
+naturalSub :: Natural -> Natural -> (# (# #) | Natural #)
{-# NOINLINE naturalSub #-}
-naturalSub (NS _) (NB _) = (# () | #)
+naturalSub (NS _) (NB _) = (# (# #) | #)
naturalSub (NB x) (NS y) = (# | naturalFromBigNat# (bigNatSubWordUnsafe# x y) #)
naturalSub (NS x) (NS y) =
case subWordC# x y of
- (# l,0# #) -> (# | NS l #)
- (# _,_ #) -> (# () | #)
+ (# l,0# #) -> (# | NS l #)
+ (# _,_ #) -> (# (# #) | #)
naturalSub (NB x) (NB y) =
case bigNatSub x y of
- (# () | #) -> (# () | #)
- (# | z #) -> (# | naturalFromBigNat# z #)
+ (# (# #) | #) -> (# (# #) | #)
+ (# | z #) -> (# | naturalFromBigNat# z #)
-- | Sub two naturals
--
-- Throw an Underflow exception if x < y
naturalSubThrow :: Natural -> Natural -> Natural
+{-# NOINLINE naturalSubThrow #-}
naturalSubThrow (NS _) (NB _) = raiseUnderflow
naturalSubThrow (NB x) (NS y) = naturalFromBigNat# (bigNatSubWordUnsafe# x y)
naturalSubThrow (NS x) (NS y) =
@@ -286,8 +298,8 @@ naturalSubThrow (NS x) (NS y) =
(# _,_ #) -> raiseUnderflow
naturalSubThrow (NB x) (NB y) =
case bigNatSub x y of
- (# () | #) -> raiseUnderflow
- (# | z #) -> naturalFromBigNat# z
+ (# (# #) | #) -> raiseUnderflow
+ (# | z #) -> naturalFromBigNat# z
-- | Sub two naturals
--
@@ -300,8 +312,8 @@ naturalSubUnsafe (NS _) (NB _) = naturalZero
naturalSubUnsafe (NB x) (NS y) = naturalFromBigNat# (bigNatSubWordUnsafe# x y)
naturalSubUnsafe (NB x) (NB y) =
case bigNatSub x y of
- (# () | #) -> naturalZero
- (# | z #) -> naturalFromBigNat# z
+ (# (# #) | #) -> naturalZero
+ (# | z #) -> naturalFromBigNat# z
-- | Multiplication
naturalMul :: Natural -> Natural -> Natural
@@ -327,6 +339,7 @@ naturalSqr !a = naturalMul a a
-- | Signum for Natural
naturalSignum :: Natural -> Natural
+{-# NOINLINE naturalSignum #-}
naturalSignum (NS 0##) = NS 0##
naturalSignum _ = NS 1##
@@ -380,30 +393,35 @@ naturalRem (NB n) (NB d) = case bigNatRem n d of
r -> naturalFromBigNat# r
naturalAnd :: Natural -> Natural -> Natural
+{-# NOINLINE naturalAnd #-}
naturalAnd (NS n) (NS m) = NS (n `and#` m)
naturalAnd (NS n) (NB m) = NS (n `and#` bigNatToWord# m)
naturalAnd (NB n) (NS m) = NS (bigNatToWord# n `and#` m)
naturalAnd (NB n) (NB m) = naturalFromBigNat# (bigNatAnd n m)
naturalAndNot :: Natural -> Natural -> Natural
+{-# NOINLINE naturalAndNot #-}
naturalAndNot (NS n) (NS m) = NS (n `and#` not# m)
naturalAndNot (NS n) (NB m) = NS (n `and#` not# (bigNatToWord# m))
naturalAndNot (NB n) (NS m) = NS (bigNatToWord# n `and#` not# m)
naturalAndNot (NB n) (NB m) = naturalFromBigNat# (bigNatAndNot n m)
naturalOr :: Natural -> Natural -> Natural
+{-# NOINLINE naturalOr #-}
naturalOr (NS n) (NS m) = NS (n `or#` m)
naturalOr (NS n) (NB m) = NB (bigNatOrWord# m n)
naturalOr (NB n) (NS m) = NB (bigNatOrWord# n m)
naturalOr (NB n) (NB m) = NB (bigNatOr n m)
naturalXor :: Natural -> Natural -> Natural
+{-# NOINLINE naturalXor #-}
naturalXor (NS n) (NS m) = NS (n `xor#` m)
naturalXor (NS n) (NB m) = NB (bigNatXorWord# m n)
naturalXor (NB n) (NS m) = NB (bigNatXorWord# n m)
naturalXor (NB n) (NB m) = naturalFromBigNat# (bigNatXor n m)
naturalTestBit# :: Natural -> Word# -> Bool#
+{-# NOINLINE naturalTestBit# #-}
naturalTestBit# (NS w) i = (i `ltWord#` WORD_SIZE_IN_BITS##) &&#
((w `and#` (1## `uncheckedShiftL#` word2Int# i)) `neWord#` 0##)
naturalTestBit# (NB bn) i = bigNatTestBit# bn i
@@ -412,6 +430,7 @@ naturalTestBit :: Natural -> Word -> Bool
naturalTestBit !n (W# i) = isTrue# (naturalTestBit# n i)
naturalBit# :: Word# -> Natural
+{-# NOINLINE naturalBit# #-}
naturalBit# i
| isTrue# (i `ltWord#` WORD_SIZE_IN_BITS##) = NS (1## `uncheckedShiftL#` word2Int# i)
| True = NB (bigNatBit# i)
@@ -421,6 +440,7 @@ naturalBit (W# i) = naturalBit# i
-- | Compute greatest common divisor.
naturalGcd :: Natural -> Natural -> Natural
+{-# NOINLINE naturalGcd #-}
naturalGcd (NS 0##) !y = y
naturalGcd x (NS 0##) = x
naturalGcd (NS 1##) _ = NS 1##
@@ -432,6 +452,7 @@ naturalGcd (NS x) (NS y) = NS (gcdWord# x y)
-- | Compute least common multiple.
naturalLcm :: Natural -> Natural -> Natural
+{-# NOINLINE naturalLcm #-}
naturalLcm (NS 0##) !_ = NS 0##
naturalLcm _ (NS 0##) = NS 0##
naturalLcm (NS 1##) y = y
@@ -443,6 +464,7 @@ naturalLcm (NB a ) (NB b ) = naturalFromBigNat# (bigNatLcm a b)
-- | Base 2 logarithm
naturalLog2# :: Natural -> Word#
+{-# NOINLINE naturalLog2# #-}
naturalLog2# (NS w) = wordLog2# w
naturalLog2# (NB b) = bigNatLog2# b
@@ -452,6 +474,7 @@ naturalLog2 !n = W# (naturalLog2# n)
-- | Logarithm for an arbitrary base
naturalLogBaseWord# :: Word# -> Natural -> Word#
+{-# NOINLINE naturalLogBaseWord# #-}
naturalLogBaseWord# base (NS a) = wordLogBase# base a
naturalLogBaseWord# base (NB a) = bigNatLogBaseWord# base a
@@ -461,6 +484,7 @@ naturalLogBaseWord (W# base) !a = W# (naturalLogBaseWord# base a)
-- | Logarithm for an arbitrary base
naturalLogBase# :: Natural -> Natural -> Word#
+{-# NOINLINE naturalLogBase# #-}
naturalLogBase# (NS base) !a = naturalLogBaseWord# base a
naturalLogBase# (NB _ ) (NS _) = 0##
naturalLogBase# (NB base) (NB a) = bigNatLogBase# base a
@@ -472,6 +496,7 @@ naturalLogBase !base !a = W# (naturalLogBase# base a)
-- | \"@'naturalPowMod' /b/ /e/ /m/@\" computes base @/b/@ raised to
-- exponent @/e/@ modulo @/m/@.
naturalPowMod :: Natural -> Natural -> Natural -> Natural
+{-# NOINLINE naturalPowMod #-}
naturalPowMod !_ !_ (NS 0##) = raiseDivZero
naturalPowMod _ _ (NS 1##) = NS 0##
naturalPowMod _ (NS 0##) _ = NS 1##
@@ -491,6 +516,7 @@ naturalPowMod b e (NB m) = naturalFromBigNat#
--
-- `base` must be > 1
naturalSizeInBase# :: Word# -> Natural -> Word#
+{-# NOINLINE naturalSizeInBase# #-}
naturalSizeInBase# base (NS w) = wordSizeInBase# base w
naturalSizeInBase# base (NB n) = bigNatSizeInBase# base n
@@ -501,6 +527,7 @@ naturalSizeInBase# base (NB n) = bigNatSizeInBase# base n
-- byte first (big-endian) if @1#@ or least significant byte first
-- (little-endian) if @0#@.
naturalToAddr# :: Natural -> Addr# -> Bool# -> State# s -> (# State# s, Word# #)
+{-# NOINLINE naturalToAddr# #-}
naturalToAddr# (NS i) = wordToAddr# i
naturalToAddr# (NB n) = bigNatToAddr# n
@@ -525,6 +552,7 @@ naturalToAddr a addr e = IO \s -> case naturalToAddr# a addr e s of
--
-- Null higher limbs are automatically trimed.
naturalFromAddr# :: Word# -> Addr# -> Bool# -> State# s -> (# State# s, Natural #)
+{-# NOINLINE naturalFromAddr# #-}
naturalFromAddr# sz addr e s =
case bigNatFromAddr# sz addr e s of
(# s', n #) -> (# s', naturalFromBigNat# n #)
@@ -549,6 +577,7 @@ naturalFromAddr sz addr e = IO (naturalFromAddr# sz addr e)
-- byte first (big-endian) if @1#@ or least significant byte first
-- (little-endian) if @0#@.
naturalToMutableByteArray# :: Natural -> MutableByteArray# s -> Word# -> Bool# -> State# s -> (# State# s, Word# #)
+{-# NOINLINE naturalToMutableByteArray# #-}
naturalToMutableByteArray# (NS w) = wordToMutableByteArray# w
naturalToMutableByteArray# (NB a) = bigNatToMutableByteArray# a
@@ -562,5 +591,6 @@ naturalToMutableByteArray# (NB a) = bigNatToMutableByteArray# a
--
-- Null higher limbs are automatically trimed.
naturalFromByteArray# :: Word# -> ByteArray# -> Word# -> Bool# -> State# s -> (# State# s, Natural #)
+{-# NOINLINE naturalFromByteArray# #-}
naturalFromByteArray# sz ba off e s = case bigNatFromByteArray# sz ba off e s of
(# s', a #) -> (# s', naturalFromBigNat# a #)
diff --git a/libraries/ghc-bignum/src/GHC/Num/Primitives.hs b/libraries/ghc-bignum/src/GHC/Num/Primitives.hs
index 033262b229..589600e047 100644
--- a/libraries/ghc-bignum/src/GHC/Num/Primitives.hs
+++ b/libraries/ghc-bignum/src/GHC/Num/Primitives.hs
@@ -271,9 +271,9 @@ wordSizeInBase# _ 0## = 0##
wordSizeInBase# base w = 1## `plusWord#` wordLogBase# base w
-- | Indicate if the value is a power of two and which one
-wordIsPowerOf2# :: Word# -> (# () | Word# #)
+wordIsPowerOf2# :: Word# -> (# (# #) | Word# #)
wordIsPowerOf2# w
- | isTrue# (popCnt# w `neWord#` 1##) = (# () | #)
+ | isTrue# (popCnt# w `neWord#` 1##) = (# (# #) | #)
| True = (# | ctz# w #)
-- | Reverse bytes in a Word#
diff --git a/libraries/ghc-bignum/src/GHC/Num/WordArray.hs b/libraries/ghc-bignum/src/GHC/Num/WordArray.hs
index dffb7e5797..d4ada9bb3b 100644
--- a/libraries/ghc-bignum/src/GHC/Num/WordArray.hs
+++ b/libraries/ghc-bignum/src/GHC/Num/WordArray.hs
@@ -108,13 +108,13 @@ withNewWordArray2Trimed# sz1 sz2 act = withNewWordArray2# sz1 sz2 \mwa1 mwa2 s -
withNewWordArrayTrimedMaybe#
:: Int# -- ^ Size in Word
-> (MutableWordArray# RealWorld -> State# RealWorld -> (# State# RealWorld, Bool# #))
- -> (# () | WordArray# #)
+ -> (# (# #) | WordArray# #)
withNewWordArrayTrimedMaybe# sz act = case runRW# io of (# _, a #) -> a
where
io s =
case newWordArray# sz s of
(# s, mwa #) -> case act mwa s of
- (# s, 0# #) -> (# s, (# () | #) #)
+ (# s, 0# #) -> (# s, (# (# #) | #) #)
(# s, _ #) -> case mwaTrimZeroes# mwa s of
s -> case unsafeFreezeByteArray# mwa s of
(# s, ba #) -> (# s, (# | ba #) #)
diff --git a/libraries/integer-gmp/src/GHC/Integer/GMP/Internals.hs b/libraries/integer-gmp/src/GHC/Integer/GMP/Internals.hs
index 2fcb0750ed..7fa06bf52c 100644
--- a/libraries/integer-gmp/src/GHC/Integer/GMP/Internals.hs
+++ b/libraries/integer-gmp/src/GHC/Integer/GMP/Internals.hs
@@ -244,14 +244,14 @@ plusBigNatWord (BN# a) w = BN# (B.bigNatAddWord# a w)
{-# DEPRECATED minusBigNat "Use bigNatSub instead" #-}
minusBigNat :: BigNat -> BigNat -> BigNat
minusBigNat (BN# a) (BN# b) = case B.bigNatSub a b of
- (# () | #) -> throw Underflow
- (# | r #) -> BN# r
+ (# (# #) | #) -> throw Underflow
+ (# | r #) -> BN# r
{-# DEPRECATED minusBigNatWord "Use bigNatSubWord# instead" #-}
minusBigNatWord :: BigNat -> GmpLimb# -> BigNat
minusBigNatWord (BN# a) b = case B.bigNatSubWord# a b of
- (# () | #) -> throw Underflow
- (# | r #) -> BN# r
+ (# (# #) | #) -> throw Underflow
+ (# | r #) -> BN# r
{-# DEPRECATED timesBigNat "Use bigNatMul instead" #-}