summaryrefslogtreecommitdiff
path: root/ghc/compiler/hsSyn/HsLit.lhs
diff options
context:
space:
mode:
Diffstat (limited to 'ghc/compiler/hsSyn/HsLit.lhs')
-rw-r--r--ghc/compiler/hsSyn/HsLit.lhs60
1 files changed, 60 insertions, 0 deletions
diff --git a/ghc/compiler/hsSyn/HsLit.lhs b/ghc/compiler/hsSyn/HsLit.lhs
new file mode 100644
index 0000000000..f18cde5a67
--- /dev/null
+++ b/ghc/compiler/hsSyn/HsLit.lhs
@@ -0,0 +1,60 @@
+%
+% (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
+%
+\section[HsLit]{Abstract syntax: source-language literals}
+
+\begin{code}
+#include "HsVersions.h"
+
+module HsLit where
+
+import Ubiq{-uitous-}
+
+import Pretty
+\end{code}
+
+\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}
+
+\begin{code}
+negLiteral (HsInt i) = HsInt (-i)
+negLiteral (HsFrac f) = HsFrac (-f)
+\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 "''"]
+\end{code}