[project @ 1998-12-02 13:17:09 by simonm]
[ghc-hetmet.git] / ghc / compiler / hsSyn / HsBasic.lhs
index 114721a..d2721ae 100644 (file)
@@ -1,27 +1,15 @@
 %
-% (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 HsBasic where
 
-IMP_Ubiq(){-uitous-}
-IMPORT_1_3(Ratio(Rational))
-
-import Pretty
-\end{code}
-
-%************************************************************************
-%*                                                                     *
-\subsection[Version]{Module and identifier version numbers}
-%*                                                                     *
-%************************************************************************
+#include "HsVersions.h"
 
-\begin{code}
-type Version = Int
+import Outputable
+import Ratio   ( Rational )
 \end{code}
 
 %************************************************************************
@@ -56,8 +44,11 @@ data HsLit
                                -- 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)
@@ -65,38 +56,17 @@ negLiteral (HsFrac f) = HsFrac (-f)
 
 \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)      = text (show c)
+    ppr (HsCharPrim c)  = text (show c) <> char '#'
+    ppr (HsStringPrim s) = pprFSAsString s <> char '#'
+    ppr (HsString s)    = pprFSAsString s
+    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}
 
-%************************************************************************
-%*                                                                     *
-\subsection[Fixity]{Fixity info}
-%*                                                                     *
-%************************************************************************
-
-\begin{code}
-data Fixity = Fixity Int FixityDirection
-data FixityDirection = InfixL | InfixR | InfixN 
-                    deriving(Eq)
-
-instance Outputable Fixity where
-    ppr sty (Fixity prec dir) = ppBesides [ppr sty dir, ppSP, ppInt prec]
-
-instance Outputable FixityDirection where
-    ppr sty InfixL = ppStr "infixl"
-    ppr sty InfixR = ppStr "infixr"
-    ppr sty InfixN = ppStr "infix"
-
-instance Eq Fixity where               -- Used to determine if two fixities conflict
-  (Fixity p1 dir1) == (Fixity p2 dir2) = p1==p2 && dir1 == dir2
-\end{code}