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