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