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