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