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