merge GHC HEAD
[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 OldCmm
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 argRegs :: RegNo -> [Reg]
253 argRegs _       = panic "MachRegs.argRegs(x86): should not be used!"
254
255 -- | The complete set of machine registers.
256 allMachRegNos :: [RegNo]
257 allMachRegNos  = intregnos ++ floatregnos
258
259 -- | Take the class of a register.
260 {-# INLINE classOfRealReg      #-}
261 classOfRealReg :: RealReg -> RegClass
262 -- On x86, we might want to have an 8-bit RegClass, which would
263 -- contain just regs 1-4 (the others don't have 8-bit versions).
264 -- However, we can get away without this at the moment because the
265 -- only allocatable integer regs are also 8-bit compatible (1, 3, 4).
266 classOfRealReg reg
267  = case reg of
268         RealRegSingle i
269           | i <= lastint  -> RcInteger
270           | i <= lastfake -> RcDouble
271           | otherwise     -> RcDoubleSSE
272
273         RealRegPair{}   -> panic "X86.Regs.classOfRealReg: RegPairs on this arch"
274
275 -- | Get the name of the register with this number.
276 showReg :: RegNo -> String
277 showReg n
278         | n >= firstxmm  = "%xmm" ++ show (n-firstxmm)
279         | n >= firstfake = "%fake" ++ show (n-firstfake)
280         | n >= 8         = "%r" ++ show n
281         | otherwise      = regNames !! n
282
283 regNames :: [String]
284 regNames 
285 #if   i386_TARGET_ARCH
286    = ["%eax", "%ebx", "%ecx", "%edx", "%esi", "%edi", "%ebp", "%esp"]
287 #elif x86_64_TARGET_ARCH
288    = ["%rax", "%rbx", "%rcx", "%rdx", "%rsi", "%rdi", "%rbp", "%rsp" ]
289 #else
290    = []
291 #endif
292
293
294
295 -- machine specific ------------------------------------------------------------
296
297
298 {-
299 Intel x86 architecture:
300 - All registers except 7 (esp) are available for use.
301 - Only ebx, esi, edi and esp are available across a C call (they are callee-saves).
302 - Registers 0-7 have 16-bit counterparts (ax, bx etc.)
303 - Registers 0-3 have 8 bit counterparts (ah, bh etc.)
304 - Registers fake0..fake5 are fakes; we pretend x86 has 6 conventionally-addressable
305   fp registers, and 3-operand insns for them, and we translate this into
306   real stack-based x86 fp code after register allocation.
307
308 The fp registers are all Double registers; we don't have any RcFloat class
309 regs.  @regClass@ barfs if you give it a VirtualRegF, and mkVReg above should
310 never generate them.
311 -}
312
313 fake0, fake1, fake2, fake3, fake4, fake5, 
314        eax, ebx, ecx, edx, esp, ebp, esi, edi :: Reg
315
316 eax   = regSingle 0
317 ebx   = regSingle 1
318 ecx   = regSingle 2
319 edx   = regSingle 3
320 esi   = regSingle 4
321 edi   = regSingle 5
322 ebp   = regSingle 6
323 esp   = regSingle 7
324 fake0 = regSingle 16
325 fake1 = regSingle 17
326 fake2 = regSingle 18
327 fake3 = regSingle 19
328 fake4 = regSingle 20
329 fake5 = regSingle 21
330
331
332
333 {-
334 AMD x86_64 architecture:
335 - All 16 integer registers are addressable as 8, 16, 32 and 64-bit values:
336
337   8     16    32    64
338   ---------------------
339   al    ax    eax   rax
340   bl    bx    ebx   rbx
341   cl    cx    ecx   rcx
342   dl    dx    edx   rdx
343   sil   si    esi   rsi
344   dil   si    edi   rdi
345   bpl   bp    ebp   rbp
346   spl   sp    esp   rsp
347   r10b  r10w  r10d  r10
348   r11b  r11w  r11d  r11
349   r12b  r12w  r12d  r12
350   r13b  r13w  r13d  r13
351   r14b  r14w  r14d  r14
352   r15b  r15w  r15d  r15
353 -}
354
355 rax, rbx, rcx, rdx, rsp, rbp, rsi, rdi, 
356   r8, r9, r10, r11, r12, r13, r14, r15,
357   xmm0, xmm1, xmm2, xmm3, xmm4, xmm5, xmm6, xmm7,
358   xmm8, xmm9, xmm10, xmm11, xmm12, xmm13, xmm14, xmm15 :: Reg
359
360 rax   = regSingle 0
361 rbx   = regSingle 1
362 rcx   = regSingle 2
363 rdx   = regSingle 3
364 rsi   = regSingle 4
365 rdi   = regSingle 5
366 rbp   = regSingle 6
367 rsp   = regSingle 7
368 r8    = regSingle 8
369 r9    = regSingle 9
370 r10   = regSingle 10
371 r11   = regSingle 11
372 r12   = regSingle 12
373 r13   = regSingle 13
374 r14   = regSingle 14
375 r15   = regSingle 15
376 xmm0  = regSingle 24
377 xmm1  = regSingle 25
378 xmm2  = regSingle 26
379 xmm3  = regSingle 27
380 xmm4  = regSingle 28
381 xmm5  = regSingle 29
382 xmm6  = regSingle 30
383 xmm7  = regSingle 31
384 xmm8  = regSingle 32
385 xmm9  = regSingle 33
386 xmm10 = regSingle 34
387 xmm11 = regSingle 35
388 xmm12 = regSingle 36
389 xmm13 = regSingle 37
390 xmm14 = regSingle 38
391 xmm15 = regSingle 39
392
393 allFPArgRegs :: [Reg]
394 allFPArgRegs    = map regSingle [firstxmm .. firstxmm+7]
395
396 ripRel :: Displacement -> AddrMode
397 ripRel imm      = AddrBaseIndex EABaseRip EAIndexNone imm
398
399
400  -- so we can re-use some x86 code:
401 {-
402 eax = rax
403 ebx = rbx
404 ecx = rcx
405 edx = rdx
406 esi = rsi
407 edi = rdi
408 ebp = rbp
409 esp = rsp
410 -}
411
412 xmm :: RegNo -> Reg
413 xmm n = regSingle (firstxmm+n)
414
415
416
417
418 -- horror show -----------------------------------------------------------------
419 freeReg                 :: RegNo -> FastBool
420 globalRegMaybe          :: GlobalReg -> Maybe RealReg
421 allArgRegs              :: [Reg]
422 callClobberedRegs       :: [Reg]
423
424 #if defined(i386_TARGET_ARCH) || defined(x86_64_TARGET_ARCH)
425
426 #if i386_TARGET_ARCH
427 #define eax 0
428 #define ebx 1
429 #define ecx 2
430 #define edx 3
431 #define esi 4
432 #define edi 5
433 #define ebp 6
434 #define esp 7
435 #endif
436
437 #if x86_64_TARGET_ARCH
438 #define rax   0
439 #define rbx   1
440 #define rcx   2
441 #define rdx   3
442 #define rsi   4
443 #define rdi   5
444 #define rbp   6
445 #define rsp   7
446 #define r8    8
447 #define r9    9
448 #define r10   10
449 #define r11   11
450 #define r12   12
451 #define r13   13
452 #define r14   14
453 #define r15   15
454 #endif
455
456 #define fake0 16
457 #define fake1 17
458 #define fake2 18
459 #define fake3 19
460 #define fake4 20
461 #define fake5 21
462
463 #define xmm0  24
464 #define xmm1  25
465 #define xmm2  26
466 #define xmm3  27
467 #define xmm4  28
468 #define xmm5  29
469 #define xmm6  30
470 #define xmm7  31
471 #define xmm8  32
472 #define xmm9  33
473 #define xmm10 34
474 #define xmm11 35
475 #define xmm12 36
476 #define xmm13 37
477 #define xmm14 38
478 #define xmm15 39
479
480 #if i386_TARGET_ARCH
481 freeReg esp = fastBool False  --        %esp is the C stack pointer
482 #endif
483
484 #if x86_64_TARGET_ARCH
485 freeReg rsp = fastBool False  --        %rsp is the C stack pointer
486 #endif
487
488 #ifdef REG_Base
489 freeReg REG_Base = fastBool False
490 #endif
491 #ifdef REG_R1
492 freeReg REG_R1   = fastBool False
493 #endif  
494 #ifdef REG_R2  
495 freeReg REG_R2   = fastBool False
496 #endif  
497 #ifdef REG_R3  
498 freeReg REG_R3   = fastBool False
499 #endif  
500 #ifdef REG_R4  
501 freeReg REG_R4   = fastBool False
502 #endif  
503 #ifdef REG_R5  
504 freeReg REG_R5   = fastBool False
505 #endif  
506 #ifdef REG_R6  
507 freeReg REG_R6   = fastBool False
508 #endif  
509 #ifdef REG_R7  
510 freeReg REG_R7   = fastBool False
511 #endif  
512 #ifdef REG_R8  
513 freeReg REG_R8   = fastBool False
514 #endif
515 #ifdef REG_F1
516 freeReg REG_F1 = fastBool False
517 #endif
518 #ifdef REG_F2
519 freeReg REG_F2 = fastBool False
520 #endif
521 #ifdef REG_F3
522 freeReg REG_F3 = fastBool False
523 #endif
524 #ifdef REG_F4
525 freeReg REG_F4 = fastBool False
526 #endif
527 #ifdef REG_D1
528 freeReg REG_D1 = fastBool False
529 #endif
530 #ifdef REG_D2
531 freeReg REG_D2 = fastBool False
532 #endif
533 #ifdef REG_Sp 
534 freeReg REG_Sp   = fastBool False
535 #endif 
536 #ifdef REG_Su
537 freeReg REG_Su   = fastBool False
538 #endif 
539 #ifdef REG_SpLim 
540 freeReg REG_SpLim = fastBool False
541 #endif 
542 #ifdef REG_Hp 
543 freeReg REG_Hp   = fastBool False
544 #endif
545 #ifdef REG_HpLim
546 freeReg REG_HpLim = fastBool False
547 #endif
548 freeReg _               = fastBool True
549
550
551 --  | Returns 'Nothing' if this global register is not stored
552 -- in a real machine register, otherwise returns @'Just' reg@, where
553 -- reg is the machine register it is stored in.
554
555 #ifdef REG_Base
556 globalRegMaybe BaseReg                  = Just (RealRegSingle REG_Base)
557 #endif
558 #ifdef REG_R1
559 globalRegMaybe (VanillaReg 1 _)         = Just (RealRegSingle REG_R1)
560 #endif 
561 #ifdef REG_R2 
562 globalRegMaybe (VanillaReg 2 _)         = Just (RealRegSingle REG_R2)
563 #endif 
564 #ifdef REG_R3 
565 globalRegMaybe (VanillaReg 3 _)         = Just (RealRegSingle REG_R3)
566 #endif 
567 #ifdef REG_R4 
568 globalRegMaybe (VanillaReg 4 _)         = Just (RealRegSingle REG_R4)
569 #endif 
570 #ifdef REG_R5 
571 globalRegMaybe (VanillaReg 5 _)         = Just (RealRegSingle REG_R5)
572 #endif 
573 #ifdef REG_R6 
574 globalRegMaybe (VanillaReg 6 _)         = Just (RealRegSingle REG_R6)
575 #endif 
576 #ifdef REG_R7 
577 globalRegMaybe (VanillaReg 7 _)         = Just (RealRegSingle REG_R7)
578 #endif 
579 #ifdef REG_R8 
580 globalRegMaybe (VanillaReg 8 _)         = Just (RealRegSingle REG_R8)
581 #endif
582 #ifdef REG_R9 
583 globalRegMaybe (VanillaReg 9 _)         = Just (RealRegSingle REG_R9)
584 #endif
585 #ifdef REG_R10 
586 globalRegMaybe (VanillaReg 10 _)        = Just (RealRegSingle REG_R10)
587 #endif
588 #ifdef REG_F1
589 globalRegMaybe (FloatReg 1)             = Just (RealRegSingle REG_F1)
590 #endif                                  
591 #ifdef REG_F2                           
592 globalRegMaybe (FloatReg 2)             = Just (RealRegSingle REG_F2)
593 #endif                                  
594 #ifdef REG_F3                           
595 globalRegMaybe (FloatReg 3)             = Just (RealRegSingle REG_F3)
596 #endif                                  
597 #ifdef REG_F4                           
598 globalRegMaybe (FloatReg 4)             = Just (RealRegSingle REG_F4)
599 #endif                                  
600 #ifdef REG_D1                           
601 globalRegMaybe (DoubleReg 1)            = Just (RealRegSingle REG_D1)
602 #endif                                  
603 #ifdef REG_D2                           
604 globalRegMaybe (DoubleReg 2)            = Just (RealRegSingle REG_D2)
605 #endif
606 #ifdef REG_Sp       
607 globalRegMaybe Sp                       = Just (RealRegSingle REG_Sp)
608 #endif
609 #ifdef REG_Lng1                         
610 globalRegMaybe (LongReg 1)              = Just (RealRegSingle REG_Lng1)
611 #endif                                  
612 #ifdef REG_Lng2                         
613 globalRegMaybe (LongReg 2)              = Just (RealRegSingle REG_Lng2)
614 #endif
615 #ifdef REG_SpLim                                
616 globalRegMaybe SpLim                    = Just (RealRegSingle REG_SpLim)
617 #endif                                  
618 #ifdef REG_Hp                           
619 globalRegMaybe Hp                       = Just (RealRegSingle REG_Hp)
620 #endif                                  
621 #ifdef REG_HpLim                        
622 globalRegMaybe HpLim                    = Just (RealRegSingle REG_HpLim)
623 #endif                                  
624 #ifdef REG_CurrentTSO                           
625 globalRegMaybe CurrentTSO               = Just (RealRegSingle REG_CurrentTSO)
626 #endif                                  
627 #ifdef REG_CurrentNursery                       
628 globalRegMaybe CurrentNursery           = Just (RealRegSingle REG_CurrentNursery)
629 #endif                                  
630 globalRegMaybe _                        = Nothing
631
632 -- 
633
634 #if   i386_TARGET_ARCH
635 allArgRegs = panic "X86.Regs.allArgRegs: should not be used!"
636
637 #elif x86_64_TARGET_ARCH
638 allArgRegs = map regSingle [rdi,rsi,rdx,rcx,r8,r9]
639
640 #else
641 allArgRegs  = panic "X86.Regs.allArgRegs: not defined for this architecture"
642 #endif
643
644
645 -- | these are the regs which we cannot assume stay alive over a C call.  
646
647 #if   i386_TARGET_ARCH
648 -- caller-saves registers
649 callClobberedRegs
650   = map regSingle ([eax,ecx,edx]  ++ floatregnos)
651
652 #elif x86_64_TARGET_ARCH
653 -- all xmm regs are caller-saves
654 -- caller-saves registers
655 callClobberedRegs    
656   = map regSingle ([rax,rcx,rdx,rsi,rdi,r8,r9,r10,r11] ++ floatregnos)
657
658 #else
659 callClobberedRegs
660   = panic "X86.Regs.callClobberedRegs: not defined for this architecture"
661 #endif
662
663 #else /* i386_TARGET_ARCH || x86_64_TARGET_ARCH */
664
665
666
667 freeReg _               = 0#
668 globalRegMaybe _        = panic "X86.Regs.globalRegMaybe: not defined"
669
670 allArgRegs              = panic "X86.Regs.globalRegMaybe: not defined"
671 callClobberedRegs       = panic "X86.Regs.globalRegMaybe: not defined"
672
673
674 #endif
675
676 -- allocatableRegs is allMachRegNos with the fixed-use regs removed.
677 -- i.e., these are the regs for which we are prepared to allow the
678 -- register allocator to attempt to map VRegs to.
679 allocatableRegs :: [RealReg]
680 allocatableRegs
681    = let isFree i = isFastTrue (freeReg i)
682      in  map RealRegSingle $ filter isFree allMachRegNos
683
684