[project @ 2003-01-23 14:54:35 by simonpj]
[ghc-hetmet.git] / ghc / compiler / basicTypes / Literal.lhs
index 7df6fca..f2d09f3 100644 (file)
@@ -13,6 +13,7 @@ module Literal
        , hashLiteral
 
        , inIntRange, inWordRange, tARGET_MAX_INT, inCharRange
+       , isZeroLit,
 
        , word2IntLit, int2WordLit
        , narrow8IntLit, narrow16IntLit, narrow32IntLit
@@ -35,12 +36,14 @@ import CStrings             ( pprFSInCStyle )
 
 import Outputable
 import FastTypes
+import FastString
+import Binary
 import Util            ( thenCmp )
 
 import Ratio           ( numerator )
 import FastString      ( uniqueOfFS, lengthFS )
-import Int             ( Int8,  Int16,  Int32 )
-import Word            ( Word8, Word16, Word32 )
+import DATA_INT                ( Int8,  Int16,  Int32 )
+import DATA_WORD       ( Word8, Word16, Word32 )
 import Char            ( ord, chr )
 \end{code}
 
@@ -96,7 +99,7 @@ data Literal
   =    ------------------
        -- First the primitive guys
     MachChar   Int             -- Char#        At least 31 bits
-  | MachStr    FAST_STRING
+  | MachStr    FastString
 
   | MachAddr   Integer -- Whatever this machine thinks is a "pointer"
 
@@ -112,13 +115,67 @@ data Literal
        -- "foreign label" declaration.
        -- string argument is the name of a symbol.  This literal
        -- refers to the *address* of the label.
-  | MachLabel   FAST_STRING            -- always an Addr#
+  | MachLabel   FastString             -- always an Addr#
 
        -- 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  FAST_STRING Type       -- Type might be Addr# or Int# 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.
+
+\begin{code}
+instance Binary Literal where
+    put_ bh (MachChar aa)     = do putByte bh 0; put_ bh aa
+    put_ bh (MachStr ab)      = do putByte bh 1; put_ bh ab
+    put_ bh (MachAddr ac)     = do putByte bh 2; put_ bh ac
+    put_ bh (MachInt ad)      = do putByte bh 3; put_ bh ad
+    put_ bh (MachInt64 ae)    = do putByte bh 4; put_ bh ae
+    put_ bh (MachWord af)     = do putByte bh 5; put_ bh af
+    put_ bh (MachWord64 ag)   = do putByte bh 6; put_ bh ag
+    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)    = do putByte bh 9; put_ bh aj
+    put_ bh (MachLitLit ak _) = do putByte bh 10; put_ bh ak
+    get bh = do
+           h <- getByte bh
+           case h of
+             0 -> do
+                   aa <- get bh
+                   return (MachChar aa)
+             1 -> do
+                   ab <- get bh
+                   return (MachStr ab)
+             2 -> do
+                   ac <- get bh
+                   return (MachAddr ac)
+             3 -> do
+                   ad <- get bh
+                   return (MachInt ad)
+             4 -> do
+                   ae <- get bh
+                   return (MachInt64 ae)
+             5 -> do
+                   af <- get bh
+                   return (MachWord af)
+             6 -> do
+                   ag <- get bh
+                   return (MachWord64 ag)
+             7 -> do
+                   ah <- get bh
+                   return (MachFloat ah)
+             8 -> do
+                   ai <- get bh
+                   return (MachDouble ai)
+             9 -> do
+                   aj <- get bh
+                   return (MachLabel aj)
+             10 -> do
+                   ak <- get bh
+                   return (MachLitLit ak (error "MachLitLit: no type"))
 \end{code}
 
 \begin{code}
@@ -163,6 +220,15 @@ inWordRange x = x >= 0                 && x <= tARGET_MAX_WORD
 
 inCharRange :: Int -> Bool
 inCharRange c =  c >= 0 && c <= tARGET_MAX_CHAR
+
+isZeroLit :: Literal -> Bool
+isZeroLit (MachInt    0) = True
+isZeroLit (MachInt64  0) = True
+isZeroLit (MachWord   0) = True
+isZeroLit (MachWord64 0) = True
+isZeroLit (MachFloat  0) = True
+isZeroLit (MachDouble 0) = True
+isZeroLit other                 = False
 \end{code}
 
        Coercions
@@ -223,8 +289,11 @@ litIsDupable (MachStr _) = False
 litIsDupable other      = True
 
 litSize :: Literal -> Int
-       -- used by CoreUnfold.sizeExpr
-litSize (MachStr str) = lengthFS str `div` 4
+-- Used by CoreUnfold.sizeExpr
+litSize (MachStr str) = 1 + (lengthFS str `div` 4)
+       -- Every literal has size at least 1, otherwise
+       --      f "x" 
+       -- might be too small
 litSize _other       = 1
 \end{code}
 
@@ -302,7 +371,6 @@ pprLit lit
   = getPprStyle $ \ sty ->
     let
       code_style  = codeStyle  sty
-      iface_style = ifaceStyle sty
     in
     case lit of
       MachChar ch | code_style -> hcat [ptext SLIT("(C_)"), text (show ch)]
@@ -327,23 +395,28 @@ pprLit lit
       MachWord64 w | code_style -> pprHexVal w
                   | otherwise  -> ptext SLIT("__word64") <+> integer w
 
-      MachFloat f | code_style -> ptext SLIT("(StgFloat)") <> rational f
+      MachFloat f | code_style -> ptext SLIT("(StgFloat)") <> code_rational f
                   | otherwise  -> ptext SLIT("__float") <+> rational f
 
-      MachDouble d | iface_style && d < 0 -> parens (rational d)
-                  | otherwise            -> rational d
+      MachDouble d | code_style -> code_rational d
+                  | otherwise  -> rational d
 
       MachAddr p | code_style -> ptext SLIT("(void*)") <> integer p
                 | otherwise  -> ptext SLIT("__addr") <+> integer p
 
-      MachLabel l | code_style -> ptext SLIT("(&") <> ptext l <> char ')'
+      MachLabel l | code_style -> ptext SLIT("(&") <> ftext l <> char ')'
                  | otherwise  -> ptext SLIT("__label") <+> pprHsString l
 
-      MachLitLit s ty | code_style  -> ptext s
+      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
+
 pprIntVal :: Integer -> SDoc
 -- Print negative integers with parens to be sure it's unambiguous
 pprIntVal i | i < 0     = parens (integer i)
@@ -394,6 +467,6 @@ hashInteger i = 1 + abs (fromInteger (i `rem` 10000))
                -- The 1+ is to avoid zero, which is a Bad Number
                -- since we use * to combine hash values
 
-hashFS :: FAST_STRING -> Int
+hashFS :: FastString -> Int
 hashFS s = iBox (uniqueOfFS s)
 \end{code}