Cmm back end upgrades
[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         ListGraph(..),
13         cmmMapGraph, cmmTopMapGraph,
14         cmmMapGraphM, cmmTopMapGraphM,
15         CmmInfo(..), UpdateFrame(..),
16         CmmInfoTable(..), ClosureTypeInfo(..), ProfilingInfo(..), ClosureTypeTag,
17         GenBasicBlock(..), CmmBasicBlock, blockId, blockStmts, mapBlockStmts,
18         CmmReturnInfo(..),
19         CmmStmt(..), CmmActual, CmmActuals, CmmFormal, CmmFormals, CmmKind,
20         CmmFormalsWithoutKinds, CmmFormalWithoutKind,
21         CmmKinded(..),
22         CmmSafety(..),
23         CmmCallTarget(..),
24         CmmStatic(..), Section(..),
25         module CmmExpr,
26
27         BlockId(..), mkBlockId,
28         BlockEnv, emptyBlockEnv, lookupBlockEnv, extendBlockEnv, mkBlockEnv,
29         BlockSet, emptyBlockSet, elemBlockSet, extendBlockSet,
30   ) where
31
32 #include "HsVersions.h"
33
34 import CmmExpr
35 import MachOp
36 import CLabel
37 import ForeignCall
38 import SMRep
39 import ClosureInfo
40 import Outputable
41 import FastString
42
43 import Data.Word
44
45 import StackSlot (      BlockId(..), mkBlockId
46                  , BlockEnv, emptyBlockEnv, lookupBlockEnv, extendBlockEnv, mkBlockEnv
47                  , BlockSet, emptyBlockSet, elemBlockSet, extendBlockSet
48                  )
49
50 -- A [[BlockId]] is a local label.
51 -- Local labels must be unique within an entire compilation unit, not
52 -- just a single top-level item, because local labels map one-to-one
53 -- with assembly-language labels.
54
55 -----------------------------------------------------------------------------
56 --              Cmm, CmmTop, CmmBasicBlock
57 -----------------------------------------------------------------------------
58
59 -- A file is a list of top-level chunks.  These may be arbitrarily
60 -- re-orderd during code generation.
61
62 -- GenCmm is abstracted over
63 --   d, the type of static data elements in CmmData
64 --   h, the static info preceding the code of a CmmProc
65 --   g, the control-flow graph of a CmmProc
66 --
67 -- We expect there to be two main instances of this type:
68 --   (a) C--, i.e. populated with various C-- constructs
69 --              (Cmm and RawCmm below)
70 --   (b) Native code, populated with data/instructions
71 --
72 -- A second family of instances based on ZipCfg is work in progress.
73 --
74 newtype GenCmm d h g = Cmm [GenCmmTop d h g]
75
76 -- | A top-level chunk, abstracted over the type of the contents of
77 -- the basic blocks (Cmm or instructions are the likely instantiations).
78 data GenCmmTop d h g
79   = CmmProc     -- A procedure
80      h                 -- Extra header such as the info table
81      CLabel            -- Used to generate both info & entry labels
82      CmmFormalsWithoutKinds -- Argument locals live on entry (C-- procedure params)
83                        -- XXX Odd that there are no kinds, but there you are ---NR
84      g                 -- Control-flow graph for the procedure's code
85
86   | CmmData     -- Static data
87         Section 
88         [d]
89
90 -- | A control-flow graph represented as a list of extended basic blocks.
91 newtype ListGraph i = ListGraph [GenBasicBlock i] 
92    -- ^ Code, may be empty.  The first block is the entry point.  The
93    -- order is otherwise initially unimportant, but at some point the
94    -- code gen will fix the order.
95
96    -- BlockIds must be unique across an entire compilation unit, since
97    -- they are translated to assembly-language labels, which scope
98    -- across a whole compilation unit.
99
100 -- | Cmm with the info table as a data type
101 type Cmm    = GenCmm    CmmStatic CmmInfo (ListGraph CmmStmt)
102 type CmmTop = GenCmmTop CmmStatic CmmInfo (ListGraph CmmStmt)
103
104 -- | Cmm with the info tables converted to a list of 'CmmStatic'
105 type RawCmm    = GenCmm    CmmStatic [CmmStatic] (ListGraph CmmStmt)
106 type RawCmmTop = GenCmmTop CmmStatic [CmmStatic] (ListGraph CmmStmt)
107
108
109 -- A basic block containing a single label, at the beginning.
110 -- The list of basic blocks in a top-level code block may be re-ordered.
111 -- Fall-through is not allowed: there must be an explicit jump at the
112 -- end of each basic block, but the code generator might rearrange basic
113 -- blocks in order to turn some jumps into fallthroughs.
114
115 data GenBasicBlock i = BasicBlock BlockId [i]
116 type CmmBasicBlock   = GenBasicBlock CmmStmt
117
118 instance UserOfLocalRegs i => UserOfLocalRegs (GenBasicBlock i) where
119     foldRegsUsed f set (BasicBlock _ l) = foldRegsUsed f set l
120
121 blockId :: GenBasicBlock i -> BlockId
122 -- The branch block id is that of the first block in 
123 -- the branch, which is that branch's entry point
124 blockId (BasicBlock blk_id _ ) = blk_id
125
126 blockStmts :: GenBasicBlock i -> [i]
127 blockStmts (BasicBlock _ stmts) = stmts
128
129
130 mapBlockStmts :: (i -> i') -> GenBasicBlock i -> GenBasicBlock i'
131 mapBlockStmts f (BasicBlock id bs) = BasicBlock id (map f bs)
132 ----------------------------------------------------------------
133 --   graph maps
134 ----------------------------------------------------------------
135
136 cmmMapGraph    :: (g -> g') -> GenCmm    d h g -> GenCmm    d h g'
137 cmmTopMapGraph :: (g -> g') -> GenCmmTop d h g -> GenCmmTop d h g'
138
139 cmmMapGraphM    :: Monad m => (String -> g -> m g') -> GenCmm    d h g -> m (GenCmm    d h g')
140 cmmTopMapGraphM :: Monad m => (String -> g -> m g') -> GenCmmTop d h g -> m (GenCmmTop d h g')
141
142 cmmMapGraph f (Cmm tops) = Cmm $ map (cmmTopMapGraph f) tops
143 cmmTopMapGraph f (CmmProc h l args g) = CmmProc h l args (f g)
144 cmmTopMapGraph _ (CmmData s ds)       = CmmData s ds
145
146 cmmMapGraphM f (Cmm tops) = mapM (cmmTopMapGraphM f) tops >>= return . Cmm
147 cmmTopMapGraphM f (CmmProc h l args g) = f (showSDoc $ ppr l) g >>= return . CmmProc h l args
148 cmmTopMapGraphM _ (CmmData s ds)       = return $ CmmData s ds
149
150 -----------------------------------------------------------------------------
151 --     Info Tables
152 -----------------------------------------------------------------------------
153
154 data CmmInfo
155   = CmmInfo
156       (Maybe BlockId)     -- GC target. Nothing <=> CPS won't do stack check
157       (Maybe UpdateFrame) -- Update frame
158       CmmInfoTable        -- Info table
159
160 -- Info table as a haskell data type
161 data CmmInfoTable
162   = CmmInfoTable
163       ProfilingInfo
164       ClosureTypeTag -- Int
165       ClosureTypeInfo
166   | CmmNonInfoTable   -- Procedure doesn't need an info table
167
168 -- TODO: The GC target shouldn't really be part of CmmInfo
169 -- as it doesn't appear in the resulting info table.
170 -- It should be factored out.
171
172 data ClosureTypeInfo
173   = ConstrInfo ClosureLayout ConstrTag ConstrDescription
174   | FunInfo ClosureLayout C_SRT FunType FunArity ArgDescr SlowEntry
175   | ThunkInfo ClosureLayout C_SRT
176   | ThunkSelectorInfo SelectorOffset C_SRT
177   | ContInfo
178       [Maybe LocalReg]  -- Forced stack parameters
179       C_SRT
180
181 data CmmReturnInfo = CmmMayReturn
182                    | CmmNeverReturns
183
184 -- TODO: These types may need refinement
185 data ProfilingInfo = ProfilingInfo CmmLit CmmLit -- closure_type, closure_desc
186 type ClosureTypeTag = StgHalfWord
187 type ClosureLayout = (StgHalfWord, StgHalfWord) -- ptrs, nptrs
188 type ConstrTag = StgHalfWord
189 type ConstrDescription = CmmLit
190 type FunType = StgHalfWord
191 type FunArity = StgHalfWord
192 type SlowEntry = CmmLit
193   -- ^We would like this to be a CLabel but
194   -- for now the parser sets this to zero on an INFO_TABLE_FUN.
195 type SelectorOffset = StgWord
196
197 -- | A frame that is to be pushed before entry to the function.
198 -- Used to handle 'update' frames.
199 data UpdateFrame =
200     UpdateFrame
201       CmmExpr    -- Frame header.  Behaves like the target of a 'jump'.
202       [CmmExpr]  -- Frame remainder.  Behaves like the arguments of a 'jump'.
203
204 -----------------------------------------------------------------------------
205 --              CmmStmt
206 -- A "statement".  Note that all branches are explicit: there are no
207 -- control transfers to computed addresses, except when transfering
208 -- control to a new function.
209 -----------------------------------------------------------------------------
210
211 data CmmStmt
212   = CmmNop
213   | CmmComment FastString
214
215   | CmmAssign CmmReg CmmExpr     -- Assign to register
216
217   | CmmStore CmmExpr CmmExpr     -- Assign to memory location.  Size is
218                                  -- given by cmmExprRep of the rhs.
219
220   | CmmCall                      -- A call (forign, native or primitive), with 
221      CmmCallTarget
222      CmmFormals          -- zero or more results
223      CmmActuals                  -- zero or more arguments
224      CmmSafety                   -- whether to build a continuation
225      CmmReturnInfo
226
227   | CmmBranch BlockId             -- branch to another BB in this fn
228
229   | CmmCondBranch CmmExpr BlockId -- conditional branch
230
231   | CmmSwitch CmmExpr [Maybe BlockId]   -- Table branch
232         -- The scrutinee is zero-based; 
233         --      zero -> first block
234         --      one  -> second block etc
235         -- Undefined outside range, and when there's a Nothing
236
237   | CmmJump CmmExpr      -- Jump to another C-- function,
238       CmmActuals         -- with these parameters.
239
240   | CmmReturn            -- Return from a native C-- function,
241       CmmActuals         -- with these return values.
242
243 type CmmKind   = MachHint
244 data CmmKinded a = CmmKinded { kindlessCmm :: a, cmmKind :: CmmKind }
245                          deriving (Eq)
246 type CmmActual = CmmKinded CmmExpr
247 type CmmFormal = CmmKinded LocalReg
248 type CmmActuals = [CmmActual]
249 type CmmFormals = [CmmFormal]
250 type CmmFormalWithoutKind   = LocalReg
251 type CmmFormalsWithoutKinds = [CmmFormalWithoutKind]
252
253 data CmmSafety      = CmmUnsafe | CmmSafe C_SRT
254
255 -- | enable us to fold used registers over 'CmmActuals' and 'CmmFormals'
256 instance UserOfLocalRegs a => UserOfLocalRegs (CmmKinded a) where
257   foldRegsUsed f set (CmmKinded a _) = foldRegsUsed f set a
258
259 instance UserOfLocalRegs CmmStmt where
260   foldRegsUsed f set s = stmt s set
261     where stmt (CmmNop)                  = id
262           stmt (CmmComment {})           = id
263           stmt (CmmAssign _ e)           = gen e
264           stmt (CmmStore e1 e2)          = gen e1 . gen e2
265           stmt (CmmCall target _ es _ _) = gen target . gen es
266           stmt (CmmBranch _)             = id
267           stmt (CmmCondBranch e _)       = gen e
268           stmt (CmmSwitch e _)           = gen e
269           stmt (CmmJump e es)            = gen e . gen es
270           stmt (CmmReturn es)            = gen es
271           gen a set = foldRegsUsed f set a
272
273 instance UserOfLocalRegs CmmCallTarget where
274     foldRegsUsed f set (CmmCallee e _) = foldRegsUsed f set e
275     foldRegsUsed _ set (CmmPrim {})    = set
276
277 instance DefinerOfLocalRegs a => DefinerOfLocalRegs (CmmKinded a) where
278   foldRegsDefd f z (CmmKinded x _) = foldRegsDefd f z x
279
280
281 --just look like a tuple, since it was a tuple before
282 -- ... is that a good idea? --Isaac Dupree
283 instance (Outputable a) => Outputable (CmmKinded a) where
284   ppr (CmmKinded a k) = ppr (a, k)
285
286 {-
287 Discussion
288 ~~~~~~~~~~
289
290 One possible problem with the above type is that the only way to do a
291 non-local conditional jump is to encode it as a branch to a block that
292 contains a single jump.  This leads to inefficient code in the back end.
293
294 [N.B. This problem will go away when we make the transition to the
295 'zipper' form of control-flow graph, in which both targets of a
296 conditional jump are explicit. ---NR]
297
298 One possible way to fix this would be:
299
300 data CmmStat = 
301   ...
302   | CmmJump CmmBranchDest
303   | CmmCondJump CmmExpr CmmBranchDest
304   ...
305
306 data CmmBranchDest
307   = Local BlockId
308   | NonLocal CmmExpr [LocalReg]
309
310 In favour:
311
312 + one fewer constructors in CmmStmt
313 + allows both cond branch and switch to jump to non-local destinations
314
315 Against:
316
317 - not strictly necessary: can already encode as branch+jump
318 - not always possible to implement any better in the back end
319 - could do the optimisation in the back end (but then plat-specific?)
320 - C-- doesn't have it
321 - back-end optimisation might be more general (jump shortcutting)
322
323 So we'll stick with the way it is, and add the optimisation to the NCG.
324 -}
325
326 -----------------------------------------------------------------------------
327 --              CmmCallTarget
328 --
329 -- The target of a CmmCall.
330 -----------------------------------------------------------------------------
331
332 data CmmCallTarget
333   = CmmCallee           -- Call a function (foreign or native)
334         CmmExpr                 -- literal label <=> static call
335                                 -- other expression <=> dynamic call
336         CCallConv               -- The calling convention
337
338   | CmmPrim             -- Call a "primitive" (eg. sin, cos)
339         CallishMachOp           -- These might be implemented as inline
340                                 -- code by the backend.
341   deriving Eq
342
343 -----------------------------------------------------------------------------
344 --              Static Data
345 -----------------------------------------------------------------------------
346
347 data Section
348   = Text
349   | Data
350   | ReadOnlyData
351   | RelocatableReadOnlyData
352   | UninitialisedData
353   | ReadOnlyData16      -- .rodata.cst16 on x86_64, 16-byte aligned
354   | OtherSection String
355
356 data CmmStatic
357   = CmmStaticLit CmmLit 
358         -- a literal value, size given by cmmLitRep of the literal.
359   | CmmUninitialised Int
360         -- uninitialised data, N bytes long
361   | CmmAlign Int
362         -- align to next N-byte boundary (N must be a power of 2).
363   | CmmDataLabel CLabel
364         -- label the current position in this section.
365   | CmmString [Word8]
366         -- string of 8-bit values only, not zero terminated.
367