[commit: ghc] master: Division fails fast for `divMod` \w integer-simple (bbea972)

git at git.haskell.org git at git.haskell.org
Fri Dec 28 03:44:38 UTC 2018


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/bbea972149882b4f5f6b0a1691488a519ba6aaf9/ghc

>---------------------------------------------------------------

commit bbea972149882b4f5f6b0a1691488a519ba6aaf9
Author: Alec Theriault <alec.theriault at gmail.com>
Date:   Mon Dec 24 13:35:18 2018 -0500

    Division fails fast for `divMod` \w integer-simple
    
    We want to match the behaviour of `Integer` as well as
    `Integer`/`Natural` from `integer-gmp`, namely to have
    
         divMod x 0 = _|_
    
    not
    
         divMod x 0 = (_|_, _|_)
    
    See #16091 for an example of where this matters.


>---------------------------------------------------------------

bbea972149882b4f5f6b0a1691488a519ba6aaf9
 libraries/base/GHC/Real.hs | 36 ++++++++++++++++++++----------------
 1 file changed, 20 insertions(+), 16 deletions(-)

diff --git a/libraries/base/GHC/Real.hs b/libraries/base/GHC/Real.hs
index da64c8b..7ba4344 100644
--- a/libraries/base/GHC/Real.hs
+++ b/libraries/base/GHC/Real.hs
@@ -481,22 +481,26 @@ instance Integral Natural where
 #else
 -- | @since 4.8.0.0
 instance Integral Natural where
-  quot (Natural a) (Natural b) = Natural (quot a b)
-  {-# INLINE quot #-}
-  rem (Natural a) (Natural b) = Natural (rem a b)
-  {-# INLINE rem #-}
-  div (Natural a) (Natural b) = Natural (div a b)
-  {-# INLINE div #-}
-  mod (Natural a) (Natural b) = Natural (mod a b)
-  {-# INLINE mod #-}
-  divMod (Natural a) (Natural b) = (Natural q, Natural r)
-    where (q,r) = divMod a b
-  {-# INLINE divMod #-}
-  quotRem (Natural a) (Natural b) = (Natural q, Natural r)
-    where (q,r) = quotRem a b
-  {-# INLINE quotRem #-}
-  toInteger (Natural a) = a
-  {-# INLINE toInteger #-}
+    {-# INLINE toInteger #-}
+    toInteger (Natural a) = a
+
+    {-# INLINE quot #-}
+    Natural a `quot` Natural b = Natural (a `quot` b)
+
+    {-# INLINE rem #-}
+    Natural a `rem` Natural b = Natural (a `rem` b)
+
+    {-# INLINE div #-}
+    Natural a `div` Natural b = Natural (a `div` b)
+
+    {-# INLINE mod #-}
+    Natural a `mod` Natural b = Natural (a `mod` b)
+
+    {-# INLINE divMod #-}
+    Natural a `divMod` Natural b = coerce (a `divMod` b)
+
+    {-# INLINE quotRem #-}
+    Natural a `quotRem` Natural b = coerce (a `quotRem` b)
 #endif
 
 --------------------------------------------------------------



More information about the ghc-commits mailing list