Repository : ssh://darcs.haskell.org//srv/darcs/packages/integer-gmp

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/2d9b4cbe7ce5ebeb7c3e269ddc848090f1a7b88d

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

commit 2d9b4cbe7ce5ebeb7c3e269ddc848090f1a7b88d
Author: Ian Lynagh <[email protected]>
Date:   Wed Jul 18 15:34:18 2012 +0100

    Simplify how gcd @ Int is implemented

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

 GHC/Integer/GMP/Internals.hs |    3 ++-
 GHC/Integer/Type.lhs         |   10 ----------
 2 files changed, 2 insertions(+), 11 deletions(-)

diff --git a/GHC/Integer/GMP/Internals.hs b/GHC/Integer/GMP/Internals.hs
index d1c1df4..4ad1f62 100644
--- a/GHC/Integer/GMP/Internals.hs
+++ b/GHC/Integer/GMP/Internals.hs
@@ -1,6 +1,7 @@
 {-# LANGUAGE NoImplicitPrelude #-}
 
-module GHC.Integer.GMP.Internals (Integer(..), gcdInteger, lcmInteger) where
+module GHC.Integer.GMP.Internals (Integer(..), gcdInt, gcdInteger, lcmInteger)
+    where
 
 import GHC.Integer.Type
 
diff --git a/GHC/Integer/Type.lhs b/GHC/Integer/Type.lhs
index 5189b25..464deb6 100644
--- a/GHC/Integer/Type.lhs
+++ b/GHC/Integer/Type.lhs
@@ -272,16 +272,6 @@ lcmInteger a b =      if a `eqInteger` S# 0# then S# 0#
   where aa = absInteger a
         ab = absInteger b
 
--- This rule needs to use absInteger so that it works correctly when
--- the result is minBound :: Int. But that isn't necessary when the
--- result is converted to an Int.
-{-# RULES
-"gcdInteger/Int" forall a b.
-    gcdInteger (smallInteger a) (smallInteger b)
-        = absInteger (smallInteger (gcdInt a b))
-"integerToInt/gcdInteger/Int" forall a b.
-    integerToInt (gcdInteger (smallInteger a) (smallInteger b)) = gcdInt a b
-  #-}
 gcdInt :: Int# -> Int# -> Int#
 gcdInt 0# y  = absInt y
 gcdInt x  0# = absInt x



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

Reply via email to