X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2FhsSyn%2FHsLit.lhs;h=f75c0a7ab2d5c470a7c1379e375c3add48e9d133;hb=57b80ee588047a212a21d7a583d44e369c671ed8;hp=f18cde5a67d609eeb36b6cf07563fd59fbe9c37d;hpb=6c381e873e222417d9a67aeec77b9555eca7b7a8;p=ghc-hetmet.git diff --git a/ghc/compiler/hsSyn/HsLit.lhs b/ghc/compiler/hsSyn/HsLit.lhs index f18cde5..f75c0a7 100644 --- a/ghc/compiler/hsSyn/HsLit.lhs +++ b/ghc/compiler/hsSyn/HsLit.lhs @@ -1,60 +1,81 @@ % -% (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 -import Ubiq{-uitous-} +#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 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 - 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 name) where + ppr (HsIntegral i _) = integer i + ppr (HsFractional f _) = rational f \end{code} + +