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