Add Outputable.blankLine and use it
[ghc-hetmet.git] / compiler / cmm / ZipCfgCmmRep.hs
index b08f2f3..451450e 100644 (file)
@@ -29,7 +29,6 @@ import CmmTx
 import CLabel
 import FastString
 import ForeignCall
-import qualified ZipCfg as Z
 import qualified ZipDataflow as DF
 import ZipCfg 
 import MkZipCfg
@@ -37,10 +36,9 @@ import Util
 
 import BasicTypes
 import Maybes
-import Monad
+import Control.Monad
 import Outputable
 import Prelude hiding (zip, unzip, last)
-import qualified Data.List as L
 import SMRep (ByteOff)
 import UniqSupply
 
@@ -87,18 +85,34 @@ data Last
         --      one  -> second block etc
         -- Undefined outside range, and when there's a Nothing
   | LastCall {                   -- A call (native or safe foreign)
-        cml_target  :: CmmExpr,  -- never a CmmPrim to a CallishMachOp!
-        cml_cont    :: Maybe BlockId,
+        cml_target :: CmmExpr,  -- never a CmmPrim to a CallishMachOp!
+
+        cml_cont :: Maybe BlockId,
             -- BlockId of continuation (Nothing for return or tail call)
-        cml_args    :: ByteOff,  -- byte offset for youngest outgoing arg
-                                 -- (includes update frame, which must be younger)
-        cml_ret_args:: ByteOff,  -- byte offset for youngest incoming arg
-        cml_ret_off :: Maybe UpdFrameOffset}
-          -- stack offset for return (update frames);
-          -- The return offset should be Nothing only if we have to create
-          -- a new call, e.g. for a procpoint, in which case it's an invariant
-          -- that the call does not stand for a return or a tail call,
-          -- and the successor does not need an info table.
+
+        cml_args :: ByteOff, 
+           -- Byte offset, from the *old* end of the Area associated with
+            -- the BlockId (if cml_cont = Nothing, then Old area), of
+            -- youngest outgoing arg.  Set the stack pointer to this before
+           -- transferring control.
+           -- (NB: an update frame might also have been stored in the Old
+           --      area, but it'll be in an older part than the args.)
+
+        cml_ret_args :: ByteOff,  
+           -- For calls *only*, the byte offset for youngest returned value
+           -- This is really needed at the *return* point rather than here
+           -- at the call, but in practice it's convenient to record it here.
+
+        cml_ret_off :: Maybe ByteOff
+          -- For calls *only*, the byte offset of the base of the frame that
+         -- must be described by the info table for the return point.  
+         -- The older words are an update frames, which have their own
+         -- info-table and layout information
+
+         -- From a liveness point of view, the stack words older than
+         -- cml_ret_off are treated as live, even if the sequel of
+         -- the call goes into a loop.
+       }
 
 data MidCallTarget     -- The target of a MidUnsafeCall
   = ForeignTarget      -- A foreign procedure
@@ -114,17 +128,17 @@ data Convention
   
   | NativeNodeCall   -- Native C-- call including the node argument
 
-  | NativeReturn -- Native C-- return
+  | NativeReturn     -- Native C-- return
 
-  | Slow         -- Slow entry points: all args pushed on the stack
+  | Slow             -- Slow entry points: all args pushed on the stack
 
-  | GC           -- Entry to the garbage collector: uses the node reg!
+  | GC               -- Entry to the garbage collector: uses the node reg!
 
-  | PrimOpCall   -- Calling prim ops
+  | PrimOpCall       -- Calling prim ops
 
-  | PrimOpReturn -- Returning from prim ops
+  | PrimOpReturn     -- Returning from prim ops
 
-  | Foreign      -- Foreign call/return
+  | Foreign          -- Foreign call/return
         ForeignConvention
 
   | Private
@@ -445,10 +459,9 @@ pprMiddle stmt = pp_stmt <+> pp_debug
        -- call "ccall" foo(x, y)[r1, r2];
        -- ToDo ppr volatile
        MidForeignCall safety target results args ->
-           hsep [ if null results
-                     then empty
-                     else parens (commafy $ map ppr results) <+> equals,
-                      ppr_safety safety,
+           hsep [ ppUnless (null results) $
+                     parens (commafy $ map ppr results) <+> equals,
+                   ppr_safety safety,
                   ptext $ sLit "call", 
                   ppr_call_target target <> parens (commafy $ map ppr args) <> semi]