NCG: Validate fixes
[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
69 data Size
70         = II8     -- byte (signed)
71 --      | II8u    -- byte (unsigned)
72         | II16    -- halfword (signed, 2 bytes)
73 --      | II16u   -- halfword (unsigned, 2 bytes)
74         | II32    -- word (4 bytes)
75         | II64    -- word (8 bytes)
76         | FF32    -- IEEE single-precision floating pt
77         | FF64    -- IEEE single-precision floating pt
78         deriving Eq
79
80
81 intSize, floatSize :: Width -> Size
82 intSize W8      = II8
83 --intSize W16 = II16u
84 intSize W16     = II16
85 intSize W32     = II32
86 intSize W64     = II64
87 intSize other   = pprPanic "MachInstrs.intSize" (ppr other)
88
89 floatSize W32   = FF32
90 floatSize W64   = FF64
91 floatSize other = pprPanic "MachInstrs.intSize" (ppr other)
92
93
94 isFloatSize :: Size -> Bool
95 isFloatSize FF32        = True
96 isFloatSize FF64        = True
97 isFloatSize _           = False
98
99
100 wordSize :: Size
101 wordSize = intSize wordWidth
102
103
104 cmmTypeSize :: CmmType -> Size
105 cmmTypeSize ty 
106         | isFloatType ty        = floatSize (typeWidth ty)
107         | otherwise             = intSize (typeWidth ty)
108
109
110 sizeToWidth :: Size -> Width
111 sizeToWidth size
112  = case size of
113         II8             -> W8
114 --      II8u            -> W8
115         II16            -> W16
116 --      II16u           -> W16
117         II32            -> W32
118         II64            -> W64
119         FF32            -> W32
120         FF64            -> W64
121
122
123 mkVReg :: Unique -> Size -> Reg
124 mkVReg u size
125         | not (isFloatSize size) 
126         = VirtualRegI u
127
128         | otherwise
129         = case size of
130                 FF32    -> VirtualRegF u
131                 FF64    -> VirtualRegD u
132                 _       -> panic "mkVReg"
133
134
135 -- immediates ------------------------------------------------------------------
136 data Imm
137         = ImmInt        Int
138         | ImmInteger    Integer     -- Sigh.
139         | ImmCLbl       CLabel      -- AbstractC Label (with baggage)
140         | ImmLit        Doc         -- Simple string
141         | ImmIndex    CLabel Int
142         | ImmFloat      Rational
143         | ImmDouble     Rational
144         | ImmConstantSum Imm Imm
145         | ImmConstantDiff Imm Imm
146         | LO Imm                    {- Possible restrictions... -}
147         | HI Imm
148
149
150 strImmLit :: String -> Imm
151 strImmLit s = ImmLit (text s)
152
153
154 -- narrow to the width: a CmmInt might be out of
155 -- range, but we assume that ImmInteger only contains
156 -- in-range values.  A signed value should be fine here.
157 litToImm :: CmmLit -> Imm
158 litToImm (CmmInt i w)        = ImmInteger (narrowS w i)
159 litToImm (CmmFloat f W32)    = ImmFloat f
160 litToImm (CmmFloat f W64)    = ImmDouble f
161 litToImm (CmmLabel l)        = ImmCLbl l
162 litToImm (CmmLabelOff l off) = ImmIndex l off
163
164 litToImm (CmmLabelDiffOff l1 l2 off)
165                              = ImmConstantSum
166                                (ImmConstantDiff (ImmCLbl l1) (ImmCLbl l2))
167                                (ImmInt off)
168 litToImm (CmmBlock id)          = ImmCLbl (infoTblLbl id)
169 litToImm _
170         = panic "SPARC.Regs.litToImm: no match"
171
172 -- addressing modes ------------------------------------------------------------
173 data AddrMode
174         = AddrRegReg    Reg Reg
175         | AddrRegImm    Reg Imm
176
177
178 addrOffset :: AddrMode -> Int -> Maybe AddrMode
179 addrOffset addr off
180   = case addr of
181       AddrRegImm r (ImmInt n)
182        | fits13Bits n2 -> Just (AddrRegImm r (ImmInt n2))
183        | otherwise     -> Nothing
184        where n2 = n + off
185
186       AddrRegImm r (ImmInteger n)
187        | fits13Bits n2 -> Just (AddrRegImm r (ImmInt (fromInteger n2)))
188        | otherwise     -> Nothing
189        where n2 = n + toInteger off
190
191       AddrRegReg r (RealReg 0)
192        | fits13Bits off -> Just (AddrRegImm r (ImmInt off))
193        | otherwise     -> Nothing
194        
195       _ -> Nothing
196
197
198
199 -- registers -------------------------------------------------------------------
200
201 -- @spRel@ gives us a stack relative addressing mode for volatile
202 -- temporaries and for excess call arguments.  @fpRel@, where
203 -- applicable, is the same but for the frame pointer.
204 spRel :: Int    -- desired stack offset in words, positive or negative
205       -> AddrMode
206
207 spRel n = AddrRegImm sp (ImmInt (n * wORD_SIZE))
208
209
210 argRegs :: RegNo -> [Reg]
211 argRegs 0 = []
212 argRegs 1 = map (RealReg . oReg) [0]
213 argRegs 2 = map (RealReg . oReg) [0,1]
214 argRegs 3 = map (RealReg . oReg) [0,1,2]
215 argRegs 4 = map (RealReg . oReg) [0,1,2,3]
216 argRegs 5 = map (RealReg . oReg) [0,1,2,3,4]
217 argRegs 6 = map (RealReg . oReg) [0,1,2,3,4,5]
218 argRegs _ = panic "MachRegs.argRegs(sparc): don't know about >6 arguments!"
219
220
221 allArgRegs :: [Reg]
222 allArgRegs = map RealReg [oReg i | i <- [0..5]]
223
224
225 -- These are the regs which we cannot assume stay alive over a C call.  
226 callClobberedRegs :: [Reg]
227 callClobberedRegs
228         = map RealReg 
229                 ( oReg 7 :
230                   [oReg i | i <- [0..5]] ++
231                   [gReg i | i <- [1..7]] ++
232                   [fReg i | i <- [0..31]] )
233
234
235 allMachRegNos :: [RegNo]
236 allMachRegNos
237         = ([0..31]
238                ++ [32,34 .. nCG_FirstFloatReg-1]
239                ++ [nCG_FirstFloatReg .. 63])    
240
241
242 -- | Get the class of a register.
243 {-# INLINE regClass      #-}
244 regClass :: Reg -> RegClass
245 regClass (VirtualRegI  _)       = RcInteger
246 regClass (VirtualRegHi _)       = RcInteger
247 regClass (VirtualRegF  _)       = RcFloat
248 regClass (VirtualRegD  _)       = RcDouble
249 regClass (RealReg i) 
250         | i < 32                = RcInteger 
251         | i < nCG_FirstFloatReg = RcDouble
252         | otherwise             = RcFloat
253
254
255 showReg :: RegNo -> String
256 showReg n
257    | n >= 0  && n < 8   = "%g" ++ show n
258    | n >= 8  && n < 16  = "%o" ++ show (n-8)
259    | n >= 16 && n < 24  = "%l" ++ show (n-16)
260    | n >= 24 && n < 32  = "%i" ++ show (n-24)
261    | n >= 32 && n < 64  = "%f" ++ show (n-32)
262    | otherwise          = "%unknown_sparc_real_reg_" ++ show n
263
264
265 -- machine specific ------------------------------------------------------------
266
267 -- Duznae work for offsets greater than 13 bits; we just hope for the best
268 fpRel :: Int -> AddrMode
269 fpRel n
270   = AddrRegImm fp (ImmInt (n * wORD_SIZE))
271
272
273 {-# SPECIALIZE fits13Bits :: Int -> Bool, Integer -> Bool #-}
274 fits13Bits :: Integral a => a -> Bool
275 fits13Bits x = x >= -4096 && x < 4096
276
277
278 largeOffsetError :: Integral a => a -> b
279 largeOffsetError i
280   = error ("ERROR: SPARC native-code generator cannot handle large offset ("
281            ++ show i ++ ");\nprobably because of large constant data structures;" ++ 
282            "\nworkaround: use -fvia-C on this module.\n")
283
284
285 {-
286 The SPARC has 64 registers of interest; 32 integer registers and 32
287 floating point registers.  The mapping of STG registers to SPARC
288 machine registers is defined in StgRegs.h.  We are, of course,
289 prepared for any eventuality.
290
291 The whole fp-register pairing thing on sparcs is a huge nuisance.  See
292 fptools/ghc/includes/MachRegs.h for a description of what's going on
293 here.
294 -}
295
296
297 gReg,lReg,iReg,oReg,fReg :: Int -> RegNo
298 gReg x = x
299 oReg x = (8 + x)
300 lReg x = (16 + x)
301 iReg x = (24 + x)
302 fReg x = (32 + x)
303
304
305 g0, g1, g2, fp, sp, o0, o1, f0, f6, f8, f22, f26, f27 :: Reg
306 f6  = RealReg (fReg 6)
307 f8  = RealReg (fReg 8)
308 f22 = RealReg (fReg 22)
309 f26 = RealReg (fReg 26)
310 f27 = RealReg (fReg 27)
311
312
313 -- g0 is useful for codegen; is always zero, and writes to it vanish.
314 g0  = RealReg (gReg 0)
315 g1  = RealReg (gReg 1)
316 g2  = RealReg (gReg 2)
317
318
319 -- FP, SP, int and float return (from C) regs.
320 fp  = RealReg (iReg 6)
321 sp  = RealReg (oReg 6)
322 o0  = RealReg (oReg 0)
323 o1  = RealReg (oReg 1)
324 f0  = RealReg (fReg 0)
325
326
327 #if sparc_TARGET_ARCH
328 nCG_FirstFloatReg :: RegNo
329 nCG_FirstFloatReg = unRealReg NCG_FirstFloatReg
330 #else
331 nCG_FirstFloatReg :: RegNo
332 nCG_FirstFloatReg = unRealReg f22
333 #endif
334
335
336 -- horror show -----------------------------------------------------------------
337 #if sparc_TARGET_ARCH
338
339 #define g0 0
340 #define g1 1
341 #define g2 2
342 #define g3 3
343 #define g4 4
344 #define g5 5
345 #define g6 6
346 #define g7 7
347 #define o0 8
348 #define o1 9
349 #define o2 10
350 #define o3 11
351 #define o4 12
352 #define o5 13
353 #define o6 14
354 #define o7 15
355 #define l0 16
356 #define l1 17
357 #define l2 18
358 #define l3 19
359 #define l4 20
360 #define l5 21
361 #define l6 22
362 #define l7 23
363 #define i0 24
364 #define i1 25
365 #define i2 26
366 #define i3 27
367 #define i4 28
368 #define i5 29
369 #define i6 30
370 #define i7 31
371
372 #define f0  32
373 #define f1  33
374 #define f2  34
375 #define f3  35
376 #define f4  36
377 #define f5  37
378 #define f6  38
379 #define f7  39
380 #define f8  40
381 #define f9  41
382 #define f10 42
383 #define f11 43
384 #define f12 44
385 #define f13 45
386 #define f14 46
387 #define f15 47
388 #define f16 48
389 #define f17 49
390 #define f18 50
391 #define f19 51
392 #define f20 52
393 #define f21 53
394 #define f22 54
395 #define f23 55
396 #define f24 56
397 #define f25 57
398 #define f26 58
399 #define f27 59
400 #define f28 60
401 #define f29 61
402 #define f30 62
403 #define f31 63
404 #endif
405
406
407 freeReg :: RegNo -> FastBool
408 globalRegMaybe :: GlobalReg -> Maybe Reg
409
410 #if defined(sparc_TARGET_ARCH)
411
412
413 freeReg g0 = fastBool False  -- %g0 is always 0.
414
415 freeReg g5 = fastBool False  -- %g5 is reserved (ABI).
416 freeReg g6 = fastBool False  -- %g6 is reserved (ABI).
417 freeReg g7 = fastBool False  -- %g7 is reserved (ABI).
418 freeReg i6 = fastBool False  -- %i6 is our frame pointer.
419 freeReg i7 = fastBool False  -- %i7 tends to have ret-addr-ish things
420 freeReg o6 = fastBool False  -- %o6 is our stack pointer.
421 freeReg o7 = fastBool False  -- %o7 holds ret addrs (???)
422 freeReg f0 = fastBool False  --  %f0/%f1 are the C fp return registers.
423 freeReg f1 = fastBool False
424
425 -- TODO: Not sure about these BL 2009/01/10
426 --      Used for NCG spill tmps? what is this?
427
428 {-
429 freeReg g1  = fastBool False  -- %g1 is used for NCG spill tmp
430 freeReg g2  = fastBool False 
431 freeReg f6  = fastBool False
432 freeReg f8  = fastBool False
433 freeReg f26 = fastBool False
434 freeReg f27 = fastBool False
435 -}
436
437 #ifdef REG_Base
438 freeReg REG_Base = fastBool False
439 #endif
440 #ifdef REG_R1
441 freeReg REG_R1   = fastBool False
442 #endif  
443 #ifdef REG_R2  
444 freeReg REG_R2   = fastBool False
445 #endif  
446 #ifdef REG_R3  
447 freeReg REG_R3   = fastBool False
448 #endif  
449 #ifdef REG_R4  
450 freeReg REG_R4   = fastBool False
451 #endif  
452 #ifdef REG_R5  
453 freeReg REG_R5   = fastBool False
454 #endif  
455 #ifdef REG_R6  
456 freeReg REG_R6   = fastBool False
457 #endif  
458 #ifdef REG_R7  
459 freeReg REG_R7   = fastBool False
460 #endif  
461 #ifdef REG_R8  
462 freeReg REG_R8   = fastBool False
463 #endif
464 #ifdef REG_F1
465 freeReg REG_F1 = fastBool False
466 #endif
467 #ifdef REG_F2
468 freeReg REG_F2 = fastBool False
469 #endif
470 #ifdef REG_F3
471 freeReg REG_F3 = fastBool False
472 #endif
473 #ifdef REG_F4
474 freeReg REG_F4 = fastBool False
475 #endif
476 #ifdef REG_D1
477 freeReg REG_D1 = fastBool False
478 #endif
479 #ifdef REG_D2
480 freeReg REG_D2 = fastBool False
481 #endif
482 #ifdef REG_Sp 
483 freeReg REG_Sp   = fastBool False
484 #endif 
485 #ifdef REG_Su
486 freeReg REG_Su   = fastBool False
487 #endif 
488 #ifdef REG_SpLim 
489 freeReg REG_SpLim = fastBool False
490 #endif 
491 #ifdef REG_Hp 
492 freeReg REG_Hp   = fastBool False
493 #endif
494 #ifdef REG_HpLim
495 freeReg REG_HpLim = fastBool False
496 #endif
497 freeReg _         = fastBool True
498
499
500
501 --  | Returns 'Nothing' if this global register is not stored
502 -- in a real machine register, otherwise returns @'Just' reg@, where
503 -- reg is the machine register it is stored in.
504
505
506 #ifdef REG_Base
507 globalRegMaybe BaseReg                  = Just (RealReg REG_Base)
508 #endif
509 #ifdef REG_R1
510 globalRegMaybe (VanillaReg 1 _)         = Just (RealReg REG_R1)
511 #endif 
512 #ifdef REG_R2 
513 globalRegMaybe (VanillaReg 2 _)         = Just (RealReg REG_R2)
514 #endif 
515 #ifdef REG_R3 
516 globalRegMaybe (VanillaReg 3 _)         = Just (RealReg REG_R3)
517 #endif 
518 #ifdef REG_R4 
519 globalRegMaybe (VanillaReg 4 _)         = Just (RealReg REG_R4)
520 #endif 
521 #ifdef REG_R5 
522 globalRegMaybe (VanillaReg 5 _)         = Just (RealReg REG_R5)
523 #endif 
524 #ifdef REG_R6 
525 globalRegMaybe (VanillaReg 6 _)         = Just (RealReg REG_R6)
526 #endif 
527 #ifdef REG_R7 
528 globalRegMaybe (VanillaReg 7 _)         = Just (RealReg REG_R7)
529 #endif 
530 #ifdef REG_R8 
531 globalRegMaybe (VanillaReg 8 _)         = Just (RealReg REG_R8)
532 #endif
533 #ifdef REG_R9 
534 globalRegMaybe (VanillaReg 9 _)         = Just (RealReg REG_R9)
535 #endif
536 #ifdef REG_R10 
537 globalRegMaybe (VanillaReg 10 _)        = Just (RealReg REG_R10)
538 #endif
539 #ifdef REG_F1
540 globalRegMaybe (FloatReg 1)             = Just (RealReg REG_F1)
541 #endif                                  
542 #ifdef REG_F2                           
543 globalRegMaybe (FloatReg 2)             = Just (RealReg REG_F2)
544 #endif                                  
545 #ifdef REG_F3                           
546 globalRegMaybe (FloatReg 3)             = Just (RealReg REG_F3)
547 #endif                                  
548 #ifdef REG_F4                           
549 globalRegMaybe (FloatReg 4)             = Just (RealReg REG_F4)
550 #endif                                  
551 #ifdef REG_D1                           
552 globalRegMaybe (DoubleReg 1)            = Just (RealReg REG_D1)
553 #endif                                  
554 #ifdef REG_D2                           
555 globalRegMaybe (DoubleReg 2)            = Just (RealReg REG_D2)
556 #endif
557 #ifdef REG_Sp       
558 globalRegMaybe Sp                       = Just (RealReg REG_Sp)
559 #endif
560 #ifdef REG_Lng1                         
561 globalRegMaybe (LongReg 1)              = Just (RealReg REG_Lng1)
562 #endif                                  
563 #ifdef REG_Lng2                         
564 globalRegMaybe (LongReg 2)              = Just (RealReg REG_Lng2)
565 #endif
566 #ifdef REG_SpLim                                
567 globalRegMaybe SpLim                    = Just (RealReg REG_SpLim)
568 #endif                                  
569 #ifdef REG_Hp                           
570 globalRegMaybe Hp                       = Just (RealReg REG_Hp)
571 #endif                                  
572 #ifdef REG_HpLim                        
573 globalRegMaybe HpLim                    = Just (RealReg REG_HpLim)
574 #endif                                  
575 #ifdef REG_CurrentTSO                           
576 globalRegMaybe CurrentTSO               = Just (RealReg REG_CurrentTSO)
577 #endif                                  
578 #ifdef REG_CurrentNursery                       
579 globalRegMaybe CurrentNursery           = Just (RealReg REG_CurrentNursery)
580 #endif                                  
581 globalRegMaybe _                        = Nothing
582
583
584 #else
585
586 freeReg _       = 0#
587 globalRegMaybe  = panic "SPARC.Regs.globalRegMaybe: not defined"
588
589 #endif
590
591