048cb5e1ba9873e717db504582be367794224384
[ghc-hetmet.git] / ghc / compiler / cmm / Cmm.hs
1 -----------------------------------------------------------------------------
2 --
3 -- Cmm data types
4 --
5 -- (c) The University of Glasgow 2004
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           ( CLabel )
30 import ForeignCall      ( CCallConv )
31 import Unique           ( Unique, Uniquable(..) )
32 import FastString       ( FastString )
33
34 -----------------------------------------------------------------------------
35 --              Cmm, CmmTop, CmmBasicBlock
36 -----------------------------------------------------------------------------
37
38 -- A file is a list of top-level chunks.  These may be arbitrarily
39 -- re-orderd during code generation.
40
41 -- GenCmm is abstracted over
42 --   (a) the type of static data elements
43 --   (b) the contents of a basic block.
44 -- We expect there to be two main instances of this type:
45 --   (a) Plain C--, i.e. populated with CmmLit and CmmExpr respectively,
46 --   (b) Native code, populated with instructions
47 --
48 newtype GenCmm d i = Cmm [GenCmmTop d i]
49
50 type Cmm = GenCmm CmmStatic CmmStmt
51
52 -- A top-level chunk, abstracted over the type of the contents of
53 -- the basic blocks (Cmm or instructions are the likely instantiations).
54 data GenCmmTop d i
55   = CmmProc
56      [d]               -- Info table, may be empty
57      CLabel            -- Used to generate both info & entry labels
58      [LocalReg]        -- Argument locals live on entry (C-- procedure params)
59      [GenBasicBlock i] -- Code, may be empty.  The first block is
60                        -- the entry point.  The order is otherwise initially 
61                        -- unimportant, but at some point the code gen will
62                        -- fix the order.
63
64                        -- the BlockId of the first block does not give rise
65                        -- to a label.  To jump to the first block in a Proc,
66                        -- use the appropriate CLabel.
67
68      [GenCmmCont i]    -- Continuations declared in this proc
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 data GenCmmCont i 
99   = CmmCont 
100         [LocalReg]              -- The formal params of the ccntinuation
101         (GenBasicBlock i)       
102
103 type ContId = BlockId   -- Continuation is named (in eg 
104                         -- also-unwinds-to annotations) via the 
105                         -- block-id of its GenBasicBlock
106
107 -----------------------------------------------------------------------------
108 --              CmmStmt
109 -- A "statement".  Note that all branches are explicit: there are no
110 -- control transfers to computed addresses, except when transfering
111 -- control to a new function.
112 -----------------------------------------------------------------------------
113
114 data CmmStmt
115   = CmmNop
116   | CmmComment FastString
117
118   | CmmAssign CmmReg CmmExpr     -- Assign to register
119
120   | CmmStore CmmExpr CmmExpr     -- Assign to memory location.  Size is
121                                  -- given by cmmExprRep of the rhs.
122
123   | CmmCall                      -- A foreign call, with 
124      CmmCallTarget
125      [(CmmReg,MachHint)]         -- zero or more results
126      [(CmmExpr,MachHint)]        -- zero or more arguments
127      Flow
128
129   | CmmBranch BlockId             -- branch to another BB in this fn
130
131   | CmmCondBranch CmmExpr BlockId -- conditional branch
132
133   | CmmSwitch CmmExpr [Maybe BlockId]   -- Table branch
134         -- The scrutinee is zero-based; 
135         --      zero -> first block
136         --      one  -> second block etc
137         -- Undefined outside range, and when there's a Nothing
138
139   | CmmJump CmmExpr [LocalReg]    -- Jump to another function, with these 
140                                   -- parameters.
141
142   | CmmSpan CmmSpan [CmmStmt]
143
144 -----------------------------------------------------------------------------
145 --              CmmSpan
146 -----------------------------------------------------------------------------
147
148 data CmmSpan = UpdateFrame | CatchFrame         -- Etc.
149
150 -----------------------------------------------------------------------------
151 --              CmmCallTarget
152 --
153 -- The target of a CmmCall.
154 -----------------------------------------------------------------------------
155
156 data CmmCallTarget
157   = CmmVanillaCall CmmExpr      -- Ordinarly call to a Cmm procedure
158  
159   | CmmForeignCall              -- Call to a foreign function
160         CmmExpr                 -- literal label <=> static call
161                                 -- other expression <=> dynamic call
162         CCallConv               -- The calling convention
163
164   | CmmPrim                     -- Call to a "primitive" (eg. sin, cos)
165         CallishMachOp           -- These might be implemented as inline
166                                 -- code by the backend.
167
168 -----------------------------------------------------------------------------
169 --              Flow
170 -- 
171 -----------------------------------------------------------------------------
172
173 data Flow
174    = Flow { normal_live :: FlowEdge ()
175           , also_unwinds :: [FlowEdge ContId]
176      }
177
178 data FlowEdge a
179   = FlowEdge { edge_target :: a
180              , live_locals :: [LocalReg]                -- Live across the call
181              , save_globals :: Maybe [GlobalReg]        -- Global regs that may need to be saved
182     }                                                   -- if they will be clobbered by the call.
183                                                         -- Nothing <=> save *all* globals that
184                                                         -- might be clobbered
185
186 -----------------------------------------------------------------------------
187 --              CmmExpr
188 -- An expression.  Expressions have no side effects.
189 -----------------------------------------------------------------------------
190
191 data CmmExpr
192   = CmmLit CmmLit               -- Literal
193   | CmmLoad CmmExpr MachRep     -- Read memory location
194   | CmmReg CmmReg               -- Contents of register
195   | CmmMachOp MachOp [CmmExpr]  -- Machine operation (+, -, *, etc.)
196   | CmmRegOff CmmReg Int        
197         -- CmmRegOff reg i
198         --        ** is shorthand only, meaning **
199         -- CmmMachOp (MO_S_Add rep (CmmReg reg) (CmmLit (CmmInt i rep)))
200         --      where rep = cmmRegRep reg
201   | CmmPicBaseReg               -- Base Register for PIC calculations
202
203 cmmExprRep :: CmmExpr -> MachRep
204 cmmExprRep (CmmLit lit)      = cmmLitRep lit
205 cmmExprRep (CmmLoad _ rep)   = rep
206 cmmExprRep (CmmReg reg)      = cmmRegRep reg
207 cmmExprRep (CmmMachOp op _)  = resultRepOfMachOp op
208 cmmExprRep (CmmRegOff reg _) = cmmRegRep reg
209 cmmExprRep CmmPicBaseReg     = wordRep
210
211 data CmmReg 
212   = CmmLocal  LocalReg
213   | CmmGlobal GlobalReg
214   deriving( Eq )
215
216 cmmRegRep :: CmmReg -> MachRep
217 cmmRegRep (CmmLocal  reg)       = localRegRep reg
218 cmmRegRep (CmmGlobal reg)       = globalRegRep reg
219
220 data LocalReg
221   = LocalReg !Unique MachRep
222
223 instance Eq LocalReg where
224   (LocalReg u1 _) == (LocalReg u2 _) = u1 == u2
225
226 instance Uniquable LocalReg where
227   getUnique (LocalReg uniq _) = uniq
228
229 localRegRep :: LocalReg -> MachRep
230 localRegRep (LocalReg _ rep) = rep
231
232 data CmmLit
233   = CmmInt Integer  MachRep
234         -- Interpretation: the 2's complement representation of the value
235         -- is truncated to the specified size.  This is easier than trying
236         -- to keep the value within range, because we don't know whether
237         -- it will be used as a signed or unsigned value (the MachRep doesn't
238         -- distinguish between signed & unsigned).
239   | CmmFloat  Rational MachRep
240   | CmmLabel    CLabel                  -- Address of label
241   | CmmLabelOff CLabel Int              -- Address of label + byte offset
242   
243         -- Due to limitations in the C backend, the following
244         -- MUST ONLY be used inside the info table indicated by label2
245         -- (label2 must be the info label), and label1 must be an
246         -- SRT, a slow entrypoint or a large bitmap (see the Mangler)
247         -- Don't use it at all unless tablesNextToCode.
248         -- It is also used inside the NCG during when generating
249         -- position-independent code. 
250   | CmmLabelDiffOff CLabel CLabel Int   -- label1 - label2 + offset
251
252 cmmLitRep :: CmmLit -> MachRep
253 cmmLitRep (CmmInt _ rep)    = rep
254 cmmLitRep (CmmFloat _ rep)  = rep
255 cmmLitRep (CmmLabel _)      = wordRep
256 cmmLitRep (CmmLabelOff _ _) = wordRep
257 cmmLitRep (CmmLabelDiffOff _ _ _) = wordRep
258
259 -----------------------------------------------------------------------------
260 -- A local label.
261
262 -- Local labels must be unique within a single compilation unit.
263
264 newtype BlockId = BlockId Unique
265   deriving (Eq,Ord)
266
267 instance Uniquable BlockId where
268   getUnique (BlockId u) = u
269
270 -----------------------------------------------------------------------------
271 --              Static Data
272 -----------------------------------------------------------------------------
273
274 data Section
275   = Text
276   | Data
277   | ReadOnlyData
278   | UninitialisedData
279   | OtherSection String
280
281 data CmmStatic
282   = CmmStaticLit CmmLit 
283         -- a literal value, size given by cmmLitRep of the literal.
284   | CmmUninitialised Int
285         -- uninitialised data, N bytes long
286   | CmmAlign Int
287         -- align to next N-byte boundary (N must be a power of 2).
288   | CmmDataLabel CLabel
289         -- label the current position in this section.
290   | CmmString String
291         -- string of 8-bit values only, not zero terminated.
292         -- ToDo: might be more honest to use [Word8] here?
293
294 -----------------------------------------------------------------------------
295 --              Global STG registers
296 -----------------------------------------------------------------------------
297
298 data GlobalReg
299   -- Argument and return registers
300   = VanillaReg                  -- pointers, unboxed ints and chars
301         {-# UNPACK #-} !Int     -- its number
302
303   | FloatReg            -- single-precision floating-point registers
304         {-# UNPACK #-} !Int     -- its number
305
306   | DoubleReg           -- double-precision floating-point registers
307         {-# UNPACK #-} !Int     -- its number
308
309   | LongReg             -- long int registers (64-bit, really)
310         {-# UNPACK #-} !Int     -- its number
311
312   -- STG registers
313   | Sp                  -- Stack ptr; points to last occupied stack location.
314   | SpLim               -- Stack limit
315   | Hp                  -- Heap ptr; points to last occupied heap location.
316   | HpLim               -- Heap limit register
317   | CurrentTSO          -- pointer to current thread's TSO
318   | CurrentNursery      -- pointer to allocation area
319   | HpAlloc             -- allocation count for heap check failure
320
321                 -- We keep the address of some commonly-called 
322                 -- functions in the register table, to keep code
323                 -- size down:
324   | GCEnter1            -- stg_gc_enter_1
325   | GCFun               -- stg_gc_fun
326
327   -- Base offset for the register table, used for accessing registers
328   -- which do not have real registers assigned to them.  This register
329   -- will only appear after we have expanded GlobalReg into memory accesses
330   -- (where necessary) in the native code generator.
331   | BaseReg
332
333   deriving( Eq
334 #ifdef DEBUG
335         , Show
336 #endif
337          )
338
339 -- convenient aliases
340 spReg, hpReg, nodeReg :: CmmReg
341 spReg = CmmGlobal Sp
342 hpReg = CmmGlobal Hp
343 nodeReg = CmmGlobal node
344
345 node :: GlobalReg
346 node = VanillaReg 1
347
348 globalRegRep :: GlobalReg -> MachRep
349 globalRegRep (VanillaReg _)     = wordRep
350 globalRegRep (FloatReg _)       = F32
351 globalRegRep (DoubleReg _)      = F64
352 globalRegRep (LongReg _)        = I64
353 globalRegRep _                  = wordRep