Added support for update frames to the CPS pass
[ghc-hetmet.git] / compiler / cmm / Cmm.hs
1 -----------------------------------------------------------------------------
2 --
3 -- Cmm data types
4 --
5 -- (c) The University of Glasgow 2004-2006
6 --
7 -----------------------------------------------------------------------------
8
9 module Cmm ( 
10         GenCmm(..), Cmm, RawCmm,
11         GenCmmTop(..), CmmTop, RawCmmTop,
12         CmmInfo(..), UpdateFrame(..),
13         CmmInfoTable(..), ClosureTypeInfo(..), ProfilingInfo(..), ClosureTypeTag,
14         GenBasicBlock(..), CmmBasicBlock, blockId, blockStmts, mapBlockStmts,
15         CmmStmt(..), CmmActuals, CmmFormal, CmmFormals, CmmHintFormals,
16         CmmSafety(..),
17         CmmCallTarget(..),
18         CmmStatic(..), Section(..),
19         CmmExpr(..), cmmExprRep, 
20         CmmReg(..), cmmRegRep,
21         CmmLit(..), cmmLitRep,
22         LocalReg(..), localRegRep, localRegGCFollow, Kind(..),
23         BlockId(..), BlockEnv,
24         GlobalReg(..), globalRegRep,
25
26         node, nodeReg, spReg, hpReg, spLimReg
27   ) where
28
29 #include "HsVersions.h"
30
31 import MachOp
32 import CLabel
33 import ForeignCall
34 import SMRep
35 import ClosureInfo
36 import Unique
37 import UniqFM
38 import FastString
39
40 import Data.Word
41
42 -----------------------------------------------------------------------------
43 --              Cmm, CmmTop, CmmBasicBlock
44 -----------------------------------------------------------------------------
45
46 -- A file is a list of top-level chunks.  These may be arbitrarily
47 -- re-orderd during code generation.
48
49 -- GenCmm is abstracted over
50 --   (a) the type of static data elements
51 --   (b) the contents of a basic block.
52 -- We expect there to be two main instances of this type:
53 --   (a) Plain C--, i.e. populated with CmmLit and CmmExpr respectively,
54 --   (b) Native code, populated with instructions
55 --
56 newtype GenCmm d h i = Cmm [GenCmmTop d h i]
57
58 -- | Cmm with the info table as a data type
59 type Cmm = GenCmm CmmStatic CmmInfo CmmStmt
60
61 -- | Cmm with the info tables converted to a list of 'CmmStatic'
62 type RawCmm = GenCmm CmmStatic [CmmStatic] CmmStmt
63
64 -- A top-level chunk, abstracted over the type of the contents of
65 -- the basic blocks (Cmm or instructions are the likely instantiations).
66 data GenCmmTop d h i
67   = CmmProc
68      h                 -- Extra header such as the info table
69      CLabel            -- Used to generate both info & entry labels
70      CmmFormals        -- Argument locals live on entry (C-- procedure params)
71      [GenBasicBlock i] -- Code, may be empty.  The first block is
72                        -- the entry point.  The order is otherwise initially 
73                        -- unimportant, but at some point the code gen will
74                        -- fix the order.
75
76                        -- the BlockId of the first block does not give rise
77                        -- to a label.  To jump to the first block in a Proc,
78                        -- use the appropriate CLabel.
79
80   -- some static data.
81   | CmmData Section [d] -- constant values only
82
83 type CmmTop = GenCmmTop CmmStatic CmmInfo CmmStmt
84 type RawCmmTop = GenCmmTop CmmStatic [CmmStatic] CmmStmt
85
86 -- A basic block containing a single label, at the beginning.
87 -- The list of basic blocks in a top-level code block may be re-ordered.
88 -- Fall-through is not allowed: there must be an explicit jump at the
89 -- end of each basic block, but the code generator might rearrange basic
90 -- blocks in order to turn some jumps into fallthroughs.
91
92 data GenBasicBlock i = BasicBlock BlockId [i]
93   -- ToDo: Julian suggests that we might need to annotate this type
94   -- with the out & in edges in the graph, i.e. two * [BlockId].  This
95   -- information can be derived from the contents, but it might be
96   -- helpful to cache it here.
97
98 type CmmBasicBlock = GenBasicBlock CmmStmt
99
100 blockId :: GenBasicBlock i -> BlockId
101 -- The branch block id is that of the first block in 
102 -- the branch, which is that branch's entry point
103 blockId (BasicBlock blk_id _ ) = blk_id
104
105 blockStmts :: GenBasicBlock i -> [i]
106 blockStmts (BasicBlock _ stmts) = stmts
107
108 mapBlockStmts f (BasicBlock id bs) = BasicBlock id (map f bs)
109
110 -----------------------------------------------------------------------------
111 --     Info Tables
112 -----------------------------------------------------------------------------
113
114 data CmmInfo
115   = CmmInfo
116       (Maybe BlockId) -- GC target
117       (Maybe UpdateFrame) -- Update frame
118       CmmInfoTable -- Info table
119
120 -- Info table as a haskell data type
121 data CmmInfoTable
122   = CmmInfoTable
123       ProfilingInfo
124       ClosureTypeTag -- Int
125       ClosureTypeInfo
126   | CmmNonInfoTable   -- Procedure doesn't need an info table
127
128 -- TODO: The GC target shouldn't really be part of CmmInfo
129 -- as it doesn't appear in the resulting info table.
130 -- It should be factored out.
131
132 data ClosureTypeInfo
133   = ConstrInfo ClosureLayout ConstrTag ConstrDescription
134   | FunInfo ClosureLayout C_SRT FunType FunArity ArgDescr SlowEntry
135   | ThunkInfo ClosureLayout C_SRT
136   | ThunkSelectorInfo SelectorOffset C_SRT
137   | ContInfo
138       [Maybe LocalReg]  -- Forced stack parameters
139       C_SRT
140
141 -- TODO: These types may need refinement
142 data ProfilingInfo = ProfilingInfo CmmLit CmmLit -- closure_type, closure_desc
143 type ClosureTypeTag = StgHalfWord
144 type ClosureLayout = (StgHalfWord, StgHalfWord) -- ptrs, nptrs
145 type ConstrTag = StgHalfWord
146 type ConstrDescription = CmmLit
147 type FunType = StgHalfWord
148 type FunArity = StgHalfWord
149 type SlowEntry = CmmLit
150   -- ^We would like this to be a CLabel but
151   -- for now the parser sets this to zero on an INFO_TABLE_FUN.
152 type SelectorOffset = StgWord
153
154 -- | A frame that is to be pushed before entry to the function.
155 -- Used to handle 'update' frames.
156 data UpdateFrame =
157     UpdateFrame
158       CmmExpr    -- Frame header.  Behaves like the target of a 'jump'.
159       [CmmExpr]  -- Frame remainder.  Behaves like the arguments of a 'jump'.
160
161 -----------------------------------------------------------------------------
162 --              CmmStmt
163 -- A "statement".  Note that all branches are explicit: there are no
164 -- control transfers to computed addresses, except when transfering
165 -- control to a new function.
166 -----------------------------------------------------------------------------
167
168 data CmmStmt
169   = CmmNop
170   | CmmComment FastString
171
172   | CmmAssign CmmReg CmmExpr     -- Assign to register
173
174   | CmmStore CmmExpr CmmExpr     -- Assign to memory location.  Size is
175                                  -- given by cmmExprRep of the rhs.
176
177   | CmmCall                      -- A foreign call, with 
178      CmmCallTarget
179      CmmHintFormals              -- zero or more results
180      CmmActuals                  -- zero or more arguments
181      CmmSafety                   -- whether to build a continuation
182
183   | CmmBranch BlockId             -- branch to another BB in this fn
184
185   | CmmCondBranch CmmExpr BlockId -- conditional branch
186
187   | CmmSwitch CmmExpr [Maybe BlockId]   -- Table branch
188         -- The scrutinee is zero-based; 
189         --      zero -> first block
190         --      one  -> second block etc
191         -- Undefined outside range, and when there's a Nothing
192
193   | CmmJump CmmExpr               -- Jump to another function,
194       CmmActuals                  -- with these parameters.
195
196   | CmmReturn                     -- Return from a function,
197       CmmActuals                  -- with these return values.
198
199 type CmmActual = CmmExpr
200 type CmmActuals = [(CmmActual,MachHint)]
201 type CmmFormal = LocalReg
202 type CmmHintFormals = [(CmmFormal,MachHint)]
203 type CmmFormals = [CmmFormal]
204 data CmmSafety = CmmUnsafe | CmmSafe C_SRT
205
206 {-
207 Discussion
208 ~~~~~~~~~~
209
210 One possible problem with the above type is that the only way to do a
211 non-local conditional jump is to encode it as a branch to a block that
212 contains a single jump.  This leads to inefficient code in the back end.
213
214 One possible way to fix this would be:
215
216 data CmmStat = 
217   ...
218   | CmmJump CmmBranchDest
219   | CmmCondJump CmmExpr CmmBranchDest
220   ...
221
222 data CmmBranchDest
223   = Local BlockId
224   | NonLocal CmmExpr [LocalReg]
225
226 In favour:
227
228 + one fewer constructors in CmmStmt
229 + allows both cond branch and switch to jump to non-local destinations
230
231 Against:
232
233 - not strictly necessary: can already encode as branch+jump
234 - not always possible to implement any better in the back end
235 - could do the optimisation in the back end (but then plat-specific?)
236 - C-- doesn't have it
237 - back-end optimisation might be more general (jump shortcutting)
238
239 So we'll stick with the way it is, and add the optimisation to the NCG.
240 -}
241
242 -----------------------------------------------------------------------------
243 --              CmmCallTarget
244 --
245 -- The target of a CmmCall.
246 -----------------------------------------------------------------------------
247
248 data CmmCallTarget
249   = CmmForeignCall              -- Call to a foreign function
250         CmmExpr                 -- literal label <=> static call
251                                 -- other expression <=> dynamic call
252         CCallConv               -- The calling convention
253
254   | CmmPrim                     -- Call to a "primitive" (eg. sin, cos)
255         CallishMachOp           -- These might be implemented as inline
256                                 -- code by the backend.
257
258 -----------------------------------------------------------------------------
259 --              CmmExpr
260 -- An expression.  Expressions have no side effects.
261 -----------------------------------------------------------------------------
262
263 data CmmExpr
264   = CmmLit CmmLit               -- Literal
265   | CmmLoad CmmExpr MachRep     -- Read memory location
266   | CmmReg CmmReg               -- Contents of register
267   | CmmMachOp MachOp [CmmExpr]  -- Machine operation (+, -, *, etc.)
268   | CmmRegOff CmmReg Int        
269         -- CmmRegOff reg i
270         --        ** is shorthand only, meaning **
271         -- CmmMachOp (MO_S_Add rep (CmmReg reg) (CmmLit (CmmInt i rep)))
272         --      where rep = cmmRegRep reg
273   deriving Eq
274
275 cmmExprRep :: CmmExpr -> MachRep
276 cmmExprRep (CmmLit lit)      = cmmLitRep lit
277 cmmExprRep (CmmLoad _ rep)   = rep
278 cmmExprRep (CmmReg reg)      = cmmRegRep reg
279 cmmExprRep (CmmMachOp op _)  = resultRepOfMachOp op
280 cmmExprRep (CmmRegOff reg _) = cmmRegRep reg
281
282 data CmmReg 
283   = CmmLocal  LocalReg
284   | CmmGlobal GlobalReg
285   deriving( Eq )
286
287 cmmRegRep :: CmmReg -> MachRep
288 cmmRegRep (CmmLocal  reg)       = localRegRep reg
289 cmmRegRep (CmmGlobal reg)       = globalRegRep reg
290
291 -- | Whether a 'LocalReg' is a GC followable pointer
292 data Kind = KindPtr | KindNonPtr deriving (Eq)
293
294 data LocalReg
295   = LocalReg
296       !Unique   -- ^ Identifier
297       MachRep   -- ^ Type
298       Kind      -- ^ Should the GC follow as a pointer
299
300 instance Eq LocalReg where
301   (LocalReg u1 _ _) == (LocalReg u2 _ _) = u1 == u2
302
303 instance Uniquable LocalReg where
304   getUnique (LocalReg uniq _ _) = uniq
305
306 localRegRep :: LocalReg -> MachRep
307 localRegRep (LocalReg _ rep _) = rep
308
309 localRegGCFollow (LocalReg _ _ p) = p
310
311 data CmmLit
312   = CmmInt Integer  MachRep
313         -- Interpretation: the 2's complement representation of the value
314         -- is truncated to the specified size.  This is easier than trying
315         -- to keep the value within range, because we don't know whether
316         -- it will be used as a signed or unsigned value (the MachRep doesn't
317         -- distinguish between signed & unsigned).
318   | CmmFloat  Rational MachRep
319   | CmmLabel    CLabel                  -- Address of label
320   | CmmLabelOff CLabel Int              -- Address of label + byte offset
321   
322         -- Due to limitations in the C backend, the following
323         -- MUST ONLY be used inside the info table indicated by label2
324         -- (label2 must be the info label), and label1 must be an
325         -- SRT, a slow entrypoint or a large bitmap (see the Mangler)
326         -- Don't use it at all unless tablesNextToCode.
327         -- It is also used inside the NCG during when generating
328         -- position-independent code. 
329   | CmmLabelDiffOff CLabel CLabel Int   -- label1 - label2 + offset
330   deriving Eq
331
332 cmmLitRep :: CmmLit -> MachRep
333 cmmLitRep (CmmInt _ rep)    = rep
334 cmmLitRep (CmmFloat _ rep)  = rep
335 cmmLitRep (CmmLabel _)      = wordRep
336 cmmLitRep (CmmLabelOff _ _) = wordRep
337 cmmLitRep (CmmLabelDiffOff _ _ _) = wordRep
338
339 -----------------------------------------------------------------------------
340 -- A local label.
341
342 -- Local labels must be unique within a single compilation unit.
343
344 newtype BlockId = BlockId Unique
345   deriving (Eq,Ord)
346
347 instance Uniquable BlockId where
348   getUnique (BlockId u) = u
349
350 type BlockEnv a = UniqFM {- BlockId -} a
351
352 -----------------------------------------------------------------------------
353 --              Static Data
354 -----------------------------------------------------------------------------
355
356 data Section
357   = Text
358   | Data
359   | ReadOnlyData
360   | RelocatableReadOnlyData
361   | UninitialisedData
362   | ReadOnlyData16      -- .rodata.cst16 on x86_64, 16-byte aligned
363   | OtherSection String
364
365 data CmmStatic
366   = CmmStaticLit CmmLit 
367         -- a literal value, size given by cmmLitRep of the literal.
368   | CmmUninitialised Int
369         -- uninitialised data, N bytes long
370   | CmmAlign Int
371         -- align to next N-byte boundary (N must be a power of 2).
372   | CmmDataLabel CLabel
373         -- label the current position in this section.
374   | CmmString [Word8]
375         -- string of 8-bit values only, not zero terminated.
376
377 -----------------------------------------------------------------------------
378 --              Global STG registers
379 -----------------------------------------------------------------------------
380
381 data GlobalReg
382   -- Argument and return registers
383   = VanillaReg                  -- pointers, unboxed ints and chars
384         {-# UNPACK #-} !Int     -- its number
385
386   | FloatReg            -- single-precision floating-point registers
387         {-# UNPACK #-} !Int     -- its number
388
389   | DoubleReg           -- double-precision floating-point registers
390         {-# UNPACK #-} !Int     -- its number
391
392   | LongReg             -- long int registers (64-bit, really)
393         {-# UNPACK #-} !Int     -- its number
394
395   -- STG registers
396   | Sp                  -- Stack ptr; points to last occupied stack location.
397   | SpLim               -- Stack limit
398   | Hp                  -- Heap ptr; points to last occupied heap location.
399   | HpLim               -- Heap limit register
400   | CurrentTSO          -- pointer to current thread's TSO
401   | CurrentNursery      -- pointer to allocation area
402   | HpAlloc             -- allocation count for heap check failure
403
404                 -- We keep the address of some commonly-called 
405                 -- functions in the register table, to keep code
406                 -- size down:
407   | GCEnter1            -- stg_gc_enter_1
408   | GCFun               -- stg_gc_fun
409
410   -- Base offset for the register table, used for accessing registers
411   -- which do not have real registers assigned to them.  This register
412   -- will only appear after we have expanded GlobalReg into memory accesses
413   -- (where necessary) in the native code generator.
414   | BaseReg
415
416   -- Base Register for PIC (position-independent code) calculations
417   -- Only used inside the native code generator. It's exact meaning differs
418   -- from platform to platform (see module PositionIndependentCode).
419   | PicBaseReg
420
421   deriving( Eq
422 #ifdef DEBUG
423         , Show
424 #endif
425          )
426
427 -- convenient aliases
428 spReg, hpReg, spLimReg, nodeReg :: CmmReg
429 spReg = CmmGlobal Sp
430 hpReg = CmmGlobal Hp
431 spLimReg = CmmGlobal SpLim
432 nodeReg = CmmGlobal node
433
434 node :: GlobalReg
435 node = VanillaReg 1
436
437 globalRegRep :: GlobalReg -> MachRep
438 globalRegRep (VanillaReg _)     = wordRep
439 globalRegRep (FloatReg _)       = F32
440 globalRegRep (DoubleReg _)      = F64
441 globalRegRep (LongReg _)        = I64
442 globalRegRep _                  = wordRep