X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2FhsSyn%2FHsLit.lhs;h=def1e352db337d5fec2321d870310577ef886c04;hp=bd125106e2d0e1c7177021d52d1a333bb050b5b0;hb=3391a03562d4056de7b16cd0f632e6c43ae44cca;hpb=ecdaf6bc29d23bd704df8c65442ee08032a585fc diff --git a/compiler/hsSyn/HsLit.lhs b/compiler/hsSyn/HsLit.lhs index bd12510..def1e35 100644 --- a/compiler/hsSyn/HsLit.lhs +++ b/compiler/hsSyn/HsLit.lhs @@ -5,16 +5,20 @@ \section[HsLit]{Abstract syntax: source-language literals} \begin{code} +{-# LANGUAGE DeriveDataTypeable #-} + module HsLit where #include "HsVersions.h" import {-# SOURCE #-} HsExpr( SyntaxExpr, pprExpr ) -import HsTypes (PostTcType) +import BasicTypes ( FractionalLit(..) ) +import HsTypes ( PostTcType ) import Type ( Type ) import Outputable import FastString -import Ratio ( Rational ) + +import Data.Data \end{code} @@ -41,6 +45,7 @@ data HsLit -- (overloaded literals are done with HsOverLit) | HsFloatPrim Rational -- Unboxed Float | HsDoublePrim Rational -- Unboxed Double + deriving (Data, Typeable) instance Eq HsLit where (HsChar x1) == (HsChar x2) = x1==x2 @@ -59,20 +64,34 @@ instance Eq HsLit where data HsOverLit id -- An overloaded literal = OverLit { ol_val :: OverLitVal, - ol_rebindable :: Bool, -- True <=> rebindable syntax - -- False <=> standard syntax + ol_rebindable :: Bool, -- Note [ol_rebindable] ol_witness :: SyntaxExpr id, -- Note [Overloaded literal witnesses] ol_type :: PostTcType } + deriving (Data, Typeable) data OverLitVal = HsIntegral !Integer -- Integer-looking literals; - | HsFractional !Rational -- Frac-looking literals + | HsFractional !FractionalLit -- Frac-looking literals | HsIsString !FastString -- String-looking literals + deriving (Data, Typeable) overLitType :: HsOverLit a -> Type overLitType = ol_type \end{code} +Note [ol_rebindable] +~~~~~~~~~~~~~~~~~~~~ +The ol_rebindable field is True if this literal is actually +using rebindable syntax. Specifically: + + False iff ol_witness is the standard one + True iff ol_witness is non-standard + +Equivalently it's True if + a) RebindableSyntax is on + b) the witness for fromInteger/fromRational/fromString + that happens to be in scope isn't the standard one + Note [Overloaded literal witnesses] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ *Before* type checking, the SyntaxExpr in an HsOverLit is the @@ -83,7 +102,7 @@ This witness should replace the literal. This dual role 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 +calls, which wouldn't be possible if the desguarar made the application. The PostTcType in each branch records the type the overload literal is found to have. @@ -137,6 +156,6 @@ instance OutputableBndr id => Outputable (HsOverLit id) where instance Outputable OverLitVal where ppr (HsIntegral i) = integer i - ppr (HsFractional f) = rational f + ppr (HsFractional f) = text (fl_text f) ppr (HsIsString s) = pprHsString s \end{code}