2 -- squeese functions for the graph allocator
25 EABase(..), EAIndex(..), addrModeRegs,
27 eax, ebx, ecx, edx, esi, edi, ebp, esp,
28 fake0, fake1, fake2, fake3, fake4, fake5,
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,
43 get_GlobalReg_reg_or_addr,
49 #include "nativeGen/NCG.h"
50 #include "HsVersions.h"
53 # define STOLEN_X86_REGS 4
54 -- HACK: go for the max
57 #include "../includes/stg/MachRegs.h"
62 import CgUtils ( get_GlobalReg_addr )
65 import CLabel ( CLabel )
67 import Outputable ( panic )
72 #if defined(i386_TARGET_ARCH) || defined(x86_64_TARGET_ARCH)
77 -- | regSqueeze_class reg
78 -- Calculuate the maximum number of register colors that could be
79 -- denied to a node of this class due to having this reg
82 {-# INLINE virtualRegSqueeze #-}
83 virtualRegSqueeze :: RegClass -> VirtualReg -> FastInt
85 virtualRegSqueeze cls vr
89 VirtualRegI{} -> _ILIT(1)
90 VirtualRegHi{} -> _ILIT(1)
91 VirtualRegD{} -> _ILIT(0)
92 VirtualRegF{} -> _ILIT(0)
94 -- We don't use floats on this arch, but we can't
95 -- return error because the return type is unboxed...
98 VirtualRegI{} -> _ILIT(0)
99 VirtualRegHi{} -> _ILIT(0)
100 VirtualRegD{} -> _ILIT(0)
101 VirtualRegF{} -> _ILIT(0)
105 VirtualRegI{} -> _ILIT(0)
106 VirtualRegHi{} -> _ILIT(0)
107 VirtualRegD{} -> _ILIT(1)
108 VirtualRegF{} -> _ILIT(0)
110 {-# INLINE realRegSqueeze #-}
111 realRegSqueeze :: RegClass -> RealReg -> FastInt
113 #if defined(i386_TARGET_ARCH)
114 realRegSqueeze cls rr
119 | regNo < 8 -> _ILIT(1) -- first fp reg is 8
120 | otherwise -> _ILIT(0)
122 RealRegPair{} -> _ILIT(0)
124 -- We don't use floats on this arch, but we can't
125 -- return error because the return type is unboxed...
129 | regNo < 8 -> _ILIT(0)
130 | otherwise -> _ILIT(0)
132 RealRegPair{} -> _ILIT(0)
137 | regNo < 8 -> _ILIT(0)
138 | otherwise -> _ILIT(1)
140 RealRegPair{} -> _ILIT(0)
142 #elif defined(x86_64_TARGET_ARCH)
143 realRegSqueeze cls rr
148 | regNo < 16 -> _ILIT(1) -- first xmm reg is 16
149 | otherwise -> _ILIT(0)
151 RealRegPair{} -> _ILIT(0)
153 -- We don't use floats on this arch, but we can't
154 -- return error because the return type is unboxed...
158 | regNo < 16 -> _ILIT(0)
159 | otherwise -> _ILIT(0)
161 RealRegPair{} -> _ILIT(0)
166 | regNo < 16 -> _ILIT(0)
167 | otherwise -> _ILIT(1)
169 RealRegPair{} -> _ILIT(0)
172 realRegSqueeze _ _ = _ILIT(0)
177 -- -----------------------------------------------------------------------------
182 | ImmInteger Integer -- Sigh.
183 | ImmCLbl CLabel -- AbstractC Label (with baggage)
184 | ImmLit Doc -- Simple string
185 | ImmIndex CLabel Int
188 | ImmConstantSum Imm Imm
189 | ImmConstantDiff Imm Imm
192 strImmLit :: String -> Imm
193 strImmLit s = ImmLit (text s)
196 litToImm :: CmmLit -> Imm
197 litToImm (CmmInt i w) = ImmInteger (narrowS w i)
198 -- narrow to the width: a CmmInt might be out of
199 -- range, but we assume that ImmInteger only contains
200 -- in-range values. A signed value should be fine here.
201 litToImm (CmmFloat f W32) = ImmFloat f
202 litToImm (CmmFloat f W64) = ImmDouble f
203 litToImm (CmmLabel l) = ImmCLbl l
204 litToImm (CmmLabelOff l off) = ImmIndex l off
205 litToImm (CmmLabelDiffOff l1 l2 off)
207 (ImmConstantDiff (ImmCLbl l1) (ImmCLbl l2))
209 litToImm (CmmBlock id) = ImmCLbl (infoTblLbl id)
210 litToImm _ = panic "X86.Regs.litToImm: no match"
212 -- addressing modes ------------------------------------------------------------
215 = AddrBaseIndex EABase EAIndex Displacement
218 data EABase = EABaseNone | EABaseReg Reg | EABaseRip
219 data EAIndex = EAIndexNone | EAIndex Reg Int
220 type Displacement = Imm
223 addrOffset :: AddrMode -> Int -> Maybe AddrMode
226 ImmAddr i off0 -> Just (ImmAddr i (off0 + off))
228 AddrBaseIndex r i (ImmInt n) -> Just (AddrBaseIndex r i (ImmInt (n + off)))
229 AddrBaseIndex r i (ImmInteger n)
230 -> Just (AddrBaseIndex r i (ImmInt (fromInteger (n + toInteger off))))
232 AddrBaseIndex r i (ImmCLbl lbl)
233 -> Just (AddrBaseIndex r i (ImmIndex lbl off))
235 AddrBaseIndex r i (ImmIndex lbl ix)
236 -> Just (AddrBaseIndex r i (ImmIndex lbl (ix+off)))
238 _ -> Nothing -- in theory, shouldn't happen
241 addrModeRegs :: AddrMode -> [Reg]
242 addrModeRegs (AddrBaseIndex b i _) = b_regs ++ i_regs
244 b_regs = case b of { EABaseReg r -> [r]; _ -> [] }
245 i_regs = case i of { EAIndex r _ -> [r]; _ -> [] }
249 -- registers -------------------------------------------------------------------
251 -- @spRel@ gives us a stack relative addressing mode for volatile
252 -- temporaries and for excess call arguments. @fpRel@, where
253 -- applicable, is the same but for the frame pointer.
256 spRel :: Int -- ^ desired stack offset in words, positive or negative
260 spRel n = AddrBaseIndex (EABaseReg esp) EAIndexNone (ImmInt (n * wORD_SIZE))
262 #elif x86_64_TARGET_ARCH
263 spRel n = AddrBaseIndex (EABaseReg rsp) EAIndexNone (ImmInt (n * wORD_SIZE))
266 spRel _ = panic "X86.Regs.spRel: not defined for this architecture"
271 -- argRegs is the set of regs which are read for an n-argument call to C.
272 -- For archs which pass all args on the stack (x86), is empty.
273 -- Sparc passes up to the first 6 args in regs.
274 -- Dunno about Alpha.
275 argRegs :: RegNo -> [Reg]
276 argRegs _ = panic "MachRegs.argRegs(x86): should not be used!"
282 -- | The complete set of machine registers.
283 allMachRegNos :: [RegNo]
286 allMachRegNos = [0..13]
288 #elif x86_64_TARGET_ARCH
289 allMachRegNos = [0..31]
292 allMachRegNos = panic "X86.Regs.callClobberedRegs: not defined for this architecture"
297 -- | Take the class of a register.
298 {-# INLINE classOfRealReg #-}
299 classOfRealReg :: RealReg -> RegClass
302 -- On x86, we might want to have an 8-bit RegClass, which would
303 -- contain just regs 1-4 (the others don't have 8-bit versions).
304 -- However, we can get away without this at the moment because the
305 -- only allocatable integer regs are also 8-bit compatible (1, 3, 4).
308 RealRegSingle i -> if i < 8 then RcInteger else RcDouble
309 RealRegPair{} -> panic "X86.Regs.classOfRealReg: RegPairs on this arch"
311 #elif x86_64_TARGET_ARCH
312 -- On x86, we might want to have an 8-bit RegClass, which would
313 -- contain just regs 1-4 (the others don't have 8-bit versions).
314 -- However, we can get away without this at the moment because the
315 -- only allocatable integer regs are also 8-bit compatible (1, 3, 4).
318 RealRegSingle i -> if i < 16 then RcInteger else RcDouble
319 RealRegPair{} -> panic "X86.Regs.classOfRealReg: RegPairs on this arch"
322 classOfRealReg _ = panic "X86.Regs.regClass: not defined for this architecture"
327 -- | Get the name of the register with this number.
328 showReg :: RegNo -> String
332 = if n >= 0 && n < 14
334 else "%unknown_x86_real_reg_" ++ show n
338 = ["%eax", "%ebx", "%ecx", "%edx", "%esi", "%edi", "%ebp", "%esp",
339 "%fake0", "%fake1", "%fake2", "%fake3", "%fake4", "%fake5", "%fake6"]
341 #elif x86_64_TARGET_ARCH
343 | n >= 16 = "%xmm" ++ show (n-16)
344 | n >= 8 = "%r" ++ show n
345 | otherwise = regNames !! n
349 = ["%rax", "%rbx", "%rcx", "%rdx", "%rsi", "%rdi", "%rbp", "%rsp" ]
352 showReg _ = panic "X86.Regs.showReg: not defined for this architecture"
359 -- machine specific ------------------------------------------------------------
363 Intel x86 architecture:
364 - All registers except 7 (esp) are available for use.
365 - Only ebx, esi, edi and esp are available across a C call (they are callee-saves).
366 - Registers 0-7 have 16-bit counterparts (ax, bx etc.)
367 - Registers 0-3 have 8 bit counterparts (ah, bh etc.)
368 - Registers 8-13 are fakes; we pretend x86 has 6 conventionally-addressable
369 fp registers, and 3-operand insns for them, and we translate this into
370 real stack-based x86 fp code after register allocation.
372 The fp registers are all Double registers; we don't have any RcFloat class
373 regs. @regClass@ barfs if you give it a VirtualRegF, and mkVReg above should
377 fake0, fake1, fake2, fake3, fake4, fake5,
378 eax, ebx, ecx, edx, esp, ebp, esi, edi :: Reg
398 AMD x86_64 architecture:
399 - Registers 0-16 have 32-bit counterparts (eax, ebx etc.)
400 - Registers 0-7 have 16-bit counterparts (ax, bx etc.)
401 - Registers 0-3 have 8 bit counterparts (ah, bh etc.)
405 rax, rbx, rcx, rdx, rsp, rbp, rsi, rdi,
406 r8, r9, r10, r11, r12, r13, r14, r15,
407 xmm0, xmm1, xmm2, xmm3, xmm4, xmm5, xmm6, xmm7,
408 xmm8, xmm9, xmm10, xmm11, xmm12, xmm13, xmm14, xmm15 :: Reg
443 allFPArgRegs :: [Reg]
444 allFPArgRegs = map regSingle [16 .. 23]
446 ripRel :: Displacement -> AddrMode
447 ripRel imm = AddrBaseIndex EABaseRip EAIndexNone imm
450 -- so we can re-use some x86 code:
463 xmm n = regSingle (16+n)
468 -- horror show -----------------------------------------------------------------
469 freeReg :: RegNo -> FastBool
470 globalRegMaybe :: GlobalReg -> Maybe RealReg
472 callClobberedRegs :: [Reg]
474 #if defined(i386_TARGET_ARCH) || defined(x86_64_TARGET_ARCH)
493 #if x86_64_TARGET_ARCH
531 freeReg esp = fastBool False -- %esp is the C stack pointer
534 #if x86_64_TARGET_ARCH
535 freeReg rsp = fastBool False -- %rsp is the C stack pointer
539 freeReg REG_Base = fastBool False
542 freeReg REG_R1 = fastBool False
545 freeReg REG_R2 = fastBool False
548 freeReg REG_R3 = fastBool False
551 freeReg REG_R4 = fastBool False
554 freeReg REG_R5 = fastBool False
557 freeReg REG_R6 = fastBool False
560 freeReg REG_R7 = fastBool False
563 freeReg REG_R8 = fastBool False
566 freeReg REG_F1 = fastBool False
569 freeReg REG_F2 = fastBool False
572 freeReg REG_F3 = fastBool False
575 freeReg REG_F4 = fastBool False
578 freeReg REG_D1 = fastBool False
581 freeReg REG_D2 = fastBool False
584 freeReg REG_Sp = fastBool False
587 freeReg REG_Su = fastBool False
590 freeReg REG_SpLim = fastBool False
593 freeReg REG_Hp = fastBool False
596 freeReg REG_HpLim = fastBool False
598 freeReg _ = fastBool True
601 -- | Returns 'Nothing' if this global register is not stored
602 -- in a real machine register, otherwise returns @'Just' reg@, where
603 -- reg is the machine register it is stored in.
606 globalRegMaybe BaseReg = Just (RealRegSingle REG_Base)
609 globalRegMaybe (VanillaReg 1 _) = Just (RealRegSingle REG_R1)
612 globalRegMaybe (VanillaReg 2 _) = Just (RealRegSingle REG_R2)
615 globalRegMaybe (VanillaReg 3 _) = Just (RealRegSingle REG_R3)
618 globalRegMaybe (VanillaReg 4 _) = Just (RealRegSingle REG_R4)
621 globalRegMaybe (VanillaReg 5 _) = Just (RealRegSingle REG_R5)
624 globalRegMaybe (VanillaReg 6 _) = Just (RealRegSingle REG_R6)
627 globalRegMaybe (VanillaReg 7 _) = Just (RealRegSingle REG_R7)
630 globalRegMaybe (VanillaReg 8 _) = Just (RealRegSingle REG_R8)
633 globalRegMaybe (VanillaReg 9 _) = Just (RealRegSingle REG_R9)
636 globalRegMaybe (VanillaReg 10 _) = Just (RealRegSingle REG_R10)
639 globalRegMaybe (FloatReg 1) = Just (RealRegSingle REG_F1)
642 globalRegMaybe (FloatReg 2) = Just (RealRegSingle REG_F2)
645 globalRegMaybe (FloatReg 3) = Just (RealRegSingle REG_F3)
648 globalRegMaybe (FloatReg 4) = Just (RealRegSingle REG_F4)
651 globalRegMaybe (DoubleReg 1) = Just (RealRegSingle REG_D1)
654 globalRegMaybe (DoubleReg 2) = Just (RealRegSingle REG_D2)
657 globalRegMaybe Sp = Just (RealRegSingle REG_Sp)
660 globalRegMaybe (LongReg 1) = Just (RealRegSingle REG_Lng1)
663 globalRegMaybe (LongReg 2) = Just (RealRegSingle REG_Lng2)
666 globalRegMaybe SpLim = Just (RealRegSingle REG_SpLim)
669 globalRegMaybe Hp = Just (RealRegSingle REG_Hp)
672 globalRegMaybe HpLim = Just (RealRegSingle REG_HpLim)
674 #ifdef REG_CurrentTSO
675 globalRegMaybe CurrentTSO = Just (RealRegSingle REG_CurrentTSO)
677 #ifdef REG_CurrentNursery
678 globalRegMaybe CurrentNursery = Just (RealRegSingle REG_CurrentNursery)
680 globalRegMaybe _ = Nothing
685 allArgRegs = panic "X86.Regs.allArgRegs: should not be used!"
687 #elif x86_64_TARGET_ARCH
688 allArgRegs = map regSingle [rdi,rsi,rdx,rcx,r8,r9]
691 allArgRegs = panic "X86.Regs.allArgRegs: not defined for this architecture"
695 -- | these are the regs which we cannot assume stay alive over a C call.
698 -- caller-saves registers
700 = map regSingle [eax,ecx,edx,fake0,fake1,fake2,fake3,fake4,fake5]
702 #elif x86_64_TARGET_ARCH
703 -- all xmm regs are caller-saves
704 -- caller-saves registers
706 = map regSingle ([rax,rcx,rdx,rsi,rdi,r8,r9,r10,r11] ++ [16..31])
710 = panic "X86.Regs.callClobberedRegs: not defined for this architecture"
713 #else /* i386_TARGET_ARCH || x86_64_TARGET_ARCH */
718 globalRegMaybe _ = panic "X86.Regs.globalRegMaybe: not defined"
720 allArgRegs = panic "X86.Regs.globalRegMaybe: not defined"
721 callClobberedRegs = panic "X86.Regs.globalRegMaybe: not defined"
726 -- We map STG registers onto appropriate CmmExprs. Either they map
727 -- to real machine registers or stored as offsets from BaseReg. Given
728 -- a GlobalReg, get_GlobalReg_reg_or_addr produces either the real
729 -- register it is in, on this platform, or a CmmExpr denoting the
730 -- address in the register table holding it.
731 -- (See also get_GlobalReg_addr in CgUtils.)
733 get_GlobalReg_reg_or_addr :: GlobalReg -> Either RealReg CmmExpr
734 get_GlobalReg_reg_or_addr mid
735 = case globalRegMaybe mid of
737 Nothing -> Right (get_GlobalReg_addr mid)
740 -- allocatableRegs is allMachRegNos with the fixed-use regs removed.
741 -- i.e., these are the regs for which we are prepared to allow the
742 -- register allocator to attempt to map VRegs to.
743 allocatableRegs :: [RealReg]
745 = let isFree i = isFastTrue (freeReg i)
746 in map RealRegSingle $ filter isFree allMachRegNos