[project @ 2004-08-13 13:04:50 by simonmar]
[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   -- some static data.
69   | CmmData Section [d] -- constant values only
70
71 type CmmTop = GenCmmTop CmmStatic CmmStmt
72
73 -- A basic block containing a single label, at the beginning.
74 -- The list of basic blocks in a top-level code block may be re-ordered.
75 -- Fall-through is not allowed: there must be an explicit jump at the
76 -- end of each basic block, but the code generator might rearrange basic
77 -- blocks in order to turn some jumps into fallthroughs.
78
79 data GenBasicBlock i = BasicBlock BlockId [i]
80   -- ToDo: Julian suggests that we might need to annotate this type
81   -- with the out & in edges in the graph, i.e. two * [BlockId].  This
82   -- information can be derived from the contents, but it might be
83   -- helpful to cache it here.
84
85 type CmmBasicBlock = GenBasicBlock CmmStmt
86
87 blockId :: GenBasicBlock i -> BlockId
88 -- The branch block id is that of the first block in 
89 -- the branch, which is that branch's entry point
90 blockId (BasicBlock blk_id _ ) = blk_id
91
92 blockStmts :: GenBasicBlock i -> [i]
93 blockStmts (BasicBlock _ stmts) = stmts
94
95
96 -----------------------------------------------------------------------------
97 --              CmmStmt
98 -- A "statement".  Note that all branches are explicit: there are no
99 -- control transfers to computed addresses, except when transfering
100 -- control to a new function.
101 -----------------------------------------------------------------------------
102
103 data CmmStmt
104   = CmmNop
105   | CmmComment FastString
106
107   | CmmAssign CmmReg CmmExpr     -- Assign to register
108
109   | CmmStore CmmExpr CmmExpr     -- Assign to memory location.  Size is
110                                  -- given by cmmExprRep of the rhs.
111
112   | CmmCall                      -- A foreign call, with 
113      CmmCallTarget
114      [(CmmReg,MachHint)]         -- zero or more results
115      [(CmmExpr,MachHint)]        -- zero or more arguments
116      (Maybe [GlobalReg])         -- Global regs that may need to be saved
117                                  -- if they will be clobbered by the call.
118                                  -- Nothing <=> save *all* globals that
119                                  -- might be clobbered.
120
121   | CmmBranch BlockId             -- branch to another BB in this fn
122
123   | CmmCondBranch CmmExpr BlockId -- conditional branch
124
125   | CmmSwitch CmmExpr [Maybe BlockId]   -- Table branch
126         -- The scrutinee is zero-based; 
127         --      zero -> first block
128         --      one  -> second block etc
129         -- Undefined outside range, and when there's a Nothing
130
131   | CmmJump CmmExpr [LocalReg]    -- Jump to another function, with these 
132                                   -- parameters.
133
134 -----------------------------------------------------------------------------
135 --              CmmCallTarget
136 --
137 -- The target of a CmmCall.
138 -----------------------------------------------------------------------------
139
140 data CmmCallTarget
141   = CmmForeignCall              -- Call to a foreign function
142         CmmExpr                 -- literal label <=> static call
143                                 -- other expression <=> dynamic call
144         CCallConv               -- The calling convention
145
146   | CmmPrim                     -- Call to a "primitive" (eg. sin, cos)
147         CallishMachOp           -- These might be implemented as inline
148                                 -- code by the backend.
149
150 -----------------------------------------------------------------------------
151 --              CmmExpr
152 -- An expression.  Expressions have no side effects.
153 -----------------------------------------------------------------------------
154
155 data CmmExpr
156   = CmmLit CmmLit               -- Literal
157   | CmmLoad CmmExpr MachRep     -- Read memory location
158   | CmmReg CmmReg               -- Contents of register
159   | CmmMachOp MachOp [CmmExpr]  -- Machine operation (+, -, *, etc.)
160   | CmmRegOff CmmReg Int        
161         -- CmmRegOff reg i
162         --        ** is shorthand only, meaning **
163         -- CmmMachOp (MO_S_Add rep (CmmReg reg) (CmmLit (CmmInt i rep)))
164         --      where rep = cmmRegRep reg
165
166 cmmExprRep :: CmmExpr -> MachRep
167 cmmExprRep (CmmLit lit)      = cmmLitRep lit
168 cmmExprRep (CmmLoad _ rep)   = rep
169 cmmExprRep (CmmReg reg)      = cmmRegRep reg
170 cmmExprRep (CmmMachOp op _)  = resultRepOfMachOp op
171 cmmExprRep (CmmRegOff reg _) = cmmRegRep reg
172
173 data CmmReg 
174   = CmmLocal  LocalReg
175   | CmmGlobal GlobalReg
176   deriving( Eq )
177
178 cmmRegRep :: CmmReg -> MachRep
179 cmmRegRep (CmmLocal  reg)       = localRegRep reg
180 cmmRegRep (CmmGlobal reg)       = globalRegRep reg
181
182 data LocalReg
183   = LocalReg !Unique MachRep
184
185 instance Eq LocalReg where
186   (LocalReg u1 _) == (LocalReg u2 _) = u1 == u2
187
188 instance Uniquable LocalReg where
189   getUnique (LocalReg uniq _) = uniq
190
191 localRegRep :: LocalReg -> MachRep
192 localRegRep (LocalReg _ rep) = rep
193
194 data CmmLit
195   = CmmInt Integer  MachRep
196         -- Interpretation: the 2's complement representation of the value
197         -- is truncated to the specified size.  This is easier than trying
198         -- to keep the value within range, because we don't know whether
199         -- it will be used as a signed or unsigned value (the MachRep doesn't
200         -- distinguish between signed & unsigned).
201   | CmmFloat  Rational MachRep
202   | CmmLabel    CLabel                  -- Address of label
203   | CmmLabelOff CLabel Int              -- Address of label + byte offset
204
205 cmmLitRep :: CmmLit -> MachRep
206 cmmLitRep (CmmInt _ rep)    = rep
207 cmmLitRep (CmmFloat _ rep)  = rep
208 cmmLitRep (CmmLabel _)      = wordRep
209 cmmLitRep (CmmLabelOff _ _) = wordRep
210
211 -----------------------------------------------------------------------------
212 -- A local label.
213
214 -- Local labels must be unique within a single compilation unit.
215
216 newtype BlockId = BlockId Unique
217   deriving (Eq,Ord)
218
219 instance Uniquable BlockId where
220   getUnique (BlockId u) = u
221
222 -----------------------------------------------------------------------------
223 --              Static Data
224 -----------------------------------------------------------------------------
225
226 data Section
227   = Text
228   | Data
229   | ReadOnlyData
230   | UninitialisedData
231   | OtherSection String
232
233 data CmmStatic
234   = CmmStaticLit CmmLit 
235         -- a literal value, size given by cmmLitRep of the literal.
236   | CmmUninitialised Int
237         -- uninitialised data, N bytes long
238   | CmmAlign Int
239         -- align to next N-byte boundary (N must be a power of 2).
240   | CmmDataLabel CLabel
241         -- label the current position in this section.
242   | CmmString String
243         -- string of 8-bit values only, not zero terminated.
244         -- ToDo: might be more honest to use [Word8] here?
245
246 -----------------------------------------------------------------------------
247 --              Global STG registers
248 -----------------------------------------------------------------------------
249
250 data GlobalReg
251   -- Argument and return registers
252   = VanillaReg                  -- pointers, unboxed ints and chars
253         {-# UNPACK #-} !Int     -- its number
254
255   | FloatReg            -- single-precision floating-point registers
256         {-# UNPACK #-} !Int     -- its number
257
258   | DoubleReg           -- double-precision floating-point registers
259         {-# UNPACK #-} !Int     -- its number
260
261   | LongReg             -- long int registers (64-bit, really)
262         {-# UNPACK #-} !Int     -- its number
263
264   -- STG registers
265   | Sp                  -- Stack ptr; points to last occupied stack location.
266   | SpLim               -- Stack limit
267   | Hp                  -- Heap ptr; points to last occupied heap location.
268   | HpLim               -- Heap limit register
269   | CurrentTSO          -- pointer to current thread's TSO
270   | CurrentNursery      -- pointer to allocation area
271   | HpAlloc             -- allocation count for heap check failure
272
273                 -- We keep the address of some commonly-called 
274                 -- functions in the register table, to keep code
275                 -- size down:
276   | GCEnter1            -- stg_gc_enter_1
277   | GCFun               -- stg_gc_fun
278
279   -- Base offset for the register table, used for accessing registers
280   -- which do not have real registers assigned to them.  This register
281   -- will only appear after we have expanded GlobalReg into memory accesses
282   -- (where necessary) in the native code generator.
283   | BaseReg
284
285   deriving( Eq
286 #ifdef DEBUG
287         , Show
288 #endif
289          )
290
291 -- convenient aliases
292 spReg, hpReg, nodeReg :: CmmReg
293 spReg = CmmGlobal Sp
294 hpReg = CmmGlobal Hp
295 nodeReg = CmmGlobal node
296
297 node :: GlobalReg
298 node = VanillaReg 1
299
300 globalRegRep :: GlobalReg -> MachRep
301 globalRegRep (VanillaReg _)     = wordRep
302 globalRegRep (FloatReg _)       = F32
303 globalRegRep (DoubleReg _)      = F64
304 globalRegRep (LongReg _)        = I64
305 globalRegRep _                  = wordRep