Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/3d886b2db7e6ade5622feb3f00f4bcc9ed0d8bbb

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

commit 3d886b2db7e6ade5622feb3f00f4bcc9ed0d8bbb
Author: David Terei <[email protected]>
Date:   Wed Aug 24 18:32:06 2011 -0700

    Use double method, not the hacked rational method.

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

 compiler/basicTypes/Literal.lhs |    7 ++++---
 compiler/cmm/PprCmmExpr.hs      |    3 ++-
 2 files changed, 6 insertions(+), 4 deletions(-)

diff --git a/compiler/basicTypes/Literal.lhs b/compiler/basicTypes/Literal.lhs
index da8685e..b25c60f 100644
--- a/compiler/basicTypes/Literal.lhs
+++ b/compiler/basicTypes/Literal.lhs
@@ -59,7 +59,8 @@ import Data.Int
 import Data.Ratio
 import Data.Word
 import Data.Char
-import Data.Data( Data, Typeable )
+import Data.Data ( Data, Typeable )
+import Numeric ( fromRat )
 \end{code}
 
 
@@ -390,8 +391,8 @@ pprLit (MachInt i)          = pprIntVal i
 pprLit (MachInt64 i)   = ptext (sLit "__int64") <+> integer i
 pprLit (MachWord w)    = ptext (sLit "__word") <+> integer w
 pprLit (MachWord64 w)  = ptext (sLit "__word64") <+> integer w
-pprLit (MachFloat f)   = ptext (sLit "__float") <+> rational f
-pprLit (MachDouble d)  = rational d
+pprLit (MachFloat f)   = ptext (sLit "__float") <+> float (fromRat f)
+pprLit (MachDouble d)  = double (fromRat d)
 pprLit (MachNullAddr)  = ptext (sLit "__NULL")
 pprLit (MachLabel l mb fod) = ptext (sLit "__label") <+> b <+> ppr fod
     where b = case mb of
diff --git a/compiler/cmm/PprCmmExpr.hs b/compiler/cmm/PprCmmExpr.hs
index 0614e8e..7630345 100644
--- a/compiler/cmm/PprCmmExpr.hs
+++ b/compiler/cmm/PprCmmExpr.hs
@@ -45,6 +45,7 @@ import Outputable
 import FastString
 
 import Data.Maybe
+import Numeric ( fromRat )
 
 -----------------------------------------------------------------------------
 
@@ -191,7 +192,7 @@ pprLit lit = case lit of
              , ppUnless (rep == wordWidth) $
                space <> dcolon <+> ppr rep ]
 
-    CmmFloat f rep     -> hsep [ rational f, dcolon, ppr rep ]
+    CmmFloat f rep     -> hsep [ double (fromRat f), dcolon, ppr rep ]
     CmmLabel clbl      -> pprCLabel clbl
     CmmLabelOff clbl i -> pprCLabel clbl <> ppr_offset i
     CmmLabelDiffOff clbl1 clbl2 i -> pprCLabel clbl1 <> char '-'  



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

Reply via email to