Major cleanup of the CPS code (but more is still to come)
[ghc-hetmet.git] / compiler / cmm / Cmm.hs
index 13961c1..0d1876e 100644 (file)
@@ -2,7 +2,7 @@
 --
 -- Cmm data types
 --
--- (c) The University of Glasgow 2004
+-- (c) The University of Glasgow 2004-2006
 --
 -----------------------------------------------------------------------------
 
@@ -10,27 +10,29 @@ module Cmm (
        GenCmm(..), Cmm,
        GenCmmTop(..), CmmTop,
        GenBasicBlock(..), CmmBasicBlock, blockId, blockStmts,
-       CmmStmt(..),  
+       CmmStmt(..), CmmActuals, CmmFormals,
        CmmCallTarget(..),
        CmmStatic(..), Section(..),
        CmmExpr(..), cmmExprRep, 
        CmmReg(..), cmmRegRep,
        CmmLit(..), cmmLitRep,
        LocalReg(..), localRegRep,
-       BlockId(..),
+       BlockId(..), BlockEnv,
        GlobalReg(..), globalRegRep,
 
-       node, nodeReg, spReg, hpReg,
+       node, nodeReg, spReg, hpReg, spLimReg
   ) where
 
 #include "HsVersions.h"
 
 import MachOp
-import CLabel          ( CLabel )
-import ForeignCall     ( CCallConv )
-import Unique          ( Unique, Uniquable(..) )
-import FastString      ( FastString )
-import DATA_WORD       ( Word8 )
+import CLabel
+import ForeignCall
+import Unique
+import UniqFM
+import FastString
+
+import Data.Word
 
 -----------------------------------------------------------------------------
 --             Cmm, CmmTop, CmmBasicBlock
@@ -112,8 +114,8 @@ data CmmStmt
 
   | CmmCall                     -- A foreign call, with 
      CmmCallTarget
-     [(CmmReg,MachHint)]        -- zero or more results
-     [(CmmExpr,MachHint)]       -- zero or more arguments
+     CmmFormals                         -- zero or more results
+     CmmActuals                         -- zero or more arguments
      (Maybe [GlobalReg])        -- Global regs that may need to be saved
                                 -- if they will be clobbered by the call.
                                 -- Nothing <=> save *all* globals that
@@ -129,8 +131,50 @@ data CmmStmt
        --      one  -> second block etc
        -- Undefined outside range, and when there's a Nothing
 
-  | CmmJump CmmExpr [LocalReg]    -- Jump to another function, with these 
-                                 -- parameters.
+  | CmmJump CmmExpr               -- Jump to another function,
+    CmmActuals                    -- with these parameters.
+
+  | CmmReturn                     -- Return from a function,
+    CmmActuals                    -- with these return values.
+
+type CmmActuals = [(CmmExpr,MachHint)]
+type CmmFormals = [(CmmReg,MachHint)]
+
+{-
+Discussion
+~~~~~~~~~~
+
+One possible problem with the above type is that the only way to do a
+non-local conditional jump is to encode it as a branch to a block that
+contains a single jump.  This leads to inefficient code in the back end.
+
+One possible way to fix this would be:
+
+data CmmStat = 
+  ...
+  | CmmJump CmmBranchDest
+  | CmmCondJump CmmExpr CmmBranchDest
+  ...
+
+data CmmBranchDest
+  = Local BlockId
+  | NonLocal CmmExpr [LocalReg]
+
+In favour:
+
++ one fewer constructors in CmmStmt
++ allows both cond branch and switch to jump to non-local destinations
+
+Against:
+
+- not strictly necessary: can already encode as branch+jump
+- not always possible to implement any better in the back end
+- could do the optimisation in the back end (but then plat-specific?)
+- C-- doesn't have it
+- back-end optimisation might be more general (jump shortcutting)
+
+So we'll stick with the way it is, and add the optimisation to the NCG.
+-}
 
 -----------------------------------------------------------------------------
 --             CmmCallTarget
@@ -163,6 +207,7 @@ data CmmExpr
        --        ** is shorthand only, meaning **
        -- CmmMachOp (MO_S_Add rep (CmmReg reg) (CmmLit (CmmInt i rep)))
        --      where rep = cmmRegRep reg
+  deriving Eq
 
 cmmExprRep :: CmmExpr -> MachRep
 cmmExprRep (CmmLit lit)      = cmmLitRep lit
@@ -211,6 +256,7 @@ data CmmLit
         -- It is also used inside the NCG during when generating
         -- position-independent code. 
   | CmmLabelDiffOff CLabel CLabel Int   -- label1 - label2 + offset
+  deriving Eq
 
 cmmLitRep :: CmmLit -> MachRep
 cmmLitRep (CmmInt _ rep)    = rep
@@ -230,6 +276,8 @@ newtype BlockId = BlockId Unique
 instance Uniquable BlockId where
   getUnique (BlockId u) = u
 
+type BlockEnv a = UniqFM {- BlockId -} a
+
 -----------------------------------------------------------------------------
 --             Static Data
 -----------------------------------------------------------------------------
@@ -306,9 +354,10 @@ data GlobalReg
         )
 
 -- convenient aliases
-spReg, hpReg, nodeReg :: CmmReg
+spReg, hpReg, spLimReg, nodeReg :: CmmReg
 spReg = CmmGlobal Sp
 hpReg = CmmGlobal Hp
+spLimReg = CmmGlobal SpLim
 nodeReg = CmmGlobal node
 
 node :: GlobalReg