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