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