e610d5d6d47c1b758a9be0d86305b04ed3821d29
[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         allocatableRegs,
21         get_GlobalReg_reg_or_addr,
22
23         -- args
24         argRegs, 
25         allArgRegs, 
26         callClobberedRegs,
27
28         -- 
29         mkVReg,
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 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 reg
146         = trace ("MachInstrs.fPair: can't get high half of supposed double reg " ++ showPpr reg)
147                 Nothing
148
149
150
151 -- allocatableRegs is allMachRegNos with the fixed-use regs removed.
152 -- i.e., these are the regs for which we are prepared to allow the
153 -- register allocator to attempt to map VRegs to.
154 allocatableRegs :: [RegNo]
155 allocatableRegs
156    = let isFree i = isFastTrue (freeReg i)
157      in  filter isFree allMachRegNos
158
159
160
161 -- We map STG registers onto appropriate CmmExprs.  Either they map
162 -- to real machine registers or stored as offsets from BaseReg.  Given
163 -- a GlobalReg, get_GlobalReg_reg_or_addr produces either the real
164 -- register it is in, on this platform, or a CmmExpr denoting the
165 -- address in the register table holding it.
166 -- (See also get_GlobalReg_addr in CgUtils.)
167
168 get_GlobalReg_reg_or_addr :: GlobalReg -> Either Reg CmmExpr
169 get_GlobalReg_reg_or_addr mid
170    = case globalRegMaybe mid of
171         Just rr -> Left rr
172         Nothing -> Right (get_GlobalReg_addr mid)
173
174
175 -- | The registers to place arguments for function calls, 
176 --      for some number of arguments.
177 --
178 argRegs :: RegNo -> [Reg]
179 argRegs r
180  = case r of
181         0       -> []
182         1       -> map (RealReg . oReg) [0]
183         2       -> map (RealReg . oReg) [0,1]
184         3       -> map (RealReg . oReg) [0,1,2]
185         4       -> map (RealReg . oReg) [0,1,2,3]
186         5       -> map (RealReg . oReg) [0,1,2,3,4]
187         6       -> map (RealReg . oReg) [0,1,2,3,4,5]
188         _       -> panic "MachRegs.argRegs(sparc): don't know about >6 arguments!"
189
190
191 -- | All all the regs that could possibly be returned by argRegs
192 --
193 allArgRegs :: [Reg]
194 allArgRegs 
195         = map RealReg [oReg i | i <- [0..5]]
196
197
198 -- These are the regs that we cannot assume stay alive over a C call.  
199 --      TODO: Why can we assume that o6 isn't clobbered? -- BL 2009/02
200 --
201 callClobberedRegs :: [Reg]
202 callClobberedRegs
203         = map RealReg 
204                 (  oReg 7 :
205                   [oReg i | i <- [0..5]] ++
206                   [gReg i | i <- [1..7]] ++
207                   [fReg i | i <- [0..31]] )
208
209
210
211 -- | Make a virtual reg with this size.
212 mkVReg :: Unique -> Size -> Reg
213 mkVReg u size
214         | not (isFloatSize size) 
215         = VirtualRegI u
216
217         | otherwise
218         = case size of
219                 FF32    -> VirtualRegF u
220                 FF64    -> VirtualRegD u
221                 _       -> panic "mkVReg"
222
223
224 regDotColor :: Reg -> SDoc
225 regDotColor reg
226  = case regClass reg of
227         RcInteger       -> text "blue"
228         RcFloat         -> text "red"
229         RcDouble        -> text "green"
230
231
232
233
234
235 -- Hard coded freeReg / globalRegMaybe -----------------------------------------
236 -- This isn't being used at the moment because we're generating
237 --      these functions from the information in includes/MachRegs.hs via RegPlate.hs
238         
239 -- | Check whether a machine register is free for allocation.
240 --      This needs to match the info in includes/MachRegs.h otherwise modules
241 --      compiled with the NCG won't be compatible with via-C ones.
242 --
243 {-
244 freeReg :: RegNo -> FastBool
245 freeReg regno
246  = case regno of
247         -- %g0(r0) is always 0.
248         0       -> fastBool False       
249
250         -- %g1(r1) - %g4(r4) are allocable -----------------
251
252         -- %g5(r5) - %g7(r7) 
253         --      are reserved for the OS
254         5       -> fastBool False
255         6       -> fastBool False
256         7       -> fastBool False
257
258         -- %o0(r8) - %o5(r13) are allocable ----------------
259
260         -- %o6(r14) 
261         --      is the C stack pointer
262         14      -> fastBool False
263
264         -- %o7(r15) 
265         --      holds C return addresses (???)
266         15      -> fastBool False
267
268         -- %l0(r16) is allocable ---------------------------
269
270         -- %l1(r17) - %l5(r21) 
271         --      are STG regs R1 - R5
272         17      -> fastBool False
273         18      -> fastBool False
274         19      -> fastBool False
275         20      -> fastBool False
276         21      -> fastBool False
277         
278         -- %l6(r22) - %l7(r23) are allocable --------------
279         
280         -- %i0(r24) - %i5(r29)
281         --      are STG regs Sp, Base, SpLim, Hp, R6
282         24      -> fastBool False
283         25      -> fastBool False
284         26      -> fastBool False
285         27      -> fastBool False
286
287         -- %i5(r28) is allocable --------------------------
288
289         29      -> fastBool False
290         
291         -- %i6(r30) 
292         --      is the C frame pointer
293         30      -> fastBool False
294
295         -- %i7(r31) 
296         --      is used for C return addresses
297         31      -> fastBool False
298         
299         -- %f0(r32) - %f1(r33)
300         --      are C fp return registers
301         32      -> fastBool False
302         33      -> fastBool False
303
304         -- %f2(r34) - %f5(r37)
305         --      are STG regs D1 - D2
306         34      -> fastBool False
307         35      -> fastBool False
308         36      -> fastBool False
309         37      -> fastBool False
310
311         -- %f22(r54) - %f25(r57)
312         --      are STG regs F1 - F4
313         54      -> fastBool False
314         55      -> fastBool False
315         56      -> fastBool False
316         57      -> fastBool False
317
318         -- regs not matched above are allocable.
319         _       -> fastBool True
320
321 -}
322
323 -- | Returns Just the real register that a global register is stored in.
324 --      Returns Nothing if the global has no real register, and is stored
325 --      in the in-memory register table instead.
326 --
327 {-
328 globalRegMaybe  :: GlobalReg -> Maybe Reg
329 globalRegMaybe gg
330  = case gg of
331         -- Argument and return regs
332         VanillaReg 1 _  -> Just (RealReg 17)    -- %l1
333         VanillaReg 2 _  -> Just (RealReg 18)    -- %l2
334         VanillaReg 3 _  -> Just (RealReg 19)    -- %l3
335         VanillaReg 4 _  -> Just (RealReg 20)    -- %l4
336         VanillaReg 5 _  -> Just (RealReg 21)    -- %l5
337         VanillaReg 6 _  -> Just (RealReg 29)    -- %i5
338
339         FloatReg 1      -> Just (RealReg 54)    -- %f22
340         FloatReg 2      -> Just (RealReg 55)    -- %f23
341         FloatReg 3      -> Just (RealReg 56)    -- %f24
342         FloatReg 4      -> Just (RealReg 57)    -- %f25
343
344         DoubleReg 1     -> Just (RealReg 34)    -- %f2
345         DoubleReg 2     -> Just (RealReg 36)    -- %f4
346
347         -- STG Regs
348         Sp              -> Just (RealReg 24)    -- %i0
349         SpLim           -> Just (RealReg 26)    -- %i2
350         Hp              -> Just (RealReg 27)    -- %i3
351
352         BaseReg         -> Just (RealReg 25)    -- %i1
353                 
354         _               -> Nothing      
355 -}