[project @ 1997-05-19 00:12:10 by sof]
[ghc-hetmet.git] / ghc / compiler / absCSyn / AbsCSyn.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
3 %
4 \section[AbstractC]{Abstract C: the last stop before machine code}
5
6 This ``Abstract C'' data type describes the raw Spineless Tagless
7 machine model at a C-ish level; it is ``abstract'' in that it only
8 includes C-like structures that we happen to need.  The conversion of
9 programs from @StgSyntax@ (basically a functional language) to
10 @AbstractC@ (basically imperative C) is the heart of code generation.
11 From @AbstractC@, one may convert to real C (for portability) or to
12 raw assembler/machine code.
13
14 \begin{code}
15 #include "HsVersions.h"
16
17 module AbsCSyn {- (
18         -- export everything
19         AbstractC(..),
20         CStmtMacro(..),
21         CExprMacro(..),
22         CAddrMode(..),
23         ReturnInfo(..),
24         mkAbstractCs, mkAbsCStmts, mkAlgAltsCSwitch,
25         mkIntCLit,
26         mkAbsCStmtList,
27         mkCCostCentre,
28
29         -- RegRelatives
30         RegRelative(..),
31
32         -- registers
33         MagicId(..), node, infoptr,
34         isVolatileReg, noLiveRegsMask, mkLiveRegsMask,
35         CostRes(Cost)
36     )-} where
37
38 IMP_Ubiq(){-uitous-}
39 IMPORT_DELOOPER(AbsCLoop)
40
41 import Constants        ( mAX_Vanilla_REG, mAX_Float_REG,
42                           mAX_Double_REG, lIVENESS_R1, lIVENESS_R2,
43                           lIVENESS_R3, lIVENESS_R4, lIVENESS_R5,
44                           lIVENESS_R6, lIVENESS_R7, lIVENESS_R8
45                         )
46 import HeapOffs         ( SYN_IE(VirtualSpAOffset), SYN_IE(VirtualSpBOffset),
47                           SYN_IE(VirtualHeapOffset), HeapOffset
48                         )
49 import CLabel           ( CLabel )
50 import CostCentre       ( CostCentre )
51 import Literal          ( mkMachInt, Literal )
52 import PrimRep          ( isFollowableRep, PrimRep(..) )
53 import PrimOp           ( PrimOp )
54 import Unique           ( Unique )
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             -- This used to be RetVecRegRel
94         CAddrMode       -- Any base address mode
95         ReturnInfo      -- How to get the return address from the base address
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                         -- [amode analog: CLabelledCode]
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         RegRelative     -- address of the info ptr
117         CAddrMode       -- cost centre to place in closure
118                         --   CReg CurCostCentre or CC_HDR(R1.p{-Node-})
119         Bool            -- inplace update or allocate
120
121   | COpStmt
122         [CAddrMode]     -- Results
123         PrimOp
124         [CAddrMode]     -- Arguments
125         Int             -- Live registers (may be obtainable from volatility? ADR)
126         [MagicId]       -- Potentially volatile/live registers
127                         -- (to save/restore around the call/op)
128
129         -- INVARIANT: When a PrimOp which can cause GC is used, the
130         -- only live data is tidily on the STG stacks or in the STG
131         -- registers (the code generator ensures this).
132         --
133         -- Why this?  Because if the arguments were arbitrary
134         -- addressing modes, they might be things like (Hp+6) which
135         -- will get utterly spongled by GC.
136
137   | CSimultaneous       -- Perform simultaneously all the statements
138         AbstractC       -- in the nested AbstractC.  They are only
139                         -- allowed to be CAssigns, COpStmts and AbsCNops, so the
140                         -- "simultaneous" part just concerns making
141                         -- sure that permutations work.
142                         -- For example { a := b, b := a }
143                         --      needs to go via (at least one) temporary
144
145   -- see the notes about these next few; they follow below...
146   | CMacroStmt          CStmtMacro      [CAddrMode]
147   | CCallProfCtrMacro   FAST_STRING     [CAddrMode]
148   | CCallProfCCMacro    FAST_STRING     [CAddrMode]
149
150   -- *** the next three [or so...] are DATA (those above are CODE) ***
151
152   | CStaticClosure
153         CLabel  -- The (full, not base) label to use for labelling the closure.
154         ClosureInfo
155         CAddrMode       -- cost centre identifier to place in closure
156         [CAddrMode]     -- free vars; ptrs, then non-ptrs
157
158
159   | CClosureInfoAndCode
160         ClosureInfo     -- Explains placement and layout of closure
161         AbstractC       -- Slow entry point code
162         (Maybe AbstractC)
163                         -- Fast entry point code, if any
164         CAddrMode       -- Address of update code; Nothing => should never be used
165                         -- (which is the case for all except constructors)
166         String          -- Closure description; NB we can't get this from
167                         -- ClosureInfo, because the latter refers to the *right* hand
168                         -- side of a defn, whereas the "description" refers to *left*
169                         -- hand side
170         Int             -- Liveness info; this is here because it is
171                         -- easy to produce w/in the CgMonad; hard
172                         -- thereafter.  (WDP 95/11)
173
174   | CRetVector                  -- Return vector with "holes"
175                                 -- (Nothings) for the default
176         CLabel                  -- vector-table label
177         [Maybe CAddrMode]
178         AbstractC               -- (and what to put in a "hole" [when Nothing])
179
180   | CRetUnVector        -- Direct return
181         CLabel          -- unvector-table label
182         CAddrMode       -- return code
183
184   | CFlatRetVector      -- A labelled block of static data
185         CLabel          -- This is the flattened version of CRetVector
186         [CAddrMode]
187
188   | CCostCentreDecl     -- A cost centre *declaration*
189         Bool            -- True  <=> local => full declaration
190                         -- False <=> extern; just say so
191         CostCentre
192
193   | CClosureUpdInfo
194         AbstractC       -- InRegs Info Table (CClosureInfoTable)
195                         --                    ^^^^^^^^^^^^^^^^^
196                         --                                out of date -- HWL
197
198   | CSplitMarker        -- Split into separate object modules here
199 \end{code}
200
201 About @CMacroStmt@, etc.: notionally, they all just call some
202 arbitrary C~macro or routine, passing the @CAddrModes@ as arguments.
203 However, we distinguish between various flavours of these things,
204 mostly just to keep things somewhat less wild and wooly.
205
206 \begin{description}
207 \item[@CMacroStmt@:]
208 Some {\em essential} bits of the STG execution model are done with C
209 macros.  An example is @STK_CHK@, which checks for stack-space
210 overflow.  This enumeration type lists all such macros:
211 \begin{code}
212 data CStmtMacro
213   = ARGS_CHK_A_LOAD_NODE
214   | ARGS_CHK_A
215   | ARGS_CHK_B_LOAD_NODE
216   | ARGS_CHK_B
217   | HEAP_CHK
218   | STK_CHK
219   | UPD_CAF
220   | UPD_IND
221   | UPD_INPLACE_NOPTRS
222   | UPD_INPLACE_PTRS
223   | UPD_BH_UPDATABLE
224   | UPD_BH_SINGLE_ENTRY
225   | PUSH_STD_UPD_FRAME
226   | POP_STD_UPD_FRAME
227   | SET_TAG
228   | GRAN_FETCH                  -- for GrAnSim only  -- HWL
229   | GRAN_RESCHEDULE             -- for GrAnSim only  -- HWL
230   | GRAN_FETCH_AND_RESCHEDULE   -- for GrAnSim only  -- HWL
231   | THREAD_CONTEXT_SWITCH       -- for GrAnSim only  -- HWL
232   | GRAN_YIELD                  -- for GrAnSim only  -- HWL 
233   deriving Text
234 \end{code}
235
236 \item[@CCallProfCtrMacro@:]
237 The @String@ names a macro that, if \tr{#define}d, will bump one/some
238 of the STG-event profiling counters.
239
240 \item[@CCallProfCCMacro@:]
241 The @String@ names a macro that, if \tr{#define}d, will perform some
242 cost-centre-profiling-related action.
243 \end{description}
244
245 HERE ARE SOME OLD NOTES ABOUT HEAP-CHK ENTRY POINTS:
246
247 \item[@CCallStgC@:]
248 Some parts of the system, {\em notably the storage manager}, are
249 implemented by C~routines that must know something about the internals
250 of the STG world, e.g., where the heap-pointer is.  (The
251 ``C-as-assembler'' documents describes this stuff in detail.)
252
253 This is quite a tricky business, especially with ``optimised~C,'' so
254 we keep close tabs on these fellows.  This enumeration type lists all
255 such ``STG~C'' routines:
256
257 HERE ARE SOME *OLD* NOTES ABOUT HEAP-CHK ENTRY POINTS:
258
259 Heap overflow invokes the garbage collector (of your choice :-), and
260 we have different entry points, to tell the GC the exact configuration
261 before it.
262 \begin{description}
263 \item[Branch of a boxed case:]
264 The @Node@ register points off to somewhere legitimate, the @TagReg@
265 holds the tag, and the @RetReg@ points to the code for the
266 alterative which should be resumed. (ToDo: update)
267
268 \item[Branch of an unboxed case:]
269 The @Node@ register points nowhere of any particular interest, a
270 kind-specific register (@IntReg@, @FloatReg@, etc.) holds the unboxed
271 value, and the @RetReg@ points to the code for the alternative
272 which should be resumed. (ToDo: update)
273
274 \item[Closure entry:]
275 The @Node@ register points to the closure, and the @RetReg@ points
276 to the code to be resumed. (ToDo: update)
277 \end{description}
278
279 %************************************************************************
280 %*                                                                      *
281 \subsection[CAddrMode]{C addressing modes}
282 %*                                                                      *
283 %************************************************************************
284
285 Addressing modes: these have @PrimitiveKinds@ pinned on them.
286 \begin{code}
287 data CAddrMode
288   = CVal  RegRelative PrimRep
289                         -- On RHS of assign: Contents of Magic[n]
290                         -- On LHS of assign: location Magic[n]
291                         -- (ie at addr Magic+n)
292
293   | CAddr RegRelative
294                         -- On RHS of assign: Address of Magic[n]; ie Magic+n
295                         --      n=0 gets the Magic location itself
296                         --      (NB: n=0 case superceded by CReg)
297                         -- On LHS of assign: only sensible if n=0,
298                         --      which gives the magic location itself
299                         --      (NB: superceded by CReg)
300
301   | CReg MagicId        -- To replace (CAddr MagicId 0)
302
303   | CTableEntry             -- CVal should be generalized to allow this
304                 CAddrMode   -- Base
305                 CAddrMode   -- Offset
306                 PrimRep    -- For casting
307
308   | CTemp Unique PrimRep        -- Temporary locations
309         -- ``Temporaries'' correspond to local variables in C, and registers in
310         -- native code.
311
312   | CLbl    CLabel      -- Labels in the runtime system, etc.
313                         -- See comment under CLabelledData about (String,Name)
314             PrimRep     -- the kind is so we can generate accurate C decls
315
316   | CUnVecLbl           -- A choice of labels left up to the back end
317               CLabel    -- direct
318               CLabel    -- vectored
319
320   | CCharLike CAddrMode -- The address of a static char-like closure for
321                         -- the specified character.  It is guaranteed to be in
322                         -- the range 0..255.
323
324   | CIntLike CAddrMode  -- The address of a static int-like closure for the
325                         -- specified small integer.  It is guaranteed to be in the
326                         -- range mIN_INTLIKE..mAX_INTLIKE
327
328   | CString FAST_STRING -- The address of the null-terminated string
329   | CLit    Literal
330   | CLitLit FAST_STRING -- completely literal literal: just spit this String
331                         -- into the C output
332             PrimRep
333
334   | COffset HeapOffset  -- A literal constant, not an offset *from* anything!
335                         -- ToDo: this should really be CLitOffset
336
337   | CCode AbstractC     -- Some code.  Used mainly for return addresses.
338
339   | CLabelledCode CLabel AbstractC  -- Almost defunct? (ToDo?) --JSM
340                         -- Some code that must have a particular label
341                         -- (which is jumpable to)
342
343   | CJoinPoint          -- This is used as the amode of a let-no-escape-bound variable
344         VirtualSpAOffset        -- SpA and SpB values after any volatile free vars
345         VirtualSpBOffset        -- of the rhs have been saved on stack.
346                                 -- Just before the code for the thing is jumped to,
347                                 -- SpA/B will be set to these values,
348                                 -- and then any stack-passed args pushed,
349                                 -- then the code for this thing will be entered
350
351   | CMacroExpr
352         PrimRep         -- the kind of the result
353         CExprMacro      -- the macro to generate a value
354         [CAddrMode]     -- and its arguments
355
356   | CCostCentre         -- If Bool is True ==> it to be printed as a String,
357         CostCentre      -- (*not* as a C identifier or some such).
358         Bool            -- (It's not just the double-quotes on either side;
359                         -- spaces and other funny characters will have been
360                         -- fiddled in the non-String variant.)
361
362 mkCCostCentre cc
363   = --ASSERT(not (currentOrSubsumedCosts cc))
364     --FALSE: We do put subsumedCC in static closures
365     CCostCentre cc False
366 \end{code}
367
368 Various C macros for values which are dependent on the back-end layout.
369
370 \begin{code}
371
372 data CExprMacro
373   = INFO_PTR
374   | ENTRY_CODE
375   | INFO_TAG
376   | EVAL_TAG
377   deriving(Text)
378
379 \end{code}
380
381 A tiny convenience:
382 \begin{code}
383 mkIntCLit :: Int -> CAddrMode
384 mkIntCLit i = CLit (mkMachInt (toInteger i))
385 \end{code}
386
387 %************************************************************************
388 %*                                                                      *
389 \subsection[RegRelative]{@RegRelatives@: ???}
390 %*                                                                      *
391 %************************************************************************
392
393 \begin{code}
394 data RegRelative
395   = HpRel        VirtualHeapOffset      -- virtual offset of Hp
396                  VirtualHeapOffset      -- virtual offset of The Thing
397   | SpARel       VirtualSpAOffset       -- virtual offset of SpA
398                  VirtualSpAOffset       -- virtual offset of The Thing
399   | SpBRel       VirtualSpBOffset       -- virtual offset of SpB
400                  VirtualSpBOffset       -- virtual offset of The Thing
401   | NodeRel      VirtualHeapOffset
402
403 data ReturnInfo
404   = DirectReturn                        -- Jump directly, if possible
405   | StaticVectoredReturn Int            -- Fixed tag, starting at zero
406   | DynamicVectoredReturn CAddrMode     -- Dynamic tag given by amode, starting at zero
407 \end{code}
408
409 %************************************************************************
410 %*                                                                      *
411 \subsection[MagicId]{@MagicIds@: registers and such}
412 %*                                                                      *
413 %************************************************************************
414
415 Much of what happens in Abstract-C is in terms of ``magic'' locations,
416 such as the stack pointer, heap pointer, etc.  If possible, these will
417 be held in registers.
418
419 Here are some notes about what's active when:
420 \begin{description}
421 \item[Always active:]
422         Hp, HpLim, SpA, SpB, SuA, SuB
423
424 \item[Entry set:]
425         ArgPtr1 (= Node)...
426
427 \item[Return set:]
428 Ptr regs: RetPtr1 (= Node), RetPtr2...
429 Int/char regs:  RetData1 (= TagReg = IntReg), RetData2...
430 Float regs: RetFloat1, ...
431 Double regs: RetDouble1, ...
432 \end{description}
433
434 \begin{code}
435 data MagicId
436   = BaseReg     -- mentioned only in nativeGen
437
438   | StkOReg     -- mentioned only in nativeGen
439
440   -- Argument and return registers
441   | VanillaReg          -- pointers, unboxed ints and chars
442         PrimRep         -- PtrRep, IntRep, CharRep, StablePtrRep or ForeignObjRep
443                         --      (in case we need to distinguish)
444         FAST_INT        -- its number (1 .. mAX_Vanilla_REG)
445
446   | FloatReg    -- single-precision floating-point registers
447         FAST_INT        -- its number (1 .. mAX_Float_REG)
448
449   | DoubleReg   -- double-precision floating-point registers
450         FAST_INT        -- its number (1 .. mAX_Double_REG)
451
452   | TagReg      -- to return constructor tags; as almost all returns are vectored,
453                 -- this is rarely used.
454
455   | RetReg      -- topmost return address from the B stack
456
457   | SpA         -- Stack ptr; points to last occupied stack location.
458                 -- Stack grows downward.
459   | SuA         -- mentioned only in nativeGen
460
461   | SpB         -- Basic values, return addresses and update frames.
462                 -- Grows upward.
463   | SuB         -- mentioned only in nativeGen
464
465   | Hp          -- Heap ptr; points to last occupied heap location.
466                 -- Free space at lower addresses.
467
468   | HpLim       -- Heap limit register: mentioned only in nativeGen
469
470   | LivenessReg -- (parallel only) used when we need to record explicitly
471                 -- what registers are live
472
473   | StdUpdRetVecReg     -- mentioned only in nativeGen
474   | StkStubReg          -- register holding STK_STUB_closure (for stubbing dead stack slots)
475
476   | CurCostCentre -- current cost centre register.
477
478   | VoidReg -- see "VoidPrim" type; just a placeholder; no actual register
479
480 node    = VanillaReg PtrRep     ILIT(1) -- A convenient alias for Node
481 infoptr = VanillaReg DataPtrRep ILIT(2) -- An alias for InfoPtr
482
483 --------------------
484 noLiveRegsMask :: Int   -- Mask indicating nothing live
485 noLiveRegsMask = 0
486
487 mkLiveRegsMask
488         :: [MagicId]    -- Candidate live regs; depends what they have in them
489         -> Int
490
491 mkLiveRegsMask regs
492   = foldl do_reg noLiveRegsMask regs
493   where
494     do_reg acc (VanillaReg kind reg_no)
495       | isFollowableRep kind
496       = acc + (reg_tbl !! IBOX(reg_no _SUB_ ILIT(1)))
497
498     do_reg acc anything_else = acc
499
500     reg_tbl -- ToDo: mk Array!
501       = [lIVENESS_R1, lIVENESS_R2, lIVENESS_R3, lIVENESS_R4,
502          lIVENESS_R5, lIVENESS_R6, lIVENESS_R7, lIVENESS_R8]
503 \end{code}
504
505 We need magical @Eq@ because @VanillaReg@s come in multiple flavors.
506
507 \begin{code}
508 instance Eq MagicId where
509     reg1 == reg2 = tag reg1 _EQ_ tag reg2
510      where
511         tag BaseReg          = (ILIT(0) :: FAST_INT)
512         tag StkOReg          = ILIT(1)
513         tag TagReg           = ILIT(2)
514         tag RetReg           = ILIT(3)
515         tag SpA              = ILIT(4)
516         tag SuA              = ILIT(5)
517         tag SpB              = ILIT(6)
518         tag SuB              = ILIT(7)
519         tag Hp               = ILIT(8)
520         tag HpLim            = ILIT(9)
521         tag LivenessReg      = ILIT(10)
522         tag StdUpdRetVecReg  = ILIT(12)
523         tag StkStubReg       = ILIT(13)
524         tag CurCostCentre    = ILIT(14)
525         tag VoidReg          = ILIT(15)
526
527         tag (VanillaReg _ i) = ILIT(15) _ADD_ i
528
529         tag (FloatReg i) = ILIT(15) _ADD_ maxv _ADD_ i
530           where
531             maxv = case mAX_Vanilla_REG of { IBOX(x) -> x }
532
533         tag (DoubleReg i) = ILIT(15) _ADD_ maxv _ADD_ maxf _ADD_ i
534           where
535             maxv = case mAX_Vanilla_REG of { IBOX(x) -> x }
536             maxf = case mAX_Float_REG   of { IBOX(x) -> x }
537 \end{code}
538
539 Returns True for any register that {\em potentially} dies across
540 C calls (or anything near equivalent).  We just say @True@ and
541 let the (machine-specific) registering macros sort things out...
542 \begin{code}
543 isVolatileReg :: MagicId -> Bool
544
545 isVolatileReg any = True
546 --isVolatileReg (FloatReg _)    = True
547 --isVolatileReg (DoubleReg _)   = True
548 \end{code}
549
550 %************************************************************************
551 %*                                                                      *
552 \subsection[AbsCSyn-printing]{Pretty-printing Abstract~C}
553 %*                                                                      *
554 %************************************************************************
555
556 It's in \tr{PprAbsC.lhs}.