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