Merge in new code generator branch.
[ghc-hetmet.git] / compiler / nativeGen / SPARC / Regs.hs
1 -- -----------------------------------------------------------------------------
2 --
3 -- (c) The University of Glasgow 1994-2004
4 -- 
5 -- -----------------------------------------------------------------------------
6
7 module SPARC.Regs (
8         -- registers
9         showReg,
10         virtualRegSqueeze,
11         realRegSqueeze,
12         classOfRealReg,
13         allRealRegs,
14
15         -- machine specific info
16         gReg, iReg, lReg, oReg, fReg,
17         fp, sp, g0, g1, g2, o0, o1, f0, f1, f6, f8, f22, f26, f27,
18
19         -- allocatable
20         allocatableRegs,
21
22         -- args
23         argRegs, 
24         allArgRegs, 
25         callClobberedRegs,
26
27         -- 
28         mkVirtualReg,
29         regDotColor
30 )
31
32 where
33
34
35 import SPARC.RegPlate
36 import Reg
37 import RegClass
38 import Size
39
40 -- import PprCmm ()
41
42 import Unique
43 import Outputable
44 import FastTypes
45 import FastBool
46
47 {-
48         The SPARC has 64 registers of interest; 32 integer registers and 32
49         floating point registers.  The mapping of STG registers to SPARC
50         machine registers is defined in StgRegs.h.  We are, of course,
51         prepared for any eventuality.
52
53         The whole fp-register pairing thing on sparcs is a huge nuisance.  See
54         includes/stg/MachRegs.h for a description of what's going on
55         here.
56 -}
57
58
59 -- | Get the standard name for the register with this number.
60 showReg :: RegNo -> String
61 showReg n
62         | n >= 0  && n < 8   = "%g" ++ show n
63         | n >= 8  && n < 16  = "%o" ++ show (n-8)
64         | n >= 16 && n < 24  = "%l" ++ show (n-16)
65         | n >= 24 && n < 32  = "%i" ++ show (n-24)
66         | n >= 32 && n < 64  = "%f" ++ show (n-32)
67         | otherwise          = panic "SPARC.Regs.showReg: unknown sparc register"
68
69
70 -- Get the register class of a certain real reg
71 classOfRealReg :: RealReg -> RegClass
72 classOfRealReg reg
73  = case reg of
74         RealRegSingle i
75                 | i < 32        -> RcInteger
76                 | otherwise     -> RcFloat
77                 
78         RealRegPair{}           -> RcDouble
79
80
81 -- | regSqueeze_class reg
82 --      Calculuate the maximum number of register colors that could be
83 --      denied to a node of this class due to having this reg 
84 --      as a neighbour.
85 --
86 {-# INLINE virtualRegSqueeze #-}
87 virtualRegSqueeze :: RegClass -> VirtualReg -> FastInt
88
89 virtualRegSqueeze cls vr
90  = case cls of
91         RcInteger
92          -> case vr of
93                 VirtualRegI{}           -> _ILIT(1)
94                 VirtualRegHi{}          -> _ILIT(1)
95                 _other                  -> _ILIT(0)
96
97         RcFloat
98          -> case vr of
99                 VirtualRegF{}           -> _ILIT(1)
100                 VirtualRegD{}           -> _ILIT(2)
101                 _other                  -> _ILIT(0)
102
103         RcDouble
104          -> case vr of
105                 VirtualRegF{}           -> _ILIT(1)
106                 VirtualRegD{}           -> _ILIT(1)
107                 _other                  -> _ILIT(0)
108
109         _other -> _ILIT(0)
110
111 {-# INLINE realRegSqueeze #-}
112 realRegSqueeze :: RegClass -> RealReg -> FastInt
113
114 realRegSqueeze cls rr
115  = case cls of
116         RcInteger
117          -> case rr of
118                 RealRegSingle regNo
119                         | regNo < 32    -> _ILIT(1)
120                         | otherwise     -> _ILIT(0)
121                         
122                 RealRegPair{}           -> _ILIT(0)
123
124         RcFloat
125          -> case rr of
126                 RealRegSingle regNo
127                         | regNo < 32    -> _ILIT(0)
128                         | otherwise     -> _ILIT(1)
129                         
130                 RealRegPair{}           -> _ILIT(2)
131
132         RcDouble
133          -> case rr of
134                 RealRegSingle regNo
135                         | regNo < 32    -> _ILIT(0)
136                         | otherwise     -> _ILIT(1)
137                         
138                 RealRegPair{}           -> _ILIT(1)
139                                         
140         _other -> _ILIT(0)
141         
142 -- | All the allocatable registers in the machine, 
143 --      including register pairs.
144 allRealRegs :: [RealReg]
145 allRealRegs  
146         =  [ (RealRegSingle i)          | i <- [0..63] ]
147         ++ [ (RealRegPair   i (i+1))    | i <- [32, 34 .. 62 ] ]
148
149
150 -- | Get the regno for this sort of reg
151 gReg, lReg, iReg, oReg, fReg :: Int -> RegNo
152
153 gReg x  = x             -- global regs
154 oReg x  = (8 + x)       -- output regs
155 lReg x  = (16 + x)      -- local regs
156 iReg x  = (24 + x)      -- input regs
157 fReg x  = (32 + x)      -- float regs
158
159
160 -- | Some specific regs used by the code generator.
161 g0, g1, g2, fp, sp, o0, o1, f0, f1, f6, f8, f22, f26, f27 :: Reg
162
163 f6  = RegReal (RealRegSingle (fReg 6))
164 f8  = RegReal (RealRegSingle (fReg 8))
165 f22 = RegReal (RealRegSingle (fReg 22))
166 f26 = RegReal (RealRegSingle (fReg 26))
167 f27 = RegReal (RealRegSingle (fReg 27))
168
169 -- g0 is always zero, and writes to it vanish.
170 g0  = RegReal (RealRegSingle (gReg 0))
171 g1  = RegReal (RealRegSingle (gReg 1))
172 g2  = RegReal (RealRegSingle (gReg 2))
173
174 -- FP, SP, int and float return (from C) regs.
175 fp  = RegReal (RealRegSingle (iReg 6))
176 sp  = RegReal (RealRegSingle (oReg 6))
177 o0  = RegReal (RealRegSingle (oReg 0))
178 o1  = RegReal (RealRegSingle (oReg 1))
179 f0  = RegReal (RealRegSingle (fReg 0))
180 f1  = RegReal (RealRegSingle (fReg 1))
181
182 -- | Produce the second-half-of-a-double register given the first half.
183 {-
184 fPair :: Reg -> Maybe Reg
185 fPair (RealReg n) 
186         | n >= 32 && n `mod` 2 == 0  = Just (RealReg (n+1))
187
188 fPair (VirtualRegD u)
189         = Just (VirtualRegHi u)
190
191 fPair reg
192         = trace ("MachInstrs.fPair: can't get high half of supposed double reg " ++ showPpr reg)
193                 Nothing
194 -}
195
196
197 -- | All the regs that the register allocator can allocate to, 
198 --      with the the fixed use regs removed.
199 -- 
200 allocatableRegs :: [RealReg]
201 allocatableRegs
202    = let isFree rr 
203            = case rr of
204                 RealRegSingle r         
205                         -> isFastTrue (freeReg r)
206
207                 RealRegPair   r1 r2     
208                         -> isFastTrue (freeReg r1) 
209                         && isFastTrue (freeReg r2)
210
211      in filter isFree allRealRegs
212
213
214 -- | The registers to place arguments for function calls, 
215 --      for some number of arguments.
216 --
217 argRegs :: RegNo -> [Reg]
218 argRegs r
219  = case r of
220         0       -> []
221         1       -> map (RegReal . RealRegSingle . oReg) [0]
222         2       -> map (RegReal . RealRegSingle . oReg) [0,1]
223         3       -> map (RegReal . RealRegSingle . oReg) [0,1,2]
224         4       -> map (RegReal . RealRegSingle . oReg) [0,1,2,3]
225         5       -> map (RegReal . RealRegSingle . oReg) [0,1,2,3,4]
226         6       -> map (RegReal . RealRegSingle . oReg) [0,1,2,3,4,5]
227         _       -> panic "MachRegs.argRegs(sparc): don't know about >6 arguments!"
228
229
230 -- | All all the regs that could possibly be returned by argRegs
231 --
232 allArgRegs :: [Reg]
233 allArgRegs 
234         = map (RegReal . RealRegSingle) [oReg i | i <- [0..5]]
235
236
237 -- These are the regs that we cannot assume stay alive over a C call.  
238 --      TODO: Why can we assume that o6 isn't clobbered? -- BL 2009/02
239 --
240 callClobberedRegs :: [Reg]
241 callClobberedRegs
242         = map (RegReal . RealRegSingle)
243                 (  oReg 7 :
244                   [oReg i | i <- [0..5]] ++
245                   [gReg i | i <- [1..7]] ++
246                   [fReg i | i <- [0..31]] )
247
248
249
250 -- | Make a virtual reg with this size.
251 mkVirtualReg :: Unique -> Size -> VirtualReg
252 mkVirtualReg u size
253         | not (isFloatSize size) 
254         = VirtualRegI u
255
256         | otherwise
257         = case size of
258                 FF32    -> VirtualRegF u
259                 FF64    -> VirtualRegD u
260                 _       -> panic "mkVReg"
261
262
263 regDotColor :: RealReg -> SDoc
264 regDotColor reg
265  = case classOfRealReg reg of
266         RcInteger       -> text "blue"
267         RcFloat         -> text "red"
268         _other          -> text "green"
269
270
271
272
273 -- Hard coded freeReg / globalRegMaybe -----------------------------------------
274 -- This isn't being used at the moment because we're generating
275 --      these functions from the information in
276 --      includes/stg/MachRegs.hs via RegPlate.hs
277         
278 -- | Check whether a machine register is free for allocation.
279 --      This needs to match the info in includes/stg/MachRegs.h
280 --      otherwise modules compiled with the NCG won't be compatible
281 --      with via-C ones.
282 --
283 {-
284 freeReg :: RegNo -> FastBool
285 freeReg regno
286  = case regno of
287         -- %g0(r0) is always 0.
288         0       -> fastBool False       
289
290         -- %g1(r1) - %g4(r4) are allocable -----------------
291
292         -- %g5(r5) - %g7(r7) 
293         --      are reserved for the OS
294         5       -> fastBool False
295         6       -> fastBool False
296         7       -> fastBool False
297
298         -- %o0(r8) - %o5(r13) are allocable ----------------
299
300         -- %o6(r14) 
301         --      is the C stack pointer
302         14      -> fastBool False
303
304         -- %o7(r15) 
305         --      holds C return addresses (???)
306         15      -> fastBool False
307
308         -- %l0(r16) is allocable ---------------------------
309
310         -- %l1(r17) - %l5(r21) 
311         --      are STG regs R1 - R5
312         17      -> fastBool False
313         18      -> fastBool False
314         19      -> fastBool False
315         20      -> fastBool False
316         21      -> fastBool False
317         
318         -- %l6(r22) - %l7(r23) are allocable --------------
319         
320         -- %i0(r24) - %i5(r29)
321         --      are STG regs Sp, Base, SpLim, Hp, R6
322         24      -> fastBool False
323         25      -> fastBool False
324         26      -> fastBool False
325         27      -> fastBool False
326
327         -- %i5(r28) is allocable --------------------------
328
329         29      -> fastBool False
330         
331         -- %i6(r30) 
332         --      is the C frame pointer
333         30      -> fastBool False
334
335         -- %i7(r31) 
336         --      is used for C return addresses
337         31      -> fastBool False
338         
339         -- %f0(r32) - %f1(r33)
340         --      are C fp return registers
341         32      -> fastBool False
342         33      -> fastBool False
343
344         -- %f2(r34) - %f5(r37)
345         --      are STG regs D1 - D2
346         34      -> fastBool False
347         35      -> fastBool False
348         36      -> fastBool False
349         37      -> fastBool False
350
351         -- %f22(r54) - %f25(r57)
352         --      are STG regs F1 - F4
353         54      -> fastBool False
354         55      -> fastBool False
355         56      -> fastBool False
356         57      -> fastBool False
357
358         -- regs not matched above are allocable.
359         _       -> fastBool True
360
361 -}
362
363 -- | Returns Just the real register that a global register is stored in.
364 --      Returns Nothing if the global has no real register, and is stored
365 --      in the in-memory register table instead.
366 --
367 {-
368 globalRegMaybe  :: GlobalReg -> Maybe Reg
369 globalRegMaybe gg
370  = case gg of
371         -- Argument and return regs
372         VanillaReg 1 _  -> Just (RealReg 17)    -- %l1
373         VanillaReg 2 _  -> Just (RealReg 18)    -- %l2
374         VanillaReg 3 _  -> Just (RealReg 19)    -- %l3
375         VanillaReg 4 _  -> Just (RealReg 20)    -- %l4
376         VanillaReg 5 _  -> Just (RealReg 21)    -- %l5
377         VanillaReg 6 _  -> Just (RealReg 29)    -- %i5
378
379         FloatReg 1      -> Just (RealReg 54)    -- %f22
380         FloatReg 2      -> Just (RealReg 55)    -- %f23
381         FloatReg 3      -> Just (RealReg 56)    -- %f24
382         FloatReg 4      -> Just (RealReg 57)    -- %f25
383
384         DoubleReg 1     -> Just (RealReg 34)    -- %f2
385         DoubleReg 2     -> Just (RealReg 36)    -- %f4
386
387         -- STG Regs
388         Sp              -> Just (RealReg 24)    -- %i0
389         SpLim           -> Just (RealReg 26)    -- %i2
390         Hp              -> Just (RealReg 27)    -- %i3
391
392         BaseReg         -> Just (RealReg 25)    -- %i1
393                 
394         _               -> Nothing      
395 -}