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