Add new LLVM code generator to GHC. (Version 2)
[ghc-hetmet.git] / compiler / nativeGen / X86 / Regs.hs
index bed9dc5..b9a23a6 100644 (file)
@@ -25,7 +25,7 @@ module X86.Regs (
        EABase(..), EAIndex(..), addrModeRegs,
 
        eax, ebx, ecx, edx, esi, edi, ebp, esp,
-       fake0, fake1, fake2, fake3, fake4, fake5,
+       fake0, fake1, fake2, fake3, fake4, fake5, firstfake,
 
        rax, rbx, rcx, rdx, rsi, rdi, rbp, rsp,
        r8,  r9,  r10, r11, r12, r13, r14, r15,
@@ -40,7 +40,6 @@ module X86.Regs (
        freeReg,
        globalRegMaybe,
        
-       get_GlobalReg_reg_or_addr,
        allocatableRegs
 )
 
@@ -54,7 +53,6 @@ where
 import Reg
 import RegClass
 
-import CgUtils          ( get_GlobalReg_addr )
 import BlockId
 import Cmm
 import CLabel           ( CLabel )
@@ -105,7 +103,7 @@ realRegSqueeze cls rr
        RcInteger
         -> case rr of
                RealRegSingle regNo
-                       | regNo < 16    -> _ILIT(1)     -- first xmm reg is 16
+                       | regNo < firstfake -> _ILIT(1)
                        | otherwise     -> _ILIT(0)
                        
                RealRegPair{}           -> _ILIT(0)
@@ -113,14 +111,14 @@ realRegSqueeze cls rr
        RcDouble
         -> case rr of
                RealRegSingle regNo
-                       | regNo >= 16 && regNo < 24 -> _ILIT(1)
+                       | regNo >= firstfake && regNo < lastfake -> _ILIT(1)
                        | otherwise     -> _ILIT(0)
                        
                RealRegPair{}           -> _ILIT(0)
 
         RcDoubleSSE
         -> case rr of
-               RealRegSingle regNo | regNo >= 24 -> _ILIT(1)
+               RealRegSingle regNo | regNo >= firstxmm -> _ILIT(1)
                 _otherwise                        -> _ILIT(0)
 
         _other -> _ILIT(0)
@@ -218,6 +216,35 @@ spRel _    = panic "X86.Regs.spRel: not defined for this architecture"
 
 #endif
 
+-- The register numbers must fit into 32 bits on x86, so that we can
+-- use a Word32 to represent the set of free registers in the register
+-- allocator.
+
+firstfake, lastfake :: RegNo
+firstfake = 16
+lastfake  = 21
+
+firstxmm, lastxmm :: RegNo
+firstxmm  = 24
+#if i386_TARGET_ARCH
+lastxmm   = 31
+#else
+lastxmm   = 39
+#endif
+
+lastint :: RegNo
+#if i386_TARGET_ARCH
+lastint = 7 -- not %r8..%r15
+#else
+lastint = 15
+#endif
+
+intregnos, fakeregnos, xmmregnos, floatregnos :: [RegNo]
+intregnos   = [0..lastint]
+fakeregnos  = [firstfake .. lastfake]
+xmmregnos   = [firstxmm  .. lastxmm]
+floatregnos = fakeregnos ++ xmmregnos;
+
 
 -- argRegs is the set of regs which are read for an n-argument call to C.
 -- For archs which pass all args on the stack (x86), is empty.
@@ -228,12 +255,7 @@ argRegs _  = panic "MachRegs.argRegs(x86): should not be used!"
 
 -- | The complete set of machine registers.
 allMachRegNos :: [RegNo]
-#if i386_TARGET_ARCH
-allMachRegNos  = [0..7]  ++ floatregs -- not %r8..%r15
-#else
-allMachRegNos  = [0..15] ++ floatregs
-#endif
-  where floatregs = fakes ++ xmms; fakes = [16..21]; xmms = [24..39]
+allMachRegNos  = intregnos ++ floatregnos
 
 -- | Take the class of a register.
 {-# INLINE classOfRealReg      #-}
@@ -245,19 +267,19 @@ classOfRealReg :: RealReg -> RegClass
 classOfRealReg reg
  = case reg of
        RealRegSingle i
-          | i < 16    -> RcInteger
-          | i < 24    -> RcDouble
-          | otherwise -> RcDoubleSSE
+          | i <= lastint  -> RcInteger
+          | i <= lastfake -> RcDouble
+          | otherwise     -> RcDoubleSSE
 
        RealRegPair{}   -> panic "X86.Regs.classOfRealReg: RegPairs on this arch"
 
 -- | Get the name of the register with this number.
 showReg :: RegNo -> String
 showReg n
-       | n >= 24       = "%xmm" ++ show (n-24)
-        | n >= 16       = "%fake" ++ show (n-16)
-       | n >= 8        = "%r" ++ show n
-       | otherwise     = regNames !! n
+       | n >= firstxmm  = "%xmm" ++ show (n-firstxmm)
+        | n >= firstfake = "%fake" ++ show (n-firstfake)
+       | n >= 8         = "%r" ++ show n
+       | otherwise      = regNames !! n
 
 regNames :: [String]
 regNames 
@@ -265,9 +287,12 @@ regNames
    = ["%eax", "%ebx", "%ecx", "%edx", "%esi", "%edi", "%ebp", "%esp"]
 #elif x86_64_TARGET_ARCH
    = ["%rax", "%rbx", "%rcx", "%rdx", "%rsi", "%rdi", "%rbp", "%rsp" ]
+#else
+   = []
 #endif
 
 
+
 -- machine specific ------------------------------------------------------------
 
 
@@ -277,7 +302,7 @@ Intel x86 architecture:
 - Only ebx, esi, edi and esp are available across a C call (they are callee-saves).
 - Registers 0-7 have 16-bit counterparts (ax, bx etc.)
 - Registers 0-3 have 8 bit counterparts (ah, bh etc.)
-- Registers 8-13 are fakes; we pretend x86 has 6 conventionally-addressable
+- Registers fake0..fake5 are fakes; we pretend x86 has 6 conventionally-addressable
   fp registers, and 3-operand insns for them, and we translate this into
   real stack-based x86 fp code after register allocation.
 
@@ -353,7 +378,7 @@ xmm14 = regSingle 38
 xmm15 = regSingle 39
 
 allFPArgRegs :: [Reg]
-allFPArgRegs   = map regSingle [24 .. 31]
+allFPArgRegs   = map regSingle [firstxmm .. firstxmm+7]
 
 ripRel :: Displacement -> AddrMode
 ripRel imm     = AddrBaseIndex EABaseRip EAIndexNone imm
@@ -372,7 +397,7 @@ esp = rsp
 -}
 
 xmm :: RegNo -> Reg
-xmm n = regSingle (24+n)
+xmm n = regSingle (firstxmm+n)
 
 
 
@@ -439,7 +464,6 @@ callClobberedRegs   :: [Reg]
 #define xmm14 38
 #define xmm15 39
 
-
 #if i386_TARGET_ARCH
 freeReg esp = fastBool False  --       %esp is the C stack pointer
 #endif
@@ -610,13 +634,13 @@ allArgRegs  = panic "X86.Regs.allArgRegs: not defined for this architecture"
 #if   i386_TARGET_ARCH
 -- caller-saves registers
 callClobberedRegs
-  = map regSingle ([eax,ecx,edx]  ++ [16..39])
+  = map regSingle ([eax,ecx,edx]  ++ floatregnos)
 
 #elif x86_64_TARGET_ARCH
 -- all xmm regs are caller-saves
 -- caller-saves registers
 callClobberedRegs    
-  = map regSingle ([rax,rcx,rdx,rsi,rdi,r8,r9,r10,r11] ++ [16..39])
+  = map regSingle ([rax,rcx,rdx,rsi,rdi,r8,r9,r10,r11] ++ floatregnos)
 
 #else
 callClobberedRegs
@@ -636,20 +660,6 @@ callClobberedRegs  = panic "X86.Regs.globalRegMaybe: not defined"
 
 #endif
 
--- We map STG registers onto appropriate CmmExprs.  Either they map
--- to real machine registers or stored as offsets from BaseReg.  Given
--- a GlobalReg, get_GlobalReg_reg_or_addr produces either the real
--- register it is in, on this platform, or a CmmExpr denoting the
--- address in the register table holding it.
--- (See also get_GlobalReg_addr in CgUtils.)
-
-get_GlobalReg_reg_or_addr :: GlobalReg -> Either RealReg CmmExpr
-get_GlobalReg_reg_or_addr mid
-   = case globalRegMaybe mid of
-        Just rr -> Left rr
-        Nothing -> Right (get_GlobalReg_addr mid)
-
-
 -- allocatableRegs is allMachRegNos with the fixed-use regs removed.
 -- i.e., these are the regs for which we are prepared to allow the
 -- register allocator to attempt to map VRegs to.