[project @ 2000-10-16 08:24:18 by simonpj]
[ghc-hetmet.git] / ghc / compiler / basicTypes / Literal.lhs
index b8f495e..62a9c30 100644 (file)
@@ -27,12 +27,13 @@ import TysPrim              ( charPrimTy, addrPrimTy, floatPrimTy, doublePrimTy,
 import PrimRep         ( PrimRep(..) )
 import Type            ( Type, typePrimRep )
 import PprType         ( pprParendType )
-import CStrings                ( charToC, charToEasyHaskell, pprFSInCStyle )
+import CStrings                ( pprFSInCStyle )
 
 import Outputable
+import FastTypes
 import Util            ( thenCmp )
 
-import Ratio           ( numerator, denominator )
+import Ratio           ( numerator )
 import FastString      ( uniqueOfFS )
 import Char            ( ord, chr )
 \end{code}
@@ -85,7 +86,7 @@ function applications, etc., etc., has not yet been done.
 data Literal
   =    ------------------
        -- First the primitive guys
-    MachChar   Char
+    MachChar   Int             -- Char#        At least 31 bits
   | MachStr    FAST_STRING
 
   | MachAddr   Integer -- Whatever this machine thinks is a "pointer"
@@ -159,8 +160,8 @@ int2WordLit (MachInt i)
   | i < 0     = MachWord (1 + tARGET_MAX_WORD + i)     -- (-1)  --->  tARGET_MAX_WORD
   | otherwise = MachWord i
 
-char2IntLit (MachChar c) = MachInt  (toInteger (ord c))
-int2CharLit (MachInt  i) = MachChar (chr (fromInteger i))
+char2IntLit (MachChar c) = MachInt  (toInteger c)
+int2CharLit (MachInt  i) = MachChar (fromInteger i)
 
 float2IntLit (MachFloat f) = MachInt   (truncate    f)
 int2FloatLit (MachInt   i) = MachFloat (fromInteger i)
@@ -239,20 +240,20 @@ 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 `compare` d)
-cmpLit lit1               lit2                 | litTag lit1 _LT_ litTag lit2 = LT
+cmpLit lit1               lit2                 | litTag lit1 <# litTag lit2 = LT
                                                | otherwise                    = GT
 
-litTag (MachChar      _)   = ILIT(1)
-litTag (MachStr       _)   = ILIT(2)
-litTag (MachAddr      _)   = ILIT(3)
-litTag (MachInt       _)   = ILIT(4)
-litTag (MachWord      _)   = ILIT(5)
-litTag (MachInt64     _)   = ILIT(6)
-litTag (MachWord64    _)   = ILIT(7)
-litTag (MachFloat     _)   = ILIT(8)
-litTag (MachDouble    _)   = ILIT(9)
-litTag (MachLabel     _)   = ILIT(10)
-litTag (MachLitLit    _ _) = ILIT(11)
+litTag (MachChar      _)   = _ILIT(1)
+litTag (MachStr       _)   = _ILIT(2)
+litTag (MachAddr      _)   = _ILIT(3)
+litTag (MachInt       _)   = _ILIT(4)
+litTag (MachWord      _)   = _ILIT(5)
+litTag (MachInt64     _)   = _ILIT(6)
+litTag (MachWord64    _)   = _ILIT(7)
+litTag (MachFloat     _)   = _ILIT(8)
+litTag (MachDouble    _)   = _ILIT(9)
+litTag (MachLabel     _)   = _ILIT(10)
+litTag (MachLitLit    _ _) = _ILIT(11)
 \end{code}
 
        Printing
@@ -268,13 +269,13 @@ pprLit lit
       iface_style = ifaceStyle sty
     in
     case lit of
-      MachChar ch | code_style  -> hcat [ptext SLIT("(C_)"), char '\'', 
-                                        text (charToC ch), char '\'']
-                 | iface_style -> char '\'' <> text (charToEasyHaskell ch) <> char '\''
-                 | otherwise   -> text ['\'', ch, '\'']
+      MachChar ch | code_style -> hcat [ptext SLIT("(C_)"), text (show ch)]
+                 | otherwise  -> pprHsChar ch
 
       MachStr s | code_style -> pprFSInCStyle s
-               | otherwise  -> pprFSAsString 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
@@ -300,11 +301,11 @@ pprLit lit
                 | otherwise  -> ptext SLIT("__addr") <+> integer p
 
       MachLabel l | code_style -> ptext SLIT("(&") <> ptext l <> char ')'
-                 | otherwise  -> ptext SLIT("__label") <+> pprFSAsString l
+                 | otherwise  -> ptext SLIT("__label") <+> pprHsString l
 
       MachLitLit s ty | code_style  -> ptext s
                      | otherwise   -> parens (hsep [ptext SLIT("__litlit"), 
-                                                    pprFSAsString s,
+                                                    pprHsString s,
                                                     pprParendType ty])
 
 pprIntVal :: Integer -> SDoc
@@ -337,7 +338,7 @@ Hash values should be zero or a positive integer.  No negatives please.
 
 \begin{code}
 hashLiteral :: Literal -> Int
-hashLiteral (MachChar c)       = ord c + 1000  -- Keep it out of range of common ints
+hashLiteral (MachChar c)       = c + 1000      -- Keep it out of range of common ints
 hashLiteral (MachStr s)        = hashFS s
 hashLiteral (MachAddr i)       = hashInteger i
 hashLiteral (MachInt i)        = hashInteger i
@@ -358,5 +359,5 @@ hashInteger i = 1 + abs (fromInteger (i `rem` 10000))
                -- since we use * to combine hash values
 
 hashFS :: FAST_STRING -> Int
-hashFS s = IBOX( uniqueOfFS s )
+hashFS s = iBox (uniqueOfFS s)
 \end{code}