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