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