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