summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSylvain Henry <sylvain@haskus.fr>2021-06-02 19:11:35 +0200
committerMarge Bot <ben+marge-bot@smart-cactus.org>2021-06-04 12:45:01 -0400
commit737b0ae194ca33f9bea9a150dada0c933fd75d4d (patch)
tree1511b12b7ce9b52f7ae4be19bf7e4014562f9777
parent733757adb54eccdb4428e5ca4b2d896804bf5965 (diff)
downloadhaskell-737b0ae194ca33f9bea9a150dada0c933fd75d4d.tar.gz
Fix Integral instances for Words
* ensure that division wrappers are INLINE * make div/mod/divMod call quot/rem/quotRem (same code) * this ensures that the quotRemWordN# primitive is used to implement divMod (it wasn't the case for sized Words) * make first argument strict for Natural and Integer (similarly to other numeric types)
-rw-r--r--libraries/base/GHC/Real.hs103
-rw-r--r--libraries/base/GHC/Word.hs127
2 files changed, 120 insertions, 110 deletions
diff --git a/libraries/base/GHC/Real.hs b/libraries/base/GHC/Real.hs
index 3fb13af822..df4143e1ee 100644
--- a/libraries/base/GHC/Real.hs
+++ b/libraries/base/GHC/Real.hs
@@ -385,37 +385,31 @@ instance Real Word where
-- | @since 2.01
instance Integral Word where
- {-# INLINE quot #-} -- see Note [INLINE division wrappers] in GHC.Base
+ -- see Note [INLINE division wrappers] in GHC.Base
+ {-# INLINE quot #-}
+ {-# INLINE rem #-}
+ {-# INLINE quotRem #-}
+ {-# INLINE div #-}
+ {-# INLINE mod #-}
+ {-# INLINE divMod #-}
+
quot (W# x#) y@(W# y#)
| y /= 0 = W# (x# `quotWord#` y#)
| otherwise = divZeroError
- {-# INLINE rem #-} -- see Note [INLINE division wrappers] in GHC.Base
rem (W# x#) y@(W# y#)
| y /= 0 = W# (x# `remWord#` y#)
| otherwise = divZeroError
- {-# INLINE div #-} -- see Note [INLINE division wrappers] in GHC.Base
- div (W# x#) y@(W# y#)
- | y /= 0 = W# (x# `quotWord#` y#)
- | otherwise = divZeroError
-
- {-# INLINE mod #-} -- see Note [INLINE division wrappers] in GHC.Base
- mod (W# x#) y@(W# y#)
- | y /= 0 = W# (x# `remWord#` y#)
- | otherwise = divZeroError
-
- {-# INLINE quotRem #-} -- see Note [INLINE division wrappers] in GHC.Base
quotRem (W# x#) y@(W# y#)
| y /= 0 = case x# `quotRemWord#` y# of
(# q, r #) ->
(W# q, W# r)
| otherwise = divZeroError
- {-# INLINE divMod #-} -- see Note [INLINE division wrappers] in GHC.Base
- divMod (W# x#) y@(W# y#)
- | y /= 0 = (W# (x# `quotWord#` y#), W# (x# `remWord#` y#))
- | otherwise = divZeroError
+ div x y = quot x y
+ mod x y = rem x y
+ divMod x y = quotRem x y
toInteger (W# x#) = integerFromWord# x#
@@ -445,59 +439,58 @@ instance Real Natural where
-- | @since 2.0.1
instance Integral Integer where
+ -- see Note [INLINE division wrappers] in GHC.Base
+ {-# INLINE quot #-}
+ {-# INLINE rem #-}
+ {-# INLINE quotRem #-}
+ {-# INLINE div #-}
+ {-# INLINE mod #-}
+ {-# INLINE divMod #-}
+
toInteger n = n
- {-# INLINE quot #-}
- _ `quot` 0 = divZeroError
- n `quot` d = n `integerQuot` d
+ !_ `quot` 0 = divZeroError
+ n `quot` d = n `integerQuot` d
- {-# INLINE rem #-}
- _ `rem` 0 = divZeroError
- n `rem` d = n `integerRem` d
+ !_ `rem` 0 = divZeroError
+ n `rem` d = n `integerRem` d
- {-# INLINE div #-}
- _ `div` 0 = divZeroError
- n `div` d = n `integerDiv` d
+ !_ `div` 0 = divZeroError
+ n `div` d = n `integerDiv` d
- {-# INLINE mod #-}
- _ `mod` 0 = divZeroError
- n `mod` d = n `integerMod` d
+ !_ `mod` 0 = divZeroError
+ n `mod` d = n `integerMod` d
- {-# INLINE divMod #-}
- _ `divMod` 0 = divZeroError
- n `divMod` d = n `integerDivMod` d
+ !_ `divMod` 0 = divZeroError
+ n `divMod` d = n `integerDivMod` d
- {-# INLINE quotRem #-}
- _ `quotRem` 0 = divZeroError
- n `quotRem` d = n `integerQuotRem` d
+ !_ `quotRem` 0 = divZeroError
+ n `quotRem` d = n `integerQuotRem` d
-- | @since 4.8.0.0
instance Integral Natural where
- toInteger = integerFromNatural
-
- {-# INLINE quot #-}
- _ `quot` 0 = divZeroError
- n `quot` d = n `naturalQuot` d
+ -- see Note [INLINE division wrappers] in GHC.Base
+ {-# INLINE quot #-}
+ {-# INLINE rem #-}
+ {-# INLINE quotRem #-}
+ {-# INLINE div #-}
+ {-# INLINE mod #-}
+ {-# INLINE divMod #-}
- {-# INLINE rem #-}
- _ `rem` 0 = divZeroError
- n `rem` d = n `naturalRem` d
+ toInteger = integerFromNatural
- {-# INLINE div #-}
- _ `div` 0 = divZeroError
- n `div` d = n `naturalQuot` d
+ !_ `quot` 0 = divZeroError
+ n `quot` d = n `naturalQuot` d
- {-# INLINE mod #-}
- _ `mod` 0 = divZeroError
- n `mod` d = n `naturalRem` d
+ !_ `rem` 0 = divZeroError
+ n `rem` d = n `naturalRem` d
- {-# INLINE divMod #-}
- _ `divMod` 0 = divZeroError
- n `divMod` d = n `naturalQuotRem` d
+ !_ `quotRem` 0 = divZeroError
+ n `quotRem` d = n `naturalQuotRem` d
- {-# INLINE quotRem #-}
- _ `quotRem` 0 = divZeroError
- n `quotRem` d = n `naturalQuotRem` d
+ div x y = quot x y
+ mod x y = rem x y
+ divMod x y = quotRem x y
--------------------------------------------------------------
-- Instances for @Ratio@
diff --git a/libraries/base/GHC/Word.hs b/libraries/base/GHC/Word.hs
index acac8acceb..8a50951344 100644
--- a/libraries/base/GHC/Word.hs
+++ b/libraries/base/GHC/Word.hs
@@ -139,26 +139,29 @@ instance Enum Word8 where
-- | @since 2.01
instance Integral Word8 where
+ -- see Note [INLINE division wrappers] in GHC.Base
+ {-# INLINE quot #-}
+ {-# INLINE rem #-}
+ {-# INLINE quotRem #-}
+ {-# INLINE div #-}
+ {-# INLINE mod #-}
+ {-# INLINE divMod #-}
+
quot (W8# x#) y@(W8# y#)
| y /= 0 = W8# (x# `quotWord8#` y#)
| otherwise = divZeroError
rem (W8# x#) y@(W8# y#)
| y /= 0 = W8# (x# `remWord8#` y#)
| otherwise = divZeroError
- div (W8# x#) y@(W8# y#)
- | y /= 0 = W8# (x# `quotWord8#` y#)
- | otherwise = divZeroError
- mod (W8# x#) y@(W8# y#)
- | y /= 0 = W8# (x# `remWord8#` y#)
- | otherwise = divZeroError
quotRem (W8# x#) y@(W8# y#)
| y /= 0 = case x# `quotRemWord8#` y# of
- (# q, r #) -> (W8# q, W8# r)
- | otherwise = divZeroError
- divMod (W8# x#) y@(W8# y#)
- | y /= 0 = (W8# (x# `quotWord8#` y#)
- ,W8# (x# `remWord8#` y#))
+ (# q, r #) -> (W8# q, W8# r)
| otherwise = divZeroError
+
+ div x y = quot x y
+ mod x y = rem x y
+ divMod x y = quotRem x y
+
toInteger (W8# x#) = IS (word2Int# (word8ToWord# x#))
-- | @since 2.01
@@ -329,26 +332,29 @@ instance Enum Word16 where
-- | @since 2.01
instance Integral Word16 where
+ -- see Note [INLINE division wrappers] in GHC.Base
+ {-# INLINE quot #-}
+ {-# INLINE rem #-}
+ {-# INLINE quotRem #-}
+ {-# INLINE div #-}
+ {-# INLINE mod #-}
+ {-# INLINE divMod #-}
+
quot (W16# x#) y@(W16# y#)
| y /= 0 = W16# (x# `quotWord16#` y#)
| otherwise = divZeroError
rem (W16# x#) y@(W16# y#)
| y /= 0 = W16# (x# `remWord16#` y#)
| otherwise = divZeroError
- div (W16# x#) y@(W16# y#)
- | y /= 0 = W16# (x# `quotWord16#` y#)
- | otherwise = divZeroError
- mod (W16# x#) y@(W16# y#)
- | y /= 0 = W16# (x# `remWord16#` y#)
- | otherwise = divZeroError
quotRem (W16# x#) y@(W16# y#)
- | y /= 0 = case x# `quotRemWord16#` y# of
- (# q, r #) -> (W16# q, W16# r)
- | otherwise = divZeroError
- divMod (W16# x#) y@(W16# y#)
- | y /= 0 = (W16# (x# `quotWord16#` y#)
- ,W16# (x# `remWord16#` y#))
+ | y /= 0 = case x# `quotRemWord16#` y# of
+ (# q, r #) -> (W16# q, W16# r)
| otherwise = divZeroError
+
+ div x y = quot x y
+ mod x y = rem x y
+ divMod x y = quotRem x y
+
toInteger (W16# x#) = IS (word2Int# (word16ToWord# x#))
-- | @since 2.01
@@ -568,26 +574,29 @@ instance Enum Word32 where
-- | @since 2.01
instance Integral Word32 where
+ -- see Note [INLINE division wrappers] in GHC.Base
+ {-# INLINE quot #-}
+ {-# INLINE rem #-}
+ {-# INLINE quotRem #-}
+ {-# INLINE div #-}
+ {-# INLINE mod #-}
+ {-# INLINE divMod #-}
+
quot (W32# x#) y@(W32# y#)
| y /= 0 = W32# (x# `quotWord32#` y#)
| otherwise = divZeroError
rem (W32# x#) y@(W32# y#)
| y /= 0 = W32# (x# `remWord32#` y#)
| otherwise = divZeroError
- div (W32# x#) y@(W32# y#)
- | y /= 0 = W32# (x# `quotWord32#` y#)
- | otherwise = divZeroError
- mod (W32# x#) y@(W32# y#)
- | y /= 0 = W32# (x# `remWord32#` y#)
- | otherwise = divZeroError
quotRem (W32# x#) y@(W32# y#)
- | y /= 0 = case x# `quotRemWord32#` y# of
- (# q, r #) -> (W32# q, W32# r)
- | otherwise = divZeroError
- divMod (W32# x#) y@(W32# y#)
- | y /= 0 = (W32# (x# `quotWord32#` y#)
- ,W32# (x# `remWord32#` y#))
+ | y /= 0 = case x# `quotRemWord32#` y# of
+ (# q, r #) -> (W32# q, W32# r)
| otherwise = divZeroError
+
+ div x y = quot x y
+ mod x y = rem x y
+ divMod x y = quotRem x y
+
toInteger (W32# x#)
#if WORD_SIZE_IN_BITS == 32
| isTrue# (i# >=# 0#) = IS i#
@@ -752,24 +761,28 @@ instance Enum Word64 where
-- | @since 2.01
instance Integral Word64 where
+ -- see Note [INLINE division wrappers] in GHC.Base
+ {-# INLINE quot #-}
+ {-# INLINE rem #-}
+ {-# INLINE quotRem #-}
+ {-# INLINE div #-}
+ {-# INLINE mod #-}
+ {-# INLINE divMod #-}
+
quot (W64# x#) y@(W64# y#)
| y /= 0 = W64# (x# `quotWord64#` y#)
| otherwise = divZeroError
rem (W64# x#) y@(W64# y#)
| y /= 0 = W64# (x# `remWord64#` y#)
| otherwise = divZeroError
- div (W64# x#) y@(W64# y#)
- | y /= 0 = W64# (x# `quotWord64#` y#)
- | otherwise = divZeroError
- mod (W64# x#) y@(W64# y#)
- | y /= 0 = W64# (x# `remWord64#` y#)
- | otherwise = divZeroError
quotRem (W64# x#) y@(W64# y#)
| y /= 0 = (W64# (x# `quotWord64#` y#), W64# (x# `remWord64#` y#))
| otherwise = divZeroError
- divMod (W64# x#) y@(W64# y#)
- | y /= 0 = (W64# (x# `quotWord64#` y#), W64# (x# `remWord64#` y#))
- | otherwise = divZeroError
+
+ div x y = quot x y
+ mod x y = rem x y
+ divMod x y = quotRem x y
+
toInteger (W64# x#) = integerFromWord64# x#
-- | @since 2.01
@@ -933,25 +946,29 @@ wordToWord64 (W# w#) = (W64# w#)
-- | @since 2.01
instance Integral Word64 where
+ -- see Note [INLINE division wrappers] in GHC.Base
+ {-# INLINE quot #-}
+ {-# INLINE rem #-}
+ {-# INLINE quotRem #-}
+ {-# INLINE div #-}
+ {-# INLINE mod #-}
+ {-# INLINE divMod #-}
+
quot (W64# x#) y@(W64# y#)
| y /= 0 = W64# (x# `quotWord#` y#)
| otherwise = divZeroError
rem (W64# x#) y@(W64# y#)
| y /= 0 = W64# (x# `remWord#` y#)
| otherwise = divZeroError
- div (W64# x#) y@(W64# y#)
- | y /= 0 = W64# (x# `quotWord#` y#)
- | otherwise = divZeroError
- mod (W64# x#) y@(W64# y#)
- | y /= 0 = W64# (x# `remWord#` y#)
- | otherwise = divZeroError
quotRem (W64# x#) y@(W64# y#)
- | y /= 0 = case x# `quotRemWord#` y# of
- (# q, r #) -> (W64# q, W64# r)
- | otherwise = divZeroError
- divMod (W64# x#) y@(W64# y#)
- | y /= 0 = (W64# (x# `quotWord#` y#), W64# (x# `remWord#` y#))
+ | y /= 0 = case x# `quotRemWord#` y# of
+ (# q, r #) -> (W64# q, W64# r)
| otherwise = divZeroError
+
+ div x y = quot x y
+ mod x y = rem x y
+ divMod x y = quotRem x y
+
toInteger (W64# x#)
| isTrue# (i# >=# 0#) = IS i#
| otherwise = integerFromWord# x#