Fix a bug introduced in the SSE2 support: callClobberedRegs was wrong
[ghc-hetmet.git] / compiler / nativeGen / X86 / Regs.hs
1 module X86.Regs (
2         -- squeese functions for the graph allocator
3         virtualRegSqueeze,
4         realRegSqueeze,
5
6         -- immediates
7         Imm(..),
8         strImmLit,
9         litToImm,
10
11         -- addressing modes
12         AddrMode(..),
13         addrOffset,
14
15         -- registers
16         spRel,
17         argRegs,
18         allArgRegs,
19         callClobberedRegs,
20         allMachRegNos,
21         classOfRealReg,
22         showReg,        
23
24         -- machine specific
25         EABase(..), EAIndex(..), addrModeRegs,
26
27         eax, ebx, ecx, edx, esi, edi, ebp, esp,
28         fake0, fake1, fake2, fake3, fake4, fake5,
29
30         rax, rbx, rcx, rdx, rsi, rdi, rbp, rsp,
31         r8,  r9,  r10, r11, r12, r13, r14, r15,
32         xmm0, xmm1, xmm2, xmm3, xmm4, xmm5, xmm6, xmm7,
33         xmm8, xmm9, xmm10, xmm11, xmm12, xmm13, xmm14, xmm15,
34         xmm,
35
36         ripRel,
37         allFPArgRegs,
38
39         -- horror show
40         freeReg,
41         globalRegMaybe,
42         
43         get_GlobalReg_reg_or_addr,
44         allocatableRegs
45 )
46
47 where
48
49 #include "nativeGen/NCG.h"
50 #include "HsVersions.h"
51
52 #include "../includes/stg/MachRegs.h"
53
54 import Reg
55 import RegClass
56
57 import CgUtils          ( get_GlobalReg_addr )
58 import BlockId
59 import Cmm
60 import CLabel           ( CLabel )
61 import Pretty
62 import Outputable       ( panic )
63 import FastTypes
64 import FastBool
65
66
67 #if  defined(i386_TARGET_ARCH) || defined(x86_64_TARGET_ARCH)
68 import Constants
69 #endif
70
71
72 -- | regSqueeze_class reg
73 --      Calculuate the maximum number of register colors that could be
74 --      denied to a node of this class due to having this reg 
75 --      as a neighbour.
76 --
77 {-# INLINE virtualRegSqueeze #-}
78 virtualRegSqueeze :: RegClass -> VirtualReg -> FastInt
79
80 virtualRegSqueeze cls vr
81  = case cls of
82         RcInteger
83          -> case vr of
84                 VirtualRegI{}           -> _ILIT(1)
85                 VirtualRegHi{}          -> _ILIT(1)
86                 _other                  -> _ILIT(0)
87
88         RcDouble
89          -> case vr of
90                 VirtualRegD{}           -> _ILIT(1)
91                 VirtualRegF{}           -> _ILIT(0)
92                 _other                  -> _ILIT(0)
93
94         RcDoubleSSE
95          -> case vr of
96                 VirtualRegSSE{}         -> _ILIT(1)
97                 _other                  -> _ILIT(0)
98
99         _other -> _ILIT(0)
100
101 {-# INLINE realRegSqueeze #-}
102 realRegSqueeze :: RegClass -> RealReg -> FastInt
103 realRegSqueeze cls rr
104  = case cls of
105         RcInteger
106          -> case rr of
107                 RealRegSingle regNo
108                         | regNo < firstfake -> _ILIT(1) -- first fake reg is 16
109                         | otherwise     -> _ILIT(0)
110                         
111                 RealRegPair{}           -> _ILIT(0)
112
113         RcDouble
114          -> case rr of
115                 RealRegSingle regNo
116                         | regNo >= firstfake && regNo < lastfake -> _ILIT(1)
117                         | otherwise     -> _ILIT(0)
118                         
119                 RealRegPair{}           -> _ILIT(0)
120
121         RcDoubleSSE
122          -> case rr of
123                 RealRegSingle regNo | regNo >= firstxmm -> _ILIT(1)
124                 _otherwise                        -> _ILIT(0)
125
126         _other -> _ILIT(0)
127
128 -- -----------------------------------------------------------------------------
129 -- Immediates
130
131 data Imm
132   = ImmInt      Int
133   | ImmInteger  Integer     -- Sigh.
134   | ImmCLbl     CLabel      -- AbstractC Label (with baggage)
135   | ImmLit      Doc         -- Simple string
136   | ImmIndex    CLabel Int
137   | ImmFloat    Rational
138   | ImmDouble   Rational
139   | ImmConstantSum Imm Imm
140   | ImmConstantDiff Imm Imm
141
142
143 strImmLit :: String -> Imm
144 strImmLit s = ImmLit (text s)
145
146
147 litToImm :: CmmLit -> Imm
148 litToImm (CmmInt i w)        = ImmInteger (narrowS w i)
149                 -- narrow to the width: a CmmInt might be out of
150                 -- range, but we assume that ImmInteger only contains
151                 -- in-range values.  A signed value should be fine here.
152 litToImm (CmmFloat f W32)    = ImmFloat f
153 litToImm (CmmFloat f W64)    = ImmDouble f
154 litToImm (CmmLabel l)        = ImmCLbl l
155 litToImm (CmmLabelOff l off) = ImmIndex l off
156 litToImm (CmmLabelDiffOff l1 l2 off)
157                              = ImmConstantSum
158                                (ImmConstantDiff (ImmCLbl l1) (ImmCLbl l2))
159                                (ImmInt off)
160 litToImm (CmmBlock id)       = ImmCLbl (infoTblLbl id)
161 litToImm _                   = panic "X86.Regs.litToImm: no match"
162
163 -- addressing modes ------------------------------------------------------------
164
165 data AddrMode
166         = AddrBaseIndex EABase EAIndex Displacement
167         | ImmAddr Imm Int
168
169 data EABase       = EABaseNone  | EABaseReg Reg | EABaseRip
170 data EAIndex      = EAIndexNone | EAIndex Reg Int
171 type Displacement = Imm
172
173
174 addrOffset :: AddrMode -> Int -> Maybe AddrMode
175 addrOffset addr off
176   = case addr of
177       ImmAddr i off0      -> Just (ImmAddr i (off0 + off))
178
179       AddrBaseIndex r i (ImmInt n) -> Just (AddrBaseIndex r i (ImmInt (n + off)))
180       AddrBaseIndex r i (ImmInteger n)
181         -> Just (AddrBaseIndex r i (ImmInt (fromInteger (n + toInteger off))))
182
183       AddrBaseIndex r i (ImmCLbl lbl)
184         -> Just (AddrBaseIndex r i (ImmIndex lbl off))
185
186       AddrBaseIndex r i (ImmIndex lbl ix)
187         -> Just (AddrBaseIndex r i (ImmIndex lbl (ix+off)))
188
189       _ -> Nothing  -- in theory, shouldn't happen
190
191
192 addrModeRegs :: AddrMode -> [Reg]
193 addrModeRegs (AddrBaseIndex b i _) =  b_regs ++ i_regs
194   where
195    b_regs = case b of { EABaseReg r -> [r]; _ -> [] }
196    i_regs = case i of { EAIndex r _ -> [r]; _ -> [] }
197 addrModeRegs _ = []
198
199
200 -- registers -------------------------------------------------------------------
201
202 -- @spRel@ gives us a stack relative addressing mode for volatile
203 -- temporaries and for excess call arguments.  @fpRel@, where
204 -- applicable, is the same but for the frame pointer.
205
206
207 spRel :: Int            -- ^ desired stack offset in words, positive or negative
208       -> AddrMode
209
210 #if   i386_TARGET_ARCH
211 spRel n = AddrBaseIndex (EABaseReg esp) EAIndexNone (ImmInt (n * wORD_SIZE))
212
213 #elif x86_64_TARGET_ARCH
214 spRel n = AddrBaseIndex (EABaseReg rsp) EAIndexNone (ImmInt (n * wORD_SIZE))
215
216 #else
217 spRel _ = panic "X86.Regs.spRel: not defined for this architecture"
218
219 #endif
220
221 firstfake, lastfake :: RegNo
222 firstfake = 16
223 lastfake  = 21
224
225 firstxmm, lastxmm :: RegNo
226 firstxmm  = 24
227 lastxmm   = 39
228
229 lastint :: RegNo
230 #if i386_TARGET_ARCH
231 lastint = 7 -- not %r8..%r15
232 #else
233 lastint = 15
234 #endif
235
236 intregnos, fakeregnos, xmmregnos, floatregnos :: [RegNo]
237 intregnos   = [0..lastint]
238 fakeregnos  = [firstfake .. lastfake]
239 xmmregnos   = [firstxmm  .. lastxmm]
240 floatregnos = fakeregnos ++ xmmregnos;
241
242
243 -- argRegs is the set of regs which are read for an n-argument call to C.
244 -- For archs which pass all args on the stack (x86), is empty.
245 -- Sparc passes up to the first 6 args in regs.
246 -- Dunno about Alpha.
247 argRegs :: RegNo -> [Reg]
248 argRegs _       = panic "MachRegs.argRegs(x86): should not be used!"
249
250 -- | The complete set of machine registers.
251 allMachRegNos :: [RegNo]
252 allMachRegNos  = intregnos ++ floatregnos
253
254 -- | Take the class of a register.
255 {-# INLINE classOfRealReg      #-}
256 classOfRealReg :: RealReg -> RegClass
257 -- On x86, we might want to have an 8-bit RegClass, which would
258 -- contain just regs 1-4 (the others don't have 8-bit versions).
259 -- However, we can get away without this at the moment because the
260 -- only allocatable integer regs are also 8-bit compatible (1, 3, 4).
261 classOfRealReg reg
262  = case reg of
263         RealRegSingle i
264           | i <= lastint  -> RcInteger
265           | i <= lastfake -> RcDouble
266           | otherwise     -> RcDoubleSSE
267
268         RealRegPair{}   -> panic "X86.Regs.classOfRealReg: RegPairs on this arch"
269
270 -- | Get the name of the register with this number.
271 showReg :: RegNo -> String
272 showReg n
273         | n >= firstxmm  = "%xmm" ++ show (n-firstxmm)
274         | n >= firstfake = "%fake" ++ show (n-firstfake)
275         | n >= 8         = "%r" ++ show n
276         | otherwise      = regNames !! n
277
278 regNames :: [String]
279 regNames 
280 #if   i386_TARGET_ARCH
281    = ["%eax", "%ebx", "%ecx", "%edx", "%esi", "%edi", "%ebp", "%esp"]
282 #elif x86_64_TARGET_ARCH
283    = ["%rax", "%rbx", "%rcx", "%rdx", "%rsi", "%rdi", "%rbp", "%rsp" ]
284 #endif
285
286
287 -- machine specific ------------------------------------------------------------
288
289
290 {-
291 Intel x86 architecture:
292 - All registers except 7 (esp) are available for use.
293 - Only ebx, esi, edi and esp are available across a C call (they are callee-saves).
294 - Registers 0-7 have 16-bit counterparts (ax, bx etc.)
295 - Registers 0-3 have 8 bit counterparts (ah, bh etc.)
296 - Registers 8-13 are fakes; we pretend x86 has 6 conventionally-addressable
297   fp registers, and 3-operand insns for them, and we translate this into
298   real stack-based x86 fp code after register allocation.
299
300 The fp registers are all Double registers; we don't have any RcFloat class
301 regs.  @regClass@ barfs if you give it a VirtualRegF, and mkVReg above should
302 never generate them.
303 -}
304
305 fake0, fake1, fake2, fake3, fake4, fake5, 
306        eax, ebx, ecx, edx, esp, ebp, esi, edi :: Reg
307
308 eax   = regSingle 0
309 ebx   = regSingle 1
310 ecx   = regSingle 2
311 edx   = regSingle 3
312 esi   = regSingle 4
313 edi   = regSingle 5
314 ebp   = regSingle 6
315 esp   = regSingle 7
316 fake0 = regSingle 16
317 fake1 = regSingle 17
318 fake2 = regSingle 18
319 fake3 = regSingle 19
320 fake4 = regSingle 20
321 fake5 = regSingle 21
322
323
324
325 {-
326 AMD x86_64 architecture:
327 - Registers 0-16 have 32-bit counterparts (eax, ebx etc.)
328 - Registers 0-7 have 16-bit counterparts (ax, bx etc.)
329 - Registers 0-3 have 8 bit counterparts (ah, bh etc.)
330
331 -}
332
333 rax, rbx, rcx, rdx, rsp, rbp, rsi, rdi, 
334   r8, r9, r10, r11, r12, r13, r14, r15,
335   xmm0, xmm1, xmm2, xmm3, xmm4, xmm5, xmm6, xmm7,
336   xmm8, xmm9, xmm10, xmm11, xmm12, xmm13, xmm14, xmm15 :: Reg
337
338 rax   = regSingle 0
339 rbx   = regSingle 1
340 rcx   = regSingle 2
341 rdx   = regSingle 3
342 rsi   = regSingle 4
343 rdi   = regSingle 5
344 rbp   = regSingle 6
345 rsp   = regSingle 7
346 r8    = regSingle 8
347 r9    = regSingle 9
348 r10   = regSingle 10
349 r11   = regSingle 11
350 r12   = regSingle 12
351 r13   = regSingle 13
352 r14   = regSingle 14
353 r15   = regSingle 15
354 xmm0  = regSingle 24
355 xmm1  = regSingle 25
356 xmm2  = regSingle 26
357 xmm3  = regSingle 27
358 xmm4  = regSingle 28
359 xmm5  = regSingle 29
360 xmm6  = regSingle 30
361 xmm7  = regSingle 31
362 xmm8  = regSingle 32
363 xmm9  = regSingle 33
364 xmm10 = regSingle 34
365 xmm11 = regSingle 35
366 xmm12 = regSingle 36
367 xmm13 = regSingle 37
368 xmm14 = regSingle 38
369 xmm15 = regSingle 39
370
371 allFPArgRegs :: [Reg]
372 allFPArgRegs    = map regSingle [24 .. 31]
373
374 ripRel :: Displacement -> AddrMode
375 ripRel imm      = AddrBaseIndex EABaseRip EAIndexNone imm
376
377
378  -- so we can re-use some x86 code:
379 {-
380 eax = rax
381 ebx = rbx
382 ecx = rcx
383 edx = rdx
384 esi = rsi
385 edi = rdi
386 ebp = rbp
387 esp = rsp
388 -}
389
390 xmm :: RegNo -> Reg
391 xmm n = regSingle (24+n)
392
393
394
395
396 -- horror show -----------------------------------------------------------------
397 freeReg                 :: RegNo -> FastBool
398 globalRegMaybe          :: GlobalReg -> Maybe RealReg
399 allArgRegs              :: [Reg]
400 callClobberedRegs       :: [Reg]
401
402 #if defined(i386_TARGET_ARCH) || defined(x86_64_TARGET_ARCH)
403
404 #if i386_TARGET_ARCH
405 #define eax 0
406 #define ebx 1
407 #define ecx 2
408 #define edx 3
409 #define esi 4
410 #define edi 5
411 #define ebp 6
412 #define esp 7
413 #endif
414
415 #if x86_64_TARGET_ARCH
416 #define rax   0
417 #define rbx   1
418 #define rcx   2
419 #define rdx   3
420 #define rsi   4
421 #define rdi   5
422 #define rbp   6
423 #define rsp   7
424 #define r8    8
425 #define r9    9
426 #define r10   10
427 #define r11   11
428 #define r12   12
429 #define r13   13
430 #define r14   14
431 #define r15   15
432 #endif
433
434 #define fake0 16
435 #define fake1 17
436 #define fake2 18
437 #define fake3 19
438 #define fake4 20
439 #define fake5 21
440
441 #define xmm0  24
442 #define xmm1  25
443 #define xmm2  26
444 #define xmm3  27
445 #define xmm4  28
446 #define xmm5  29
447 #define xmm6  30
448 #define xmm7  31
449 #define xmm8  32
450 #define xmm9  33
451 #define xmm10 34
452 #define xmm11 35
453 #define xmm12 36
454 #define xmm13 37
455 #define xmm14 38
456 #define xmm15 39
457
458
459 #if i386_TARGET_ARCH
460 freeReg esp = fastBool False  --        %esp is the C stack pointer
461 #endif
462
463 #if x86_64_TARGET_ARCH
464 freeReg rsp = fastBool False  --        %rsp is the C stack pointer
465 #endif
466
467 #ifdef REG_Base
468 freeReg REG_Base = fastBool False
469 #endif
470 #ifdef REG_R1
471 freeReg REG_R1   = fastBool False
472 #endif  
473 #ifdef REG_R2  
474 freeReg REG_R2   = fastBool False
475 #endif  
476 #ifdef REG_R3  
477 freeReg REG_R3   = fastBool False
478 #endif  
479 #ifdef REG_R4  
480 freeReg REG_R4   = fastBool False
481 #endif  
482 #ifdef REG_R5  
483 freeReg REG_R5   = fastBool False
484 #endif  
485 #ifdef REG_R6  
486 freeReg REG_R6   = fastBool False
487 #endif  
488 #ifdef REG_R7  
489 freeReg REG_R7   = fastBool False
490 #endif  
491 #ifdef REG_R8  
492 freeReg REG_R8   = fastBool False
493 #endif
494 #ifdef REG_F1
495 freeReg REG_F1 = fastBool False
496 #endif
497 #ifdef REG_F2
498 freeReg REG_F2 = fastBool False
499 #endif
500 #ifdef REG_F3
501 freeReg REG_F3 = fastBool False
502 #endif
503 #ifdef REG_F4
504 freeReg REG_F4 = fastBool False
505 #endif
506 #ifdef REG_D1
507 freeReg REG_D1 = fastBool False
508 #endif
509 #ifdef REG_D2
510 freeReg REG_D2 = fastBool False
511 #endif
512 #ifdef REG_Sp 
513 freeReg REG_Sp   = fastBool False
514 #endif 
515 #ifdef REG_Su
516 freeReg REG_Su   = fastBool False
517 #endif 
518 #ifdef REG_SpLim 
519 freeReg REG_SpLim = fastBool False
520 #endif 
521 #ifdef REG_Hp 
522 freeReg REG_Hp   = fastBool False
523 #endif
524 #ifdef REG_HpLim
525 freeReg REG_HpLim = fastBool False
526 #endif
527 freeReg _               = fastBool True
528
529
530 --  | Returns 'Nothing' if this global register is not stored
531 -- in a real machine register, otherwise returns @'Just' reg@, where
532 -- reg is the machine register it is stored in.
533
534 #ifdef REG_Base
535 globalRegMaybe BaseReg                  = Just (RealRegSingle REG_Base)
536 #endif
537 #ifdef REG_R1
538 globalRegMaybe (VanillaReg 1 _)         = Just (RealRegSingle REG_R1)
539 #endif 
540 #ifdef REG_R2 
541 globalRegMaybe (VanillaReg 2 _)         = Just (RealRegSingle REG_R2)
542 #endif 
543 #ifdef REG_R3 
544 globalRegMaybe (VanillaReg 3 _)         = Just (RealRegSingle REG_R3)
545 #endif 
546 #ifdef REG_R4 
547 globalRegMaybe (VanillaReg 4 _)         = Just (RealRegSingle REG_R4)
548 #endif 
549 #ifdef REG_R5 
550 globalRegMaybe (VanillaReg 5 _)         = Just (RealRegSingle REG_R5)
551 #endif 
552 #ifdef REG_R6 
553 globalRegMaybe (VanillaReg 6 _)         = Just (RealRegSingle REG_R6)
554 #endif 
555 #ifdef REG_R7 
556 globalRegMaybe (VanillaReg 7 _)         = Just (RealRegSingle REG_R7)
557 #endif 
558 #ifdef REG_R8 
559 globalRegMaybe (VanillaReg 8 _)         = Just (RealRegSingle REG_R8)
560 #endif
561 #ifdef REG_R9 
562 globalRegMaybe (VanillaReg 9 _)         = Just (RealRegSingle REG_R9)
563 #endif
564 #ifdef REG_R10 
565 globalRegMaybe (VanillaReg 10 _)        = Just (RealRegSingle REG_R10)
566 #endif
567 #ifdef REG_F1
568 globalRegMaybe (FloatReg 1)             = Just (RealRegSingle REG_F1)
569 #endif                                  
570 #ifdef REG_F2                           
571 globalRegMaybe (FloatReg 2)             = Just (RealRegSingle REG_F2)
572 #endif                                  
573 #ifdef REG_F3                           
574 globalRegMaybe (FloatReg 3)             = Just (RealRegSingle REG_F3)
575 #endif                                  
576 #ifdef REG_F4                           
577 globalRegMaybe (FloatReg 4)             = Just (RealRegSingle REG_F4)
578 #endif                                  
579 #ifdef REG_D1                           
580 globalRegMaybe (DoubleReg 1)            = Just (RealRegSingle REG_D1)
581 #endif                                  
582 #ifdef REG_D2                           
583 globalRegMaybe (DoubleReg 2)            = Just (RealRegSingle REG_D2)
584 #endif
585 #ifdef REG_Sp       
586 globalRegMaybe Sp                       = Just (RealRegSingle REG_Sp)
587 #endif
588 #ifdef REG_Lng1                         
589 globalRegMaybe (LongReg 1)              = Just (RealRegSingle REG_Lng1)
590 #endif                                  
591 #ifdef REG_Lng2                         
592 globalRegMaybe (LongReg 2)              = Just (RealRegSingle REG_Lng2)
593 #endif
594 #ifdef REG_SpLim                                
595 globalRegMaybe SpLim                    = Just (RealRegSingle REG_SpLim)
596 #endif                                  
597 #ifdef REG_Hp                           
598 globalRegMaybe Hp                       = Just (RealRegSingle REG_Hp)
599 #endif                                  
600 #ifdef REG_HpLim                        
601 globalRegMaybe HpLim                    = Just (RealRegSingle REG_HpLim)
602 #endif                                  
603 #ifdef REG_CurrentTSO                           
604 globalRegMaybe CurrentTSO               = Just (RealRegSingle REG_CurrentTSO)
605 #endif                                  
606 #ifdef REG_CurrentNursery                       
607 globalRegMaybe CurrentNursery           = Just (RealRegSingle REG_CurrentNursery)
608 #endif                                  
609 globalRegMaybe _                        = Nothing
610
611 -- 
612
613 #if   i386_TARGET_ARCH
614 allArgRegs = panic "X86.Regs.allArgRegs: should not be used!"
615
616 #elif x86_64_TARGET_ARCH
617 allArgRegs = map regSingle [rdi,rsi,rdx,rcx,r8,r9]
618
619 #else
620 allArgRegs  = panic "X86.Regs.allArgRegs: not defined for this architecture"
621 #endif
622
623
624 -- | these are the regs which we cannot assume stay alive over a C call.  
625
626 #if   i386_TARGET_ARCH
627 -- caller-saves registers
628 callClobberedRegs
629   = map regSingle ([eax,ecx,edx]  ++ floatregnos)
630
631 #elif x86_64_TARGET_ARCH
632 -- all xmm regs are caller-saves
633 -- caller-saves registers
634 callClobberedRegs    
635   = map regSingle ([rax,rcx,rdx,rsi,rdi,r8,r9,r10,r11] ++ floatregnos)
636
637 #else
638 callClobberedRegs
639   = panic "X86.Regs.callClobberedRegs: not defined for this architecture"
640 #endif
641
642 #else /* i386_TARGET_ARCH || x86_64_TARGET_ARCH */
643
644
645
646 freeReg _               = 0#
647 globalRegMaybe _        = panic "X86.Regs.globalRegMaybe: not defined"
648
649 allArgRegs              = panic "X86.Regs.globalRegMaybe: not defined"
650 callClobberedRegs       = panic "X86.Regs.globalRegMaybe: not defined"
651
652
653 #endif
654
655 -- We map STG registers onto appropriate CmmExprs.  Either they map
656 -- to real machine registers or stored as offsets from BaseReg.  Given
657 -- a GlobalReg, get_GlobalReg_reg_or_addr produces either the real
658 -- register it is in, on this platform, or a CmmExpr denoting the
659 -- address in the register table holding it.
660 -- (See also get_GlobalReg_addr in CgUtils.)
661
662 get_GlobalReg_reg_or_addr :: GlobalReg -> Either RealReg CmmExpr
663 get_GlobalReg_reg_or_addr mid
664    = case globalRegMaybe mid of
665         Just rr -> Left rr
666         Nothing -> Right (get_GlobalReg_addr mid)
667
668
669 -- allocatableRegs is allMachRegNos with the fixed-use regs removed.
670 -- i.e., these are the regs for which we are prepared to allow the
671 -- register allocator to attempt to map VRegs to.
672 allocatableRegs :: [RealReg]
673 allocatableRegs
674    = let isFree i = isFastTrue (freeReg i)
675      in  map RealRegSingle $ filter isFree allMachRegNos
676
677