[project @ 2001-05-23 09:59:18 by simonmar]
[ghc-hetmet.git] / ghc / compiler / hsSyn / HsLit.lhs
index e0f7364..7111cbd 100644 (file)
@@ -1,61 +1,79 @@
 %
-% (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
+% (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
 %
 \section[HsLit]{Abstract syntax: source-language literals}
 
 \begin{code}
-#include "HsVersions.h"
-
 module HsLit where
 
-IMP_Ubiq(){-uitous-}
-IMPORT_1_3(Ratio(Rational))
+#include "HsVersions.h"
 
-import Pretty
+import Type    ( Type )        
+import Outputable
+import Ratio   ( Rational )
 \end{code}
 
+
+%************************************************************************
+%*                                                                     *
+\subsection[HsLit]{Literals}
+%*                                                                     *
+%************************************************************************
+
+
 \begin{code}
 data HsLit
-  = HsChar         Char        -- characters
-  | HsCharPrim     Char        -- unboxed char literals
-  | HsString       FAST_STRING -- strings
-  | HsStringPrim    FAST_STRING        -- packed string
-
-  | HsInt          Integer     -- integer-looking literals
-  | HsFrac         Rational    -- frac-looking literals
-       -- Up through dict-simplification, HsInt and HsFrac simply
-       -- mean the literal was integral- or fractional-looking; i.e.,
-       -- whether it had an explicit decimal-point in it.  *After*
-       -- dict-simplification, they mean (boxed) "Integer" and
-       -- "Rational" [Ratio Integer], respectively.
-
-       -- Dict-simplification tries to replace such lits w/ more
-       -- specific ones, using the unboxed variants that follow...
-  | HsIntPrim      Integer     -- unboxed Int literals
-  | HsFloatPrim            Rational    -- unboxed Float literals
-  | HsDoublePrim    Rational   -- unboxed Double literals
-
-  | HsLitLit       FAST_STRING -- to pass ``literal literals'' through to C
-                               -- also: "overloaded" type; but
-                               -- must resolve to boxed-primitive!
-                               -- (WDP 94/10)
-\end{code}
+  = HsChar         Int                 -- Character
+  | HsCharPrim     Int                 -- Unboxed character
+  | HsString       FAST_STRING         -- String
+  | HsStringPrim    FAST_STRING                -- 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
+  | 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!
+       -- The Type in HsLitLit is needed when desuaring;
+       -- before the typechecker it's just an error value
+  deriving( Eq )
 
-\begin{code}
-negLiteral (HsInt  i) = HsInt  (-i)
-negLiteral (HsFrac f) = HsFrac (-f)
+data HsOverLit                 -- An overloaded literal
+  = HsIntegral     Integer             -- Integer-looking literals;
+  | HsFractional    Rational           -- Frac-looking literals
+
+instance Eq HsOverLit where
+  (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
 \end{code}
 
 \begin{code}
 instance Outputable HsLit where
-    ppr sty (HsChar c)         = ppStr (show c)
-    ppr sty (HsCharPrim c)     = ppBeside (ppStr (show c)) (ppChar '#')
-    ppr sty (HsString s)       = ppStr (show s)
-    ppr sty (HsStringPrim s)   = ppBeside (ppStr (show s)) (ppChar '#')
-    ppr sty (HsInt i)          = ppInteger i
-    ppr sty (HsFrac f)         = ppRational f
-    ppr sty (HsFloatPrim f)    = ppBeside (ppRational f) (ppChar '#')
-    ppr sty (HsDoublePrim d)   = ppBeside (ppRational d) (ppStr "##")
-    ppr sty (HsIntPrim i)      = ppBeside (ppInteger i) (ppChar '#')
-    ppr sty (HsLitLit s)       = ppBesides [ppStr "``", ppPStr s, ppStr "''"]
+       -- Use "show" because it puts in appropriate escapes
+    ppr (HsChar c)      = pprHsChar c
+    ppr (HsCharPrim c)  = pprHsChar c <> char '#'
+    ppr (HsString s)    = pprHsString s
+    ppr (HsStringPrim s) = pprHsString s <> char '#'
+    ppr (HsInt 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 "``", ptext s, text "''"]
+
+instance Outputable HsOverLit where
+  ppr (HsIntegral i)   = integer i
+  ppr (HsFractional f) = rational f
 \end{code}
+
+