[project @ 2000-03-08 17:48:24 by simonmar]
[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.27 2000/03/08 17:48:24 simonmar 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   | CModuleInitBlock            -- module initialisation block
205         CAddrMode               -- label for init block
206         AbstractC               -- initialisation code
207
208   | CCostCentreDecl             -- A cost centre *declaration*
209         Bool                    -- True  <=> local => full declaration
210                                 -- False <=> extern; just say so
211         CostCentre
212
213   | CCostCentreStackDecl        -- A cost centre stack *declaration*
214         CostCentreStack         -- this is the declaration for a
215                                 -- pre-defined singleton CCS (see 
216                                 -- CostCentre.lhs)
217
218   | CSplitMarker                -- Split into separate object modules here
219 \end{code}
220
221 About @CMacroStmt@, etc.: notionally, they all just call some
222 arbitrary C~macro or routine, passing the @CAddrModes@ as arguments.
223 However, we distinguish between various flavours of these things,
224 mostly just to keep things somewhat less wild and wooly.
225
226 \begin{description}
227 \item[@CMacroStmt@:]
228 Some {\em essential} bits of the STG execution model are done with C
229 macros.  An example is @STK_CHK@, which checks for stack-space
230 overflow.  This enumeration type lists all such macros:
231 \begin{code}
232 data CStmtMacro
233   = ARGS_CHK                            -- arg satisfaction check
234   | ARGS_CHK_LOAD_NODE                  -- arg check for top-level functions
235   | UPD_CAF                             -- update CAF closure with indirection
236   | UPD_BH_UPDATABLE                    -- eager backholing
237   | UPD_BH_SINGLE_ENTRY                 -- more eager blackholing
238   | PUSH_UPD_FRAME                      -- push update frame
239   | PUSH_SEQ_FRAME                      -- push seq frame
240   | UPDATE_SU_FROM_UPD_FRAME            -- pull Su out of the update frame
241   | SET_TAG                             -- set TagReg if it exists
242
243   | REGISTER_FOREIGN_EXPORT             -- register a foreign exported fun
244   | REGISTER_IMPORT                     -- register an imported module
245
246   | GRAN_FETCH                  -- for GrAnSim only  -- HWL
247   | GRAN_RESCHEDULE             -- for GrAnSim only  -- HWL
248   | GRAN_FETCH_AND_RESCHEDULE   -- for GrAnSim only  -- HWL
249   | THREAD_CONTEXT_SWITCH       -- for GrAnSim only  -- HWL
250   | GRAN_YIELD                  -- for GrAnSim only  -- HWL 
251 \end{code}
252
253 Heap/Stack checks.  There are far too many of these.
254
255 \begin{code}
256 data CCheckMacro
257
258   = HP_CHK_NP                           -- heap/stack checks when
259   | STK_CHK_NP                          -- node points to the closure
260   | HP_STK_CHK_NP
261   | HP_CHK_SEQ_NP                       -- for 'seq' style case alternatives
262
263   | HP_CHK                              -- heap/stack checks when
264   | STK_CHK                             -- node doesn't point
265   | HP_STK_CHK
266                                         -- case alternative heap checks:
267
268   | HP_CHK_NOREGS                       --   no registers live
269   | HP_CHK_UNPT_R1                      --   R1 is boxed/unlifted
270   | HP_CHK_UNBX_R1                      --   R1 is unboxed
271   | HP_CHK_F1                           --   FloatReg1 (only) is live 
272   | HP_CHK_D1                           --   DblReg1   (only) is live
273   | HP_CHK_L1                           --   LngReg1   (only) is live
274   | HP_CHK_UT_ALT                       --   unboxed tuple return.
275
276   | HP_CHK_GEN                          -- generic heap check
277 \end{code}
278
279 \item[@CCallProfCtrMacro@:]
280 The @String@ names a macro that, if \tr{#define}d, will bump one/some
281 of the STG-event profiling counters.
282
283 \item[@CCallProfCCMacro@:]
284 The @String@ names a macro that, if \tr{#define}d, will perform some
285 cost-centre-profiling-related action.
286 \end{description}
287
288 %************************************************************************
289 %*                                                                      *
290 \subsection[CAddrMode]{C addressing modes}
291 %*                                                                      *
292 %************************************************************************
293
294 \begin{code}
295 data CAddrMode
296   = CVal  RegRelative PrimRep
297                         -- On RHS of assign: Contents of Magic[n]
298                         -- On LHS of assign: location Magic[n]
299                         -- (ie at addr Magic+n)
300
301   | CAddr RegRelative
302                         -- On RHS of assign: Address of Magic[n]; ie Magic+n
303                         --      n=0 gets the Magic location itself
304                         --      (NB: n=0 case superceded by CReg)
305                         -- On LHS of assign: only sensible if n=0,
306                         --      which gives the magic location itself
307                         --      (NB: superceded by CReg)
308
309   | CReg MagicId        -- To replace (CAddr MagicId 0)
310
311   | CTemp !Unique !PrimRep      -- Temporary locations
312         -- ``Temporaries'' correspond to local variables in C, and registers in
313         -- native code.
314
315   | CLbl    CLabel      -- Labels in the runtime system, etc.
316             PrimRep     -- the kind is so we can generate accurate C decls
317
318   | CCharLike CAddrMode -- The address of a static char-like closure for
319                         -- the specified character.  It is guaranteed to be in
320                         -- the range 0..255.
321
322   | CIntLike CAddrMode  -- The address of a static int-like closure for the
323                         -- specified small integer.  It is guaranteed to be in
324                         -- the range mIN_INTLIKE..mAX_INTLIKE
325
326   | CLit    Literal
327
328   | CLitLit FAST_STRING -- completely literal literal: just spit this String
329                         -- into the C output
330             PrimRep
331
332   | CJoinPoint          -- This is used as the amode of a let-no-escape-bound
333                         -- variable.
334         VirtualSpOffset   -- Sp value after any volatile free vars
335                           -- of the rhs have been saved on stack.
336                           -- Just before the code for the thing is jumped to,
337                           -- Sp will be set to this value,
338                           -- and then any stack-passed args pushed,
339                           -- then the code for this thing will be entered
340   | CMacroExpr
341         !PrimRep        -- the kind of the result
342         CExprMacro      -- the macro to generate a value
343         [CAddrMode]     -- and its arguments
344 \end{code}
345
346 Various C macros for values which are dependent on the back-end layout.
347
348 \begin{code}
349
350 data CExprMacro
351   = ENTRY_CODE
352   | ARG_TAG                             -- stack argument tagging
353   | GET_TAG                             -- get current constructor tag
354   | UPD_FRAME_UPDATEE
355
356 \end{code}
357
358 Convenience functions:
359
360 \begin{code}
361 mkIntCLit :: Int -> CAddrMode
362 mkIntCLit i = CLit (mkMachInt (toInteger i))
363
364 mkCString :: FAST_STRING -> CAddrMode
365 mkCString s = CLit (MachStr s)
366
367 mkCCostCentre :: CostCentre -> CAddrMode
368 mkCCostCentre cc = CLbl (mkCC_Label cc) DataPtrRep
369
370 mkCCostCentreStack :: CostCentreStack -> CAddrMode
371 mkCCostCentreStack ccs = CLbl (mkCCS_Label ccs) DataPtrRep
372 \end{code}
373
374 %************************************************************************
375 %*                                                                      *
376 \subsection[RegRelative]{@RegRelatives@: ???}
377 %*                                                                      *
378 %************************************************************************
379
380 \begin{code}
381 data RegRelative
382   = HpRel       FAST_INT        -- }
383   | SpRel       FAST_INT        -- }- offsets in StgWords
384   | NodeRel     FAST_INT        -- }
385   | CIndex      CAddrMode CAddrMode PrimRep     -- pointer arithmetic :-)
386                                                 -- CIndex a b k === (k*)a[b]
387
388 data ReturnInfo
389   = DirectReturn                        -- Jump directly, if possible
390   | StaticVectoredReturn Int            -- Fixed tag, starting at zero
391   | DynamicVectoredReturn CAddrMode     -- Dynamic tag given by amode, starting at zero
392
393 hpRel :: VirtualHeapOffset      -- virtual offset of Hp
394       -> VirtualHeapOffset      -- virtual offset of The Thing
395       -> RegRelative            -- integer offset
396 hpRel IBOX(hp) IBOX(off) = HpRel (hp _SUB_ off)
397
398 spRel :: VirtualSpOffset        -- virtual offset of Sp
399       -> VirtualSpOffset        -- virtual offset of The Thing
400       -> RegRelative            -- integer offset
401 spRel sp off = SpRel (case spRelToInt sp off of { IBOX(i) -> i })
402
403 nodeRel :: VirtualHeapOffset
404         -> RegRelative
405 nodeRel IBOX(off) = NodeRel off
406
407 \end{code}
408
409 %************************************************************************
410 %*                                                                      *
411 \subsection[Liveness]{Liveness Masks}
412 %*                                                                      *
413 %************************************************************************
414
415 We represent liveness bitmaps as a BitSet (whose internal
416 representation really is a bitmap).  These are pinned onto case return
417 vectors to indicate the state of the stack for the garbage collector.
418
419 \begin{code}
420 type LivenessMask = [BitSet]
421
422 data Liveness = LvSmall BitSet
423               | LvLarge CLabel
424 \end{code}
425
426 %************************************************************************
427 %*                                                                      *
428 \subsection[HeapOffset]{@Heap Offsets@}
429 %*                                                                      *
430 %************************************************************************
431
432 This used to be a grotesquely complicated datatype in an attempt to
433 hide the details of header sizes from the compiler itself.  Now these
434 constants are imported from the RTS, and we deal in real Ints.
435
436 \begin{code}
437 type HeapOffset = Int                   -- ToDo: remove
438
439 type VirtualHeapOffset  = HeapOffset
440 type VirtualSpOffset    = Int
441
442 type HpRelOffset        = HeapOffset
443 type SpRelOffset        = Int
444 \end{code}
445
446 %************************************************************************
447 %*                                                                      *
448 \subsection[MagicId]{@MagicIds@: registers and such}
449 %*                                                                      *
450 %************************************************************************
451
452 \begin{code}
453 data MagicId
454   = BaseReg     -- mentioned only in nativeGen
455
456   -- Argument and return registers
457   | VanillaReg          -- pointers, unboxed ints and chars
458         PrimRep
459         FAST_INT        -- its number (1 .. mAX_Vanilla_REG)
460
461   | FloatReg            -- single-precision floating-point registers
462         FAST_INT        -- its number (1 .. mAX_Float_REG)
463
464   | DoubleReg           -- double-precision floating-point registers
465         FAST_INT        -- its number (1 .. mAX_Double_REG)
466
467   -- STG registers
468   | Sp                  -- Stack ptr; points to last occupied stack location.
469   | Su                  -- Stack update frame pointer
470   | SpLim               -- Stack limit
471   | Hp                  -- Heap ptr; points to last occupied heap location.
472   | HpLim               -- Heap limit register
473   | CurCostCentre       -- current cost centre register.
474   | VoidReg             -- see "VoidPrim" type; just a placeholder; 
475                         --   no actual register
476   | LongReg             -- long int registers (64-bit, really)
477         PrimRep         -- Int64Rep or Word64Rep
478         FAST_INT        -- its number (1 .. mAX_Long_REG)
479
480
481 node    = VanillaReg PtrRep     ILIT(1) -- A convenient alias for Node
482 tagreg  = VanillaReg WordRep    ILIT(2) -- A convenient alias for TagReg
483
484 nodeReg = CReg node
485 \end{code}
486
487 We need magical @Eq@ because @VanillaReg@s come in multiple flavors.
488
489 \begin{code}
490 instance Eq MagicId where
491     reg1 == reg2 = tag reg1 _EQ_ tag reg2
492      where
493         tag BaseReg          = (ILIT(0) :: FAST_INT)
494         tag Sp               = ILIT(1)
495         tag Su               = ILIT(2)
496         tag SpLim            = ILIT(3)
497         tag Hp               = ILIT(4)
498         tag HpLim            = ILIT(5)
499         tag CurCostCentre    = ILIT(6)
500         tag VoidReg          = ILIT(7)
501
502         tag (VanillaReg _ i) = ILIT(8) _ADD_ i
503
504         tag (FloatReg i)  = ILIT(8) _ADD_ maxv _ADD_ i
505         tag (DoubleReg i) = ILIT(8) _ADD_ maxv _ADD_ maxf _ADD_ i
506         tag (LongReg _ i) = ILIT(8) _ADD_ maxv _ADD_ maxf _ADD_ maxd _ADD_ i
507
508         maxv = case mAX_Vanilla_REG of { IBOX(x) -> x }
509         maxf = case mAX_Float_REG   of { IBOX(x) -> x }
510         maxd = case mAX_Double_REG of { IBOX(x) -> x }
511 \end{code}
512
513 Returns True for any register that {\em potentially} dies across
514 C calls (or anything near equivalent).  We just say @True@ and
515 let the (machine-specific) registering macros sort things out...
516
517 \begin{code}
518 isVolatileReg :: MagicId -> Bool
519 isVolatileReg any = True
520 \end{code}