summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--libraries/base/GHC/Real.hs105
-rw-r--r--libraries/base/GHC/Word.hs134
2 files changed, 139 insertions, 100 deletions
diff --git a/libraries/base/GHC/Real.hs b/libraries/base/GHC/Real.hs
index ed5fcd022c..c47764f7a3 100644
--- a/libraries/base/GHC/Real.hs
+++ b/libraries/base/GHC/Real.hs
@@ -326,34 +326,40 @@ instance Real Int where
instance Integral Int where
toInteger (I# i) = IS i
+ {-# INLINE quot #-} -- see Note [INLINE division wrappers] in GHC.Base
a `quot` b
| b == 0 = divZeroError
| b == (-1) && a == minBound = overflowError -- Note [Order of tests]
-- in GHC.Int
| otherwise = a `quotInt` b
+ {-# INLINE rem #-} -- see Note [INLINE division wrappers] in GHC.Base
!a `rem` b -- See Note [Special case of mod and rem is lazy]
| b == 0 = divZeroError
| b == (-1) = 0
| otherwise = a `remInt` b
+ {-# INLINE div #-} -- see Note [INLINE division wrappers] in GHC.Base
a `div` b
| b == 0 = divZeroError
| b == (-1) && a == minBound = overflowError -- Note [Order of tests]
-- in GHC.Int
| otherwise = a `divInt` b
+ {-# INLINE mod #-} -- see Note [INLINE division wrappers] in GHC.Base
!a `mod` b -- See Note [Special case of mod and rem is lazy]
| b == 0 = divZeroError
| b == (-1) = 0
| otherwise = a `modInt` b
+ {-# INLINE quotRem #-} -- see Note [INLINE division wrappers] in GHC.Base
a `quotRem` b
| b == 0 = divZeroError
-- Note [Order of tests] in GHC.Int
| b == (-1) && a == minBound = (overflowError, 0)
| otherwise = a `quotRemInt` b
+ {-# INLINE divMod #-} -- see Note [INLINE division wrappers] in GHC.Base
a `divMod` b
| b == 0 = divZeroError
-- Note [Order of tests] in GHC.Int
@@ -379,26 +385,32 @@ instance Real Word where
-- | @since 2.01
instance Integral Word where
+ -- 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
+
rem (W# x#) y@(W# y#)
| y /= 0 = W# (x# `remWord#` y#)
| otherwise = divZeroError
- div (W# x#) y@(W# y#)
- | y /= 0 = W# (x# `quotWord#` y#)
- | otherwise = divZeroError
- mod (W# x#) y@(W# y#)
- | y /= 0 = W# (x# `remWord#` y#)
- | otherwise = divZeroError
+
quotRem (W# x#) y@(W# y#)
| y /= 0 = case x# `quotRemWord#` y# of
(# q, r #) ->
(W# q, W# r)
| otherwise = divZeroError
- 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#
--------------------------------------------------------------
@@ -427,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 x = integerFromNatural x
-
- {-# 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 7187817d06..2c5ea72788 100644
--- a/libraries/base/GHC/Word.hs
+++ b/libraries/base/GHC/Word.hs
@@ -143,27 +143,30 @@ 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# (wordToWord8# ((word8ToWord# x#) `quotWord#` (word8ToWord# y#)))
| otherwise = divZeroError
rem (W8# x#) y@(W8# y#)
| y /= 0 = W8# (wordToWord8# ((word8ToWord# x#) `remWord#` (word8ToWord# y#)))
| otherwise = divZeroError
- div (W8# x#) y@(W8# y#)
- | y /= 0 = W8# (wordToWord8# ((word8ToWord# x#) `quotWord#` (word8ToWord# y#)))
- | otherwise = divZeroError
- mod (W8# x#) y@(W8# y#)
- | y /= 0 = W8# (wordToWord8# ((word8ToWord# x#) `remWord#` (word8ToWord# y#)))
- | otherwise = divZeroError
quotRem (W8# x#) y@(W8# y#)
| y /= 0 = case (word8ToWord# x#) `quotRemWord#` (word8ToWord# y#) of
(# q, r #) ->
(W8# (wordToWord8# q), W8# (wordToWord8# r))
| otherwise = divZeroError
- divMod (W8# x#) y@(W8# y#)
- | y /= 0 = (W8# (wordToWord8# ((word8ToWord# x#) `quotWord#` (word8ToWord# y#)))
- ,W8# (wordToWord8# ((word8ToWord# x#) `remWord#` (word8ToWord# y#))))
- | 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
@@ -331,27 +334,30 @@ 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# (wordToWord16# ((word16ToWord# x#) `quotWord#` (word16ToWord# y#)))
| otherwise = divZeroError
rem (W16# x#) y@(W16# y#)
| y /= 0 = W16# (wordToWord16# ((word16ToWord# x#) `remWord#` (word16ToWord# y#)))
| otherwise = divZeroError
- div (W16# x#) y@(W16# y#)
- | y /= 0 = W16# (wordToWord16# ((word16ToWord# x#) `quotWord#` (word16ToWord# y#)))
- | otherwise = divZeroError
- mod (W16# x#) y@(W16# y#)
- | y /= 0 = W16# (wordToWord16# ((word16ToWord# x#) `remWord#` (word16ToWord# y#)))
- | otherwise = divZeroError
quotRem (W16# x#) y@(W16# y#)
| y /= 0 = case (word16ToWord# x#) `quotRemWord#` (word16ToWord# y#) of
(# q, r #) ->
(W16# (wordToWord16# q), W16# (wordToWord16# r))
| otherwise = divZeroError
- divMod (W16# x#) y@(W16# y#)
- | y /= 0 = (W16# (wordToWord16# ((word16ToWord# x#) `quotWord#` (word16ToWord# y#)))
- ,W16# (wordToWord16# ((word16ToWord# x#) `remWord#` (word16ToWord# y#))))
- | 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
@@ -567,28 +573,39 @@ 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# (wordToWord32# ((word32ToWord# x#) `quotWord#` (word32ToWord# y#)))
| otherwise = divZeroError
rem (W32# x#) y@(W32# y#)
| y /= 0 = W32# (wordToWord32# ((word32ToWord# x#) `remWord#` (word32ToWord# y#)))
| otherwise = divZeroError
- div (W32# x#) y@(W32# y#)
- | y /= 0 = W32# (wordToWord32# ((word32ToWord# x#) `quotWord#` (word32ToWord# y#)))
- | otherwise = divZeroError
- mod (W32# x#) y@(W32# y#)
- | y /= 0 = W32# (wordToWord32# ((word32ToWord# x#) `remWord#` (word32ToWord# y#)))
- | otherwise = divZeroError
quotRem (W32# x#) y@(W32# y#)
| y /= 0 = case (word32ToWord# x#) `quotRemWord#` (word32ToWord# y#) of
(# q, r #) ->
(W32# (wordToWord32# q), W32# (wordToWord32# r))
| otherwise = divZeroError
- divMod (W32# x#) y@(W32# y#)
- | y /= 0 = (W32# (wordToWord32# ((word32ToWord# x#) `quotWord#` (word32ToWord# y#)))
- ,W32# (wordToWord32# ((word32ToWord# x#) `remWord#` (word32ToWord# y#))))
- | otherwise = divZeroError
- toInteger (W32# x#) = integerFromWord# (word32ToWord# x#)
+
+ 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#
+ | otherwise = integerFromWord# (word32ToWord# x#)
+ where
+ !i# = word2Int# (word32ToWord# x#)
+#else
+ = IS (word2Int# (word32ToWord# x#))
+#endif
-- | @since 2.01
instance Bits Word32 where
@@ -743,24 +760,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
@@ -924,27 +945,34 @@ 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
- toInteger (W64# x#) = integerFromWord# x#
+
+ 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#
+ where
+ !i# = word2Int# x#
-- | @since 2.01
instance Bits Word64 where