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