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