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