6863c3d222715ceb7a0a1877bf289134cdc22304
[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.37 2001/07/24 05:04:58 ken 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 ForeignCall      ( CCallSpec )
48 import PrimRep          ( PrimRep(..) )
49 import Unique           ( Unique )
50 import StgSyn           ( StgOp, SRT(..) )
51 import TyCon            ( TyCon )
52 import BitSet                           -- for liveness masks
53 import FastTypes
54
55 \end{code}
56
57 @AbstractC@ is a list of Abstract~C statements, but the data structure
58 is tree-ish, for easier and more efficient putting-together.
59 \begin{code}
60 absCNop = AbsCNop
61
62 data AbstractC
63   = AbsCNop
64   | AbsCStmts           AbstractC AbstractC
65
66   -- and the individual stmts...
67 \end{code}
68
69 A note on @CAssign@: In general, the type associated with an assignment
70 is the type of the lhs.  However, when the lhs is a pointer to mixed
71 types (e.g. SpB relative), the type of the assignment is the type of
72 the rhs for float types, or the generic StgWord for all other types.
73 (In particular, a CharRep on the rhs is promoted to IntRep when
74 stored in a mixed type location.)
75
76 \begin{code}
77   | CAssign
78         !CAddrMode      -- target
79         !CAddrMode      -- source
80
81   | CJump
82         CAddrMode       -- Put this in the program counter
83                         -- eg `CJump (CReg (VanillaReg PtrRep 1))' puts Ret1 in PC
84                         -- Enter can be done by:
85                         --        CJump (CVal NodeRel zeroOff)
86
87   | CFallThrough
88         CAddrMode       -- Fall through into this routine
89                         -- (for the benefit of the native code generators)
90                         -- Equivalent to CJump in C land
91
92   | CReturn             -- Perform a return
93         CAddrMode       -- Address of a RET_<blah> info table
94         ReturnInfo      -- Whether it's a direct or vectored return
95
96   | CSwitch !CAddrMode
97         [(Literal, AbstractC)]  -- alternatives
98         AbstractC               -- default; if there is no real Abstract C in here
99                                 -- (e.g., all comments; see function "nonemptyAbsC"),
100                                 -- then that means the default _cannot_ occur.
101                                 -- If there is only one alternative & no default code,
102                                 -- then there is no need to check the tag.
103                                 -- Therefore, e.g.:
104                                 --  CSwitch m [(tag,code)] AbsCNop == code
105
106   | CCodeBlock CLabel AbstractC
107                         -- A labelled block of code; this "statement" is not
108                         -- executed; rather, the labelled code will be hoisted
109                         -- out to the top level (out of line) & it can be
110                         -- jumped to.
111
112   | CInitHdr            -- to initialise the header of a closure (both fixed/var parts)
113         ClosureInfo
114         CAddrMode       -- address of the info ptr
115         CAddrMode       -- cost centre to place in closure
116                         --   CReg CurCostCentre or CC_HDR(R1.p{-Node-})
117
118   | COpStmt
119         [CAddrMode]     -- Results
120         StgOp
121         [CAddrMode]     -- Arguments
122         [MagicId]       -- Potentially volatile/live registers
123                         -- (to save/restore around the call/op)
124
125         -- INVARIANT: When a PrimOp which can cause GC is used, the
126         -- only live data is tidily on the STG stacks or in the STG
127         -- registers (the code generator ensures this).
128         --
129         -- Why this?  Because if the arguments were arbitrary
130         -- addressing modes, they might be things like (Hp+6) which
131         -- will get utterly spongled by GC.
132
133   | CSimultaneous       -- Perform simultaneously all the statements
134         AbstractC       -- in the nested AbstractC.  They are only
135                         -- allowed to be CAssigns, COpStmts and AbsCNops, so the
136                         -- "simultaneous" part just concerns making
137                         -- sure that permutations work.
138                         -- For example { a := b, b := a }
139                         --      needs to go via (at least one) temporary
140
141   | CCheck              -- heap or stack checks, or both.  
142         CCheckMacro     -- These might include some code to fill in tags 
143         [CAddrMode]     -- on the stack, so we can't use CMacroStmt below.
144         AbstractC
145
146   | CRetDirect                  -- Direct return
147         !Unique                 -- for making labels
148         AbstractC               -- return code
149         (CLabel,SRT)            -- SRT info
150         Liveness                -- stack liveness at the return point
151
152   -- see the notes about these next few; they follow below...
153   | CMacroStmt          CStmtMacro      [CAddrMode]
154   | CCallProfCtrMacro   FAST_STRING     [CAddrMode]
155   | CCallProfCCMacro    FAST_STRING     [CAddrMode]
156
157     {- The presence of this constructor is a makeshift solution;
158        it being used to work around a gcc-related problem of
159        handling typedefs within statement blocks (or, rather,
160        the inability to do so.)
161        
162        The AbstractC flattener takes care of lifting out these
163        typedefs if needs be (i.e., when generating .hc code and
164        compiling 'foreign import dynamic's)
165     -}
166   | CCallTypedef Bool {- True => use "typedef"; False => use "extern"-}
167                  CCallSpec Unique [CAddrMode] [CAddrMode]
168
169   -- *** the next three [or so...] are DATA (those above are CODE) ***
170
171   | CStaticClosure
172         CLabel  -- The (full, not base) label to use for labelling the closure.
173         ClosureInfo
174         CAddrMode               -- cost centre identifier to place in closure
175         [CAddrMode]             -- free vars; ptrs, then non-ptrs.
176
177   | CSRT CLabel [CLabel]        -- SRT declarations: basically an array of 
178                                 -- pointers to static closures.
179   
180   | CBitmap CLabel LivenessMask -- A bitmap to be emitted if and only if
181                                 -- it is larger than a target machine word.
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         String                  -- Closure description; NB we can't get this
189                                 -- from ClosureInfo, because the latter refers 
190                                 -- to the *right* hand side of a defn, whereas
191                                 -- the  "description" refers to *left* hand side
192
193   | CRetVector                  -- A labelled block of static data
194         CLabel
195         [CAddrMode]
196         (CLabel,SRT)            -- SRT info
197         Liveness                -- stack liveness at the return point
198
199   | CClosureTbl                 -- table of constructors for enumerated types
200         TyCon                   -- which TyCon this table is for
201
202   | CModuleInitBlock            -- module initialisation block
203         CLabel                  -- label for init block
204         AbstractC               -- initialisation code
205
206   | CCostCentreDecl             -- A cost centre *declaration*
207         Bool                    -- True  <=> local => full declaration
208                                 -- False <=> extern; just say so
209         CostCentre
210
211   | CCostCentreStackDecl        -- A cost centre stack *declaration*
212         CostCentreStack         -- this is the declaration for a
213                                 -- pre-defined singleton CCS (see 
214                                 -- CostCentre.lhs)
215
216   | CSplitMarker                -- Split into separate object modules here
217 \end{code}
218
219 About @CMacroStmt@, etc.: notionally, they all just call some
220 arbitrary C~macro or routine, passing the @CAddrModes@ as arguments.
221 However, we distinguish between various flavours of these things,
222 mostly just to keep things somewhat less wild and wooly.
223
224 \begin{description}
225 \item[@CMacroStmt@:]
226 Some {\em essential} bits of the STG execution model are done with C
227 macros.  An example is @STK_CHK@, which checks for stack-space
228 overflow.  This enumeration type lists all such macros:
229 \begin{code}
230 data CStmtMacro
231   = ARGS_CHK                            -- arg satisfaction check
232   | ARGS_CHK_LOAD_NODE                  -- arg check for top-level functions
233   | UPD_CAF                             -- update CAF closure with indirection
234   | UPD_BH_UPDATABLE                    -- eager backholing
235   | UPD_BH_SINGLE_ENTRY                 -- more eager blackholing
236   | PUSH_UPD_FRAME                      -- push update frame
237   | PUSH_SEQ_FRAME                      -- push seq frame
238   | UPDATE_SU_FROM_UPD_FRAME            -- pull Su out of the update frame
239   | SET_TAG                             -- set TagReg if it exists
240
241   | REGISTER_FOREIGN_EXPORT             -- register a foreign exported fun
242   | REGISTER_IMPORT                     -- register an imported module
243   | REGISTER_DIMPORT                    -- register an imported module from
244                                         -- another DLL
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 mIN_CHARLIKE..mAX_CHARLIKE
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   | 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   | CCS_HDR
352
353 \end{code}
354
355 Convenience functions:
356
357 \begin{code}
358 mkIntCLit :: Int -> CAddrMode
359 mkIntCLit i = CLit (mkMachInt (toInteger i))
360
361 mkCString :: FAST_STRING -> CAddrMode
362 mkCString s = CLit (MachStr s)
363
364 mkCCostCentre :: CostCentre -> CAddrMode
365 mkCCostCentre cc = CLbl (mkCC_Label cc) DataPtrRep
366
367 mkCCostCentreStack :: CostCentreStack -> CAddrMode
368 mkCCostCentreStack ccs = CLbl (mkCCS_Label ccs) DataPtrRep
369 \end{code}
370
371 %************************************************************************
372 %*                                                                      *
373 \subsection[RegRelative]{@RegRelatives@: ???}
374 %*                                                                      *
375 %************************************************************************
376
377 \begin{code}
378 data RegRelative
379   = HpRel       FastInt -- }
380   | SpRel       FastInt -- }- offsets in StgWords
381   | NodeRel     FastInt -- }
382   | CIndex      CAddrMode CAddrMode PrimRep     -- pointer arithmetic :-)
383                                                 -- CIndex a b k === (k*)a[b]
384
385 data ReturnInfo
386   = DirectReturn                        -- Jump directly, if possible
387   | StaticVectoredReturn Int            -- Fixed tag, starting at zero
388   | DynamicVectoredReturn CAddrMode     -- Dynamic tag given by amode, starting at zero
389
390 hpRel :: VirtualHeapOffset      -- virtual offset of Hp
391       -> VirtualHeapOffset      -- virtual offset of The Thing
392       -> RegRelative            -- integer offset
393 hpRel hp off = HpRel (iUnbox (hp - off))
394
395 spRel :: VirtualSpOffset        -- virtual offset of Sp
396       -> VirtualSpOffset        -- virtual offset of The Thing
397       -> RegRelative            -- integer offset
398 spRel sp off = SpRel (iUnbox (spRelToInt sp off))
399
400 nodeRel :: VirtualHeapOffset
401         -> RegRelative
402 nodeRel off = NodeRel (iUnbox off)
403
404 \end{code}
405
406 %************************************************************************
407 %*                                                                      *
408 \subsection[Liveness]{Liveness Masks}
409 %*                                                                      *
410 %************************************************************************
411
412 We represent liveness bitmaps as a BitSet (whose internal
413 representation really is a bitmap).  These are pinned onto case return
414 vectors to indicate the state of the stack for the garbage collector.
415
416 In the compiled program, liveness bitmaps that fit inside a single
417 word (StgWord) are stored as a single word, while larger bitmaps are
418 stored as a pointer to an array of words.  When we compile via C
419 (especially when we bootstrap via HC files), we generate identical C
420 code regardless of whether words are 32- or 64-bit on the target
421 machine, by postponing the decision of how to store each liveness
422 bitmap to C compilation time (or rather, C preprocessing time).
423
424 \begin{code}
425 type LivenessMask = [BitSet]
426
427 data Liveness = Liveness CLabel LivenessMask
428 \end{code}
429
430 %************************************************************************
431 %*                                                                      *
432 \subsection[HeapOffset]{@Heap Offsets@}
433 %*                                                                      *
434 %************************************************************************
435
436 This used to be a grotesquely complicated datatype in an attempt to
437 hide the details of header sizes from the compiler itself.  Now these
438 constants are imported from the RTS, and we deal in real Ints.
439
440 \begin{code}
441 type HeapOffset = Int                   -- ToDo: remove
442
443 type VirtualHeapOffset  = HeapOffset
444 type VirtualSpOffset    = Int
445
446 type HpRelOffset        = HeapOffset
447 type SpRelOffset        = Int
448 \end{code}
449
450 %************************************************************************
451 %*                                                                      *
452 \subsection[MagicId]{@MagicIds@: registers and such}
453 %*                                                                      *
454 %************************************************************************
455
456 \begin{code}
457 data MagicId
458   = BaseReg     -- mentioned only in nativeGen
459
460   -- Argument and return registers
461   | VanillaReg          -- pointers, unboxed ints and chars
462         PrimRep
463         FastInt -- its number (1 .. mAX_Vanilla_REG)
464
465   | FloatReg            -- single-precision floating-point registers
466         FastInt -- its number (1 .. mAX_Float_REG)
467
468   | DoubleReg           -- double-precision floating-point registers
469         FastInt -- its number (1 .. mAX_Double_REG)
470
471   -- STG registers
472   | Sp                  -- Stack ptr; points to last occupied stack location.
473   | Su                  -- Stack update frame pointer
474   | SpLim               -- Stack limit
475   | Hp                  -- Heap ptr; points to last occupied heap location.
476   | HpLim               -- Heap limit register
477   | CurCostCentre       -- current cost centre register.
478   | VoidReg             -- see "VoidPrim" type; just a placeholder; 
479                         --   no actual register
480   | LongReg             -- long int registers (64-bit, really)
481         PrimRep         -- Int64Rep or Word64Rep
482         FastInt -- its number (1 .. mAX_Long_REG)
483
484   | CurrentTSO          -- pointer to current thread's TSO
485   | CurrentNursery      -- pointer to allocation area
486
487
488 node    = VanillaReg PtrRep     (_ILIT 1) -- A convenient alias for Node
489 tagreg  = VanillaReg WordRep    (_ILIT 2) -- A convenient alias for TagReg
490
491 nodeReg = CReg node
492 \end{code}
493
494 We need magical @Eq@ because @VanillaReg@s come in multiple flavors.
495
496 \begin{code}
497 instance Eq MagicId where
498     reg1 == reg2 = tag reg1 ==# tag reg2
499      where
500         tag BaseReg          = (_ILIT(0) :: FastInt)
501         tag Sp               = _ILIT(1)
502         tag Su               = _ILIT(2)
503         tag SpLim            = _ILIT(3)
504         tag Hp               = _ILIT(4)
505         tag HpLim            = _ILIT(5)
506         tag CurCostCentre    = _ILIT(6)
507         tag VoidReg          = _ILIT(7)
508
509         tag (VanillaReg _ i) = _ILIT(8) +# i
510
511         tag (FloatReg i)  = _ILIT(8) +# maxv +# i
512         tag (DoubleReg i) = _ILIT(8) +# maxv +# maxf +# i
513         tag (LongReg _ i) = _ILIT(8) +# maxv +# maxf +# maxd +# i
514
515         maxv = iUnbox mAX_Vanilla_REG
516         maxf = iUnbox mAX_Float_REG
517         maxd = iUnbox mAX_Double_REG
518 \end{code}
519
520 Returns True for any register that {\em potentially} dies across
521 C calls (or anything near equivalent).  We just say @True@ and
522 let the (machine-specific) registering macros sort things out...
523
524 \begin{code}
525 isVolatileReg :: MagicId -> Bool
526 isVolatileReg any = True
527 \end{code}