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