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