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