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