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