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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/56ef866b701b6432931c844cc73ba03052168c44

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

commit 56ef866b701b6432931c844cc73ba03052168c44
Author: John Lato <[email protected]>
Date:   Mon Oct 8 17:29:43 2012 +0800

    move fromRational into rationalToFloat/Double

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

 GHC/Float.lhs |   54 ++++++++++++++++++++++++++++++++----------------------
 1 files changed, 32 insertions(+), 22 deletions(-)

diff --git a/GHC/Float.lhs b/GHC/Float.lhs
index 025b4f1..66318d4 100644
--- a/GHC/Float.lhs
+++ b/GHC/Float.lhs
@@ -230,19 +230,24 @@ instance  Real Float  where
 
 instance  Fractional Float  where
     (/) x y             =  divideFloat x y
-    fromRational (n:%0)
-        | n == 0        = 0/0
-        | n < 0         = (-1)/0
-        | otherwise     = 1/0
-    fromRational (n:%d)
-        | n == 0        = encodeFloat 0 0
-        | n < 0         = -(fromRat'' minEx mantDigs (-n) d)
-        | otherwise     = fromRat'' minEx mantDigs n d
-          where
-            minEx       = FLT_MIN_EXP
-            mantDigs    = FLT_MANT_DIG
+    {-# INLINE fromRational #-}
+    fromRational (n:%d) = rationalToFloat n d
     recip x             =  1.0 / x
 
+rationalToFloat :: Integer -> Integer -> Float
+{-# NOINLINE [1] rationalToFloat #-}
+rationalToFloat n 0
+    | n == 0        = 0/0
+    | n < 0         = (-1)/0
+    | otherwise     = 1/0
+rationalToFloat n d
+    | n == 0        = encodeFloat 0 0
+    | n < 0         = -(fromRat'' minEx mantDigs (-n) d)
+    | otherwise     = fromRat'' minEx mantDigs n d
+      where
+        minEx       = FLT_MIN_EXP
+        mantDigs    = FLT_MANT_DIG
+
 -- RULES for Integer and Int
 {-# RULES
 "properFraction/Float->Integer"     properFraction = properFractionFloatInteger
@@ -391,19 +396,24 @@ instance  Real Double  where
 
 instance  Fractional Double  where
     (/) x y             =  divideDouble x y
-    fromRational (n:%0)
-        | n == 0        = 0/0
-        | n < 0         = (-1)/0
-        | otherwise     = 1/0
-    fromRational (n:%d)
-        | n == 0        = encodeFloat 0 0
-        | n < 0         = -(fromRat'' minEx mantDigs (-n) d)
-        | otherwise     = fromRat'' minEx mantDigs n d
-          where
-            minEx       = DBL_MIN_EXP
-            mantDigs    = DBL_MANT_DIG
+    {-# INLINE fromRational #-}
+    fromRational (n:%d) = rationalToDouble n d
     recip x             =  1.0 / x
 
+rationalToDouble :: Integer -> Integer -> Double
+{-# NOINLINE [1] rationalToDouble #-}
+rationalToDouble n 0
+    | n == 0        = 0/0
+    | n < 0         = (-1)/0
+    | otherwise     = 1/0
+rationalToDouble n d
+    | n == 0        = encodeFloat 0 0
+    | n < 0         = -(fromRat'' minEx mantDigs (-n) d)
+    | otherwise     = fromRat'' minEx mantDigs n d
+      where
+        minEx       = DBL_MIN_EXP
+        mantDigs    = DBL_MANT_DIG
+
 instance  Floating Double  where
     pi                  =  3.141592653589793238
     exp x               =  expDouble x



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

Reply via email to