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