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