Remove some dead code from VectType
[ghc-hetmet.git] / compiler / hsSyn / HsLit.lhs
index 3c18102..55260eb 100644 (file)
@@ -5,13 +5,6 @@
 \section[HsLit]{Abstract syntax: source-language literals}
 
 \begin{code}
-{-# OPTIONS -w #-}
--- The above warning supression flag is a temporary kludge.
--- While working on this module you are encouraged to remove it and fix
--- any warnings in the module. See
---     http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
--- for details
-
 module HsLit where
 
 #include "HsVersions.h"
@@ -41,6 +34,7 @@ data HsLit
   | HsInt          Integer             -- Genuinely an Int; arises from TcGenDeriv, 
                                        --      and from TRANSLATION
   | HsIntPrim      Integer             -- Unboxed Int
+  | HsWordPrim     Integer             -- Unboxed Word
   | 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
@@ -55,16 +49,17 @@ instance Eq HsLit where
   (HsStringPrim x1) == (HsStringPrim x2) = x1==x2
   (HsInt x1)       == (HsInt x2)        = x1==x2
   (HsIntPrim x1)    == (HsIntPrim x2)    = x1==x2
+  (HsWordPrim x1)   == (HsWordPrim 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
-  lit1             == lit2              = False
+  _                 == _                 = False
 
 data HsOverLit id      -- An overloaded literal
-  = HsIntegral   Integer    (SyntaxExpr id)  PostTcType        -- Integer-looking literals;
-  | HsFractional Rational   (SyntaxExpr id)  PostTcType        -- Frac-looking literals
-  | HsIsString   FastString (SyntaxExpr id)  PostTcType        -- String-looking literals
+  = HsIntegral   !Integer    (SyntaxExpr id)  PostTcType       -- Integer-looking literals;
+  | HsFractional !Rational   (SyntaxExpr id)  PostTcType       -- Frac-looking literals
+  | HsIsString   !FastString (SyntaxExpr id)  PostTcType       -- String-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.
@@ -92,18 +87,18 @@ instance Eq (HsOverLit id) where
   (HsIntegral i1 _ _)   == (HsIntegral i2 _ _)   = i1 == i2
   (HsFractional f1 _ _) == (HsFractional f2 _ _) = f1 == f2
   (HsIsString s1 _ _)   == (HsIsString s2 _ _)   = s1 == s2
-  l1                 == l2                  = False
+  _                     == _                     = False
 
 instance Ord (HsOverLit id) where
   compare (HsIntegral i1 _ _)   (HsIntegral i2 _ _)   = i1 `compare` i2
   compare (HsIntegral _ _ _)    (HsFractional _ _ _)  = LT
   compare (HsIntegral _ _ _)    (HsIsString _ _ _)    = LT
   compare (HsFractional f1 _ _) (HsFractional f2 _ _) = f1 `compare` f2
-  compare (HsFractional f1 _ _) (HsIntegral _ _ _)    = GT
-  compare (HsFractional f1 _ _) (HsIsString _ _ _)    = LT
+  compare (HsFractional _ _ _)  (HsIntegral _ _ _)    = GT
+  compare (HsFractional _ _ _)  (HsIsString _ _ _)    = LT
   compare (HsIsString s1 _ _)   (HsIsString s2 _ _)   = s1 `compare` s2
-  compare (HsIsString s1 _ _)   (HsIntegral _ _ _)    = GT
-  compare (HsIsString s1 _ _)   (HsFractional _ _ _)  = GT
+  compare (HsIsString _ _ _)    (HsIntegral _ _ _)    = GT
+  compare (HsIsString _ _ _)    (HsFractional _ _ _)  = GT
 \end{code}
 
 \begin{code}
@@ -119,6 +114,7 @@ instance Outputable HsLit where
     ppr (HsFloatPrim f)         = rational f <> char '#'
     ppr (HsDoublePrim d) = rational d <> text "##"
     ppr (HsIntPrim i)   = integer i  <> char '#'
+    ppr (HsWordPrim w)  = integer w  <> text "##"
 
 -- in debug mode, print the expression that it's resolved to, too
 instance OutputableBndr id => Outputable (HsOverLit id) where