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