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