X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2FbasicTypes%2FLiteral.lhs;h=01b21b12ee4cb7add0512666a44501b1ccbf25b9;hb=423d477bfecd490de1449c59325c8776f91d7aac;hp=1e39e65a55394df277c3905bf9f5f38cc50d4fac;hpb=1d87bd263e2d7cbaf08fed9c5ee2edba8124e4ea;p=ghc-hetmet.git diff --git a/ghc/compiler/basicTypes/Literal.lhs b/ghc/compiler/basicTypes/Literal.lhs index 1e39e65..01b21b1 100644 --- a/ghc/compiler/basicTypes/Literal.lhs +++ b/ghc/compiler/basicTypes/Literal.lhs @@ -8,9 +8,9 @@ module Literal ( Literal(..) -- Exported to ParseIface , mkMachInt, mkMachWord , mkMachInt64, mkMachWord64 - , isLitLitLit, maybeLitLit, litSize + , litSize , litIsDupable, litIsTrivial - , literalType, literalPrimRep + , literalType, , hashLiteral , inIntRange, inWordRange, tARGET_MAX_INT, inCharRange @@ -29,17 +29,11 @@ module Literal import TysPrim ( charPrimTy, addrPrimTy, floatPrimTy, doublePrimTy, intPrimTy, wordPrimTy, int64PrimTy, word64PrimTy ) -import PrimRep ( PrimRep(..) ) -import TcType ( Type, tcCmpType ) -import Type ( typePrimRep ) -import PprType ( pprParendType ) -import CStrings ( pprFSInCStyle ) - +import Type ( Type ) import Outputable import FastTypes import FastString import Binary -import Util ( thenCmp ) import Ratio ( numerator ) import FastString ( uniqueOfFS, lengthFS ) @@ -99,7 +93,7 @@ function applications, etc., etc., has not yet been done. data Literal = ------------------ -- First the primitive guys - MachChar Int -- Char# At least 31 bits + MachChar Char -- Char# At least 31 bits | MachStr FastString | MachNullAddr -- the NULL pointer, the only pointer value @@ -123,16 +117,9 @@ data Literal -- 'stdcall' labels. -- Just x => "@" will be appended to label -- name when emitting asm. - - -- lit-lits only work for via-C compilation, hence they - -- are deprecated. The string is emitted verbatim into - -- the C file, and can therefore be any C expression, - -- macro call, #defined constant etc. - | MachLitLit FastString Type -- Type might be Addr# or Int# etc \end{code} -Binary instance: must do this manually, because we don't want the type -arg of MachLitLit involved. +Binary instance \begin{code} instance Binary Literal where @@ -146,7 +133,6 @@ instance Binary Literal where put_ bh (MachFloat ah) = do putByte bh 7; put_ bh ah put_ bh (MachDouble ai) = do putByte bh 8; put_ bh ai put_ bh (MachLabel aj mb) = do putByte bh 9; put_ bh aj ; put_ bh mb - put_ bh (MachLitLit ak _) = do putByte bh 10; put_ bh ak get bh = do h <- getByte bh case h of @@ -180,9 +166,6 @@ instance Binary Literal where aj <- get bh mb <- get bh return (MachLabel aj mb) - 10 -> do - ak <- get bh - return (MachLitLit ak (error "MachLitLit: no type")) \end{code} \begin{code} @@ -225,8 +208,8 @@ inIntRange, inWordRange :: Integer -> Bool inIntRange x = x >= tARGET_MIN_INT && x <= tARGET_MAX_INT inWordRange x = x >= 0 && x <= tARGET_MAX_WORD -inCharRange :: Int -> Bool -inCharRange c = c >= 0 && c <= tARGET_MAX_CHAR +inCharRange :: Char -> Bool +inCharRange c = c >= '\0' && c <= chr tARGET_MAX_CHAR isZeroLit :: Literal -> Bool isZeroLit (MachInt 0) = True @@ -264,8 +247,8 @@ narrow8WordLit (MachWord w) = MachWord (toInteger (fromInteger w :: Word8)) narrow16WordLit (MachWord w) = MachWord (toInteger (fromInteger w :: Word16)) narrow32WordLit (MachWord w) = MachWord (toInteger (fromInteger w :: Word32)) -char2IntLit (MachChar c) = MachInt (toInteger c) -int2CharLit (MachInt i) = MachChar (fromInteger i) +char2IntLit (MachChar c) = MachInt (toInteger (ord c)) +int2CharLit (MachInt i) = MachChar (chr (fromInteger i)) float2IntLit (MachFloat f) = MachInt (truncate f) int2FloatLit (MachInt i) = MachFloat (fromInteger i) @@ -283,12 +266,6 @@ nullAddrLit = MachNullAddr Predicates ~~~~~~~~~~ \begin{code} -isLitLitLit (MachLitLit _ _) = True -isLitLitLit _ = False - -maybeLitLit (MachLitLit s t) = Just (s,t) -maybeLitLit _ = Nothing - litIsTrivial :: Literal -> Bool -- True if there is absolutely no penalty to duplicating the literal -- c.f. CoreUtils.exprIsTrivial @@ -305,10 +282,12 @@ litIsDupable other = True litSize :: Literal -> Int -- Used by CoreUnfold.sizeExpr -litSize (MachStr str) = 1 + (lengthFS str `div` 4) +litSize (MachStr str) = 1 + ((lengthFS str + 3) `div` 4) -- Every literal has size at least 1, otherwise -- 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} @@ -316,33 +295,16 @@ litSize _other = 1 ~~~~~ \begin{code} literalType :: Literal -> Type -literalType (MachChar _) = charPrimTy -literalType (MachStr _) = addrPrimTy -literalType (MachNullAddr) = addrPrimTy -literalType (MachInt _) = intPrimTy -literalType (MachWord _) = wordPrimTy -literalType (MachInt64 _) = int64PrimTy -literalType (MachWord64 _) = word64PrimTy -literalType (MachFloat _) = floatPrimTy -literalType (MachDouble _) = doublePrimTy -literalType (MachLabel _ _) = addrPrimTy -literalType (MachLitLit _ ty) = ty -\end{code} - -\begin{code} -literalPrimRep :: Literal -> PrimRep - -literalPrimRep (MachChar _) = CharRep -literalPrimRep (MachStr _) = AddrRep -- specifically: "char *" -literalPrimRep (MachNullAddr) = AddrRep -literalPrimRep (MachInt _) = IntRep -literalPrimRep (MachWord _) = WordRep -literalPrimRep (MachInt64 _) = Int64Rep -literalPrimRep (MachWord64 _) = Word64Rep -literalPrimRep (MachFloat _) = FloatRep -literalPrimRep (MachDouble _) = DoubleRep -literalPrimRep (MachLabel _ _) = AddrRep -literalPrimRep (MachLitLit _ ty) = typePrimRep ty +literalType MachNullAddr = addrPrimTy +literalType (MachChar _) = charPrimTy +literalType (MachStr _) = addrPrimTy +literalType (MachInt _) = intPrimTy +literalType (MachWord _) = wordPrimTy +literalType (MachInt64 _) = int64PrimTy +literalType (MachWord64 _) = word64PrimTy +literalType (MachFloat _) = floatPrimTy +literalType (MachDouble _) = doublePrimTy +literalType (MachLabel _ _) = addrPrimTy \end{code} @@ -359,9 +321,8 @@ cmpLit (MachWord64 a) (MachWord64 b) = a `compare` b cmpLit (MachFloat a) (MachFloat b) = a `compare` b cmpLit (MachDouble a) (MachDouble b) = a `compare` b cmpLit (MachLabel a _) (MachLabel b _) = a `compare` b -cmpLit (MachLitLit a b) (MachLitLit c d) = (a `compare` c) `thenCmp` (b `tcCmpType` d) cmpLit lit1 lit2 | litTag lit1 <# litTag lit2 = LT - | otherwise = GT + | otherwise = GT litTag (MachChar _) = _ILIT(1) litTag (MachStr _) = _ILIT(2) @@ -373,7 +334,6 @@ litTag (MachWord64 _) = _ILIT(7) litTag (MachFloat _) = _ILIT(8) litTag (MachDouble _) = _ILIT(9) litTag (MachLabel _ _) = _ILIT(10) -litTag (MachLitLit _ _) = _ILIT(11) \end{code} Printing @@ -382,76 +342,24 @@ litTag (MachLitLit _ _) = _ILIT(11) exceptions: MachFloat gets an initial keyword prefix. \begin{code} -pprLit lit - = getPprStyle $ \ sty -> - let - code_style = codeStyle sty - in - case lit of - MachChar ch | code_style -> hcat [ptext SLIT("(C_)"), text (show ch)] - | otherwise -> pprHsChar ch - - MachStr s | code_style -> pprFSInCStyle s - | otherwise -> pprHsString s - -- Warning: printing MachStr in code_style assumes it contains - -- only characters '\0'..'\xFF'! - - MachInt i | code_style && i == tARGET_MIN_INT -> parens (integer (i+1) <> text "-1") - -- Avoid a problem whereby gcc interprets - -- the constant minInt as unsigned. - | otherwise -> pprIntVal i - - MachInt64 i | code_style -> pprIntVal i -- Same problem with gcc??? - | otherwise -> ptext SLIT("__int64") <+> integer i - - MachWord w | code_style -> pprHexVal w - | otherwise -> ptext SLIT("__word") <+> integer w - - MachWord64 w | code_style -> pprHexVal w - | otherwise -> ptext SLIT("__word64") <+> integer w - - MachFloat f | code_style -> ptext SLIT("(StgFloat)") <> code_rational f - | otherwise -> ptext SLIT("__float") <+> rational f - - MachDouble d | code_style -> code_rational d - | otherwise -> rational d - - MachNullAddr | code_style -> ptext SLIT("(void*)0") - | otherwise -> ptext SLIT("__NULL") - - MachLabel l mb - | code_style -> ptext SLIT("(&") <> ftext l <> char ')' - | otherwise -> ptext SLIT("__label") <+> - case mb of - Nothing -> pprHsString l - Just x -> doubleQuotes (text (unpackFS l ++ '@':show x)) - - MachLitLit s ty | code_style -> ftext s - | otherwise -> parens (hsep [ptext SLIT("__litlit"), - pprHsString s, - pprParendType ty]) - --- negative floating literals in code style need parentheses to avoid --- interacting with surrounding syntax. -code_rational d | d < 0 = parens (rational d) - | otherwise = rational d +pprLit (MachChar ch) = pprHsChar ch +pprLit (MachStr s) = pprHsString s +pprLit (MachInt i) = pprIntVal i +pprLit (MachInt64 i) = ptext SLIT("__int64") <+> integer i +pprLit (MachWord w) = ptext SLIT("__word") <+> integer w +pprLit (MachWord64 w) = ptext SLIT("__word64") <+> integer w +pprLit (MachFloat f) = ptext SLIT("__float") <+> rational f +pprLit (MachDouble d) = rational d +pprLit (MachNullAddr) = ptext SLIT("__NULL") +pprLit (MachLabel l mb) = ptext SLIT("__label") <+> + case mb of + Nothing -> pprHsString l + Just x -> doubleQuotes (text (unpackFS l ++ '@':show x)) pprIntVal :: Integer -> SDoc -- Print negative integers with parens to be sure it's unambiguous pprIntVal i | i < 0 = parens (integer i) | otherwise = integer i - -pprHexVal :: Integer -> SDoc --- Print in C hex format: 0x13fa -pprHexVal 0 = ptext SLIT("0x0") -pprHexVal w = ptext SLIT("0x") <> go w - where - go 0 = empty - go w = go quot <> dig - where - (quot,rem) = w `quotRem` 16 - dig | rem < 10 = char (chr (fromInteger rem + ord '0')) - | otherwise = char (chr (fromInteger rem - 10 + ord 'a')) \end{code} @@ -466,7 +374,7 @@ Hash values should be zero or a positive integer. No negatives please. \begin{code} hashLiteral :: Literal -> Int -hashLiteral (MachChar c) = c + 1000 -- Keep it out of range of common ints +hashLiteral (MachChar c) = ord c + 1000 -- Keep it out of range of common ints hashLiteral (MachStr s) = hashFS s hashLiteral (MachNullAddr) = 0 hashLiteral (MachInt i) = hashInteger i @@ -476,7 +384,6 @@ hashLiteral (MachWord64 i) = hashInteger i hashLiteral (MachFloat r) = hashRational r hashLiteral (MachDouble r) = hashRational r hashLiteral (MachLabel s _) = hashFS s -hashLiteral (MachLitLit s _) = hashFS s hashRational :: Rational -> Int hashRational r = hashInteger (numerator r)