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