Merging in the new codegen branch
[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, 
20         HintedCmmFormal, HintedCmmFormals, HintedCmmActual, HintedCmmActuals,
21         CmmSafety(..),
22         CmmCallTarget(..), CallishMachOp(..), pprCallishMachOp,
23         ForeignHint(..), CmmHinted(..),
24         CmmStatic(..), Section(..),
25         module CmmExpr,
26   ) where
27
28 #include "HsVersions.h"
29
30 import BlockId
31 import CmmExpr
32 import CLabel
33 import ForeignCall
34 import SMRep
35
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      CmmFormals              -- 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 FunArity ArgDescr SlowEntry
168   | ThunkInfo  ClosureLayout C_SRT
169   | ThunkSelectorInfo SelectorOffset C_SRT
170   | ContInfo
171       [Maybe LocalReg]  -- stack layout
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 FunArity = StgHalfWord
184 type SlowEntry = CmmLit
185   -- We would like this to be a CLabel but
186   -- for now the parser sets this to zero on an INFO_TABLE_FUN.
187 type SelectorOffset = StgWord
188
189 -- | A frame that is to be pushed before entry to the function.
190 -- Used to handle 'update' frames.
191 data UpdateFrame =
192     UpdateFrame
193       CmmExpr    -- Frame header.  Behaves like the target of a 'jump'.
194       [CmmExpr]  -- Frame remainder.  Behaves like the arguments of a 'jump'.
195
196 -----------------------------------------------------------------------------
197 --              CmmStmt
198 -- A "statement".  Note that all branches are explicit: there are no
199 -- control transfers to computed addresses, except when transfering
200 -- control to a new function.
201 -----------------------------------------------------------------------------
202
203 data CmmStmt    -- Old-style
204   = CmmNop
205   | CmmComment FastString
206
207   | CmmAssign CmmReg CmmExpr     -- Assign to register
208
209   | CmmStore CmmExpr CmmExpr     -- Assign to memory location.  Size is
210                                  -- given by cmmExprType of the rhs.
211
212   | CmmCall                      -- A call (forign, native or primitive), with 
213      CmmCallTarget
214      HintedCmmFormals            -- zero or more results
215      HintedCmmActuals            -- zero or more arguments
216      CmmSafety                   -- whether to build a continuation
217      CmmReturnInfo
218
219   | CmmBranch BlockId             -- branch to another BB in this fn
220
221   | CmmCondBranch CmmExpr BlockId -- conditional branch
222
223   | CmmSwitch CmmExpr [Maybe BlockId]   -- Table branch
224         -- The scrutinee is zero-based; 
225         --      zero -> first block
226         --      one  -> second block etc
227         -- Undefined outside range, and when there's a Nothing
228
229   | CmmJump CmmExpr      -- Jump to another C-- function,
230       HintedCmmActuals         -- with these parameters.  (parameters never used)
231
232   | CmmReturn            -- Return from a native C-- function,
233       HintedCmmActuals         -- with these return values. (parameters never used)
234
235 type CmmActual = CmmExpr
236 type CmmFormal = LocalReg
237 type CmmActuals = [CmmActual]
238 type CmmFormals = [CmmFormal]
239
240 data CmmHinted a = CmmHinted { hintlessCmm :: a, cmmHint :: ForeignHint }
241                  deriving( Eq )
242
243 type HintedCmmActuals = [HintedCmmActual]
244 type HintedCmmFormals = [HintedCmmFormal]
245 type HintedCmmFormal  = CmmHinted CmmFormal
246 type HintedCmmActual  = CmmHinted CmmActual
247
248 data CmmSafety      = CmmUnsafe | CmmSafe C_SRT
249
250 -- | enable us to fold used registers over 'CmmActuals' and 'CmmFormals'
251 instance UserOfLocalRegs CmmStmt where
252   foldRegsUsed f set s = stmt s set
253     where stmt (CmmNop)                  = id
254           stmt (CmmComment {})           = id
255           stmt (CmmAssign _ e)           = gen e
256           stmt (CmmStore e1 e2)          = gen e1 . gen e2
257           stmt (CmmCall target _ es _ _) = gen target . gen es
258           stmt (CmmBranch _)             = id
259           stmt (CmmCondBranch e _)       = gen e
260           stmt (CmmSwitch e _)           = gen e
261           stmt (CmmJump e es)            = gen e . gen es
262           stmt (CmmReturn es)            = gen es
263           gen a set = foldRegsUsed f set a
264
265 instance UserOfLocalRegs CmmCallTarget where
266     foldRegsUsed f set (CmmCallee e _) = foldRegsUsed f set e
267     foldRegsUsed _ set (CmmPrim {})    = set
268
269 instance UserOfSlots CmmCallTarget where
270     foldSlotsUsed f set (CmmCallee e _) = foldSlotsUsed f set e
271     foldSlotsUsed _ set (CmmPrim {})    = set
272
273 instance UserOfLocalRegs a => UserOfLocalRegs (CmmHinted a) where
274   foldRegsUsed f set a = foldRegsUsed f set (hintlessCmm a)
275
276 instance UserOfSlots a => UserOfSlots (CmmHinted a) where
277   foldSlotsUsed f set a = foldSlotsUsed f set (hintlessCmm a)
278
279 instance DefinerOfLocalRegs a => DefinerOfLocalRegs (CmmHinted a) where
280   foldRegsDefd f set a = foldRegsDefd f set (hintlessCmm a)
281
282 {-
283 Discussion
284 ~~~~~~~~~~
285
286 One possible problem with the above type is that the only way to do a
287 non-local conditional jump is to encode it as a branch to a block that
288 contains a single jump.  This leads to inefficient code in the back end.
289
290 [N.B. This problem will go away when we make the transition to the
291 'zipper' form of control-flow graph, in which both targets of a
292 conditional jump are explicit. ---NR]
293
294 One possible way to fix this would be:
295
296 data CmmStat = 
297   ...
298   | CmmJump CmmBranchDest
299   | CmmCondJump CmmExpr CmmBranchDest
300   ...
301
302 data CmmBranchDest
303   = Local BlockId
304   | NonLocal CmmExpr [LocalReg]
305
306 In favour:
307
308 + one fewer constructors in CmmStmt
309 + allows both cond branch and switch to jump to non-local destinations
310
311 Against:
312
313 - not strictly necessary: can already encode as branch+jump
314 - not always possible to implement any better in the back end
315 - could do the optimisation in the back end (but then plat-specific?)
316 - C-- doesn't have it
317 - back-end optimisation might be more general (jump shortcutting)
318
319 So we'll stick with the way it is, and add the optimisation to the NCG.
320 -}
321
322 -----------------------------------------------------------------------------
323 --              CmmCallTarget
324 --
325 -- The target of a CmmCall.
326 -----------------------------------------------------------------------------
327
328 data CmmCallTarget
329   = CmmCallee           -- Call a function (foreign or native)
330         CmmExpr                 -- literal label <=> static call
331                                 -- other expression <=> dynamic call
332         CCallConv               -- The calling convention
333
334   | CmmPrim             -- Call a "primitive" (eg. sin, cos)
335         CallishMachOp           -- These might be implemented as inline
336                                 -- code by the backend.
337   deriving Eq
338
339
340 data ForeignHint
341   = NoHint | AddrHint | SignedHint
342   deriving( Eq )
343         -- Used to give extra per-argument or per-result
344         -- information needed by foreign calling conventions
345
346
347 -- CallishMachOps tend to be implemented by foreign calls in some backends,
348 -- so we separate them out.  In Cmm, these can only occur in a
349 -- statement position, in contrast to an ordinary MachOp which can occur
350 -- anywhere in an expression.
351 data CallishMachOp
352   = MO_F64_Pwr
353   | MO_F64_Sin
354   | MO_F64_Cos
355   | MO_F64_Tan
356   | MO_F64_Sinh
357   | MO_F64_Cosh
358   | MO_F64_Tanh
359   | MO_F64_Asin
360   | MO_F64_Acos
361   | MO_F64_Atan
362   | MO_F64_Log
363   | MO_F64_Exp
364   | MO_F64_Sqrt
365   | MO_F32_Pwr
366   | MO_F32_Sin
367   | MO_F32_Cos
368   | MO_F32_Tan
369   | MO_F32_Sinh
370   | MO_F32_Cosh
371   | MO_F32_Tanh
372   | MO_F32_Asin
373   | MO_F32_Acos
374   | MO_F32_Atan
375   | MO_F32_Log
376   | MO_F32_Exp
377   | MO_F32_Sqrt
378   | MO_WriteBarrier
379   deriving (Eq, Show)
380
381 pprCallishMachOp :: CallishMachOp -> SDoc
382 pprCallishMachOp mo = text (show mo)
383   
384 -----------------------------------------------------------------------------
385 --              Static Data
386 -----------------------------------------------------------------------------
387
388 data Section
389   = Text
390   | Data
391   | ReadOnlyData
392   | RelocatableReadOnlyData
393   | UninitialisedData
394   | ReadOnlyData16      -- .rodata.cst16 on x86_64, 16-byte aligned
395   | OtherSection String
396
397 data CmmStatic
398   = CmmStaticLit CmmLit 
399         -- a literal value, size given by cmmLitRep of the literal.
400   | CmmUninitialised Int
401         -- uninitialised data, N bytes long
402   | CmmAlign Int
403         -- align to next N-byte boundary (N must be a power of 2).
404   | CmmDataLabel CLabel
405         -- label the current position in this section.
406   | CmmString [Word8]
407         -- string of 8-bit values only, not zero terminated.
408