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