Repository : ssh://darcs.haskell.org//srv/darcs/packages/base

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/a2b000f7420475f8318811e11f8f291c90f2fae4

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

commit a2b000f7420475f8318811e11f8f291c90f2fae4
Author: Ian Lynagh <[email protected]>
Date:   Sun Jan 29 22:59:50 2012 +0000

    Define a divModInt function that only does 1 division

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

 GHC/Base.lhs |   12 ++++++++++++
 GHC/Int.hs   |   22 +++++++++++++++-------
 GHC/Num.lhs  |    4 ----
 3 files changed, 27 insertions(+), 11 deletions(-)

diff --git a/GHC/Base.lhs b/GHC/Base.lhs
index 26ea47a..bf4a8c1 100644
--- a/GHC/Base.lhs
+++ b/GHC/Base.lhs
@@ -712,6 +712,18 @@ quotRemInt :: Int -> Int -> (Int, Int)
                              (# q, r #) ->
                                  (I# q, I# r)
 
+divModInt :: Int -> Int -> (Int, Int)
+(I# x) `divModInt` (I# y) = case x `divModInt#` y of
+                            (# q, r #) -> (I# q, I# r)
+
+divModInt# :: Int# -> Int# -> (# Int#, Int# #)
+x# `divModInt#` y#
+ | (x# ># 0#) && (y# <# 0#) = case (x# -# 1#) `quotRemInt#` y# of
+                              (# q, r #) -> (# q -# 1#, r +# y# +# 1# #)
+ | (x# <# 0#) && (y# ># 0#) = case (x# +# 1#) `quotRemInt#` y# of
+                              (# q, r #) -> (# q -# 1#, r +# y# -# 1# #)
+ | otherwise                = x# `quotRemInt#` y#
+
 {-# RULES
 "x# +# 0#" forall x#. x# +# 0# = x#
 "0# +# x#" forall x#. 0# +# x# = x#
diff --git a/GHC/Int.hs b/GHC/Int.hs
index bcf2a7d..7182cba 100644
--- a/GHC/Int.hs
+++ b/GHC/Int.hs
@@ -113,8 +113,10 @@ instance Integral Int8 where
         | y == 0                     = divZeroError
           -- Note [Order of tests]
         | y == (-1) && x == minBound = (overflowError, 0)
-        | otherwise                  = (I8# (narrow8Int# (x# `divInt#` y#)),
-                                       I8# (narrow8Int# (x# `modInt#` y#)))
+        | otherwise                  = case x# `divModInt#` y# of
+                                       (# d, m #) ->
+                                           (I8# (narrow8Int# d),
+                                            I8# (narrow8Int# m))
     toInteger (I8# x#)               = smallInteger x#
 
 instance Bounded Int8 where
@@ -266,8 +268,10 @@ instance Integral Int16 where
         | y == 0                     = divZeroError
           -- Note [Order of tests]
         | y == (-1) && x == minBound = (overflowError, 0)
-        | otherwise                  = (I16# (narrow16Int# (x# `divInt#` y#)),
-                                        I16# (narrow16Int# (x# `modInt#` y#)))
+        | otherwise                  = case x# `divModInt#` y# of
+                                       (# d, m #) ->
+                                           (I16# (narrow16Int# d),
+                                            I16# (narrow16Int# m))
     toInteger (I16# x#)              = smallInteger x#
 
 instance Bounded Int16 where
@@ -433,8 +437,10 @@ instance Integral Int32 where
         | y == 0                     = divZeroError
           -- Note [Order of tests]
         | y == (-1) && x == minBound = (overflowError, 0)
-        | otherwise                  = (I32# (narrow32Int# (x# `divInt#` y#)),
-                                     I32# (narrow32Int# (x# `modInt#` y#)))
+        | otherwise                  = case x# `divModInt#` y# of
+                                       (# d, m #) ->
+                                           (I32# (narrow32Int# d),
+                                            I32# (narrow32Int# m))
     toInteger (I32# x#)              = smallInteger x#
 
 instance Read Int32 where
@@ -760,7 +766,9 @@ instance Integral Int64 where
         | y == 0                     = divZeroError
           -- Note [Order of tests]
         | y == (-1) && x == minBound = (overflowError, 0)
-        | otherwise                  = (I64# (x# `divInt#` y#), I64# (x# 
`modInt#` y#))
+        | otherwise                  = case x# `divModInt#` y# of
+                                       (# d, m #) ->
+                                           (I64# d, I64# m)
     toInteger (I64# x#)              = smallInteger x#
 
 instance Read Int64 where
diff --git a/GHC/Num.lhs b/GHC/Num.lhs
index 644b8f4..5dc8ee9 100644
--- a/GHC/Num.lhs
+++ b/GHC/Num.lhs
@@ -95,10 +95,6 @@ instance  Num Int  where
 
     {-# INLINE fromInteger #-}  -- Just to be sure!
     fromInteger i = I# (integerToInt i)
-
-divModInt ::  Int -> Int -> (Int, Int)
-divModInt x@(I# _) y@(I# _) = (x `divInt` y, x `modInt` y)
-    -- Stricter.  Sorry if you don't like it.  (WDP 94/10)
 \end{code}
 
 %*********************************************************



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to