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