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