X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2FhsSyn%2FHsLit.lhs;h=c6d7e5dbeaf1b96222e2907cc1a598c36a219772;hb=4dd415e9d8e564ca09937042b5c5605f7f2991c9;hp=03dd717c6e64056f9479964f23c54c373024827a;hpb=f3d24c87016078e0e50fa80575e04f340f86acb4;p=ghc-hetmet.git diff --git a/ghc/compiler/hsSyn/HsLit.lhs b/ghc/compiler/hsSyn/HsLit.lhs index 03dd717..c6d7e5d 100644 --- a/ghc/compiler/hsSyn/HsLit.lhs +++ b/ghc/compiler/hsSyn/HsLit.lhs @@ -8,8 +8,8 @@ module HsLit where #include "HsVersions.h" +import {-# SOURCE #-} HsExpr( SyntaxExpr ) import Type ( Type ) -import HsTypes ( SyntaxName, PostTcType ) import Outputable import FastString import Ratio ( Rational ) @@ -25,22 +25,19 @@ import Ratio ( Rational ) \begin{code} data HsLit - = HsChar Int -- Character - | HsCharPrim Int -- Unboxed character + = 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 -- Genuinely an integer; arises only from TRANSLATION + | 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 - | HsLitLit FastString PostTcType -- 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 instance Eq HsLit where (HsChar x1) == (HsChar x2) = x1==x2 @@ -49,24 +46,30 @@ instance Eq HsLit where (HsStringPrim x1) == (HsStringPrim x2) = x1==x2 (HsInt x1) == (HsInt x2) = x1==x2 (HsIntPrim x1) == (HsIntPrim x2) = x1==x2 - (HsInteger x1) == (HsInteger 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 - (HsLitLit x1 _) == (HsLitLit 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 +data HsOverLit id -- An overloaded literal + = HsIntegral Integer (SyntaxExpr id) -- Integer-looking literals; + | HsFractional Rational (SyntaxExpr id) -- Frac-looking literals + -- Before type checking, the SyntaxExpr is 'fromInteger' or 'fromRational' + -- After type checking, it is (fromInteger 3) or lit_78; that is, + -- the expression that should replace the literal. + -- This is unusual, because we're replacing 'fromInteger' with a call + -- to fromInteger. Reason: it allows commoning up of the fromInteger + -- calls, which wouldn't be possible if the desguarar made the application -instance Eq HsOverLit where +-- Comparison operations are needed when grouping literals +-- for compiling pattern-matching (module MatchLit) +instance Eq (HsOverLit id) where (HsIntegral i1 _) == (HsIntegral i2 _) = i1 == i2 (HsFractional f1 _) == (HsFractional f2 _) = f1 == f2 + l1 == l2 = False -instance Ord HsOverLit where +instance Ord (HsOverLit id) where compare (HsIntegral i1 _) (HsIntegral i2 _) = i1 `compare` i2 compare (HsIntegral _ _) (HsFractional _ _) = LT compare (HsFractional f1 _) (HsFractional f2 _) = f1 `compare` f2 @@ -81,16 +84,13 @@ instance Outputable HsLit where ppr (HsString s) = pprHsString s ppr (HsStringPrim s) = pprHsString s <> char '#' ppr (HsInt i) = integer i - ppr (HsInteger 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 "``", ftext s, text "''"] -instance Outputable HsOverLit where +instance Outputable (HsOverLit id) where ppr (HsIntegral i _) = integer i ppr (HsFractional f _) = rational f \end{code} - -