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