Big collection of patches for 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(..), HasStaticClosure, ClosureTypeInfo(..), ConstrDescription,
17         ProfilingInfo(..), ClosureTypeTag,
18         GenBasicBlock(..), CmmBasicBlock, blockId, blockStmts, mapBlockStmts,
19         CmmReturnInfo(..),
20         CmmStmt(..), CmmActual, CmmActuals, CmmFormal, CmmFormals, 
21         HintedCmmFormal, HintedCmmFormals, HintedCmmActual, HintedCmmActuals,
22         CmmSafety(..),
23         CmmCallTarget(..), CallishMachOp(..), pprCallishMachOp,
24         ForeignHint(..), CmmHinted(..),
25         CmmStatic(..), Section(..),
26         module CmmExpr,
27   ) where
28
29 #include "HsVersions.h"
30
31 import BlockId
32 import CmmExpr
33 import CLabel
34 import ForeignCall
35 import SMRep
36
37 import ClosureInfo
38 import Outputable
39 import FastString
40
41 import Data.Word
42
43
44 -- A [[BlockId]] is a local label.
45 -- Local labels must be unique within an entire compilation unit, not
46 -- just a single top-level item, because local labels map one-to-one
47 -- with assembly-language labels.
48
49 -----------------------------------------------------------------------------
50 --  Cmm, CmmTop, CmmBasicBlock
51 -----------------------------------------------------------------------------
52
53 -- A file is a list of top-level chunks.  These may be arbitrarily
54 -- re-orderd during code generation.
55
56 -- GenCmm is abstracted over
57 --   d, the type of static data elements in CmmData
58 --   h, the static info preceding the code of a CmmProc
59 --   g, the control-flow graph of a CmmProc
60 --
61 -- We expect there to be two main instances of this type:
62 --   (a) C--, i.e. populated with various C-- constructs
63 --       (Cmm and RawCmm below)
64 --   (b) Native code, populated with data/instructions
65 --
66 -- A second family of instances based on ZipCfg is work in progress.
67 --
68 newtype GenCmm d h g = Cmm [GenCmmTop d h g]
69
70 -- | A top-level chunk, abstracted over the type of the contents of
71 -- the basic blocks (Cmm or instructions are the likely instantiations).
72 data GenCmmTop d h g
73   = CmmProc     -- A procedure
74      h                 -- Extra header such as the info table
75      CLabel            -- Used to generate both info & entry labels
76      CmmFormals              -- Argument locals live on entry (C-- procedure params)
77                        -- XXX Odd that there are no kinds, but there you are ---NR
78      g                 -- Control-flow graph for the procedure's code
79
80   | CmmData     -- Static data
81         Section 
82         [d]
83
84 -- | A control-flow graph represented as a list of extended basic blocks.
85 newtype ListGraph i = ListGraph [GenBasicBlock i] 
86    -- ^ Code, may be empty.  The first block is the entry point.  The
87    -- order is otherwise initially unimportant, but at some point the
88    -- code gen will fix the order.
89
90    -- BlockIds must be unique across an entire compilation unit, since
91    -- they are translated to assembly-language labels, which scope
92    -- across a whole compilation unit.
93
94 -- | Cmm with the info table as a data type
95 type Cmm    = GenCmm    CmmStatic CmmInfo (ListGraph CmmStmt)
96 type CmmTop = GenCmmTop CmmStatic CmmInfo (ListGraph CmmStmt)
97
98 -- | Cmm with the info tables converted to a list of 'CmmStatic'
99 type RawCmm    = GenCmm    CmmStatic [CmmStatic] (ListGraph CmmStmt)
100 type RawCmmTop = GenCmmTop CmmStatic [CmmStatic] (ListGraph CmmStmt)
101
102
103 -- A basic block containing a single label, at the beginning.
104 -- The list of basic blocks in a top-level code block may be re-ordered.
105 -- Fall-through is not allowed: there must be an explicit jump at the
106 -- end of each basic block, but the code generator might rearrange basic
107 -- blocks in order to turn some jumps into fallthroughs.
108
109 data GenBasicBlock i = BasicBlock BlockId [i]
110 type CmmBasicBlock   = GenBasicBlock CmmStmt
111
112 instance UserOfLocalRegs i => UserOfLocalRegs (GenBasicBlock i) where
113     foldRegsUsed f set (BasicBlock _ l) = foldRegsUsed f set l
114
115 blockId :: GenBasicBlock i -> BlockId
116 -- The branch block id is that of the first block in 
117 -- the branch, which is that branch's entry point
118 blockId (BasicBlock blk_id _ ) = blk_id
119
120 blockStmts :: GenBasicBlock i -> [i]
121 blockStmts (BasicBlock _ stmts) = stmts
122
123
124 mapBlockStmts :: (i -> i') -> GenBasicBlock i -> GenBasicBlock i'
125 mapBlockStmts f (BasicBlock id bs) = BasicBlock id (map f bs)
126 ----------------------------------------------------------------
127 --   graph maps
128 ----------------------------------------------------------------
129
130 cmmMapGraph    :: (g -> g') -> GenCmm    d h g -> GenCmm    d h g'
131 cmmTopMapGraph :: (g -> g') -> GenCmmTop d h g -> GenCmmTop d h g'
132
133 cmmMapGraphM    :: Monad m => (String -> g -> m g') -> GenCmm    d h g -> m (GenCmm    d h g')
134 cmmTopMapGraphM :: Monad m => (String -> g -> m g') -> GenCmmTop d h g -> m (GenCmmTop d h g')
135
136 cmmMapGraph f (Cmm tops) = Cmm $ map (cmmTopMapGraph f) tops
137 cmmTopMapGraph f (CmmProc h l args g) = CmmProc h l args (f g)
138 cmmTopMapGraph _ (CmmData s ds)       = CmmData s ds
139
140 cmmMapGraphM f (Cmm tops) = mapM (cmmTopMapGraphM f) tops >>= return . Cmm
141 cmmTopMapGraphM f (CmmProc h l args g) =
142   f (showSDoc $ ppr l) g >>= return . CmmProc h l args
143 cmmTopMapGraphM _ (CmmData s ds)       = return $ CmmData s ds
144
145 -----------------------------------------------------------------------------
146 --     Info Tables
147 -----------------------------------------------------------------------------
148
149 data CmmInfo
150   = CmmInfo
151       (Maybe BlockId)     -- GC target. Nothing <=> CPS won't do stack check
152                           -- JD: NOT USED BY NEW CODE GEN
153       (Maybe UpdateFrame) -- Update frame
154       CmmInfoTable        -- Info table
155
156 -- Info table as a haskell data type
157 data CmmInfoTable
158   = CmmInfoTable
159       HasStaticClosure
160       ProfilingInfo
161       ClosureTypeTag -- Int
162       ClosureTypeInfo
163   | CmmNonInfoTable   -- Procedure doesn't need an info table
164
165 type HasStaticClosure = Bool
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 FunArity ArgDescr SlowEntry
174   | ThunkInfo  ClosureLayout C_SRT
175   | ThunkSelectorInfo SelectorOffset C_SRT
176   | ContInfo
177       [Maybe LocalReg]  -- stack layout
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 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    -- Old-style
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 cmmExprType of the rhs.
217
218   | CmmCall                      -- A call (forign, native or primitive), with 
219      CmmCallTarget
220      HintedCmmFormals            -- zero or more results
221      HintedCmmActuals            -- 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       HintedCmmActuals         -- with these parameters.  (parameters never used)
237
238   | CmmReturn            -- Return from a native C-- function,
239       HintedCmmActuals         -- with these return values. (parameters never used)
240
241 type CmmActual = CmmExpr
242 type CmmFormal = LocalReg
243 type CmmActuals = [CmmActual]
244 type CmmFormals = [CmmFormal]
245
246 data CmmHinted a = CmmHinted { hintlessCmm :: a, cmmHint :: ForeignHint }
247                  deriving( Eq )
248
249 type HintedCmmActuals = [HintedCmmActual]
250 type HintedCmmFormals = [HintedCmmFormal]
251 type HintedCmmFormal  = CmmHinted CmmFormal
252 type HintedCmmActual  = CmmHinted CmmActual
253
254 data CmmSafety      = CmmUnsafe | CmmSafe C_SRT
255
256 -- | enable us to fold used registers over 'CmmActuals' and 'CmmFormals'
257 instance UserOfLocalRegs CmmStmt where
258   foldRegsUsed f set s = stmt s set
259     where stmt (CmmNop)                  = id
260           stmt (CmmComment {})           = id
261           stmt (CmmAssign _ e)           = gen e
262           stmt (CmmStore e1 e2)          = gen e1 . gen e2
263           stmt (CmmCall target _ es _ _) = gen target . gen es
264           stmt (CmmBranch _)             = id
265           stmt (CmmCondBranch e _)       = gen e
266           stmt (CmmSwitch e _)           = gen e
267           stmt (CmmJump e es)            = gen e . gen es
268           stmt (CmmReturn es)            = gen es
269           gen a set = foldRegsUsed f set a
270
271 instance UserOfLocalRegs CmmCallTarget where
272     foldRegsUsed f set (CmmCallee e _) = foldRegsUsed f set e
273     foldRegsUsed _ set (CmmPrim {})    = set
274
275 instance UserOfSlots CmmCallTarget where
276     foldSlotsUsed f set (CmmCallee e _) = foldSlotsUsed f set e
277     foldSlotsUsed _ set (CmmPrim {})    = set
278
279 instance UserOfLocalRegs a => UserOfLocalRegs (CmmHinted a) where
280   foldRegsUsed f set a = foldRegsUsed f set (hintlessCmm a)
281
282 instance UserOfSlots a => UserOfSlots (CmmHinted a) where
283   foldSlotsUsed f set a = foldSlotsUsed f set (hintlessCmm a)
284
285 instance DefinerOfLocalRegs a => DefinerOfLocalRegs (CmmHinted a) where
286   foldRegsDefd f set a = foldRegsDefd f set (hintlessCmm a)
287
288 {-
289 Discussion
290 ~~~~~~~~~~
291
292 One possible problem with the above type is that the only way to do a
293 non-local conditional jump is to encode it as a branch to a block that
294 contains a single jump.  This leads to inefficient code in the back end.
295
296 [N.B. This problem will go away when we make the transition to the
297 'zipper' form of control-flow graph, in which both targets of a
298 conditional jump are explicit. ---NR]
299
300 One possible way to fix this would be:
301
302 data CmmStat = 
303   ...
304   | CmmJump CmmBranchDest
305   | CmmCondJump CmmExpr CmmBranchDest
306   ...
307
308 data CmmBranchDest
309   = Local BlockId
310   | NonLocal CmmExpr [LocalReg]
311
312 In favour:
313
314 + one fewer constructors in CmmStmt
315 + allows both cond branch and switch to jump to non-local destinations
316
317 Against:
318
319 - not strictly necessary: can already encode as branch+jump
320 - not always possible to implement any better in the back end
321 - could do the optimisation in the back end (but then plat-specific?)
322 - C-- doesn't have it
323 - back-end optimisation might be more general (jump shortcutting)
324
325 So we'll stick with the way it is, and add the optimisation to the NCG.
326 -}
327
328 -----------------------------------------------------------------------------
329 --              CmmCallTarget
330 --
331 -- The target of a CmmCall.
332 -----------------------------------------------------------------------------
333
334 data CmmCallTarget
335   = CmmCallee           -- Call a function (foreign or native)
336         CmmExpr                 -- literal label <=> static call
337                                 -- other expression <=> dynamic call
338         CCallConv               -- The calling convention
339
340   | CmmPrim             -- Call a "primitive" (eg. sin, cos)
341         CallishMachOp           -- These might be implemented as inline
342                                 -- code by the backend.
343   deriving Eq
344
345
346 data ForeignHint
347   = NoHint | AddrHint | SignedHint
348   deriving( Eq )
349         -- Used to give extra per-argument or per-result
350         -- information needed by foreign calling conventions
351
352
353 -- CallishMachOps tend to be implemented by foreign calls in some backends,
354 -- so we separate them out.  In Cmm, these can only occur in a
355 -- statement position, in contrast to an ordinary MachOp which can occur
356 -- anywhere in an expression.
357 data CallishMachOp
358   = MO_F64_Pwr
359   | MO_F64_Sin
360   | MO_F64_Cos
361   | MO_F64_Tan
362   | MO_F64_Sinh
363   | MO_F64_Cosh
364   | MO_F64_Tanh
365   | MO_F64_Asin
366   | MO_F64_Acos
367   | MO_F64_Atan
368   | MO_F64_Log
369   | MO_F64_Exp
370   | MO_F64_Sqrt
371   | MO_F32_Pwr
372   | MO_F32_Sin
373   | MO_F32_Cos
374   | MO_F32_Tan
375   | MO_F32_Sinh
376   | MO_F32_Cosh
377   | MO_F32_Tanh
378   | MO_F32_Asin
379   | MO_F32_Acos
380   | MO_F32_Atan
381   | MO_F32_Log
382   | MO_F32_Exp
383   | MO_F32_Sqrt
384   | MO_WriteBarrier
385   deriving (Eq, Show)
386
387 pprCallishMachOp :: CallishMachOp -> SDoc
388 pprCallishMachOp mo = text (show mo)
389   
390 -----------------------------------------------------------------------------
391 --              Static Data
392 -----------------------------------------------------------------------------
393
394 data Section
395   = Text
396   | Data
397   | ReadOnlyData
398   | RelocatableReadOnlyData
399   | UninitialisedData
400   | ReadOnlyData16      -- .rodata.cst16 on x86_64, 16-byte aligned
401   | OtherSection String
402
403 data CmmStatic
404   = CmmStaticLit CmmLit 
405         -- a literal value, size given by cmmLitRep of the literal.
406   | CmmUninitialised Int
407         -- uninitialised data, N bytes long
408   | CmmAlign Int
409         -- align to next N-byte boundary (N must be a power of 2).
410   | CmmDataLabel CLabel
411         -- label the current position in this section.
412   | CmmString [Word8]
413         -- string of 8-bit values only, not zero terminated.
414