[project @ 2002-11-06 13:10:46 by simonpj]
[ghc-hetmet.git] / ghc / compiler / hsSyn / HsLit.lhs
index 7111cbd..03dd717 100644 (file)
@@ -8,8 +8,10 @@ module HsLit where
 
 #include "HsVersions.h"
 
-import Type    ( Type )        
+import Type    ( Type )
+import HsTypes ( SyntaxName, PostTcType )
 import Outputable
+import FastString
 import Ratio   ( Rational )
 \end{code}
 
@@ -25,8 +27,8 @@ import Ratio  ( Rational )
 data HsLit
   = HsChar         Int                 -- Character
   | HsCharPrim     Int                 -- Unboxed character
-  | HsString       FAST_STRING         -- String
-  | HsStringPrim    FAST_STRING                -- Packed string
+  | HsString       FastString          -- String
+  | HsStringPrim    FastString         -- Packed string
   | HsInt          Integer             -- Genuinely an Int; arises from TcGenDeriv, 
                                        --      and from TRANSLATION
   | HsIntPrim      Integer             -- Unboxed Int
@@ -34,26 +36,41 @@ data HsLit
   | HsRat          Rational Type       -- Genuinely a rational; arises only from TRANSLATION
   | HsFloatPrim            Rational            -- Unboxed Float
   | HsDoublePrim    Rational           -- Unboxed Double
-  | HsLitLit       FAST_STRING Type    -- to pass ``literal literals'' through to C
-                                       -- also: "overloaded" type; but
-                                       -- must resolve to boxed-primitive!
+  | HsLitLit       FastString PostTcType       -- to pass ``literal literals'' through to C
+                                               -- also: "overloaded" type; but
+                                               -- must resolve to boxed-primitive!
        -- The Type in HsLitLit is needed when desuaring;
        -- before the typechecker it's just an error value
-  deriving( Eq )
 
-data HsOverLit                 -- An overloaded literal
-  = HsIntegral     Integer             -- Integer-looking literals;
-  | HsFractional    Rational           -- Frac-looking literals
+instance Eq HsLit where
+  (HsChar x1)      == (HsChar x2)       = x1==x2
+  (HsCharPrim x1)   == (HsCharPrim x2)  = x1==x2
+  (HsString x1)     == (HsString x2)    = x1==x2
+  (HsStringPrim x1) == (HsStringPrim x2) = x1==x2
+  (HsInt x1)       == (HsInt x2)        = x1==x2
+  (HsIntPrim x1)    == (HsIntPrim x2)    = x1==x2
+  (HsInteger x1)    == (HsInteger x2)    = x1==x2
+  (HsRat x1 _)     == (HsRat x2 _)      = x1==x2
+  (HsFloatPrim x1)  == (HsFloatPrim x2)  = x1==x2
+  (HsDoublePrim x1) == (HsDoublePrim x2) = x1==x2
+  (HsLitLit x1 _)   == (HsLitLit x2 _)   = x1==x2
+  lit1             == lit2              = False
+
+data HsOverLit                         -- An overloaded literal
+  = HsIntegral     Integer  SyntaxName -- Integer-looking literals;
+                                       -- The name is fromInteger
+  | HsFractional    Rational SyntaxName        -- Frac-looking literals
+                                       -- The name is fromRational
 
 instance Eq HsOverLit where
-  (HsIntegral i1)   == (HsIntegral i2)   = i1 == i2
-  (HsFractional f1) == (HsFractional f2) = f1 == f2
+  (HsIntegral i1 _)   == (HsIntegral i2 _)   = i1 == i2
+  (HsFractional f1 _) == (HsFractional f2 _) = f1 == f2
 
 instance Ord HsOverLit where
-  compare (HsIntegral i1)   (HsIntegral i2)   = i1 `compare` i2
-  compare (HsIntegral _)    (HsFractional _)  = LT
-  compare (HsFractional f1) (HsFractional f2) = f1 `compare` f2
-  compare (HsFractional f1) (HsIntegral _)    = GT
+  compare (HsIntegral i1 _)   (HsIntegral i2 _)   = i1 `compare` i2
+  compare (HsIntegral _ _)    (HsFractional _ _)  = LT
+  compare (HsFractional f1 _) (HsFractional f2 _) = f1 `compare` f2
+  compare (HsFractional f1 _) (HsIntegral _ _)    = GT
 \end{code}
 
 \begin{code}
@@ -69,11 +86,11 @@ instance Outputable HsLit where
     ppr (HsFloatPrim f)         = rational f <> char '#'
     ppr (HsDoublePrim d) = rational d <> text "##"
     ppr (HsIntPrim i)   = integer i  <> char '#'
-    ppr (HsLitLit s _)  = hcat [text "``", ptext s, text "''"]
+    ppr (HsLitLit s _)  = hcat [text "``", ftext s, text "''"]
 
 instance Outputable HsOverLit where
-  ppr (HsIntegral i)   = integer i
-  ppr (HsFractional f) = rational f
+  ppr (HsIntegral i _)   = integer i
+  ppr (HsFractional f _) = rational f
 \end{code}