[project @ 1998-12-02 13:17:09 by simonm]
[ghc-hetmet.git] / ghc / compiler / absCSyn / AbsCSyn.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 % $Id: AbsCSyn.lhs,v 1.18 1998/12/02 13:17:16 simonm Exp $
5 %
6 \section[AbstractC]{Abstract C: the last stop before machine code}
7
8 This ``Abstract C'' data type describes the raw Spineless Tagless
9 machine model at a C-ish level; it is ``abstract'' in that it only
10 includes C-like structures that we happen to need.  The conversion of
11 programs from @StgSyntax@ (basically a functional language) to
12 @AbstractC@ (basically imperative C) is the heart of code generation.
13 From @AbstractC@, one may convert to real C (for portability) or to
14 raw assembler/machine code.
15
16 \begin{code}
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,
35         CostRes(Cost)
36     )-} where
37
38 #include "HsVersions.h"
39
40 import {-# SOURCE #-} ClosureInfo ( ClosureInfo )
41
42 #if  ! OMIT_NATIVE_CODEGEN
43 import {-# SOURCE #-} MachMisc
44 #endif
45
46 import CLabel
47 import Constants        ( mAX_Vanilla_REG, mAX_Float_REG,
48                           mAX_Double_REG, spRelToInt )
49 import CostCentre       ( CostCentre, CostCentreStack )
50 import Const            ( mkMachInt, Literal )
51 import PrimRep          ( PrimRep(..) )
52 import PrimOp           ( PrimOp )
53 import Unique           ( Unique )
54 import StgSyn           ( SRT(..) )
55 import BitSet                           -- for liveness masks
56
57 \end{code}
58
59 @AbstractC@ is a list of Abstract~C statements, but the data structure
60 is tree-ish, for easier and more efficient putting-together.
61 \begin{code}
62 absCNop = AbsCNop
63
64 data AbstractC
65   = AbsCNop
66   | AbsCStmts           AbstractC AbstractC
67
68   -- and the individual stmts...
69 \end{code}
70
71 A note on @CAssign@: In general, the type associated with an assignment
72 is the type of the lhs.  However, when the lhs is a pointer to mixed
73 types (e.g. SpB relative), the type of the assignment is the type of
74 the rhs for float types, or the generic StgWord for all other types.
75 (In particular, a CharRep on the rhs is promoted to IntRep when
76 stored in a mixed type location.)
77
78 \begin{code}
79   | CAssign
80         CAddrMode       -- target
81         CAddrMode       -- source
82
83   | CJump
84         CAddrMode       -- Put this in the program counter
85                         -- eg `CJump (CReg (VanillaReg PtrRep 1))' puts Ret1 in PC
86                         -- Enter can be done by:
87                         --        CJump (CVal NodeRel zeroOff)
88
89   | CFallThrough
90         CAddrMode       -- Fall through into this routine
91                         -- (for the benefit of the native code generators)
92                         -- Equivalent to CJump in C land
93
94   | CReturn             -- This used to be RetVecRegRel
95         CAddrMode       -- Any base address mode
96         ReturnInfo      -- How to get the return address from the base address
97
98   | CSwitch CAddrMode
99         [(Literal, AbstractC)]  -- alternatives
100         AbstractC               -- default; if there is no real Abstract C in here
101                                 -- (e.g., all comments; see function "nonemptyAbsC"),
102                                 -- then that means the default _cannot_ occur.
103                                 -- If there is only one alternative & no default code,
104                                 -- then there is no need to check the tag.
105                                 -- Therefore, e.g.:
106                                 --  CSwitch m [(tag,code)] AbsCNop == code
107
108   | CCodeBlock CLabel AbstractC
109                         -- A labelled block of code; this "statement" is not
110                         -- executed; rather, the labelled code will be hoisted
111                         -- out to the top level (out of line) & it can be
112                         -- jumped to.
113
114   | CInitHdr            -- to initialise the header of a closure (both fixed/var parts)
115         ClosureInfo
116         RegRelative     -- address of the info ptr
117         CAddrMode       -- cost centre to place in closure
118                         --   CReg CurCostCentre or CC_HDR(R1.p{-Node-})
119
120   | COpStmt
121         [CAddrMode]     -- Results
122         PrimOp
123         [CAddrMode]     -- Arguments
124         [MagicId]       -- Potentially volatile/live registers
125                         -- (to save/restore around the call/op)
126
127         -- INVARIANT: When a PrimOp which can cause GC is used, the
128         -- only live data is tidily on the STG stacks or in the STG
129         -- registers (the code generator ensures this).
130         --
131         -- Why this?  Because if the arguments were arbitrary
132         -- addressing modes, they might be things like (Hp+6) which
133         -- will get utterly spongled by GC.
134
135   | CSimultaneous       -- Perform simultaneously all the statements
136         AbstractC       -- in the nested AbstractC.  They are only
137                         -- allowed to be CAssigns, COpStmts and AbsCNops, so the
138                         -- "simultaneous" part just concerns making
139                         -- sure that permutations work.
140                         -- For example { a := b, b := a }
141                         --      needs to go via (at least one) temporary
142
143   | CCheck              -- heap or stack checks, or both.  
144         CCheckMacro     -- These might include some code to fill in tags 
145         [CAddrMode]     -- on the stack, so we can't use CMacroStmt below.
146         AbstractC
147
148   | CRetDirect                  -- Direct return
149         Unique                  -- for making labels
150         AbstractC               -- return code
151         (CLabel,SRT)            -- SRT info
152         Liveness                -- stack liveness at the return point
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 presence of this constructor is a makeshift solution;
160        it being used to work around a gcc-related problem of
161        handling typedefs within statement blocks (or, rather,
162        the inability to do so.)
163        
164        The AbstractC flattener takes care of lifting out these
165        typedefs if needs be (i.e., when generating .hc code and
166        compiling 'foreign import dynamic's)
167     -}
168   | CCallTypedef        PrimOp{-CCallOp-} [CAddrMode] [CAddrMode]
169
170   -- *** the next three [or so...] are DATA (those above are CODE) ***
171
172   | CStaticClosure
173         CLabel  -- The (full, not base) label to use for labelling the closure.
174         ClosureInfo
175         CAddrMode               -- cost centre identifier to place in closure
176         [CAddrMode]             -- free vars; ptrs, then non-ptrs.
177
178   | CSRT CLabel [CLabel]        -- SRT declarations: basically an array of 
179                                 -- pointers to static closures.
180   
181   | CBitmap CLabel LivenessMask -- A larger-than-32-bits bitmap.
182
183   | CClosureInfoAndCode
184         ClosureInfo             -- Explains placement and layout of closure
185         AbstractC               -- Slow entry point code
186         (Maybe AbstractC)
187                                 -- Fast entry point code, if any
188         (CLabel,SRT)            -- SRT info
189         String                  -- Closure description; NB we can't get this
190                                 -- from ClosureInfo, because the latter refers 
191                                 -- to the *right* hand side of a defn, whereas
192                                 -- the  "description" refers to *left* hand side
193
194   | CRetVector                  -- A labelled block of static data
195         CLabel
196         [CAddrMode]
197         (CLabel,SRT)            -- SRT info
198         Liveness                -- stack liveness at the return point
199
200   | CCostCentreDecl             -- A cost centre *declaration*
201         Bool                    -- True  <=> local => full declaration
202                                 -- False <=> extern; just say so
203         CostCentre
204
205   | CCostCentreStackDecl        -- A cost centre stack *declaration*
206         CostCentreStack         -- this is the declaration for a
207                                 -- pre-defined singleton CCS (see 
208                                 -- CostCentre.lhs)
209
210   | CSplitMarker                -- Split into separate object modules here
211 \end{code}
212
213 About @CMacroStmt@, etc.: notionally, they all just call some
214 arbitrary C~macro or routine, passing the @CAddrModes@ as arguments.
215 However, we distinguish between various flavours of these things,
216 mostly just to keep things somewhat less wild and wooly.
217
218 \begin{description}
219 \item[@CMacroStmt@:]
220 Some {\em essential} bits of the STG execution model are done with C
221 macros.  An example is @STK_CHK@, which checks for stack-space
222 overflow.  This enumeration type lists all such macros:
223 \begin{code}
224 data CStmtMacro
225   = ARGS_CHK                            -- arg satisfaction check
226   | ARGS_CHK_LOAD_NODE                  -- arg check for top-level functions
227   | UPD_CAF                             -- update CAF closure with indirection
228   | UPD_BH_UPDATABLE                    -- eager backholing
229   | UPD_BH_SINGLE_ENTRY                 -- more eager blackholing
230   | PUSH_UPD_FRAME                      -- push update frame
231   | PUSH_SEQ_FRAME                      -- push seq frame
232   | SET_TAG                             -- set TagReg if it exists
233   | GRAN_FETCH                  -- for GrAnSim only  -- HWL
234   | GRAN_RESCHEDULE             -- for GrAnSim only  -- HWL
235   | GRAN_FETCH_AND_RESCHEDULE   -- for GrAnSim only  -- HWL
236   | THREAD_CONTEXT_SWITCH       -- for GrAnSim only  -- HWL
237   | GRAN_YIELD                  -- for GrAnSim only  -- HWL 
238   deriving Text
239 \end{code}
240
241 Heap/Stack checks.  There are far too many of these.
242
243 \begin{code}
244 data CCheckMacro
245
246   = HP_CHK_NP                           -- heap/stack checks when
247   | STK_CHK_NP                          -- node points to the closure
248   | HP_STK_CHK_NP
249   | HP_CHK_SEQ_NP                       -- for 'seq' style case alternatives
250
251   | HP_CHK                              -- heap/stack checks when
252   | STK_CHK                             -- node doesn't point
253   | HP_STK_CHK
254                                         -- case alternative heap checks:
255
256   | HP_CHK_NOREGS                       --   no registers live
257   | HP_CHK_UNPT_R1                      --   R1 is boxed/unlifted
258   | HP_CHK_UNBX_R1                      --   R1 is unboxed
259   | HP_CHK_F1                           --   FloatReg1 (only) is live 
260   | HP_CHK_D1                           --   DblReg1   (only) is live
261   | HP_CHK_L1                           --   LngReg1   (only) is live
262   | HP_CHK_UT_ALT                       --   unboxed tuple return.
263
264   | HP_CHK_GEN                          -- generic heap check
265   deriving Text
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 %************************************************************************
278 %*                                                                      *
279 \subsection[CAddrMode]{C addressing modes}
280 %*                                                                      *
281 %************************************************************************
282
283 \begin{code}
284 data CAddrMode
285   = CVal  RegRelative PrimRep
286                         -- On RHS of assign: Contents of Magic[n]
287                         -- On LHS of assign: location Magic[n]
288                         -- (ie at addr Magic+n)
289
290   | CAddr RegRelative
291                         -- On RHS of assign: Address of Magic[n]; ie Magic+n
292                         --      n=0 gets the Magic location itself
293                         --      (NB: n=0 case superceded by CReg)
294                         -- On LHS of assign: only sensible if n=0,
295                         --      which gives the magic location itself
296                         --      (NB: superceded by CReg)
297
298   | CReg MagicId        -- To replace (CAddr MagicId 0)
299
300   | CTableEntry             -- CVal should be generalized to allow this
301                 CAddrMode   -- Base
302                 CAddrMode   -- Offset
303                 PrimRep    -- For casting
304
305   | CTemp Unique PrimRep        -- Temporary locations
306         -- ``Temporaries'' correspond to local variables in C, and registers in
307         -- native code.
308
309   | CLbl    CLabel      -- Labels in the runtime system, etc.
310             PrimRep     -- the kind is so we can generate accurate C decls
311
312   | CCharLike CAddrMode -- The address of a static char-like closure for
313                         -- the specified character.  It is guaranteed to be in
314                         -- the range 0..255.
315
316   | CIntLike CAddrMode  -- The address of a static int-like closure for the
317                         -- specified small integer.  It is guaranteed to be in
318                         -- the range mIN_INTLIKE..mAX_INTLIKE
319
320   | CString FAST_STRING -- The address of the null-terminated string
321   | CLit    Literal
322   | CLitLit FAST_STRING -- completely literal literal: just spit this String
323                         -- into the C output
324             PrimRep
325
326   | CJoinPoint          -- This is used as the amode of a let-no-escape-bound
327                         -- variable.
328         VirtualSpOffset   -- Sp value after any volatile free vars
329                           -- of the rhs have been saved on stack.
330                           -- Just before the code for the thing is jumped to,
331                           -- Sp will be set to this value,
332                           -- and then any stack-passed args pushed,
333                           -- then the code for this thing will be entered
334   | CMacroExpr
335         !PrimRep        -- the kind of the result
336         CExprMacro      -- the macro to generate a value
337         [CAddrMode]     -- and its arguments
338 \end{code}
339
340 Various C macros for values which are dependent on the back-end layout.
341
342 \begin{code}
343
344 data CExprMacro
345   = ENTRY_CODE
346   | ARG_TAG                             -- stack argument tagging
347   | GET_TAG                             -- get current constructor tag
348   deriving(Text)
349
350 \end{code}
351
352 Convenience functions:
353
354 \begin{code}
355 mkIntCLit :: Int -> CAddrMode
356 mkIntCLit i = CLit (mkMachInt (toInteger i))
357
358 mkCCostCentre :: CostCentre -> CAddrMode
359 mkCCostCentre cc = CLbl (mkCC_Label cc) DataPtrRep
360
361 mkCCostCentreStack :: CostCentreStack -> CAddrMode
362 mkCCostCentreStack ccs = CLbl (mkCCS_Label ccs) DataPtrRep
363 \end{code}
364
365 %************************************************************************
366 %*                                                                      *
367 \subsection[RegRelative]{@RegRelatives@: ???}
368 %*                                                                      *
369 %************************************************************************
370
371 \begin{code}
372 data RegRelative
373   = HpRel       FAST_INT        -- }
374   | SpRel       FAST_INT        -- }- offsets in StgWords
375   | NodeRel     FAST_INT        -- }
376
377 data ReturnInfo
378   = DirectReturn                        -- Jump directly, if possible
379   | StaticVectoredReturn Int            -- Fixed tag, starting at zero
380   | DynamicVectoredReturn CAddrMode     -- Dynamic tag given by amode, starting at zero
381
382 hpRel :: VirtualHeapOffset      -- virtual offset of Hp
383       -> VirtualHeapOffset      -- virtual offset of The Thing
384       -> RegRelative            -- integer offset
385 hpRel IBOX(hp) IBOX(off) = HpRel (hp _SUB_ off)
386
387 spRel :: VirtualSpOffset        -- virtual offset of Sp
388       -> VirtualSpOffset        -- virtual offset of The Thing
389       -> RegRelative            -- integer offset
390 spRel sp off = SpRel (case spRelToInt sp off of { IBOX(i) -> i })
391
392 nodeRel :: VirtualHeapOffset
393         -> RegRelative
394 nodeRel IBOX(off) = NodeRel off
395
396 \end{code}
397
398 %************************************************************************
399 %*                                                                      *
400 \subsection[RegRelative]{@RegRelatives@: ???}
401 %*                                                                      *
402 %************************************************************************
403
404 We represent liveness bitmaps as a BitSet (whose internal
405 representation really is a bitmap).  These are pinned onto case return
406 vectors to indicate the state of the stack for the garbage collector.
407
408 \begin{code}
409 type LivenessMask = [BitSet]
410
411 data Liveness = LvSmall BitSet
412               | LvLarge CLabel
413 \end{code}
414
415 %************************************************************************
416 %*                                                                      *
417 \subsection[HeapOffset]{@Heap Offsets@}
418 %*                                                                      *
419 %************************************************************************
420
421 This used to be a grotesquely complicated datatype in an attempt to
422 hide the details of header sizes from the compiler itself.  Now these
423 constants are imported from the RTS, and we deal in real Ints.
424
425 \begin{code}
426 type HeapOffset = Int                   -- ToDo: remove
427
428 type VirtualHeapOffset  = HeapOffset
429 type VirtualSpOffset    = Int
430
431 type HpRelOffset        = HeapOffset
432 type SpRelOffset        = Int
433 \end{code}
434
435 %************************************************************************
436 %*                                                                      *
437 \subsection[MagicId]{@MagicIds@: registers and such}
438 %*                                                                      *
439 %************************************************************************
440
441 \begin{code}
442 data MagicId
443   = BaseReg     -- mentioned only in nativeGen
444
445   -- Argument and return registers
446   | VanillaReg          -- pointers, unboxed ints and chars
447         PrimRep
448         FAST_INT        -- its number (1 .. mAX_Vanilla_REG)
449
450   | FloatReg            -- single-precision floating-point registers
451         FAST_INT        -- its number (1 .. mAX_Float_REG)
452
453   | DoubleReg           -- double-precision floating-point registers
454         FAST_INT        -- its number (1 .. mAX_Double_REG)
455
456   -- STG registers
457   | Sp                  -- Stack ptr; points to last occupied stack location.
458   | Su                  -- Stack update frame pointer
459   | SpLim               -- Stack limit
460   | Hp                  -- Heap ptr; points to last occupied heap location.
461   | HpLim               -- Heap limit register
462   | CurCostCentre       -- current cost centre register.
463   | VoidReg             -- see "VoidPrim" type; just a placeholder; 
464                         --   no actual register
465   | LongReg             -- long int registers (64-bit, really)
466         PrimRep         -- Int64Rep or Word64Rep
467         FAST_INT        -- its number (1 .. mAX_Long_REG)
468
469
470 node    = VanillaReg PtrRep     ILIT(1) -- A convenient alias for Node
471 tagreg  = VanillaReg WordRep    ILIT(2) -- A convenient alias for TagReg
472
473 \end{code}
474
475 We need magical @Eq@ because @VanillaReg@s come in multiple flavors.
476
477 \begin{code}
478 instance Eq MagicId where
479     reg1 == reg2 = tag reg1 _EQ_ tag reg2
480      where
481         tag BaseReg          = (ILIT(0) :: FAST_INT)
482         tag Sp               = ILIT(1)
483         tag Su               = ILIT(2)
484         tag SpLim            = ILIT(3)
485         tag Hp               = ILIT(4)
486         tag HpLim            = ILIT(5)
487         tag CurCostCentre    = ILIT(6)
488         tag VoidReg          = ILIT(7)
489
490         tag (VanillaReg _ i) = ILIT(8) _ADD_ i
491
492         tag (FloatReg i)  = ILIT(8) _ADD_ maxv _ADD_ i
493         tag (DoubleReg i) = ILIT(8) _ADD_ maxv _ADD_ maxf _ADD_ i
494         tag (LongReg _ i) = ILIT(8) _ADD_ maxv _ADD_ maxf _ADD_ maxd _ADD_ i
495
496         maxv = case mAX_Vanilla_REG of { IBOX(x) -> x }
497         maxf = case mAX_Float_REG   of { IBOX(x) -> x }
498         maxd = case mAX_Double_REG of { IBOX(x) -> x }
499 \end{code}
500
501 Returns True for any register that {\em potentially} dies across
502 C calls (or anything near equivalent).  We just say @True@ and
503 let the (machine-specific) registering macros sort things out...
504
505 \begin{code}
506 isVolatileReg :: MagicId -> Bool
507 isVolatileReg any = True
508 \end{code}