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