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