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