Merge branch 'master' of http://darcs.haskell.org/ghc
[ghc-hetmet.git] / compiler / basicTypes / Literal.lhs
index f2ea137..da8685e 100644 (file)
@@ -11,6 +11,7 @@
 -- any warnings in the module. See
 --     http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
 -- for details
+{-# LANGUAGE DeriveDataTypeable #-}
 
 module Literal
        ( 
@@ -24,9 +25,9 @@ module Literal
        , mkMachChar, mkMachString
        
        -- ** Operations on Literals
-       , litSize
        , literalType
        , hashLiteral
+        , absentLiteralOf
 
         -- ** Predicates on Literals and their contents
        , litIsDupable, litIsTrivial
@@ -44,48 +45,26 @@ module Literal
        ) where
 
 import TysPrim
+import PrelNames
 import Type
+import TyCon
 import Outputable
 import FastTypes
 import FastString
 import BasicTypes
 import Binary
-import Ratio
-
+import Constants
+import UniqFM
 import Data.Int
+import Data.Ratio
 import Data.Word
 import Data.Char
+import Data.Data( Data, Typeable )
 \end{code}
 
 
 %************************************************************************
 %*                                                                     *
-\subsection{Sizes}
-%*                                                                     *
-%************************************************************************
-
-If we're compiling with GHC (and we're not cross-compiling), then we
-know that minBound and maxBound :: Int are the right values for the
-target architecture.  Otherwise, we assume -2^31 and 2^31-1
-respectively (which will be wrong on a 64-bit machine).
-
-\begin{code}
-tARGET_MIN_INT, tARGET_MAX_INT, tARGET_MAX_WORD :: Integer
-#ifdef __GLASGOW_HASKELL__
-tARGET_MIN_INT  = toInteger (minBound :: Int)
-tARGET_MAX_INT  = toInteger (maxBound :: Int)
-#else
-tARGET_MIN_INT = -2147483648
-tARGET_MAX_INT =  2147483647
-#endif
-tARGET_MAX_WORD = (tARGET_MAX_INT * 2) + 1
-
-tARGET_MAX_CHAR :: Int
-tARGET_MAX_CHAR = 0x10ffff
-\end{code}
-
-%************************************************************************
-%*                                                                     *
 \subsection{Literals}
 %*                                                                     *
 %************************************************************************
@@ -132,6 +111,7 @@ data Literal
                                --    the label expects. Only applicable with
                                --    @stdcall@ labels. @Just x@ => @\<x\>@ will
                                --    be appended to label name when emitting assembly.
+  deriving (Data, Typeable)
 \end{code}
 
 Binary instance
@@ -332,15 +312,6 @@ litFitsInChar (MachInt i)
                         = fromInteger i <= ord minBound 
                         && fromInteger i >= ord maxBound 
 litFitsInChar _         = False
-
--- | Finds a nominal size of a string literal. Every literal has size at least 1
-litSize :: Literal -> Int
--- Used by CoreUnfold.sizeExpr
-litSize (MachStr str) = 1 + ((lengthFS str + 3) `div` 4)
-       -- If size could be 0 then @f "x"@ might be too small
-       -- [Sept03: make literal strings a bit bigger to avoid fruitless 
-       --  duplication of little strings]
-litSize _other       = 1
 \end{code}
 
        Types
@@ -358,6 +329,21 @@ literalType (MachWord64  _) = word64PrimTy
 literalType (MachFloat _)   = floatPrimTy
 literalType (MachDouble _)  = doublePrimTy
 literalType (MachLabel _ _ _) = addrPrimTy
+
+absentLiteralOf :: TyCon -> Maybe Literal
+-- Return a literal of the appropriate primtive
+-- TyCon, to use as a placeholder when it doesn't matter
+absentLiteralOf tc = lookupUFM absent_lits (tyConName tc)
+
+absent_lits :: UniqFM Literal
+absent_lits = listToUFM [ (addrPrimTyConKey,    MachNullAddr)
+                       , (charPrimTyConKey,    MachChar 'x')
+                       , (intPrimTyConKey,     MachInt 0)
+                       , (int64PrimTyConKey,   MachInt64 0)
+                       , (floatPrimTyConKey,   MachFloat 0)
+                       , (doublePrimTyConKey,  MachDouble 0)
+                       , (wordPrimTyConKey,    MachWord 0)
+                       , (word64PrimTyConKey,  MachWord64 0) ]
 \end{code}