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