Interruptible FFI calls with pthread_kill and CancelSynchronousIO. v4
[ghc-hetmet.git] / compiler / cmm / Cmm.hs
index 5e52a57..4ea7f00 100644 (file)
@@ -13,7 +13,8 @@ module Cmm (
         cmmMapGraph, cmmTopMapGraph,
         cmmMapGraphM, cmmTopMapGraphM,
         CmmInfo(..), UpdateFrame(..),
-        CmmInfoTable(..), ClosureTypeInfo(..), ProfilingInfo(..), ClosureTypeTag,
+        CmmInfoTable(..), HasStaticClosure, ClosureTypeInfo(..), ConstrDescription,
+        ProfilingInfo(..), ClosureTypeTag,
         GenBasicBlock(..), CmmBasicBlock, blockId, blockStmts, mapBlockStmts,
         CmmReturnInfo(..),
         CmmStmt(..), CmmActual, CmmActuals, CmmFormal, CmmFormals, 
@@ -134,10 +135,11 @@ cmmTopMapGraphM :: Monad m => (String -> g -> m g') -> GenCmmTop d h g -> m (Gen
 
 cmmMapGraph f (Cmm tops) = Cmm $ map (cmmTopMapGraph f) tops
 cmmTopMapGraph f (CmmProc h l args g) = CmmProc h l args (f g)
-cmmTopMapGraph _ (CmmData s ds)       = CmmData s ds
+cmmTopMapGraph _ (CmmData s ds)             = CmmData s ds
 
 cmmMapGraphM f (Cmm tops) = mapM (cmmTopMapGraphM f) tops >>= return . Cmm
-cmmTopMapGraphM f (CmmProc h l args g) = f (showSDoc $ ppr l) g >>= return . CmmProc h l args
+cmmTopMapGraphM f (CmmProc h l args g) =
+  f (showSDoc $ ppr l) g >>= return . CmmProc h l args
 cmmTopMapGraphM _ (CmmData s ds)       = return $ CmmData s ds
 
 -----------------------------------------------------------------------------
@@ -147,17 +149,21 @@ cmmTopMapGraphM _ (CmmData s ds)       = return $ CmmData s ds
 data CmmInfo
   = CmmInfo
       (Maybe BlockId)     -- GC target. Nothing <=> CPS won't do stack check
+                          -- JD: NOT USED BY NEW CODE GEN
       (Maybe UpdateFrame) -- Update frame
       CmmInfoTable        -- Info table
 
 -- Info table as a haskell data type
 data CmmInfoTable
   = CmmInfoTable
+      HasStaticClosure
       ProfilingInfo
       ClosureTypeTag -- Int
       ClosureTypeInfo
   | CmmNonInfoTable   -- Procedure doesn't need an info table
 
+type HasStaticClosure = Bool
+
 -- TODO: The GC target shouldn't really be part of CmmInfo
 -- as it doesn't appear in the resulting info table.
 -- It should be factored out.
@@ -168,11 +174,14 @@ data ClosureTypeInfo
   | ThunkInfo  ClosureLayout C_SRT
   | ThunkSelectorInfo SelectorOffset C_SRT
   | ContInfo
-      [Maybe LocalReg]  -- stack layout
+      [Maybe LocalReg]  -- Stack layout: Just x, an item x
+                        --               Nothing: a 1-word gap
+                       -- Start of list is the *young* end
       C_SRT
 
 data CmmReturnInfo = CmmMayReturn
                    | CmmNeverReturns
+    deriving ( Eq )
 
 -- TODO: These types may need refinement
 data ProfilingInfo = ProfilingInfo CmmLit CmmLit -- closure_type, closure_desc
@@ -245,22 +254,26 @@ type HintedCmmFormals = [HintedCmmFormal]
 type HintedCmmFormal  = CmmHinted CmmFormal
 type HintedCmmActual  = CmmHinted CmmActual
 
-data CmmSafety      = CmmUnsafe | CmmSafe C_SRT
+data CmmSafety      = CmmUnsafe | CmmSafe C_SRT | CmmInterruptible
 
 -- | enable us to fold used registers over 'CmmActuals' and 'CmmFormals'
 instance UserOfLocalRegs CmmStmt where
-  foldRegsUsed f set s = stmt s set
-    where stmt (CmmNop)                  = id
-          stmt (CmmComment {})           = id
-          stmt (CmmAssign _ e)           = gen e
-          stmt (CmmStore e1 e2)          = gen e1 . gen e2
-          stmt (CmmCall target _ es _ _) = gen target . gen es
-          stmt (CmmBranch _)             = id
-          stmt (CmmCondBranch e _)       = gen e
-          stmt (CmmSwitch e _)           = gen e
-          stmt (CmmJump e es)            = gen e . gen es
-          stmt (CmmReturn es)            = gen es
-          gen a set = foldRegsUsed f set a
+  foldRegsUsed f (set::b) s = stmt s set
+    where 
+      stmt :: CmmStmt -> b -> b
+      stmt (CmmNop)                  = id
+      stmt (CmmComment {})           = id
+      stmt (CmmAssign _ e)           = gen e
+      stmt (CmmStore e1 e2)          = gen e1 . gen e2
+      stmt (CmmCall target _ es _ _) = gen target . gen es
+      stmt (CmmBranch _)             = id
+      stmt (CmmCondBranch e _)       = gen e
+      stmt (CmmSwitch e _)           = gen e
+      stmt (CmmJump e es)            = gen e . gen es
+      stmt (CmmReturn es)            = gen es
+
+      gen :: UserOfLocalRegs a => a -> b -> b
+      gen a set = foldRegsUsed f set a
 
 instance UserOfLocalRegs CmmCallTarget where
     foldRegsUsed f set (CmmCallee e _) = foldRegsUsed f set e
@@ -376,6 +389,7 @@ data CallishMachOp
   | MO_F32_Exp
   | MO_F32_Sqrt
   | MO_WriteBarrier
+  | MO_Touch         -- Keep variables live (when using interior pointers)
   deriving (Eq, Show)
 
 pprCallishMachOp :: CallishMachOp -> SDoc