[project @ 2000-09-22 16:00:08 by simonpj]
authorsimonpj <unknown>
Fri, 22 Sep 2000 16:00:08 +0000 (16:00 +0000)
committersimonpj <unknown>
Fri, 22 Sep 2000 16:00:08 +0000 (16:00 +0000)
Forgot to remove HsBasic and add HsLit

ghc/compiler/hsSyn/HsBasic.lhs [deleted file]
ghc/compiler/hsSyn/HsLit.lhs [new file with mode: 0644]

diff --git a/ghc/compiler/hsSyn/HsBasic.lhs b/ghc/compiler/hsSyn/HsBasic.lhs
deleted file mode 100644 (file)
index 11558f7..0000000
+++ /dev/null
@@ -1,72 +0,0 @@
-%
-% (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
-%
-\section[HsLit]{Abstract syntax: source-language literals}
-
-\begin{code}
-module HsBasic where
-
-#include "HsVersions.h"
-
-import Outputable
-import Ratio   ( Rational )
-\end{code}
-
-%************************************************************************
-%*                                                                     *
-\subsection[HsLit]{Literals}
-%*                                                                     *
-%************************************************************************
-
-
-\begin{code}
-data HsLit
-  = HsChar         Int         -- characters
-  | HsCharPrim     Int         -- 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)
-       deriving Eq
-\end{code}
-
-ToDo: an improved Eq instance JJQC 30-Nov-1997
-
-\begin{code}
-negLiteral (HsInt  i) = HsInt  (-i)
-negLiteral (HsFrac f) = HsFrac (-f)
-\end{code}
-
-\begin{code}
-instance Outputable HsLit where
-       -- 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 (HsFrac 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 "''"]
-\end{code}
-
-
diff --git a/ghc/compiler/hsSyn/HsLit.lhs b/ghc/compiler/hsSyn/HsLit.lhs
new file mode 100644 (file)
index 0000000..f75c0a7
--- /dev/null
@@ -0,0 +1,81 @@
+%
+% (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
+%
+\section[HsLit]{Abstract syntax: source-language literals}
+
+\begin{code}
+module HsLit where
+
+#include "HsVersions.h"
+
+import Type    ( Type )        
+import Outputable
+import Ratio   ( Rational )
+\end{code}
+
+
+%************************************************************************
+%*                                                                     *
+\subsection[HsLit]{Literals}
+%*                                                                     *
+%************************************************************************
+
+
+\begin{code}
+data HsLit
+  = 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 )
+
+data HsOverLit name    -- An overloaded literal
+  = HsIntegral     Integer name        -- Integer-looking literals;
+                                       -- The names is "fromInteger"
+  | HsFractional    Rational name      -- Frac-looking literals
+                                       -- The name is "fromRational"
+
+instance Eq (HsOverLit name) where
+  (HsIntegral i1 _)   == (HsIntegral i2 _)   = i1 == i2
+  (HsFractional f1 _) == (HsFractional f2 _) = f1 == f2
+
+instance Ord (HsOverLit name) 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
+       -- 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 name) where
+  ppr (HsIntegral i _)   = integer i
+  ppr (HsFractional f _) = rational f
+\end{code}
+
+