Record the original text along with parsed Rationals: fixes #2245
[ghc-hetmet.git] / compiler / hsSyn / HsLit.lhs
index c29083c..def1e35 100644 (file)
@@ -12,7 +12,8 @@ module HsLit where
 #include "HsVersions.h"
 
 import {-# SOURCE #-} HsExpr( SyntaxExpr, pprExpr )
 #include "HsVersions.h"
 
 import {-# SOURCE #-} HsExpr( SyntaxExpr, pprExpr )
-import HsTypes (PostTcType)
+import BasicTypes ( FractionalLit(..) )
+import HsTypes  ( PostTcType )
 import Type    ( Type )
 import Outputable
 import FastString
 import Type    ( Type )
 import Outputable
 import FastString
@@ -63,14 +64,14 @@ instance Eq HsLit where
 data HsOverLit id      -- An overloaded literal
   = OverLit {
        ol_val :: OverLitVal, 
 data HsOverLit id      -- An overloaded literal
   = OverLit {
        ol_val :: OverLitVal, 
-       ol_rebindable :: Bool,          -- 
+       ol_rebindable :: Bool,          -- Note [ol_rebindable]
        ol_witness :: SyntaxExpr id,    -- Note [Overloaded literal witnesses]
        ol_type :: PostTcType }
   deriving (Data, Typeable)
 
 data OverLitVal
   = HsIntegral   !Integer      -- Integer-looking literals;
        ol_witness :: SyntaxExpr id,    -- Note [Overloaded literal witnesses]
        ol_type :: PostTcType }
   deriving (Data, Typeable)
 
 data OverLitVal
   = HsIntegral   !Integer      -- Integer-looking literals;
-  | HsFractional !Rational     -- Frac-looking literals
+  | HsFractional !FractionalLit        -- Frac-looking literals
   | HsIsString   !FastString   -- String-looking literals
   deriving (Data, Typeable)
 
   | HsIsString   !FastString   -- String-looking literals
   deriving (Data, Typeable)
 
@@ -101,7 +102,7 @@ This witness should replace the literal.
 
 This dual role is unusual, because we're replacing 'fromInteger' with 
 a call to fromInteger.  Reason: it allows commoning up of the fromInteger
 
 This dual role is unusual, because we're replacing 'fromInteger' with 
 a call to fromInteger.  Reason: it allows commoning up of the fromInteger
-calls, which wouldn't be possible if the desguarar made the application
+calls, which wouldn't be possible if the desguarar made the application.
 
 The PostTcType in each branch records the type the overload literal is
 found to have.
 
 The PostTcType in each branch records the type the overload literal is
 found to have.
@@ -155,6 +156,6 @@ instance OutputableBndr id => Outputable (HsOverLit id) where
 
 instance Outputable OverLitVal where
   ppr (HsIntegral i)   = integer i 
 
 instance Outputable OverLitVal where
   ppr (HsIntegral i)   = integer i 
-  ppr (HsFractional f) = rational f
+  ppr (HsFractional f) = text (fl_text f)
   ppr (HsIsString s)   = pprHsString s
 \end{code}
   ppr (HsIsString s)   = pprHsString s
 \end{code}