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