Repository : ssh://darcs.haskell.org//srv/darcs/ghc On branch : master
http://hackage.haskell.org/trac/ghc/changeset/62f45ffa5f489df415a5e4b99c3dc6f54f26594e >--------------------------------------------------------------- commit 62f45ffa5f489df415a5e4b99c3dc6f54f26594e Author: Simon Marlow <marlo...@gmail.com> Date: Fri Jul 8 10:41:22 2011 +0100 Add 64-bit signed and unsigned integer literals to HsSyn. No concrete syntax yet, but I need to be able to use these in code generated for derived Typeable instances. >--------------------------------------------------------------- compiler/deSugar/MatchLit.lhs | 4 ++++ compiler/hsSyn/HsLit.lhs | 10 ++++++++-- compiler/typecheck/TcHsSyn.lhs | 2 ++ 3 files changed, 14 insertions(+), 2 deletions(-) diff --git a/compiler/deSugar/MatchLit.lhs b/compiler/deSugar/MatchLit.lhs index 0bd2538..173bad9 100644 --- a/compiler/deSugar/MatchLit.lhs +++ b/compiler/deSugar/MatchLit.lhs @@ -65,6 +65,8 @@ dsLit (HsStringPrim s) = return (Lit (MachStr s)) dsLit (HsCharPrim c) = return (Lit (MachChar c)) dsLit (HsIntPrim i) = return (Lit (MachInt i)) dsLit (HsWordPrim w) = return (Lit (MachWord w)) +dsLit (HsInt64Prim i) = return (Lit (MachInt64 i)) +dsLit (HsWord64Prim w) = return (Lit (MachWord64 w)) dsLit (HsFloatPrim f) = return (Lit (MachFloat (fl_value f))) dsLit (HsDoublePrim d) = return (Lit (MachDouble (fl_value d))) @@ -111,6 +113,8 @@ hsLitKey :: HsLit -> Literal -- others have been removed by tidy hsLitKey (HsIntPrim i) = mkMachInt i hsLitKey (HsWordPrim w) = mkMachWord w +hsLitKey (HsInt64Prim i) = mkMachInt64 i +hsLitKey (HsWord64Prim w) = mkMachWord64 w hsLitKey (HsCharPrim c) = MachChar c hsLitKey (HsStringPrim s) = MachStr s hsLitKey (HsFloatPrim f) = MachFloat (fl_value f) diff --git a/compiler/hsSyn/HsLit.lhs b/compiler/hsSyn/HsLit.lhs index 2cda103..2b556ea 100644 --- a/compiler/hsSyn/HsLit.lhs +++ b/compiler/hsSyn/HsLit.lhs @@ -37,8 +37,10 @@ data HsLit | HsStringPrim FastString -- Packed string | HsInt Integer -- Genuinely an Int; arises from TcGenDeriv, -- and from TRANSLATION - | HsIntPrim Integer -- Unboxed Int - | HsWordPrim Integer -- Unboxed Word + | HsIntPrim Integer -- literal Int# + | HsWordPrim Integer -- literal Word# + | HsInt64Prim Integer -- literal Int64# + | HsWord64Prim Integer -- literal Word64# | HsInteger Integer Type -- Genuinely an integer; arises only from TRANSLATION -- (overloaded literals are done with HsOverLit) | HsRat FractionalLit Type -- Genuinely a rational; arises only from TRANSLATION @@ -55,6 +57,8 @@ instance Eq HsLit where (HsInt x1) == (HsInt x2) = x1==x2 (HsIntPrim x1) == (HsIntPrim x2) = x1==x2 (HsWordPrim x1) == (HsWordPrim x2) = x1==x2 + (HsInt64Prim x1) == (HsInt64Prim x2) = x1==x2 + (HsWord64Prim x1) == (HsWord64Prim x2) = x1==x2 (HsInteger x1 _) == (HsInteger x2 _) = x1==x2 (HsRat x1 _) == (HsRat x2 _) = x1==x2 (HsFloatPrim x1) == (HsFloatPrim x2) = x1==x2 @@ -148,6 +152,8 @@ instance Outputable HsLit where ppr (HsDoublePrim d) = ppr d <> text "##" ppr (HsIntPrim i) = integer i <> char '#' ppr (HsWordPrim w) = integer w <> text "##" + ppr (HsInt64Prim i) = integer i <> text "L#" + ppr (HsWord64Prim w) = integer w <> text "L##" -- in debug mode, print the expression that it's resolved to, too instance OutputableBndr id => Outputable (HsOverLit id) where diff --git a/compiler/typecheck/TcHsSyn.lhs b/compiler/typecheck/TcHsSyn.lhs index 3b4afae..be0bc49 100644 --- a/compiler/typecheck/TcHsSyn.lhs +++ b/compiler/typecheck/TcHsSyn.lhs @@ -107,6 +107,8 @@ hsLitType (HsStringPrim _) = addrPrimTy hsLitType (HsInt _) = intTy hsLitType (HsIntPrim _) = intPrimTy hsLitType (HsWordPrim _) = wordPrimTy +hsLitType (HsInt64Prim _) = int64PrimTy +hsLitType (HsWord64Prim _) = word64PrimTy hsLitType (HsInteger _ ty) = ty hsLitType (HsRat _ ty) = ty hsLitType (HsFloatPrim _) = floatPrimTy _______________________________________________ Cvs-ghc mailing list Cvs-ghc@haskell.org http://www.haskell.org/mailman/listinfo/cvs-ghc