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