Rename a constructor CmmForeignCall to CmmCallee, and tidy Cmm code
[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         CmmInfo(..), UpdateFrame(..),
13         CmmInfoTable(..), ClosureTypeInfo(..), ProfilingInfo(..), ClosureTypeTag,
14         GenBasicBlock(..), CmmBasicBlock, blockId, blockStmts, mapBlockStmts,
15         CmmStmt(..), CmmActuals, CmmFormal, CmmFormals, CmmHintFormals,
16         CmmSafety(..),
17         CmmCallTarget(..),
18         CmmStatic(..), Section(..),
19         CmmExpr(..), cmmExprRep, 
20         CmmReg(..), cmmRegRep,
21         CmmLit(..), cmmLitRep,
22         LocalReg(..), localRegRep, localRegGCFollow, Kind(..),
23         BlockId(..), BlockEnv,
24         GlobalReg(..), globalRegRep,
25
26         node, nodeReg, spReg, hpReg, spLimReg
27   ) where
28
29 #include "HsVersions.h"
30
31 import MachOp
32 import CLabel
33 import ForeignCall
34 import SMRep
35 import ClosureInfo
36 import Unique
37 import UniqFM
38 import FastString
39
40 import Data.Word
41
42 -----------------------------------------------------------------------------
43 --              Cmm, CmmTop, CmmBasicBlock
44 -----------------------------------------------------------------------------
45
46 -- A file is a list of top-level chunks.  These may be arbitrarily
47 -- re-orderd during code generation.
48
49 -- GenCmm is abstracted over
50 --   d, the type of static data elements in CmmData
51 --   h, the static info preceding the code of a CmmProc
52 --   i, the contents of a basic block within a CmmProc
53 --
54 -- We expect there to be two main instances of this type:
55 --   (a) C--, i.e. populated with various C-- constructs
56 --              (Cmm and RawCmm below)
57 --   (b) Native code, populated with data/instructions
58 --
59 newtype GenCmm d h i = Cmm [GenCmmTop d h i]
60
61 -- | A top-level chunk, abstracted over the type of the contents of
62 -- the basic blocks (Cmm or instructions are the likely instantiations).
63 data GenCmmTop d h i
64   = CmmProc     -- A procedure
65      h                 -- Extra header such as the info table
66      CLabel            -- Used to generate both info & entry labels
67      CmmFormals        -- Argument locals live on entry (C-- procedure params)
68      [GenBasicBlock i] -- Code, may be empty.  The first block is
69                        -- the entry point, and should be labelled by the code gen
70                        -- with the CLabel.  The order is otherwise initially 
71                        -- unimportant, but at some point the code gen will
72                        -- fix the order.
73
74                        -- The BlockId of the first block does not give rise
75                        -- to a label.  To jump to the first block in a Proc,
76                        -- use the appropriate CLabel.
77
78                        -- BlockIds are only unique within a procedure
79
80   | CmmData     -- Static data
81         Section 
82         [d]
83
84 -- | Cmm with the info table as a data type
85 type Cmm    = GenCmm    CmmStatic CmmInfo CmmStmt
86 type CmmTop = GenCmmTop CmmStatic CmmInfo CmmStmt
87
88 -- | Cmm with the info tables converted to a list of 'CmmStatic'
89 type RawCmm    = GenCmm    CmmStatic [CmmStatic] CmmStmt
90 type RawCmmTop = GenCmmTop CmmStatic [CmmStatic] CmmStmt
91
92
93 -- A basic block containing a single label, at the beginning.
94 -- The list of basic blocks in a top-level code block may be re-ordered.
95 -- Fall-through is not allowed: there must be an explicit jump at the
96 -- end of each basic block, but the code generator might rearrange basic
97 -- blocks in order to turn some jumps into fallthroughs.
98
99 data GenBasicBlock i = BasicBlock BlockId [i]
100 type CmmBasicBlock   = GenBasicBlock CmmStmt
101
102 blockId :: GenBasicBlock i -> BlockId
103 -- The branch block id is that of the first block in 
104 -- the branch, which is that branch's entry point
105 blockId (BasicBlock blk_id _ ) = blk_id
106
107 blockStmts :: GenBasicBlock i -> [i]
108 blockStmts (BasicBlock _ stmts) = stmts
109
110 mapBlockStmts f (BasicBlock id bs) = BasicBlock id (map f bs)
111
112 -----------------------------------------------------------------------------
113 --     Info Tables
114 -----------------------------------------------------------------------------
115
116 data CmmInfo
117   = CmmInfo
118       (Maybe BlockId)     -- GC target. Nothing <=> CPS won't do stack check
119       (Maybe UpdateFrame) -- Update frame
120       CmmInfoTable        -- Info table
121
122 -- Info table as a haskell data type
123 data CmmInfoTable
124   = CmmInfoTable
125       ProfilingInfo
126       ClosureTypeTag -- Int
127       ClosureTypeInfo
128   | CmmNonInfoTable   -- Procedure doesn't need an info table
129
130 -- TODO: The GC target shouldn't really be part of CmmInfo
131 -- as it doesn't appear in the resulting info table.
132 -- It should be factored out.
133
134 data ClosureTypeInfo
135   = ConstrInfo ClosureLayout ConstrTag ConstrDescription
136   | FunInfo ClosureLayout C_SRT FunType FunArity ArgDescr SlowEntry
137   | ThunkInfo ClosureLayout C_SRT
138   | ThunkSelectorInfo SelectorOffset C_SRT
139   | ContInfo
140       [Maybe LocalReg]  -- Forced stack parameters
141       C_SRT
142
143 -- TODO: These types may need refinement
144 data ProfilingInfo = ProfilingInfo CmmLit CmmLit -- closure_type, closure_desc
145 type ClosureTypeTag = StgHalfWord
146 type ClosureLayout = (StgHalfWord, StgHalfWord) -- ptrs, nptrs
147 type ConstrTag = StgHalfWord
148 type ConstrDescription = CmmLit
149 type FunType = StgHalfWord
150 type FunArity = StgHalfWord
151 type SlowEntry = CmmLit
152   -- ^We would like this to be a CLabel but
153   -- for now the parser sets this to zero on an INFO_TABLE_FUN.
154 type SelectorOffset = StgWord
155
156 -- | A frame that is to be pushed before entry to the function.
157 -- Used to handle 'update' frames.
158 data UpdateFrame =
159     UpdateFrame
160       CmmExpr    -- Frame header.  Behaves like the target of a 'jump'.
161       [CmmExpr]  -- Frame remainder.  Behaves like the arguments of a 'jump'.
162
163 -----------------------------------------------------------------------------
164 --              CmmStmt
165 -- A "statement".  Note that all branches are explicit: there are no
166 -- control transfers to computed addresses, except when transfering
167 -- control to a new function.
168 -----------------------------------------------------------------------------
169
170 data CmmStmt
171   = CmmNop
172   | CmmComment FastString
173
174   | CmmAssign CmmReg CmmExpr     -- Assign to register
175
176   | CmmStore CmmExpr CmmExpr     -- Assign to memory location.  Size is
177                                  -- given by cmmExprRep of the rhs.
178
179   | CmmCall                      -- A call (forign, native or primitive), with 
180      CmmCallTarget
181      CmmHintFormals              -- zero or more results
182      CmmActuals                  -- zero or more arguments
183      CmmSafety                   -- whether to build a continuation
184
185   | CmmBranch BlockId             -- branch to another BB in this fn
186
187   | CmmCondBranch CmmExpr BlockId -- conditional branch
188
189   | CmmSwitch CmmExpr [Maybe BlockId]   -- Table branch
190         -- The scrutinee is zero-based; 
191         --      zero -> first block
192         --      one  -> second block etc
193         -- Undefined outside range, and when there's a Nothing
194
195   | CmmJump CmmExpr      -- Jump to another C-- function,
196       CmmActuals         -- with these parameters.
197
198   | CmmReturn            -- Return from a native C-- function,
199       CmmActuals         -- with these return values.
200
201 type CmmActual      = CmmExpr
202 type CmmActuals     = [(CmmActual,MachHint)]
203 type CmmFormal      = LocalReg
204 type CmmHintFormals = [(CmmFormal,MachHint)]
205 type CmmFormals     = [CmmFormal]
206 data CmmSafety      = CmmUnsafe | CmmSafe C_SRT
207
208 {-
209 Discussion
210 ~~~~~~~~~~
211
212 One possible problem with the above type is that the only way to do a
213 non-local conditional jump is to encode it as a branch to a block that
214 contains a single jump.  This leads to inefficient code in the back end.
215
216 One possible way to fix this would be:
217
218 data CmmStat = 
219   ...
220   | CmmJump CmmBranchDest
221   | CmmCondJump CmmExpr CmmBranchDest
222   ...
223
224 data CmmBranchDest
225   = Local BlockId
226   | NonLocal CmmExpr [LocalReg]
227
228 In favour:
229
230 + one fewer constructors in CmmStmt
231 + allows both cond branch and switch to jump to non-local destinations
232
233 Against:
234
235 - not strictly necessary: can already encode as branch+jump
236 - not always possible to implement any better in the back end
237 - could do the optimisation in the back end (but then plat-specific?)
238 - C-- doesn't have it
239 - back-end optimisation might be more general (jump shortcutting)
240
241 So we'll stick with the way it is, and add the optimisation to the NCG.
242 -}
243
244 -----------------------------------------------------------------------------
245 --              CmmCallTarget
246 --
247 -- The target of a CmmCall.
248 -----------------------------------------------------------------------------
249
250 data CmmCallTarget
251   = CmmCallee           -- Call a function (foreign or native)
252         CmmExpr                 -- literal label <=> static call
253                                 -- other expression <=> dynamic call
254         CCallConv               -- The calling convention
255
256   | CmmPrim             -- Call a "primitive" (eg. sin, cos)
257         CallishMachOp           -- These might be implemented as inline
258                                 -- code by the backend.
259
260 -----------------------------------------------------------------------------
261 --              CmmExpr
262 -- An expression.  Expressions have no side effects.
263 -----------------------------------------------------------------------------
264
265 data CmmExpr
266   = CmmLit CmmLit               -- Literal
267   | CmmLoad CmmExpr MachRep     -- Read memory location
268   | CmmReg CmmReg               -- Contents of register
269   | CmmMachOp MachOp [CmmExpr]  -- Machine operation (+, -, *, etc.)
270   | CmmRegOff CmmReg Int        
271         -- CmmRegOff reg i
272         --        ** is shorthand only, meaning **
273         -- CmmMachOp (MO_S_Add rep (CmmReg reg) (CmmLit (CmmInt i rep)))
274         --      where rep = cmmRegRep reg
275   deriving Eq
276
277 data CmmReg 
278   = CmmLocal  LocalReg
279   | CmmGlobal GlobalReg
280   deriving( Eq )
281
282 -- | Whether a 'LocalReg' is a GC followable pointer
283 data Kind = KindPtr | KindNonPtr deriving (Eq)
284
285 data LocalReg
286   = LocalReg
287       !Unique   -- ^ Identifier
288       MachRep   -- ^ Type
289       Kind      -- ^ Should the GC follow as a pointer
290
291 data CmmLit
292   = CmmInt Integer  MachRep
293         -- Interpretation: the 2's complement representation of the value
294         -- is truncated to the specified size.  This is easier than trying
295         -- to keep the value within range, because we don't know whether
296         -- it will be used as a signed or unsigned value (the MachRep doesn't
297         -- distinguish between signed & unsigned).
298   | CmmFloat  Rational MachRep
299   | CmmLabel    CLabel                  -- Address of label
300   | CmmLabelOff CLabel Int              -- Address of label + byte offset
301   
302         -- Due to limitations in the C backend, the following
303         -- MUST ONLY be used inside the info table indicated by label2
304         -- (label2 must be the info label), and label1 must be an
305         -- SRT, a slow entrypoint or a large bitmap (see the Mangler)
306         -- Don't use it at all unless tablesNextToCode.
307         -- It is also used inside the NCG during when generating
308         -- position-independent code. 
309   | CmmLabelDiffOff CLabel CLabel Int   -- label1 - label2 + offset
310   deriving Eq
311
312 instance Eq LocalReg where
313   (LocalReg u1 _ _) == (LocalReg u2 _ _) = u1 == u2
314
315 instance Uniquable LocalReg where
316   getUnique (LocalReg uniq _ _) = uniq
317
318 -----------------------------------------------------------------------------
319 --              MachRep
320 -----------------------------------------------------------------------------
321 cmmExprRep :: CmmExpr -> MachRep
322 cmmExprRep (CmmLit lit)      = cmmLitRep lit
323 cmmExprRep (CmmLoad _ rep)   = rep
324 cmmExprRep (CmmReg reg)      = cmmRegRep reg
325 cmmExprRep (CmmMachOp op _)  = resultRepOfMachOp op
326 cmmExprRep (CmmRegOff reg _) = cmmRegRep reg
327
328 cmmRegRep :: CmmReg -> MachRep
329 cmmRegRep (CmmLocal  reg)       = localRegRep reg
330 cmmRegRep (CmmGlobal reg)       = globalRegRep reg
331
332 localRegRep :: LocalReg -> MachRep
333 localRegRep (LocalReg _ rep _) = rep
334
335 localRegGCFollow (LocalReg _ _ p) = p
336
337 cmmLitRep :: CmmLit -> MachRep
338 cmmLitRep (CmmInt _ rep)    = rep
339 cmmLitRep (CmmFloat _ rep)  = rep
340 cmmLitRep (CmmLabel _)      = wordRep
341 cmmLitRep (CmmLabelOff _ _) = wordRep
342 cmmLitRep (CmmLabelDiffOff _ _ _) = wordRep
343
344 -----------------------------------------------------------------------------
345 -- A local label.
346
347 -- Local labels must be unique within a single compilation unit.
348
349 newtype BlockId = BlockId Unique
350   deriving (Eq,Ord)
351
352 instance Uniquable BlockId where
353   getUnique (BlockId u) = u
354
355 type BlockEnv a = UniqFM {- BlockId -} a
356
357 -----------------------------------------------------------------------------
358 --              Static Data
359 -----------------------------------------------------------------------------
360
361 data Section
362   = Text
363   | Data
364   | ReadOnlyData
365   | RelocatableReadOnlyData
366   | UninitialisedData
367   | ReadOnlyData16      -- .rodata.cst16 on x86_64, 16-byte aligned
368   | OtherSection String
369
370 data CmmStatic
371   = CmmStaticLit CmmLit 
372         -- a literal value, size given by cmmLitRep of the literal.
373   | CmmUninitialised Int
374         -- uninitialised data, N bytes long
375   | CmmAlign Int
376         -- align to next N-byte boundary (N must be a power of 2).
377   | CmmDataLabel CLabel
378         -- label the current position in this section.
379   | CmmString [Word8]
380         -- string of 8-bit values only, not zero terminated.
381
382 -----------------------------------------------------------------------------
383 --              Global STG registers
384 -----------------------------------------------------------------------------
385
386 data GlobalReg
387   -- Argument and return registers
388   = VanillaReg                  -- pointers, unboxed ints and chars
389         {-# UNPACK #-} !Int     -- its number
390
391   | FloatReg            -- single-precision floating-point registers
392         {-# UNPACK #-} !Int     -- its number
393
394   | DoubleReg           -- double-precision floating-point registers
395         {-# UNPACK #-} !Int     -- its number
396
397   | LongReg             -- long int registers (64-bit, really)
398         {-# UNPACK #-} !Int     -- its number
399
400   -- STG registers
401   | Sp                  -- Stack ptr; points to last occupied stack location.
402   | SpLim               -- Stack limit
403   | Hp                  -- Heap ptr; points to last occupied heap location.
404   | HpLim               -- Heap limit register
405   | CurrentTSO          -- pointer to current thread's TSO
406   | CurrentNursery      -- pointer to allocation area
407   | HpAlloc             -- allocation count for heap check failure
408
409                 -- We keep the address of some commonly-called 
410                 -- functions in the register table, to keep code
411                 -- size down:
412   | GCEnter1            -- stg_gc_enter_1
413   | GCFun               -- stg_gc_fun
414
415   -- Base offset for the register table, used for accessing registers
416   -- which do not have real registers assigned to them.  This register
417   -- will only appear after we have expanded GlobalReg into memory accesses
418   -- (where necessary) in the native code generator.
419   | BaseReg
420
421   -- Base Register for PIC (position-independent code) calculations
422   -- Only used inside the native code generator. It's exact meaning differs
423   -- from platform to platform (see module PositionIndependentCode).
424   | PicBaseReg
425
426   deriving( Eq
427 #ifdef DEBUG
428         , Show
429 #endif
430          )
431
432 -- convenient aliases
433 spReg, hpReg, spLimReg, nodeReg :: CmmReg
434 spReg = CmmGlobal Sp
435 hpReg = CmmGlobal Hp
436 spLimReg = CmmGlobal SpLim
437 nodeReg = CmmGlobal node
438
439 node :: GlobalReg
440 node = VanillaReg 1
441
442 globalRegRep :: GlobalReg -> MachRep
443 globalRegRep (VanillaReg _)     = wordRep
444 globalRegRep (FloatReg _)       = F32
445 globalRegRep (DoubleReg _)      = F64
446 globalRegRep (LongReg _)        = I64
447 globalRegRep _                  = wordRep