NCG: Split up the native code generator into arch specific modules
[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         -- immediate values
9         Imm(..),
10         strImmLit,
11         litToImm,
12
13         -- addressing modes
14         AddrMode(..),
15         addrOffset,
16
17         -- registers
18         spRel,
19         argRegs, 
20         allArgRegs, 
21         callClobberedRegs,
22         allMachRegNos,
23         regClass,
24         showReg,
25
26         -- machine specific info
27         fpRel,
28         fits13Bits, 
29         largeOffsetError,
30         gReg, iReg, lReg, oReg, fReg,
31         fp, sp, g0, g1, g2, o0, o1, f0, f6, f8, f22, f26, f27,
32         nCG_FirstFloatReg,
33
34         -- allocatable
35         freeReg,
36         allocatableRegs,
37         globalRegMaybe,
38
39         get_GlobalReg_reg_or_addr
40 )
41
42 where
43
44
45 import Reg
46 import RegClass
47
48 import CgUtils          ( get_GlobalReg_addr )
49 import BlockId
50 import Cmm
51 import CLabel           ( CLabel )
52 import Pretty
53 import Outputable       ( panic )
54 import qualified Outputable
55 import Constants
56 import FastBool
57
58
59 -- immediates ------------------------------------------------------------------
60
61 -- | An immediate value.
62 --      Not all of these are directly representable by the machine. 
63 --      Things like ImmLit are slurped out and put in a data segment instead.
64 --
65 data Imm
66         = ImmInt        Int
67
68         -- Sigh.
69         | ImmInteger    Integer     
70
71         -- AbstractC Label (with baggage)
72         | ImmCLbl       CLabel      
73
74         -- Simple string
75         | ImmLit        Doc         
76         | ImmIndex      CLabel Int
77         | ImmFloat      Rational
78         | ImmDouble     Rational
79
80         | ImmConstantSum  Imm Imm
81         | ImmConstantDiff Imm Imm
82
83         | LO    Imm                
84         | HI    Imm
85
86
87 -- | Create a ImmLit containing this string.
88 strImmLit :: String -> Imm
89 strImmLit s = ImmLit (text s)
90
91
92 -- | Convert a CmmLit to an Imm.
93 --      Narrow to the width: a CmmInt might be out of
94 --      range, but we assume that ImmInteger only contains
95 --      in-range values.  A signed value should be fine here.
96 --
97 litToImm :: CmmLit -> Imm
98 litToImm lit
99  = case lit of
100         CmmInt i w              -> ImmInteger (narrowS w i)
101         CmmFloat f W32          -> ImmFloat f
102         CmmFloat f W64          -> ImmDouble f
103         CmmLabel l              -> ImmCLbl l
104         CmmLabelOff l off       -> ImmIndex l off
105
106         CmmLabelDiffOff l1 l2 off
107          -> ImmConstantSum
108                 (ImmConstantDiff (ImmCLbl l1) (ImmCLbl l2))
109                 (ImmInt off)
110
111         CmmBlock id     -> ImmCLbl (infoTblLbl id)
112         _               -> panic "SPARC.Regs.litToImm: no match"
113
114
115
116 -- addressing modes ------------------------------------------------------------
117
118 -- | Represents a memory address in an instruction.
119 --      Being a RISC machine, the SPARC addressing modes are very regular.
120 --
121 data AddrMode
122         = AddrRegReg    Reg Reg         -- addr = r1 + r2
123         | AddrRegImm    Reg Imm         -- addr = r1 + imm
124
125
126 -- | Add an integer offset to the address in an AddrMode.
127 --
128 addrOffset :: AddrMode -> Int -> Maybe AddrMode
129 addrOffset addr off
130   = case addr of
131       AddrRegImm r (ImmInt n)
132        | fits13Bits n2 -> Just (AddrRegImm r (ImmInt n2))
133        | otherwise     -> Nothing
134        where n2 = n + off
135
136       AddrRegImm r (ImmInteger n)
137        | fits13Bits n2 -> Just (AddrRegImm r (ImmInt (fromInteger n2)))
138        | otherwise     -> Nothing
139        where n2 = n + toInteger off
140
141       AddrRegReg r (RealReg 0)
142        | fits13Bits off -> Just (AddrRegImm r (ImmInt off))
143        | otherwise     -> Nothing
144        
145       _ -> Nothing
146
147
148
149 -- registers -------------------------------------------------------------------
150
151 -- | Get an AddrMode relative to the address in sp.
152 --      This gives us a stack relative addressing mode for volatile
153 --      temporaries and for excess call arguments.  
154 --
155 spRel :: Int            -- ^ stack offset in words, positive or negative
156       -> AddrMode
157
158 spRel n = AddrRegImm sp (ImmInt (n * wORD_SIZE))
159
160
161 -- | The registers to place arguments for function calls, 
162 --      for some number of arguments.
163 --
164 argRegs :: RegNo -> [Reg]
165 argRegs r
166  = case r of
167         0       -> []
168         1       -> map (RealReg . oReg) [0]
169         2       -> map (RealReg . oReg) [0,1]
170         3       -> map (RealReg . oReg) [0,1,2]
171         4       -> map (RealReg . oReg) [0,1,2,3]
172         5       -> map (RealReg . oReg) [0,1,2,3,4]
173         6       -> map (RealReg . oReg) [0,1,2,3,4,5]
174         _       -> panic "MachRegs.argRegs(sparc): don't know about >6 arguments!"
175
176
177 -- | All all the regs that could possibly be returned by argRegs
178 --
179 allArgRegs :: [Reg]
180 allArgRegs 
181         = map RealReg [oReg i | i <- [0..5]]
182
183
184 -- These are the regs that we cannot assume stay alive over a C call.  
185 --      TODO: Why can we assume that o6 isn't clobbered? -- BL 2009/02
186 --
187 callClobberedRegs :: [Reg]
188 callClobberedRegs
189         = map RealReg 
190                 (  oReg 7 :
191                   [oReg i | i <- [0..5]] ++
192                   [gReg i | i <- [1..7]] ++
193                   [fReg i | i <- [0..31]] )
194
195
196 -- | The RegNos corresponding to all the registers in the machine.
197 --      For SPARC we use f0-f22 as doubles, so pretend that the high halves
198 --      of these, ie f23, f25 .. don't exist.
199 --
200 allMachRegNos :: [RegNo]
201 allMachRegNos   
202         = ([0..31]
203                ++ [32,34 .. nCG_FirstFloatReg-1]
204                ++ [nCG_FirstFloatReg .. 63])    
205
206
207 -- | Get the class of a register.
208 {-# INLINE regClass      #-}
209 regClass :: Reg -> RegClass
210 regClass reg
211  = case reg of
212         VirtualRegI  _  -> RcInteger
213         VirtualRegHi _  -> RcInteger
214         VirtualRegF  _  -> RcFloat
215         VirtualRegD  _  -> RcDouble
216         RealReg i
217           | i < 32                      -> RcInteger 
218           | i < nCG_FirstFloatReg       -> RcDouble
219           | otherwise                   -> RcFloat
220
221
222 -- | Get the standard name for the register with this number.
223 showReg :: RegNo -> String
224 showReg n
225         | n >= 0  && n < 8   = "%g" ++ show n
226         | n >= 8  && n < 16  = "%o" ++ show (n-8)
227         | n >= 16 && n < 24  = "%l" ++ show (n-16)
228         | n >= 24 && n < 32  = "%i" ++ show (n-24)
229         | n >= 32 && n < 64  = "%f" ++ show (n-32)
230         | otherwise          = panic "SPARC.Regs.showReg: unknown sparc register"
231
232
233 -- machine specific ------------------------------------------------------------
234
235 -- | Get an address relative to the frame pointer.
236 --      This doesn't work work for offsets greater than 13 bits; we just hope for the best
237 --
238 fpRel :: Int -> AddrMode
239 fpRel n
240         = AddrRegImm fp (ImmInt (n * wORD_SIZE))
241
242
243 -- | Check whether an offset is representable with 13 bits.
244 fits13Bits :: Integral a => a -> Bool
245 fits13Bits x = x >= -4096 && x < 4096
246
247 {-# SPECIALIZE fits13Bits :: Int -> Bool, Integer -> Bool #-}
248
249
250 -- | Sadness.
251 largeOffsetError :: Integral a => a -> b
252 largeOffsetError i
253   = panic ("ERROR: SPARC native-code generator cannot handle large offset ("
254                 ++ show i ++ ");\nprobably because of large constant data structures;" ++ 
255                 "\nworkaround: use -fvia-C on this module.\n")
256
257
258
259 {-
260         The SPARC has 64 registers of interest; 32 integer registers and 32
261         floating point registers.  The mapping of STG registers to SPARC
262         machine registers is defined in StgRegs.h.  We are, of course,
263         prepared for any eventuality.
264
265         The whole fp-register pairing thing on sparcs is a huge nuisance.  See
266         fptools/ghc/includes/MachRegs.h for a description of what's going on
267         here.
268 -}
269
270
271 -- | Get the regno for this sort of reg
272 gReg, lReg, iReg, oReg, fReg :: Int -> RegNo
273
274 gReg x  = x             -- global regs
275 oReg x  = (8 + x)       -- output regs
276 lReg x  = (16 + x)      -- local regs
277 iReg x  = (24 + x)      -- input regs
278 fReg x  = (32 + x)      -- float regs
279
280
281 -- | Some specific regs used by the code generator.
282 g0, g1, g2, fp, sp, o0, o1, f0, f6, f8, f22, f26, f27 :: Reg
283
284 f6  = RealReg (fReg 6)
285 f8  = RealReg (fReg 8)
286 f22 = RealReg (fReg 22)
287 f26 = RealReg (fReg 26)
288 f27 = RealReg (fReg 27)
289
290 g0  = RealReg (gReg 0)  -- g0 is always zero, and writes to it vanish.
291 g1  = RealReg (gReg 1)
292 g2  = RealReg (gReg 2)
293
294 -- FP, SP, int and float return (from C) regs.
295 fp  = RealReg (iReg 6)
296 sp  = RealReg (oReg 6)
297 o0  = RealReg (oReg 0)
298 o1  = RealReg (oReg 1)
299 f0  = RealReg (fReg 0)
300
301
302 -- | We use he first few float regs as double precision. 
303 --      This is the RegNo of the first float regs we use as single precision.
304 --
305 nCG_FirstFloatReg :: RegNo
306 nCG_FirstFloatReg = 54
307
308
309
310 -- | Check whether a machine register is free for allocation.
311 --      This needs to match the info in includes/MachRegs.h otherwise modules
312 --      compiled with the NCG won't be compatible with via-C ones.
313 --
314 freeReg :: RegNo -> FastBool
315 freeReg regno
316  = case regno of
317         -- %g0(r0) is always 0.
318         0       -> fastBool False       
319
320         -- %g1(r1) - %g4(r4) are allocable -----------------
321
322         -- %g5(r5) - %g7(r7) 
323         --      are reserved for the OS
324         5       -> fastBool False
325         6       -> fastBool False
326         7       -> fastBool False
327
328         -- %o0(r8) - %o5(r13) are allocable ----------------
329
330         -- %o6(r14) 
331         --      is the C stack pointer
332         14      -> fastBool False
333
334         -- %o7(r15) 
335         --      holds C return addresses (???)
336         15      -> fastBool False
337
338         -- %l0(r16) is allocable ---------------------------
339
340         -- %l1(r17) - %l5(r21) 
341         --      are STG regs R1 - R5
342         17      -> fastBool False
343         18      -> fastBool False
344         19      -> fastBool False
345         20      -> fastBool False
346         21      -> fastBool False
347         
348         -- %l6(r22) - %l7(r23) are allocable --------------
349         
350         -- %i0(r24) - %i5(r29)
351         --      are STG regs Sp, Base, SpLim, Hp, HpLim, R6
352         24      -> fastBool False
353         25      -> fastBool False
354         26      -> fastBool False
355         27      -> fastBool False
356         28      -> fastBool False
357         29      -> fastBool False
358         
359         -- %i6(r30) 
360         --      is the C frame pointer
361         30      -> fastBool False
362
363         -- %i7(r31) 
364         --      is used for C return addresses
365         31      -> fastBool False
366         
367         -- %f0(r32) - %f1(r33)
368         --      are C fp return registers
369         32      -> fastBool False
370         33      -> fastBool False
371
372         -- %f2(r34) - %f5(r37)
373         --      are STG regs D1 - D2
374         34      -> fastBool False
375         35      -> fastBool False
376         36      -> fastBool False
377         37      -> fastBool False
378
379         -- %f22(r54) - %f25(r57)
380         --      are STG regs F1 - F4
381         54      -> fastBool False
382         55      -> fastBool False
383         56      -> fastBool False
384         57      -> fastBool False
385
386         -- regs not matched above are allocable.
387         _       -> fastBool True
388
389
390 -- allocatableRegs is allMachRegNos with the fixed-use regs removed.
391 -- i.e., these are the regs for which we are prepared to allow the
392 -- register allocator to attempt to map VRegs to.
393 allocatableRegs :: [RegNo]
394 allocatableRegs
395    = let isFree i = isFastTrue (freeReg i)
396      in  filter isFree allMachRegNos
397
398
399 -- | Returns Just the real register that a global register is stored in.
400 --      Returns Nothing if the global has no real register, and is stored
401 --      in the in-memory register table instead.
402 --
403 globalRegMaybe  :: GlobalReg -> Maybe Reg
404 globalRegMaybe gg
405  = case gg of
406         -- Argument and return regs
407         VanillaReg 1 _  -> Just (RealReg 17)    -- %l1
408         VanillaReg 2 _  -> Just (RealReg 18)    -- %l2
409         VanillaReg 3 _  -> Just (RealReg 19)    -- %l3
410         VanillaReg 4 _  -> Just (RealReg 20)    -- %l4
411         VanillaReg 5 _  -> Just (RealReg 21)    -- %l5
412         VanillaReg 6 _  -> Just (RealReg 29)    -- %i5
413
414         FloatReg 1      -> Just (RealReg 54)    -- %f22
415         FloatReg 2      -> Just (RealReg 55)    -- %f23
416         FloatReg 3      -> Just (RealReg 56)    -- %f24
417         FloatReg 4      -> Just (RealReg 57)    -- %f25
418
419         DoubleReg 1     -> Just (RealReg 34)    -- %f2
420         DoubleReg 2     -> Just (RealReg 36)    -- %f4
421
422         -- STG Regs
423         Sp              -> Just (RealReg 24)    -- %i0
424         SpLim           -> Just (RealReg 26)    -- %i2
425         Hp              -> Just (RealReg 27)    -- %i3
426         HpLim           -> Just (RealReg 28)    -- %i4
427
428         BaseReg         -> Just (RealReg 25)    -- %i1
429                 
430         _               -> Nothing      
431
432
433 -- We map STG registers onto appropriate CmmExprs.  Either they map
434 -- to real machine registers or stored as offsets from BaseReg.  Given
435 -- a GlobalReg, get_GlobalReg_reg_or_addr produces either the real
436 -- register it is in, on this platform, or a CmmExpr denoting the
437 -- address in the register table holding it.
438 -- (See also get_GlobalReg_addr in CgUtils.)
439
440 get_GlobalReg_reg_or_addr :: GlobalReg -> Either Reg CmmExpr
441 get_GlobalReg_reg_or_addr mid
442    = case globalRegMaybe mid of
443         Just rr -> Left rr
444         Nothing -> Right (get_GlobalReg_addr mid)