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