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