[project @ 2000-10-12 15:17:07 by sewardj]
[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.35 2000/10/12 15:17:07 sewardj 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 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         PrimOp
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                  CCall [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 larger-than-32-bits bitmap.
181
182   | CClosureInfoAndCode
183         ClosureInfo             -- Explains placement and layout of closure
184         AbstractC               -- Slow entry point code
185         (Maybe AbstractC)
186                                 -- Fast entry point code, if any
187         String                  -- Closure description; NB we can't get this
188                                 -- from ClosureInfo, because the latter refers 
189                                 -- to the *right* hand side of a defn, whereas
190                                 -- the  "description" refers to *left* hand side
191
192   | CRetVector                  -- A labelled block of static data
193         CLabel
194         [CAddrMode]
195         (CLabel,SRT)            -- SRT info
196         Liveness                -- stack liveness at the return point
197
198   | CClosureTbl                 -- table of constructors for enumerated types
199         TyCon                   -- which TyCon this table is for
200
201   | CModuleInitBlock            -- module initialisation block
202         CLabel                  -- label for init block
203         AbstractC               -- initialisation code
204
205   | CCostCentreDecl             -- A cost centre *declaration*
206         Bool                    -- True  <=> local => full declaration
207                                 -- False <=> extern; just say so
208         CostCentre
209
210   | CCostCentreStackDecl        -- A cost centre stack *declaration*
211         CostCentreStack         -- this is the declaration for a
212                                 -- pre-defined singleton CCS (see 
213                                 -- CostCentre.lhs)
214
215   | CSplitMarker                -- Split into separate object modules here
216 \end{code}
217
218 About @CMacroStmt@, etc.: notionally, they all just call some
219 arbitrary C~macro or routine, passing the @CAddrModes@ as arguments.
220 However, we distinguish between various flavours of these things,
221 mostly just to keep things somewhat less wild and wooly.
222
223 \begin{description}
224 \item[@CMacroStmt@:]
225 Some {\em essential} bits of the STG execution model are done with C
226 macros.  An example is @STK_CHK@, which checks for stack-space
227 overflow.  This enumeration type lists all such macros:
228 \begin{code}
229 data CStmtMacro
230   = ARGS_CHK                            -- arg satisfaction check
231   | ARGS_CHK_LOAD_NODE                  -- arg check for top-level functions
232   | UPD_CAF                             -- update CAF closure with indirection
233   | UPD_BH_UPDATABLE                    -- eager backholing
234   | UPD_BH_SINGLE_ENTRY                 -- more eager blackholing
235   | PUSH_UPD_FRAME                      -- push update frame
236   | PUSH_SEQ_FRAME                      -- push seq frame
237   | UPDATE_SU_FROM_UPD_FRAME            -- pull Su out of the update frame
238   | SET_TAG                             -- set TagReg if it exists
239
240   | REGISTER_FOREIGN_EXPORT             -- register a foreign exported fun
241   | REGISTER_IMPORT                     -- register an imported module
242   | REGISTER_DIMPORT                    -- register an imported module from
243                                         -- another DLL
244
245   | GRAN_FETCH                  -- for GrAnSim only  -- HWL
246   | GRAN_RESCHEDULE             -- for GrAnSim only  -- HWL
247   | GRAN_FETCH_AND_RESCHEDULE   -- for GrAnSim only  -- HWL
248   | THREAD_CONTEXT_SWITCH       -- for GrAnSim only  -- HWL
249   | GRAN_YIELD                  -- for GrAnSim only  -- HWL 
250 \end{code}
251
252 Heap/Stack checks.  There are far too many of these.
253
254 \begin{code}
255 data CCheckMacro
256
257   = HP_CHK_NP                           -- heap/stack checks when
258   | STK_CHK_NP                          -- node points to the closure
259   | HP_STK_CHK_NP
260   | HP_CHK_SEQ_NP                       -- for 'seq' style case alternatives
261
262   | HP_CHK                              -- heap/stack checks when
263   | STK_CHK                             -- node doesn't point
264   | HP_STK_CHK
265                                         -- case alternative heap checks:
266
267   | HP_CHK_NOREGS                       --   no registers live
268   | HP_CHK_UNPT_R1                      --   R1 is boxed/unlifted
269   | HP_CHK_UNBX_R1                      --   R1 is unboxed
270   | HP_CHK_F1                           --   FloatReg1 (only) is live 
271   | HP_CHK_D1                           --   DblReg1   (only) is live
272   | HP_CHK_L1                           --   LngReg1   (only) is live
273   | HP_CHK_UT_ALT                       --   unboxed tuple return.
274
275   | HP_CHK_GEN                          -- generic heap check
276 \end{code}
277
278 \item[@CCallProfCtrMacro@:]
279 The @String@ names a macro that, if \tr{#define}d, will bump one/some
280 of the STG-event profiling counters.
281
282 \item[@CCallProfCCMacro@:]
283 The @String@ names a macro that, if \tr{#define}d, will perform some
284 cost-centre-profiling-related action.
285 \end{description}
286
287 %************************************************************************
288 %*                                                                      *
289 \subsection[CAddrMode]{C addressing modes}
290 %*                                                                      *
291 %************************************************************************
292
293 \begin{code}
294 data CAddrMode
295   = CVal  RegRelative PrimRep
296                         -- On RHS of assign: Contents of Magic[n]
297                         -- On LHS of assign: location Magic[n]
298                         -- (ie at addr Magic+n)
299
300   | CAddr RegRelative
301                         -- On RHS of assign: Address of Magic[n]; ie Magic+n
302                         --      n=0 gets the Magic location itself
303                         --      (NB: n=0 case superceded by CReg)
304                         -- On LHS of assign: only sensible if n=0,
305                         --      which gives the magic location itself
306                         --      (NB: superceded by CReg)
307
308   | CReg MagicId        -- To replace (CAddr MagicId 0)
309
310   | CTemp !Unique !PrimRep      -- Temporary locations
311         -- ``Temporaries'' correspond to local variables in C, and registers in
312         -- native code.
313
314   | CLbl    CLabel      -- Labels in the runtime system, etc.
315             PrimRep     -- the kind is so we can generate accurate C decls
316
317   | CCharLike CAddrMode -- The address of a static char-like closure for
318                         -- the specified character.  It is guaranteed to be in
319                         -- the range mIN_CHARLIKE..mAX_CHARLIKE
320
321   | CIntLike CAddrMode  -- The address of a static int-like closure for the
322                         -- specified small integer.  It is guaranteed to be in
323                         -- the range mIN_INTLIKE..mAX_INTLIKE
324
325   | CLit    Literal
326
327   | CJoinPoint          -- This is used as the amode of a let-no-escape-bound
328                         -- variable.
329         VirtualSpOffset   -- Sp value after any volatile free vars
330                           -- of the rhs have been saved on stack.
331                           -- Just before the code for the thing is jumped to,
332                           -- Sp will be set to this value,
333                           -- and then any stack-passed args pushed,
334                           -- then the code for this thing will be entered
335   | CMacroExpr
336         !PrimRep        -- the kind of the result
337         CExprMacro      -- the macro to generate a value
338         [CAddrMode]     -- and its arguments
339 \end{code}
340
341 Various C macros for values which are dependent on the back-end layout.
342
343 \begin{code}
344
345 data CExprMacro
346   = ENTRY_CODE
347   | ARG_TAG                             -- stack argument tagging
348   | GET_TAG                             -- get current constructor tag
349   | UPD_FRAME_UPDATEE
350   | CCS_HDR
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       FastInt -- }
379   | SpRel       FastInt -- }- offsets in StgWords
380   | NodeRel     FastInt -- }
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 hp off = HpRel (iUnbox (hp - 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 (iUnbox (spRelToInt sp off))
398
399 nodeRel :: VirtualHeapOffset
400         -> RegRelative
401 nodeRel off = NodeRel (iUnbox 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         FastInt -- its number (1 .. mAX_Vanilla_REG)
456
457   | FloatReg            -- single-precision floating-point registers
458         FastInt -- its number (1 .. mAX_Float_REG)
459
460   | DoubleReg           -- double-precision floating-point registers
461         FastInt -- 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         FastInt -- its number (1 .. mAX_Long_REG)
475
476   | CurrentTSO          -- pointer to current thread's TSO
477   | CurrentNursery      -- pointer to allocation area
478
479
480 node    = VanillaReg PtrRep     (_ILIT 1) -- A convenient alias for Node
481 tagreg  = VanillaReg WordRep    (_ILIT 2) -- A convenient alias for TagReg
482
483 nodeReg = CReg node
484 \end{code}
485
486 We need magical @Eq@ because @VanillaReg@s come in multiple flavors.
487
488 \begin{code}
489 instance Eq MagicId where
490     reg1 == reg2 = tag reg1 ==# tag reg2
491      where
492         tag BaseReg          = (_ILIT(0) :: FastInt)
493         tag Sp               = _ILIT(1)
494         tag Su               = _ILIT(2)
495         tag SpLim            = _ILIT(3)
496         tag Hp               = _ILIT(4)
497         tag HpLim            = _ILIT(5)
498         tag CurCostCentre    = _ILIT(6)
499         tag VoidReg          = _ILIT(7)
500
501         tag (VanillaReg _ i) = _ILIT(8) +# i
502
503         tag (FloatReg i)  = _ILIT(8) +# maxv +# i
504         tag (DoubleReg i) = _ILIT(8) +# maxv +# maxf +# i
505         tag (LongReg _ i) = _ILIT(8) +# maxv +# maxf +# maxd +# i
506
507         maxv = iUnbox mAX_Vanilla_REG
508         maxf = iUnbox mAX_Float_REG
509         maxd = iUnbox mAX_Double_REG
510 \end{code}
511
512 Returns True for any register that {\em potentially} dies across
513 C calls (or anything near equivalent).  We just say @True@ and
514 let the (machine-specific) registering macros sort things out...
515
516 \begin{code}
517 isVolatileReg :: MagicId -> Bool
518 isVolatileReg any = True
519 \end{code}