[project @ 2001-11-08 12:56:00 by simonmar]
[ghc-hetmet.git] / ghc / compiler / absCSyn / AbsCSyn.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 % $Id: AbsCSyn.lhs,v 1.39 2001/11/08 12:56:01 simonmar Exp $
5 %
6 \section[AbstractC]{Abstract C: the last stop before machine code}
7
8 This ``Abstract C'' data type describes the raw Spineless Tagless
9 machine model at a C-ish level; it is ``abstract'' in that it only
10 includes C-like structures that we happen to need.  The conversion of
11 programs from @StgSyntax@ (basically a functional language) to
12 @AbstractC@ (basically imperative C) is the heart of code generation.
13 From @AbstractC@, one may convert to real C (for portability) or to
14 raw assembler/machine code.
15
16 \begin{code}
17 module AbsCSyn {- (
18         -- export everything
19         AbstractC(..),
20         C_SRT(..)
21         CStmtMacro(..),
22         CExprMacro(..),
23         CAddrMode(..),
24         ReturnInfo(..),
25         mkAbstractCs, mkAbsCStmts, mkAlgAltsCSwitch,
26         mkIntCLit,
27         mkAbsCStmtList,
28         mkCCostCentre,
29
30         -- RegRelatives
31         RegRelative(..),
32
33         -- registers
34         MagicId(..), node, infoptr,
35         isVolatileReg,
36         CostRes(Cost)
37     )-} where
38
39 #include "HsVersions.h"
40
41 import {-# SOURCE #-} ClosureInfo ( ClosureInfo )
42
43 import CLabel
44 import Constants        ( mAX_Vanilla_REG, mAX_Float_REG,
45                           mAX_Double_REG, spRelToInt )
46 import CostCentre       ( CostCentre, CostCentreStack )
47 import Literal          ( mkMachInt, Literal(..) )
48 import ForeignCall      ( CCallSpec )
49 import PrimRep          ( PrimRep(..) )
50 import Unique           ( Unique )
51 import StgSyn           ( StgOp )
52 import TyCon            ( TyCon )
53 import BitSet                           -- for liveness masks
54 import FastTypes
55
56 \end{code}
57
58 @AbstractC@ is a list of Abstract~C statements, but the data structure
59 is tree-ish, for easier and more efficient putting-together.
60 \begin{code}
61 absCNop = AbsCNop
62
63 data AbstractC
64   = AbsCNop
65   | AbsCStmts           AbstractC AbstractC
66
67   -- and the individual stmts...
68 \end{code}
69
70 A note on @CAssign@: In general, the type associated with an assignment
71 is the type of the lhs.  However, when the lhs is a pointer to mixed
72 types (e.g. SpB relative), the type of the assignment is the type of
73 the rhs for float types, or the generic StgWord for all other types.
74 (In particular, a CharRep on the rhs is promoted to IntRep when
75 stored in a mixed type location.)
76
77 \begin{code}
78   | CAssign
79         !CAddrMode      -- target
80         !CAddrMode      -- source
81
82   | CJump
83         CAddrMode       -- Put this in the program counter
84                         -- eg `CJump (CReg (VanillaReg PtrRep 1))' puts Ret1 in PC
85                         -- Enter can be done by:
86                         --        CJump (CVal NodeRel zeroOff)
87
88   | CFallThrough
89         CAddrMode       -- Fall through into this routine
90                         -- (for the benefit of the native code generators)
91                         -- Equivalent to CJump in C land
92
93   | CReturn             -- Perform a return
94         CAddrMode       -- Address of a RET_<blah> info table
95         ReturnInfo      -- Whether it's a direct or vectored return
96
97   | CSwitch !CAddrMode
98         [(Literal, AbstractC)]  -- alternatives
99         AbstractC               -- default; if there is no real Abstract C in here
100                                 -- (e.g., all comments; see function "nonemptyAbsC"),
101                                 -- then that means the default _cannot_ occur.
102                                 -- If there is only one alternative & no default code,
103                                 -- then there is no need to check the tag.
104                                 -- Therefore, e.g.:
105                                 --  CSwitch m [(tag,code)] AbsCNop == code
106
107   | CCodeBlock CLabel AbstractC
108                         -- A labelled block of code; this "statement" is not
109                         -- executed; rather, the labelled code will be hoisted
110                         -- out to the top level (out of line) & it can be
111                         -- jumped to.
112
113   | CInitHdr            -- to initialise the header of a closure (both fixed/var parts)
114         ClosureInfo
115         CAddrMode       -- address of the info ptr
116         CAddrMode       -- cost centre to place in closure
117                         --   CReg CurCostCentre or CC_HDR(R1.p{-Node-})
118
119   | COpStmt
120         [CAddrMode]     -- Results
121         StgOp
122         [CAddrMode]     -- Arguments
123         [MagicId]       -- Potentially volatile/live registers
124                         -- (to save/restore around the call/op)
125
126         -- INVARIANT: When a PrimOp which can cause GC is used, the
127         -- only live data is tidily on the STG stacks or in the STG
128         -- registers (the code generator ensures this).
129         --
130         -- Why this?  Because if the arguments were arbitrary
131         -- addressing modes, they might be things like (Hp+6) which
132         -- will get utterly spongled by GC.
133
134   | CSimultaneous       -- Perform simultaneously all the statements
135         AbstractC       -- in the nested AbstractC.  They are only
136                         -- allowed to be CAssigns, COpStmts and AbsCNops, so the
137                         -- "simultaneous" part just concerns making
138                         -- sure that permutations work.
139                         -- For example { a := b, b := a }
140                         --      needs to go via (at least one) temporary
141
142   | CCheck              -- heap or stack checks, or both.  
143         CCheckMacro     -- These might include some code to fill in tags 
144         [CAddrMode]     -- on the stack, so we can't use CMacroStmt below.
145         AbstractC
146
147   | CRetDirect                  -- Direct return
148         !Unique                 -- for making labels
149         AbstractC               -- return code
150         C_SRT                   -- SRT info
151         Liveness                -- stack liveness at the return point
152
153   -- see the notes about these next few; they follow below...
154   | CMacroStmt          CStmtMacro      [CAddrMode]
155   | CCallProfCtrMacro   FAST_STRING     [CAddrMode]
156   | CCallProfCCMacro    FAST_STRING     [CAddrMode]
157
158     {- The presence of this constructor is a makeshift solution;
159        it being used to work around a gcc-related problem of
160        handling typedefs within statement blocks (or, rather,
161        the inability to do so.)
162        
163        The AbstractC flattener takes care of lifting out these
164        typedefs if needs be (i.e., when generating .hc code and
165        compiling 'foreign import dynamic's)
166     -}
167   | CCallTypedef Bool {- True => use "typedef"; False => use "extern"-}
168                  CCallSpec Unique [CAddrMode] [CAddrMode]
169
170   -- *** the next three [or so...] are DATA (those above are CODE) ***
171
172   | CStaticClosure
173         CLabel  -- The (full, not base) label to use for labelling the closure.
174         ClosureInfo
175         CAddrMode               -- cost centre identifier to place in closure
176         [CAddrMode]             -- free vars; ptrs, then non-ptrs.
177
178   | CSRT CLabel [CLabel]        -- SRT declarations: basically an array of 
179                                 -- pointers to static closures.
180   
181   | CBitmap CLabel LivenessMask -- A bitmap to be emitted if and only if
182                                 -- it is larger than a target machine word.
183
184   | CClosureInfoAndCode
185         ClosureInfo             -- Explains placement and layout of closure
186         AbstractC               -- Slow entry point code
187         (Maybe AbstractC)
188                                 -- Fast entry point code, if any
189         String                  -- Closure description; NB we can't get this
190                                 -- from ClosureInfo, because the latter refers 
191                                 -- to the *right* hand side of a defn, whereas
192                                 -- the  "description" refers to *left* hand side
193
194   | CRetVector                  -- A labelled block of static data
195         CLabel
196         [CAddrMode]
197         C_SRT                   -- SRT info
198         Liveness                -- stack liveness at the return point
199
200   | CClosureTbl                 -- table of constructors for enumerated types
201         TyCon                   -- which TyCon this table is for
202
203   | CModuleInitBlock            -- module initialisation block
204         CLabel                  -- label for init block
205         AbstractC               -- initialisation code
206
207   | CCostCentreDecl             -- A cost centre *declaration*
208         Bool                    -- True  <=> local => full declaration
209                                 -- False <=> extern; just say so
210         CostCentre
211
212   | CCostCentreStackDecl        -- A cost centre stack *declaration*
213         CostCentreStack         -- this is the declaration for a
214                                 -- pre-defined singleton CCS (see 
215                                 -- CostCentre.lhs)
216
217   | CSplitMarker                -- Split into separate object modules here
218
219 -- C_SRT is what StgSyn.SRT gets translated to... 
220 -- we add a label for the table, and expect only the 'offset/length' form
221
222 data C_SRT = NoC_SRT
223            | C_SRT CLabel !Int{-offset-} !Int{-length-}
224
225 needsSRT :: C_SRT -> Bool
226 needsSRT NoC_SRT       = False
227 needsSRT (C_SRT _ _ _) = True
228 \end{code}
229
230 About @CMacroStmt@, etc.: notionally, they all just call some
231 arbitrary C~macro or routine, passing the @CAddrModes@ as arguments.
232 However, we distinguish between various flavours of these things,
233 mostly just to keep things somewhat less wild and wooly.
234
235 \begin{description}
236 \item[@CMacroStmt@:]
237 Some {\em essential} bits of the STG execution model are done with C
238 macros.  An example is @STK_CHK@, which checks for stack-space
239 overflow.  This enumeration type lists all such macros:
240 \begin{code}
241 data CStmtMacro
242   = ARGS_CHK                            -- arg satisfaction check
243   | ARGS_CHK_LOAD_NODE                  -- arg check for top-level functions
244   | UPD_CAF                             -- update CAF closure with indirection
245   | UPD_BH_UPDATABLE                    -- eager backholing
246   | UPD_BH_SINGLE_ENTRY                 -- more eager blackholing
247   | PUSH_UPD_FRAME                      -- push update frame
248   | PUSH_SEQ_FRAME                      -- push seq frame
249   | UPDATE_SU_FROM_UPD_FRAME            -- pull Su out of the update frame
250   | SET_TAG                             -- set TagReg if it exists
251
252   | REGISTER_FOREIGN_EXPORT             -- register a foreign exported fun
253   | REGISTER_IMPORT                     -- register an imported module
254   | REGISTER_DIMPORT                    -- register an imported module from
255                                         -- another DLL
256
257   | GRAN_FETCH                  -- for GrAnSim only  -- HWL
258   | GRAN_RESCHEDULE             -- for GrAnSim only  -- HWL
259   | GRAN_FETCH_AND_RESCHEDULE   -- for GrAnSim only  -- HWL
260   | THREAD_CONTEXT_SWITCH       -- for GrAnSim only  -- HWL
261   | GRAN_YIELD                  -- for GrAnSim only  -- HWL 
262 \end{code}
263
264 Heap/Stack checks.  There are far too many of these.
265
266 \begin{code}
267 data CCheckMacro
268
269   = HP_CHK_NP                           -- heap/stack checks when
270   | STK_CHK_NP                          -- node points to the closure
271   | HP_STK_CHK_NP
272   | HP_CHK_SEQ_NP                       -- for 'seq' style case alternatives
273
274   | HP_CHK                              -- heap/stack checks when
275   | STK_CHK                             -- node doesn't point
276   | HP_STK_CHK
277                                         -- case alternative heap checks:
278
279   | HP_CHK_NOREGS                       --   no registers live
280   | HP_CHK_UNPT_R1                      --   R1 is boxed/unlifted
281   | HP_CHK_UNBX_R1                      --   R1 is unboxed
282   | HP_CHK_F1                           --   FloatReg1 (only) is live 
283   | HP_CHK_D1                           --   DblReg1   (only) is live
284   | HP_CHK_L1                           --   LngReg1   (only) is live
285   | HP_CHK_UT_ALT                       --   unboxed tuple return.
286
287   | HP_CHK_GEN                          -- generic heap check
288 \end{code}
289
290 \item[@CCallProfCtrMacro@:]
291 The @String@ names a macro that, if \tr{#define}d, will bump one/some
292 of the STG-event profiling counters.
293
294 \item[@CCallProfCCMacro@:]
295 The @String@ names a macro that, if \tr{#define}d, will perform some
296 cost-centre-profiling-related action.
297 \end{description}
298
299 %************************************************************************
300 %*                                                                      *
301 \subsection[CAddrMode]{C addressing modes}
302 %*                                                                      *
303 %************************************************************************
304
305 \begin{code}
306 data CAddrMode
307   = CVal  RegRelative PrimRep
308                         -- On RHS of assign: Contents of Magic[n]
309                         -- On LHS of assign: location Magic[n]
310                         -- (ie at addr Magic+n)
311
312   | CAddr RegRelative
313                         -- On RHS of assign: Address of Magic[n]; ie Magic+n
314                         --      n=0 gets the Magic location itself
315                         --      (NB: n=0 case superceded by CReg)
316                         -- On LHS of assign: only sensible if n=0,
317                         --      which gives the magic location itself
318                         --      (NB: superceded by CReg)
319
320   | CReg MagicId        -- To replace (CAddr MagicId 0)
321
322   | CTemp !Unique !PrimRep      -- Temporary locations
323         -- ``Temporaries'' correspond to local variables in C, and registers in
324         -- native code.
325
326   | CLbl    CLabel      -- Labels in the runtime system, etc.
327             PrimRep     -- the kind is so we can generate accurate C decls
328
329   | CCharLike CAddrMode -- The address of a static char-like closure for
330                         -- the specified character.  It is guaranteed to be in
331                         -- the range mIN_CHARLIKE..mAX_CHARLIKE
332
333   | CIntLike CAddrMode  -- The address of a static int-like closure for the
334                         -- specified small integer.  It is guaranteed to be in
335                         -- the range mIN_INTLIKE..mAX_INTLIKE
336
337   | CLit    Literal
338
339   | CJoinPoint          -- This is used as the amode of a let-no-escape-bound
340                         -- variable.
341         VirtualSpOffset   -- Sp value after any volatile free vars
342                           -- of the rhs have been saved on stack.
343                           -- Just before the code for the thing is jumped to,
344                           -- Sp will be set to this value,
345                           -- and then any stack-passed args pushed,
346                           -- then the code for this thing will be entered
347   | CMacroExpr
348         !PrimRep        -- the kind of the result
349         CExprMacro      -- the macro to generate a value
350         [CAddrMode]     -- and its arguments
351 \end{code}
352
353 Various C macros for values which are dependent on the back-end layout.
354
355 \begin{code}
356
357 data CExprMacro
358   = ENTRY_CODE
359   | ARG_TAG                             -- stack argument tagging
360   | GET_TAG                             -- get current constructor tag
361   | UPD_FRAME_UPDATEE
362   | CCS_HDR
363
364 \end{code}
365
366 Convenience functions:
367
368 \begin{code}
369 mkIntCLit :: Int -> CAddrMode
370 mkIntCLit i = CLit (mkMachInt (toInteger i))
371
372 mkCString :: FAST_STRING -> CAddrMode
373 mkCString s = CLit (MachStr s)
374
375 mkCCostCentre :: CostCentre -> CAddrMode
376 mkCCostCentre cc = CLbl (mkCC_Label cc) DataPtrRep
377
378 mkCCostCentreStack :: CostCentreStack -> CAddrMode
379 mkCCostCentreStack ccs = CLbl (mkCCS_Label ccs) DataPtrRep
380 \end{code}
381
382 %************************************************************************
383 %*                                                                      *
384 \subsection[RegRelative]{@RegRelatives@: ???}
385 %*                                                                      *
386 %************************************************************************
387
388 \begin{code}
389 data RegRelative
390   = HpRel       FastInt -- }
391   | SpRel       FastInt -- }- offsets in StgWords
392   | NodeRel     FastInt -- }
393   | CIndex      CAddrMode CAddrMode PrimRep     -- pointer arithmetic :-)
394                                                 -- CIndex a b k === (k*)a[b]
395
396 data ReturnInfo
397   = DirectReturn                        -- Jump directly, if possible
398   | StaticVectoredReturn Int            -- Fixed tag, starting at zero
399   | DynamicVectoredReturn CAddrMode     -- Dynamic tag given by amode, starting at zero
400
401 hpRel :: VirtualHeapOffset      -- virtual offset of Hp
402       -> VirtualHeapOffset      -- virtual offset of The Thing
403       -> RegRelative            -- integer offset
404 hpRel hp off = HpRel (iUnbox (hp - off))
405
406 spRel :: VirtualSpOffset        -- virtual offset of Sp
407       -> VirtualSpOffset        -- virtual offset of The Thing
408       -> RegRelative            -- integer offset
409 spRel sp off = SpRel (iUnbox (spRelToInt sp off))
410
411 nodeRel :: VirtualHeapOffset
412         -> RegRelative
413 nodeRel off = NodeRel (iUnbox off)
414
415 \end{code}
416
417 %************************************************************************
418 %*                                                                      *
419 \subsection[Liveness]{Liveness Masks}
420 %*                                                                      *
421 %************************************************************************
422
423 We represent liveness bitmaps as a BitSet (whose internal
424 representation really is a bitmap).  These are pinned onto case return
425 vectors to indicate the state of the stack for the garbage collector.
426
427 In the compiled program, liveness bitmaps that fit inside a single
428 word (StgWord) are stored as a single word, while larger bitmaps are
429 stored as a pointer to an array of words.  When we compile via C
430 (especially when we bootstrap via HC files), we generate identical C
431 code regardless of whether words are 32- or 64-bit on the target
432 machine, by postponing the decision of how to store each liveness
433 bitmap to C compilation time (or rather, C preprocessing time).
434
435 \begin{code}
436 type LivenessMask = [BitSet]
437
438 data Liveness = Liveness CLabel LivenessMask
439 \end{code}
440
441 %************************************************************************
442 %*                                                                      *
443 \subsection[HeapOffset]{@Heap Offsets@}
444 %*                                                                      *
445 %************************************************************************
446
447 This used to be a grotesquely complicated datatype in an attempt to
448 hide the details of header sizes from the compiler itself.  Now these
449 constants are imported from the RTS, and we deal in real Ints.
450
451 \begin{code}
452 type HeapOffset = Int                   -- ToDo: remove
453
454 type VirtualHeapOffset  = HeapOffset
455 type VirtualSpOffset    = Int
456
457 type HpRelOffset        = HeapOffset
458 type SpRelOffset        = Int
459 \end{code}
460
461 %************************************************************************
462 %*                                                                      *
463 \subsection[MagicId]{@MagicIds@: registers and such}
464 %*                                                                      *
465 %************************************************************************
466
467 \begin{code}
468 data MagicId
469   = BaseReg     -- mentioned only in nativeGen
470
471   -- Argument and return registers
472   | VanillaReg          -- pointers, unboxed ints and chars
473         PrimRep
474         FastInt -- its number (1 .. mAX_Vanilla_REG)
475
476   | FloatReg            -- single-precision floating-point registers
477         FastInt -- its number (1 .. mAX_Float_REG)
478
479   | DoubleReg           -- double-precision floating-point registers
480         FastInt -- its number (1 .. mAX_Double_REG)
481
482   -- STG registers
483   | Sp                  -- Stack ptr; points to last occupied stack location.
484   | Su                  -- Stack update frame pointer
485   | SpLim               -- Stack limit
486   | Hp                  -- Heap ptr; points to last occupied heap location.
487   | HpLim               -- Heap limit register
488   | CurCostCentre       -- current cost centre register.
489   | VoidReg             -- see "VoidPrim" type; just a placeholder; 
490                         --   no actual register
491   | LongReg             -- long int registers (64-bit, really)
492         PrimRep         -- Int64Rep or Word64Rep
493         FastInt -- its number (1 .. mAX_Long_REG)
494
495   | CurrentTSO          -- pointer to current thread's TSO
496   | CurrentNursery      -- pointer to allocation area
497   | HpAlloc             -- allocation count for heap check failure
498
499
500 node    = VanillaReg PtrRep     (_ILIT 1) -- A convenient alias for Node
501 tagreg  = VanillaReg WordRep    (_ILIT 2) -- A convenient alias for TagReg
502
503 nodeReg = CReg node
504 \end{code}
505
506 We need magical @Eq@ because @VanillaReg@s come in multiple flavors.
507
508 \begin{code}
509 instance Eq MagicId where
510     reg1 == reg2 = tag reg1 ==# tag reg2
511      where
512         tag BaseReg          = (_ILIT(0) :: FastInt)
513         tag Sp               = _ILIT(1)
514         tag Su               = _ILIT(2)
515         tag SpLim            = _ILIT(3)
516         tag Hp               = _ILIT(4)
517         tag HpLim            = _ILIT(5)
518         tag CurCostCentre    = _ILIT(6)
519         tag VoidReg          = _ILIT(7)
520
521         tag (VanillaReg _ i) = _ILIT(8) +# i
522
523         tag (FloatReg i)  = _ILIT(8) +# maxv +# i
524         tag (DoubleReg i) = _ILIT(8) +# maxv +# maxf +# i
525         tag (LongReg _ i) = _ILIT(8) +# maxv +# maxf +# maxd +# i
526
527         maxv = iUnbox mAX_Vanilla_REG
528         maxf = iUnbox mAX_Float_REG
529         maxd = iUnbox mAX_Double_REG
530 \end{code}
531
532 Returns True for any register that {\em potentially} dies across
533 C calls (or anything near equivalent).  We just say @True@ and
534 let the (machine-specific) registering macros sort things out...
535
536 \begin{code}
537 isVolatileReg :: MagicId -> Bool
538 isVolatileReg any = True
539 \end{code}