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