[project @ 2003-12-10 14:15:16 by simonmar]
[ghc-hetmet.git] / ghc / compiler / hsSyn / HsLit.lhs
index e0f7364..9840647 100644 (file)
@@ -1,61 +1,92 @@
 %
-% (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 HsTypes ( SyntaxName )
+import Outputable
+import FastString
+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         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  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
 
-\begin{code}
-negLiteral (HsInt  i) = HsInt  (-i)
-negLiteral (HsFrac f) = HsFrac (-f)
+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
+  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
+
+-- 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
+  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 '#'
+
+instance Outputable HsOverLit where
+  ppr (HsIntegral i _)   = integer i
+  ppr (HsFractional f _) = rational f
 \end{code}