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