[project @ 2003-12-10 14:15:16 by simonmar]
[ghc-hetmet.git] / ghc / compiler / hsSyn / HsLit.lhs
index 03dd717..9840647 100644 (file)
@@ -9,7 +9,7 @@ module HsLit where
 #include "HsVersions.h"
 
 import Type    ( Type )
-import HsTypes ( SyntaxName, PostTcType )
+import HsTypes ( SyntaxName )
 import Outputable
 import FastString
 import Ratio   ( Rational )
@@ -25,22 +25,19 @@ import Ratio        ( Rational )
 
 \begin{code}
 data HsLit
-  = HsChar         Int                 -- Character
-  | HsCharPrim     Int                 -- Unboxed character
+  = HsChar         Char                -- Character
+  | HsCharPrim     Char                -- Unboxed character
   | HsString       FastString          -- String
   | HsStringPrim    FastString         -- Packed string
   | HsInt          Integer             -- Genuinely an Int; arises from TcGenDeriv, 
                                        --      and from TRANSLATION
   | HsIntPrim      Integer             -- Unboxed Int
-  | HsInteger      Integer             -- Genuinely an integer; arises only from TRANSLATION
+  | HsInteger      Integer  Type       -- Genuinely an integer; arises only from TRANSLATION
+                                       --      (overloaded literals are done with HsOverLit)
   | HsRat          Rational Type       -- Genuinely a rational; arises only from TRANSLATION
+                                       --      (overloaded literals are done with HsOverLit)
   | HsFloatPrim            Rational            -- Unboxed Float
   | HsDoublePrim    Rational           -- Unboxed Double
-  | 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
 
 instance Eq HsLit where
   (HsChar x1)      == (HsChar x2)       = x1==x2
@@ -49,11 +46,10 @@ instance Eq HsLit where
   (HsStringPrim x1) == (HsStringPrim x2) = x1==x2
   (HsInt x1)       == (HsInt x2)        = x1==x2
   (HsIntPrim x1)    == (HsIntPrim x2)    = x1==x2
-  (HsInteger x1)    == (HsInteger 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
@@ -62,9 +58,12 @@ data HsOverLit                       -- An overloaded literal
   | HsFractional    Rational SyntaxName        -- Frac-looking literals
                                        -- The name is fromRational
 
+-- Comparison operations are needed when grouping literals
+-- for compiling pattern-matching (module MatchLit)
 instance Eq HsOverLit where
   (HsIntegral i1 _)   == (HsIntegral i2 _)   = i1 == i2
   (HsFractional f1 _) == (HsFractional f2 _) = f1 == f2
+  l1                 == l2                  = False
 
 instance Ord HsOverLit where
   compare (HsIntegral i1 _)   (HsIntegral i2 _)   = i1 `compare` i2
@@ -81,16 +80,13 @@ instance Outputable HsLit where
     ppr (HsString s)    = pprHsString s
     ppr (HsStringPrim s) = pprHsString s <> char '#'
     ppr (HsInt i)       = integer i
-    ppr (HsInteger i)   = integer i
+    ppr (HsInteger i _)         = integer i
     ppr (HsRat f _)     = rational f
     ppr (HsFloatPrim f)         = rational f <> char '#'
     ppr (HsDoublePrim d) = rational d <> text "##"
     ppr (HsIntPrim i)   = integer i  <> char '#'
-    ppr (HsLitLit s _)  = hcat [text "``", ftext s, text "''"]
 
 instance Outputable HsOverLit where
   ppr (HsIntegral i _)   = integer i
   ppr (HsFractional f _) = rational f
 \end{code}
-
-