[project @ 2001-12-14 15:26:14 by sewardj]
[ghc-hetmet.git] / ghc / compiler / absCSyn / AbsCSyn.lhs
index 6bd34a6..04e1367 100644 (file)
@@ -1,7 +1,7 @@
 %
 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
 %
-% $Id: AbsCSyn.lhs,v 1.34 2000/10/12 13:11:46 simonmar Exp $
+% $Id: AbsCSyn.lhs,v 1.43 2001/12/14 15:26:14 sewardj Exp $
 %
 \section[AbstractC]{Abstract C: the last stop before machine code}
 
@@ -17,6 +17,7 @@ raw assembler/machine code.
 module AbsCSyn {- (
        -- export everything
        AbstractC(..),
+       C_SRT(..)
        CStmtMacro(..),
        CExprMacro(..),
        CAddrMode(..),
@@ -44,13 +45,16 @@ import Constants    ( mAX_Vanilla_REG, mAX_Float_REG,
                          mAX_Double_REG, spRelToInt )
 import CostCentre       ( CostCentre, CostCentreStack )
 import Literal         ( mkMachInt, Literal(..) )
+import ForeignCall     ( CCallSpec )
 import PrimRep         ( PrimRep(..) )
-import PrimOp           ( PrimOp, CCall )
+import MachOp          ( MachOp(..) )
 import Unique           ( Unique )
-import StgSyn          ( SRT(..) )
+import StgSyn          ( StgOp )
 import TyCon           ( TyCon )
 import BitSet                          -- for liveness masks
+import FastTypes
 
+import Outputable
 \end{code}
 
 @AbstractC@ is a list of Abstract~C statements, but the data structure
@@ -113,10 +117,30 @@ stored in a mixed type location.)
        CAddrMode       -- address of the info ptr
        CAddrMode       -- cost centre to place in closure
                        --   CReg CurCostCentre or CC_HDR(R1.p{-Node-})
+       Int             -- size of closure, for profiling
+
+  -- NEW CASES FOR EXPANDED PRIMOPS
+
+  | CMachOpStmt                        -- Machine-level operation
+       (Maybe CAddrMode)       -- 0 or 1 results
+       MachOp
+       [CAddrMode]             -- Arguments
+        (Maybe [MagicId])      -- list of regs which need to be preserved
+       -- across the primop.  This is allowed to be Nothing only if
+       -- machOpIsDefinitelyInline returns True.  And that in turn may
+       -- only return True if we are absolutely sure that the mach op
+       -- can be done inline on all platforms.  
+
+  | CSequential                -- Do the nested AbstractCs sequentially.
+       [AbstractC]     -- In particular, as far as the AbsCUtils.doSimultaneously
+                       -- is concerned, these stmts are to be treated as atomic
+                       -- and are not to be reordered.
+
+  -- end of NEW CASES FOR EXPANDED PRIMOPS
 
   | COpStmt
        [CAddrMode]     -- Results
-       PrimOp
+       StgOp
        [CAddrMode]     -- Arguments
        [MagicId]       -- Potentially volatile/live registers
                        -- (to save/restore around the call/op)
@@ -145,7 +169,7 @@ stored in a mixed type location.)
   | CRetDirect                 -- Direct return
         !Unique                        -- for making labels
        AbstractC               -- return code
-       (CLabel,SRT)            -- SRT info
+       C_SRT                   -- SRT info
        Liveness                -- stack liveness at the return point
 
   -- see the notes about these next few; they follow below...
@@ -163,7 +187,7 @@ stored in a mixed type location.)
        compiling 'foreign import dynamic's)
     -}
   | CCallTypedef Bool {- True => use "typedef"; False => use "extern"-}
-                CCall [CAddrMode] [CAddrMode]
+                CCallSpec Unique [CAddrMode] [CAddrMode]
 
   -- *** the next three [or so...] are DATA (those above are CODE) ***
 
@@ -176,7 +200,8 @@ stored in a mixed type location.)
   | CSRT CLabel [CLabel]       -- SRT declarations: basically an array of 
                                -- pointers to static closures.
   
-  | CBitmap CLabel LivenessMask        -- A larger-than-32-bits bitmap.
+  | CBitmap CLabel LivenessMask        -- A bitmap to be emitted if and only if
+                               -- it is larger than a target machine word.
 
   | CClosureInfoAndCode
        ClosureInfo             -- Explains placement and layout of closure
@@ -191,7 +216,7 @@ stored in a mixed type location.)
   | CRetVector                 -- A labelled block of static data
        CLabel
        [CAddrMode]
-       (CLabel,SRT)            -- SRT info
+       C_SRT                   -- SRT info
        Liveness                -- stack liveness at the return point
 
   | CClosureTbl                -- table of constructors for enumerated types
@@ -212,6 +237,16 @@ stored in a mixed type location.)
                                -- CostCentre.lhs)
 
   | CSplitMarker               -- Split into separate object modules here
+
+-- C_SRT is what StgSyn.SRT gets translated to... 
+-- we add a label for the table, and expect only the 'offset/length' form
+
+data C_SRT = NoC_SRT
+          | C_SRT CLabel !Int{-offset-} !Int{-length-}
+
+needsSRT :: C_SRT -> Bool
+needsSRT NoC_SRT       = False
+needsSRT (C_SRT _ _ _) = True
 \end{code}
 
 About @CMacroStmt@, etc.: notionally, they all just call some
@@ -335,6 +370,11 @@ data CAddrMode
        !PrimRep        -- the kind of the result
        CExprMacro      -- the macro to generate a value
        [CAddrMode]     -- and its arguments
+
+  | CMem   PrimRep     -- A value :: PrimRep, in memory, at the 
+           CAddrMode   -- specified address
+
+  | CBytesPerWord      -- Word size, in bytes, on this platform
 \end{code}
 
 Various C macros for values which are dependent on the back-end layout.
@@ -388,16 +428,16 @@ data ReturnInfo
 hpRel :: VirtualHeapOffset     -- virtual offset of Hp
       -> VirtualHeapOffset     -- virtual offset of The Thing
       -> RegRelative           -- integer offset
-hpRel _IBOX(hp) _IBOX(off) = HpRel (hp _SUB_ off)
+hpRel hp off = HpRel (iUnbox (hp - off))
 
 spRel :: VirtualSpOffset       -- virtual offset of Sp
       -> VirtualSpOffset       -- virtual offset of The Thing
       -> RegRelative           -- integer offset
-spRel sp off = SpRel (case spRelToInt sp off of { _IBOX(i) -> i })
+spRel sp off = SpRel (iUnbox (spRelToInt sp off))
 
 nodeRel :: VirtualHeapOffset
         -> RegRelative
-nodeRel _IBOX(off) = NodeRel off
+nodeRel off = NodeRel (iUnbox off)
 
 \end{code}
 
@@ -411,11 +451,18 @@ We represent liveness bitmaps as a BitSet (whose internal
 representation really is a bitmap).  These are pinned onto case return
 vectors to indicate the state of the stack for the garbage collector.
 
+In the compiled program, liveness bitmaps that fit inside a single
+word (StgWord) are stored as a single word, while larger bitmaps are
+stored as a pointer to an array of words.  When we compile via C
+(especially when we bootstrap via HC files), we generate identical C
+code regardless of whether words are 32- or 64-bit on the target
+machine, by postponing the decision of how to store each liveness
+bitmap to C compilation time (or rather, C preprocessing time).
+
 \begin{code}
 type LivenessMask = [BitSet]
 
-data Liveness = LvSmall BitSet
-              | LvLarge CLabel
+data Liveness = Liveness CLabel LivenessMask
 \end{code}
 
 %************************************************************************
@@ -474,10 +521,11 @@ data MagicId
 
   | CurrentTSO         -- pointer to current thread's TSO
   | CurrentNursery     -- pointer to allocation area
+  | HpAlloc            -- allocation count for heap check failure
 
 
-node   = VanillaReg PtrRep     _ILIT(1) -- A convenient alias for Node
-tagreg  = VanillaReg WordRep    _ILIT(2) -- A convenient alias for TagReg
+node   = VanillaReg PtrRep     (_ILIT 1) -- A convenient alias for Node
+tagreg  = VanillaReg WordRep    (_ILIT 2) -- A convenient alias for TagReg
 
 nodeReg = CReg node
 \end{code}