[project @ 2002-03-02 18:02:30 by sof]
[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.46 2002/03/02 18:02:30 sof 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         C_SRT(..)
21         CStmtMacro(..),
22         CExprMacro(..),
23         CAddrMode(..),
24         ReturnInfo(..),
25         mkAbstractCs, mkAbsCStmts, mkAlgAltsCSwitch,
26         mkIntCLit,
27         mkAbsCStmtList,
28         mkCCostCentre,
29
30         -- RegRelatives
31         RegRelative(..),
32
33         -- registers
34         MagicId(..), node, infoptr,
35         isVolatileReg,
36         CostRes(Cost)
37     )-} where
38
39 #include "HsVersions.h"
40
41 import {-# SOURCE #-} ClosureInfo ( ClosureInfo )
42
43 import CLabel
44 import Constants        ( mAX_Vanilla_REG, mAX_Float_REG,
45                           mAX_Double_REG, spRelToInt )
46 import CostCentre       ( CostCentre, CostCentreStack )
47 import Literal          ( mkMachInt, Literal(..) )
48 import ForeignCall      ( CCallSpec )
49 import PrimRep          ( PrimRep(..) )
50 import MachOp           ( MachOp(..) )
51 import Unique           ( Unique )
52 import StgSyn           ( StgOp )
53 import TyCon            ( TyCon )
54 import BitSet                           -- for liveness masks
55 import FastTypes
56
57 import Outputable
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         Int             -- size of closure, for profiling
121
122   -- NEW CASES FOR EXPANDED PRIMOPS
123
124   | CMachOpStmt                 -- Machine-level operation
125         CAddrMode               -- result
126         MachOp
127         [CAddrMode]             -- Arguments
128         (Maybe [MagicId])       -- list of regs which need to be preserved
129         -- across the primop.  This is allowed to be Nothing only if
130         -- machOpIsDefinitelyInline returns True.  And that in turn may
131         -- only return True if we are absolutely sure that the mach op
132         -- can be done inline on all platforms.  
133
134   | CSequential         -- Do the nested AbstractCs sequentially.
135         [AbstractC]     -- In particular, as far as the AbsCUtils.doSimultaneously
136                         -- is concerned, these stmts are to be treated as atomic
137                         -- and are not to be reordered.
138
139   -- end of NEW CASES FOR EXPANDED PRIMOPS
140
141   | COpStmt
142         [CAddrMode]     -- Results
143         StgOp
144         [CAddrMode]     -- Arguments
145         [MagicId]       -- Potentially volatile/live registers
146                         -- (to save/restore around the call/op)
147
148         -- INVARIANT: When a PrimOp which can cause GC is used, the
149         -- only live data is tidily on the STG stacks or in the STG
150         -- registers (the code generator ensures this).
151         --
152         -- Why this?  Because if the arguments were arbitrary
153         -- addressing modes, they might be things like (Hp+6) which
154         -- will get utterly spongled by GC.
155
156   | CSimultaneous       -- Perform simultaneously all the statements
157         AbstractC       -- in the nested AbstractC.  They are only
158                         -- allowed to be CAssigns, COpStmts and AbsCNops, so the
159                         -- "simultaneous" part just concerns making
160                         -- sure that permutations work.
161                         -- For example { a := b, b := a }
162                         --      needs to go via (at least one) temporary
163
164   | CCheck              -- heap or stack checks, or both.  
165         CCheckMacro     -- These might include some code to fill in tags 
166         [CAddrMode]     -- on the stack, so we can't use CMacroStmt below.
167         AbstractC
168
169   | CRetDirect                  -- Direct return
170         !Unique                 -- for making labels
171         AbstractC               -- return code
172         C_SRT                   -- SRT info
173         Liveness                -- stack liveness at the return point
174
175   -- see the notes about these next few; they follow below...
176   | CMacroStmt          CStmtMacro      [CAddrMode]
177   | CCallProfCtrMacro   FAST_STRING     [CAddrMode]
178   | CCallProfCCMacro    FAST_STRING     [CAddrMode]
179
180     {- The presence of this constructor is a makeshift solution;
181        it being used to work around a gcc-related problem of
182        handling typedefs within statement blocks (or, rather,
183        the inability to do so.)
184        
185        The AbstractC flattener takes care of lifting out these
186        typedefs if needs be (i.e., when generating .hc code and
187        compiling 'foreign import dynamic's)
188     -}
189   | CCallTypedef Bool {- True => use "typedef"; False => use "extern"-}
190                  CCallSpec Unique [CAddrMode] [CAddrMode]
191
192   -- *** the next three [or so...] are DATA (those above are CODE) ***
193
194   | CStaticClosure
195         ClosureInfo             -- Todo: maybe info_lbl & closure_lbl instead?
196         CAddrMode               -- cost centre identifier to place in closure
197         [CAddrMode]             -- free vars; ptrs, then non-ptrs.
198
199   | CSRT CLabel [CLabel]        -- SRT declarations: basically an array of 
200                                 -- pointers to static closures.
201   
202   | CBitmap CLabel LivenessMask -- A bitmap to be emitted if and only if
203                                 -- it is larger than a target machine word.
204
205   | CClosureInfoAndCode
206         ClosureInfo             -- Explains placement and layout of closure
207         AbstractC               -- Slow entry point code
208         (Maybe AbstractC)
209                                 -- Fast entry point code, if any
210         String                  -- Closure description; NB we can't get this
211                                 -- from ClosureInfo, because the latter refers 
212                                 -- to the *right* hand side of a defn, whereas
213                                 -- the  "description" refers to *left* hand side
214
215   | CRetVector                  -- A labelled block of static data
216         CLabel
217         [CAddrMode]
218         C_SRT                   -- SRT info
219         Liveness                -- stack liveness at the return point
220
221   | CClosureTbl                 -- table of constructors for enumerated types
222         TyCon                   -- which TyCon this table is for
223
224   | CModuleInitBlock            -- module initialisation block
225         CLabel                  -- label for init block
226         AbstractC               -- initialisation code
227
228   | CCostCentreDecl             -- A cost centre *declaration*
229         Bool                    -- True  <=> local => full declaration
230                                 -- False <=> extern; just say so
231         CostCentre
232
233   | CCostCentreStackDecl        -- A cost centre stack *declaration*
234         CostCentreStack         -- this is the declaration for a
235                                 -- pre-defined singleton CCS (see 
236                                 -- CostCentre.lhs)
237
238   | CSplitMarker                -- Split into separate object modules here
239
240 -- C_SRT is what StgSyn.SRT gets translated to... 
241 -- we add a label for the table, and expect only the 'offset/length' form
242
243 data C_SRT = NoC_SRT
244            | C_SRT CLabel !Int{-offset-} !Int{-length-}
245
246 needsSRT :: C_SRT -> Bool
247 needsSRT NoC_SRT       = False
248 needsSRT (C_SRT _ _ _) = True
249 \end{code}
250
251 About @CMacroStmt@, etc.: notionally, they all just call some
252 arbitrary C~macro or routine, passing the @CAddrModes@ as arguments.
253 However, we distinguish between various flavours of these things,
254 mostly just to keep things somewhat less wild and wooly.
255
256 \begin{description}
257 \item[@CMacroStmt@:]
258 Some {\em essential} bits of the STG execution model are done with C
259 macros.  An example is @STK_CHK@, which checks for stack-space
260 overflow.  This enumeration type lists all such macros:
261 \begin{code}
262 data CStmtMacro
263   = ARGS_CHK                            -- arg satisfaction check
264   | ARGS_CHK_LOAD_NODE                  -- arg check for top-level functions
265   | UPD_CAF                             -- update CAF closure with indirection
266   | UPD_BH_UPDATABLE                    -- eager backholing
267   | UPD_BH_SINGLE_ENTRY                 -- more eager blackholing
268   | PUSH_UPD_FRAME                      -- push update frame
269   | PUSH_SEQ_FRAME                      -- push seq frame
270   | UPDATE_SU_FROM_UPD_FRAME            -- pull Su out of the update frame
271   | SET_TAG                             -- set TagReg if it exists
272       -- dataToTag# primop -- *only* used in unregisterised builds.
273       -- (see AbsCUtils.dsCOpStmt)
274   | DATA_TO_TAGZH
275
276   | REGISTER_FOREIGN_EXPORT             -- register a foreign exported fun
277   | REGISTER_IMPORT                     -- register an imported module
278   | REGISTER_DIMPORT                    -- register an imported module from
279                                         -- another DLL
280
281   | GRAN_FETCH                  -- for GrAnSim only  -- HWL
282   | GRAN_RESCHEDULE             -- for GrAnSim only  -- HWL
283   | GRAN_FETCH_AND_RESCHEDULE   -- for GrAnSim only  -- HWL
284   | THREAD_CONTEXT_SWITCH       -- for GrAnSim only  -- HWL
285   | GRAN_YIELD                  -- for GrAnSim only  -- HWL 
286 \end{code}
287
288 Heap/Stack checks.  There are far too many of these.
289
290 \begin{code}
291 data CCheckMacro
292
293   = HP_CHK_NP                           -- heap/stack checks when
294   | STK_CHK_NP                          -- node points to the closure
295   | HP_STK_CHK_NP
296   | HP_CHK_SEQ_NP                       -- for 'seq' style case alternatives
297
298   | HP_CHK                              -- heap/stack checks when
299   | STK_CHK                             -- node doesn't point
300   | HP_STK_CHK
301                                         -- case alternative heap checks:
302
303   | HP_CHK_NOREGS                       --   no registers live
304   | HP_CHK_UNPT_R1                      --   R1 is boxed/unlifted
305   | HP_CHK_UNBX_R1                      --   R1 is unboxed
306   | HP_CHK_F1                           --   FloatReg1 (only) is live 
307   | HP_CHK_D1                           --   DblReg1   (only) is live
308   | HP_CHK_L1                           --   LngReg1   (only) is live
309   | HP_CHK_UT_ALT                       --   unboxed tuple return.
310
311   | HP_CHK_GEN                          -- generic heap check
312 \end{code}
313
314 \item[@CCallProfCtrMacro@:]
315 The @String@ names a macro that, if \tr{#define}d, will bump one/some
316 of the STG-event profiling counters.
317
318 \item[@CCallProfCCMacro@:]
319 The @String@ names a macro that, if \tr{#define}d, will perform some
320 cost-centre-profiling-related action.
321 \end{description}
322
323 %************************************************************************
324 %*                                                                      *
325 \subsection[CAddrMode]{C addressing modes}
326 %*                                                                      *
327 %************************************************************************
328
329 \begin{code}
330 data CAddrMode
331   = CVal  RegRelative PrimRep
332                         -- On RHS of assign: Contents of Magic[n]
333                         -- On LHS of assign: location Magic[n]
334                         -- (ie at addr Magic+n)
335
336   | CAddr RegRelative
337                         -- On RHS of assign: Address of Magic[n]; ie Magic+n
338                         --      n=0 gets the Magic location itself
339                         --      (NB: n=0 case superceded by CReg)
340                         -- On LHS of assign: only sensible if n=0,
341                         --      which gives the magic location itself
342                         --      (NB: superceded by CReg)
343
344              -- JRS 2002-02-05: CAddr is really scummy and should be fixed.
345              -- The effect is that the semantics of CAddr depend on what the
346              -- contained RegRelative is; it is decidely non-orthogonal.
347
348   | CReg MagicId        -- To replace (CAddr MagicId 0)
349
350   | CTemp !Unique !PrimRep      -- Temporary locations
351         -- ``Temporaries'' correspond to local variables in C, and registers in
352         -- native code.
353
354   | CLbl    CLabel      -- Labels in the runtime system, etc.
355             PrimRep     -- the kind is so we can generate accurate C decls
356
357   | CCharLike CAddrMode -- The address of a static char-like closure for
358                         -- the specified character.  It is guaranteed to be in
359                         -- the range mIN_CHARLIKE..mAX_CHARLIKE
360
361   | CIntLike CAddrMode  -- The address of a static int-like closure for the
362                         -- specified small integer.  It is guaranteed to be in
363                         -- the range mIN_INTLIKE..mAX_INTLIKE
364
365   | CLit    Literal
366
367   | CJoinPoint          -- This is used as the amode of a let-no-escape-bound
368                         -- variable.
369         VirtualSpOffset   -- Sp value after any volatile free vars
370                           -- of the rhs have been saved on stack.
371                           -- Just before the code for the thing is jumped to,
372                           -- Sp will be set to this value,
373                           -- and then any stack-passed args pushed,
374                           -- then the code for this thing will be entered
375   | CMacroExpr
376         !PrimRep        -- the kind of the result
377         CExprMacro      -- the macro to generate a value
378         [CAddrMode]     -- and its arguments
379
380   | CBytesPerWord       -- Word size, in bytes, on this platform
381                         -- required for: half-word loads (used in fishing tags
382                         -- out of info tables), and sizeofByteArray#.
383 \end{code}
384
385 Various C macros for values which are dependent on the back-end layout.
386
387 \begin{code}
388
389 data CExprMacro
390   = ENTRY_CODE
391   | ARG_TAG                             -- stack argument tagging
392   | GET_TAG                             -- get current constructor tag
393   | UPD_FRAME_UPDATEE
394   | CCS_HDR
395
396 \end{code}
397
398 Convenience functions:
399
400 \begin{code}
401 mkIntCLit :: Int -> CAddrMode
402 mkIntCLit i = CLit (mkMachInt (toInteger i))
403
404 mkCString :: FAST_STRING -> CAddrMode
405 mkCString s = CLit (MachStr s)
406
407 mkCCostCentre :: CostCentre -> CAddrMode
408 mkCCostCentre cc = CLbl (mkCC_Label cc) DataPtrRep
409
410 mkCCostCentreStack :: CostCentreStack -> CAddrMode
411 mkCCostCentreStack ccs = CLbl (mkCCS_Label ccs) DataPtrRep
412 \end{code}
413
414 %************************************************************************
415 %*                                                                      *
416 \subsection[RegRelative]{@RegRelatives@: ???}
417 %*                                                                      *
418 %************************************************************************
419
420 \begin{code}
421 data RegRelative
422   = HpRel       FastInt -- }
423   | SpRel       FastInt -- }- offsets in StgWords
424   | NodeRel     FastInt -- }
425   | CIndex      CAddrMode CAddrMode PrimRep     -- pointer arithmetic :-)
426                                                 -- CIndex a b k === (k*)a[b]
427
428 data ReturnInfo
429   = DirectReturn                        -- Jump directly, if possible
430   | StaticVectoredReturn Int            -- Fixed tag, starting at zero
431   | DynamicVectoredReturn CAddrMode     -- Dynamic tag given by amode, starting at zero
432
433 hpRel :: VirtualHeapOffset      -- virtual offset of Hp
434       -> VirtualHeapOffset      -- virtual offset of The Thing
435       -> RegRelative            -- integer offset
436 hpRel hp off = HpRel (iUnbox (hp - off))
437
438 spRel :: VirtualSpOffset        -- virtual offset of Sp
439       -> VirtualSpOffset        -- virtual offset of The Thing
440       -> RegRelative            -- integer offset
441 spRel sp off = SpRel (iUnbox (spRelToInt sp off))
442
443 nodeRel :: VirtualHeapOffset
444         -> RegRelative
445 nodeRel off = NodeRel (iUnbox off)
446
447 \end{code}
448
449 %************************************************************************
450 %*                                                                      *
451 \subsection[Liveness]{Liveness Masks}
452 %*                                                                      *
453 %************************************************************************
454
455 We represent liveness bitmaps as a BitSet (whose internal
456 representation really is a bitmap).  These are pinned onto case return
457 vectors to indicate the state of the stack for the garbage collector.
458
459 In the compiled program, liveness bitmaps that fit inside a single
460 word (StgWord) are stored as a single word, while larger bitmaps are
461 stored as a pointer to an array of words.  When we compile via C
462 (especially when we bootstrap via HC files), we generate identical C
463 code regardless of whether words are 32- or 64-bit on the target
464 machine, by postponing the decision of how to store each liveness
465 bitmap to C compilation time (or rather, C preprocessing time).
466
467 \begin{code}
468 type LivenessMask = [BitSet]
469
470 data Liveness = Liveness CLabel LivenessMask
471 \end{code}
472
473 %************************************************************************
474 %*                                                                      *
475 \subsection[HeapOffset]{@Heap Offsets@}
476 %*                                                                      *
477 %************************************************************************
478
479 This used to be a grotesquely complicated datatype in an attempt to
480 hide the details of header sizes from the compiler itself.  Now these
481 constants are imported from the RTS, and we deal in real Ints.
482
483 \begin{code}
484 type HeapOffset = Int                   -- ToDo: remove
485
486 type VirtualHeapOffset  = HeapOffset
487 type VirtualSpOffset    = Int
488
489 type HpRelOffset        = HeapOffset
490 type SpRelOffset        = Int
491 \end{code}
492
493 %************************************************************************
494 %*                                                                      *
495 \subsection[MagicId]{@MagicIds@: registers and such}
496 %*                                                                      *
497 %************************************************************************
498
499 \begin{code}
500 data MagicId
501   = BaseReg     -- mentioned only in nativeGen
502
503   -- Argument and return registers
504   | VanillaReg          -- pointers, unboxed ints and chars
505         PrimRep
506         FastInt -- its number (1 .. mAX_Vanilla_REG)
507
508   | FloatReg            -- single-precision floating-point registers
509         FastInt -- its number (1 .. mAX_Float_REG)
510
511   | DoubleReg           -- double-precision floating-point registers
512         FastInt -- its number (1 .. mAX_Double_REG)
513
514   -- STG registers
515   | Sp                  -- Stack ptr; points to last occupied stack location.
516   | Su                  -- Stack update frame pointer
517   | SpLim               -- Stack limit
518   | Hp                  -- Heap ptr; points to last occupied heap location.
519   | HpLim               -- Heap limit register
520   | CurCostCentre       -- current cost centre register.
521   | VoidReg             -- see "VoidPrim" type; just a placeholder; 
522                         --   no actual register
523   | LongReg             -- long int registers (64-bit, really)
524         PrimRep         -- Int64Rep or Word64Rep
525         FastInt -- its number (1 .. mAX_Long_REG)
526
527   | CurrentTSO          -- pointer to current thread's TSO
528   | CurrentNursery      -- pointer to allocation area
529   | HpAlloc             -- allocation count for heap check failure
530
531
532 node    = VanillaReg PtrRep     (_ILIT 1) -- A convenient alias for Node
533 tagreg  = VanillaReg WordRep    (_ILIT 2) -- A convenient alias for TagReg
534
535 nodeReg = CReg node
536 \end{code}
537
538 We need magical @Eq@ because @VanillaReg@s come in multiple flavors.
539
540 \begin{code}
541 instance Eq MagicId where
542     reg1 == reg2 = tag reg1 ==# tag reg2
543      where
544         tag BaseReg          = (_ILIT(0) :: FastInt)
545         tag Sp               = _ILIT(1)
546         tag Su               = _ILIT(2)
547         tag SpLim            = _ILIT(3)
548         tag Hp               = _ILIT(4)
549         tag HpLim            = _ILIT(5)
550         tag CurCostCentre    = _ILIT(6)
551         tag VoidReg          = _ILIT(7)
552
553         tag (VanillaReg _ i) = _ILIT(8) +# i
554
555         tag (FloatReg i)  = _ILIT(8) +# maxv +# i
556         tag (DoubleReg i) = _ILIT(8) +# maxv +# maxf +# i
557         tag (LongReg _ i) = _ILIT(8) +# maxv +# maxf +# maxd +# i
558
559         maxv = iUnbox mAX_Vanilla_REG
560         maxf = iUnbox mAX_Float_REG
561         maxd = iUnbox mAX_Double_REG
562 \end{code}
563
564 Returns True for any register that {\em potentially} dies across
565 C calls (or anything near equivalent).  We just say @True@ and
566 let the (machine-specific) registering macros sort things out...
567
568 \begin{code}
569 isVolatileReg :: MagicId -> Bool
570 isVolatileReg any = True
571 \end{code}