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