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