{-# LANGUAGE CPP #-}
module X86.Regs (
virtualRegSqueeze,
realRegSqueeze,
Imm(..),
strImmLit,
litToImm,
AddrMode(..),
addrOffset,
spRel,
argRegs,
allArgRegs,
allIntArgRegs,
callClobberedRegs,
instrClobberedRegs,
allMachRegNos,
classOfRealReg,
showReg,
EABase(..), EAIndex(..), addrModeRegs,
eax, ebx, ecx, edx, esi, edi, ebp, esp,
fake0, fake1, fake2, fake3, fake4, fake5, firstfake,
rax, rbx, rcx, rdx, rsi, rdi, rbp, rsp,
r8, r9, r10, r11, r12, r13, r14, r15,
xmm0, xmm1, xmm2, xmm3, xmm4, xmm5, xmm6, xmm7,
xmm8, xmm9, xmm10, xmm11, xmm12, xmm13, xmm14, xmm15,
xmm,
ripRel,
allFPArgRegs,
allocatableRegs
)
where
#include "nativeGen/NCG.h"
#include "HsVersions.h"
import GhcPrelude
import CodeGen.Platform
import Reg
import RegClass
import Cmm
import CLabel ( CLabel )
import DynFlags
import Outputable
import Platform
import qualified Data.Array as A
{-# INLINE virtualRegSqueeze #-}
virtualRegSqueeze :: RegClass -> VirtualReg -> Int
virtualRegSqueeze :: RegClass -> VirtualReg -> Int
virtualRegSqueeze cls :: RegClass
cls vr :: VirtualReg
vr
= case RegClass
cls of
RcInteger
-> case VirtualReg
vr of
VirtualRegI{} -> 1
VirtualRegHi{} -> 1
_other :: VirtualReg
_other -> 0
RcDouble
-> case VirtualReg
vr of
VirtualRegD{} -> 1
VirtualRegF{} -> 0
_other :: VirtualReg
_other -> 0
RcDoubleSSE
-> case VirtualReg
vr of
VirtualRegSSE{} -> 1
_other :: VirtualReg
_other -> 0
_other :: RegClass
_other -> 0
{-# INLINE realRegSqueeze #-}
realRegSqueeze :: RegClass -> RealReg -> Int
realRegSqueeze :: RegClass -> RealReg -> Int
realRegSqueeze cls :: RegClass
cls rr :: RealReg
rr
= case RegClass
cls of
RcInteger
-> case RealReg
rr of
RealRegSingle regNo :: Int
regNo
| Int
regNo Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
firstfake -> 1
| Bool
otherwise -> 0
RealRegPair{} -> 0
RcDouble
-> case RealReg
rr of
RealRegSingle regNo :: Int
regNo
| Int
regNo Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
firstfake Bool -> Bool -> Bool
&& Int
regNo Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
lastfake -> 1
| Bool
otherwise -> 0
RealRegPair{} -> 0
RcDoubleSSE
-> case RealReg
rr of
RealRegSingle regNo :: Int
regNo | Int
regNo Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
firstxmm -> 1
_otherwise :: RealReg
_otherwise -> 0
_other :: RegClass
_other -> 0
data Imm
= ImmInt Int
| ImmInteger Integer
| ImmCLbl CLabel
| ImmLit SDoc
| ImmIndex CLabel Int
| ImmFloat Rational
| ImmDouble Rational
| ImmConstantSum Imm Imm
| ImmConstantDiff Imm Imm
strImmLit :: String -> Imm
strImmLit :: String -> Imm
strImmLit s :: String
s = SDoc -> Imm
ImmLit (String -> SDoc
text String
s)
litToImm :: CmmLit -> Imm
litToImm :: CmmLit -> Imm
litToImm (CmmInt i :: Integer
i w :: Width
w) = Integer -> Imm
ImmInteger (Width -> Integer -> Integer
narrowS Width
w Integer
i)
litToImm (CmmFloat f :: Rational
f W32) = Rational -> Imm
ImmFloat Rational
f
litToImm (CmmFloat f :: Rational
f W64) = Rational -> Imm
ImmDouble Rational
f
litToImm (CmmLabel l :: CLabel
l) = CLabel -> Imm
ImmCLbl CLabel
l
litToImm (CmmLabelOff l :: CLabel
l off :: Int
off) = CLabel -> Int -> Imm
ImmIndex CLabel
l Int
off
litToImm (CmmLabelDiffOff l1 :: CLabel
l1 l2 :: CLabel
l2 off :: Int
off _)
= Imm -> Imm -> Imm
ImmConstantSum
(Imm -> Imm -> Imm
ImmConstantDiff (CLabel -> Imm
ImmCLbl CLabel
l1) (CLabel -> Imm
ImmCLbl CLabel
l2))
(Int -> Imm
ImmInt Int
off)
litToImm _ = String -> Imm
forall a. String -> a
panic "X86.Regs.litToImm: no match"
data AddrMode
= AddrBaseIndex EABase EAIndex Displacement
| ImmAddr Imm Int
data EABase = EABaseNone | EABaseReg Reg | EABaseRip
data EAIndex = EAIndexNone | EAIndex Reg Int
type Displacement = Imm
addrOffset :: AddrMode -> Int -> Maybe AddrMode
addrOffset :: AddrMode -> Int -> Maybe AddrMode
addrOffset addr :: AddrMode
addr off :: Int
off
= case AddrMode
addr of
ImmAddr i :: Imm
i off0 :: Int
off0 -> AddrMode -> Maybe AddrMode
forall a. a -> Maybe a
Just (Imm -> Int -> AddrMode
ImmAddr Imm
i (Int
off0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
off))
AddrBaseIndex r :: EABase
r i :: EAIndex
i (ImmInt n :: Int
n) -> AddrMode -> Maybe AddrMode
forall a. a -> Maybe a
Just (EABase -> EAIndex -> Imm -> AddrMode
AddrBaseIndex EABase
r EAIndex
i (Int -> Imm
ImmInt (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
off)))
AddrBaseIndex r :: EABase
r i :: EAIndex
i (ImmInteger n :: Integer
n)
-> AddrMode -> Maybe AddrMode
forall a. a -> Maybe a
Just (EABase -> EAIndex -> Imm -> AddrMode
AddrBaseIndex EABase
r EAIndex
i (Int -> Imm
ImmInt (Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Integer
n Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Int -> Integer
forall a. Integral a => a -> Integer
toInteger Int
off))))
AddrBaseIndex r :: EABase
r i :: EAIndex
i (ImmCLbl lbl :: CLabel
lbl)
-> AddrMode -> Maybe AddrMode
forall a. a -> Maybe a
Just (EABase -> EAIndex -> Imm -> AddrMode
AddrBaseIndex EABase
r EAIndex
i (CLabel -> Int -> Imm
ImmIndex CLabel
lbl Int
off))
AddrBaseIndex r :: EABase
r i :: EAIndex
i (ImmIndex lbl :: CLabel
lbl ix :: Int
ix)
-> AddrMode -> Maybe AddrMode
forall a. a -> Maybe a
Just (EABase -> EAIndex -> Imm -> AddrMode
AddrBaseIndex EABase
r EAIndex
i (CLabel -> Int -> Imm
ImmIndex CLabel
lbl (Int
ixInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
off)))
_ -> Maybe AddrMode
forall a. Maybe a
Nothing
addrModeRegs :: AddrMode -> [Reg]
addrModeRegs :: AddrMode -> [Reg]
addrModeRegs (AddrBaseIndex b :: EABase
b i :: EAIndex
i _) = [Reg]
b_regs [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ [Reg]
i_regs
where
b_regs :: [Reg]
b_regs = case EABase
b of { EABaseReg r :: Reg
r -> [Reg
r]; _ -> [] }
i_regs :: [Reg]
i_regs = case EAIndex
i of { EAIndex r :: Reg
r _ -> [Reg
r]; _ -> [] }
addrModeRegs _ = []
spRel :: DynFlags
-> Int
-> AddrMode
spRel :: DynFlags -> Int -> AddrMode
spRel dflags :: DynFlags
dflags n :: Int
n
| Platform -> Bool
target32Bit (DynFlags -> Platform
targetPlatform DynFlags
dflags)
= EABase -> EAIndex -> Imm -> AddrMode
AddrBaseIndex (Reg -> EABase
EABaseReg Reg
esp) EAIndex
EAIndexNone (Int -> Imm
ImmInt Int
n)
| Bool
otherwise
= EABase -> EAIndex -> Imm -> AddrMode
AddrBaseIndex (Reg -> EABase
EABaseReg Reg
rsp) EAIndex
EAIndexNone (Int -> Imm
ImmInt Int
n)
firstfake, lastfake :: RegNo
firstfake :: Int
firstfake = 16
lastfake :: Int
lastfake = 21
firstxmm :: RegNo
firstxmm :: Int
firstxmm = 24
lastxmm :: Platform -> RegNo
lastxmm :: Platform -> Int
lastxmm platform :: Platform
platform
| Platform -> Bool
target32Bit Platform
platform = 31
| Bool
otherwise = 39
lastint :: Platform -> RegNo
lastint :: Platform -> Int
lastint platform :: Platform
platform
| Platform -> Bool
target32Bit Platform
platform = 7
| Bool
otherwise = 15
intregnos :: Platform -> [RegNo]
intregnos :: Platform -> [Int]
intregnos platform :: Platform
platform = [0 .. Platform -> Int
lastint Platform
platform]
fakeregnos :: [RegNo]
fakeregnos :: [Int]
fakeregnos = [Int
firstfake .. Int
lastfake]
xmmregnos :: Platform -> [RegNo]
xmmregnos :: Platform -> [Int]
xmmregnos platform :: Platform
platform = [Int
firstxmm .. Platform -> Int
lastxmm Platform
platform]
floatregnos :: Platform -> [RegNo]
floatregnos :: Platform -> [Int]
floatregnos platform :: Platform
platform = [Int]
fakeregnos [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ Platform -> [Int]
xmmregnos Platform
platform
argRegs :: RegNo -> [Reg]
argRegs :: Int -> [Reg]
argRegs _ = String -> [Reg]
forall a. String -> a
panic "MachRegs.argRegs(x86): should not be used!"
allMachRegNos :: Platform -> [RegNo]
allMachRegNos :: Platform -> [Int]
allMachRegNos platform :: Platform
platform = Platform -> [Int]
intregnos Platform
platform [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ Platform -> [Int]
floatregnos Platform
platform
{-# INLINE classOfRealReg #-}
classOfRealReg :: Platform -> RealReg -> RegClass
classOfRealReg :: Platform -> RealReg -> RegClass
classOfRealReg platform :: Platform
platform reg :: RealReg
reg
= case RealReg
reg of
RealRegSingle i :: Int
i
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Platform -> Int
lastint Platform
platform -> RegClass
RcInteger
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
lastfake -> RegClass
RcDouble
| Bool
otherwise -> RegClass
RcDoubleSSE
RealRegPair{} -> String -> RegClass
forall a. String -> a
panic "X86.Regs.classOfRealReg: RegPairs on this arch"
showReg :: Platform -> RegNo -> String
showReg :: Platform -> Int -> String
showReg platform :: Platform
platform n :: Int
n
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
firstxmm = "%xmm" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
firstxmm)
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
firstfake = "%fake" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
firstfake)
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 8 = "%r" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n
| Bool
otherwise = Platform -> Array Int String
regNames Platform
platform Array Int String -> Int -> String
forall i e. Ix i => Array i e -> i -> e
A.! Int
n
regNames :: Platform -> A.Array Int String
regNames :: Platform -> Array Int String
regNames platform :: Platform
platform
= if Platform -> Bool
target32Bit Platform
platform
then (Int, Int) -> [String] -> Array Int String
forall i e. Ix i => (i, i) -> [e] -> Array i e
A.listArray (0,8) ["%eax", "%ebx", "%ecx", "%edx", "%esi", "%edi", "%ebp", "%esp"]
else (Int, Int) -> [String] -> Array Int String
forall i e. Ix i => (i, i) -> [e] -> Array i e
A.listArray (0,8) ["%rax", "%rbx", "%rcx", "%rdx", "%rsi", "%rdi", "%rbp", "%rsp"]
fake0, fake1, fake2, fake3, fake4, fake5,
eax, ebx, ecx, edx, esp, ebp, esi, edi :: Reg
eax :: Reg
eax = Int -> Reg
regSingle 0
ebx :: Reg
ebx = Int -> Reg
regSingle 1
ecx :: Reg
ecx = Int -> Reg
regSingle 2
edx :: Reg
edx = Int -> Reg
regSingle 3
esi :: Reg
esi = Int -> Reg
regSingle 4
edi :: Reg
edi = Int -> Reg
regSingle 5
ebp :: Reg
ebp = Int -> Reg
regSingle 6
esp :: Reg
esp = Int -> Reg
regSingle 7
fake0 :: Reg
fake0 = Int -> Reg
regSingle 16
fake1 :: Reg
fake1 = Int -> Reg
regSingle 17
fake2 :: Reg
fake2 = Int -> Reg
regSingle 18
fake3 :: Reg
fake3 = Int -> Reg
regSingle 19
fake4 :: Reg
fake4 = Int -> Reg
regSingle 20
fake5 :: Reg
fake5 = Int -> Reg
regSingle 21
rax, rbx, rcx, rdx, rsp, rbp, rsi, rdi,
r8, r9, r10, r11, r12, r13, r14, r15,
xmm0, xmm1, xmm2, xmm3, xmm4, xmm5, xmm6, xmm7,
xmm8, xmm9, xmm10, xmm11, xmm12, xmm13, xmm14, xmm15 :: Reg
rax :: Reg
rax = Int -> Reg
regSingle 0
rbx :: Reg
rbx = Int -> Reg
regSingle 1
rcx :: Reg
rcx = Int -> Reg
regSingle 2
rdx :: Reg
rdx = Int -> Reg
regSingle 3
rsi :: Reg
rsi = Int -> Reg
regSingle 4
rdi :: Reg
rdi = Int -> Reg
regSingle 5
rbp :: Reg
rbp = Int -> Reg
regSingle 6
rsp :: Reg
rsp = Int -> Reg
regSingle 7
r8 :: Reg
r8 = Int -> Reg
regSingle 8
r9 :: Reg
r9 = Int -> Reg
regSingle 9
r10 :: Reg
r10 = Int -> Reg
regSingle 10
r11 :: Reg
r11 = Int -> Reg
regSingle 11
r12 :: Reg
r12 = Int -> Reg
regSingle 12
r13 :: Reg
r13 = Int -> Reg
regSingle 13
r14 :: Reg
r14 = Int -> Reg
regSingle 14
r15 :: Reg
r15 = Int -> Reg
regSingle 15
xmm0 :: Reg
xmm0 = Int -> Reg
regSingle 24
xmm1 :: Reg
xmm1 = Int -> Reg
regSingle 25
xmm2 :: Reg
xmm2 = Int -> Reg
regSingle 26
xmm3 :: Reg
xmm3 = Int -> Reg
regSingle 27
xmm4 :: Reg
xmm4 = Int -> Reg
regSingle 28
xmm5 :: Reg
xmm5 = Int -> Reg
regSingle 29
xmm6 :: Reg
xmm6 = Int -> Reg
regSingle 30
xmm7 :: Reg
xmm7 = Int -> Reg
regSingle 31
xmm8 :: Reg
xmm8 = Int -> Reg
regSingle 32
xmm9 :: Reg
xmm9 = Int -> Reg
regSingle 33
xmm10 :: Reg
xmm10 = Int -> Reg
regSingle 34
xmm11 :: Reg
xmm11 = Int -> Reg
regSingle 35
xmm12 :: Reg
xmm12 = Int -> Reg
regSingle 36
xmm13 :: Reg
xmm13 = Int -> Reg
regSingle 37
xmm14 :: Reg
xmm14 = Int -> Reg
regSingle 38
xmm15 :: Reg
xmm15 = Int -> Reg
regSingle 39
ripRel :: Displacement -> AddrMode
ripRel :: Imm -> AddrMode
ripRel imm :: Imm
imm = EABase -> EAIndex -> Imm -> AddrMode
AddrBaseIndex EABase
EABaseRip EAIndex
EAIndexNone Imm
imm
xmm :: RegNo -> Reg
xmm :: Int -> Reg
xmm n :: Int
n = Int -> Reg
regSingle (Int
firstxmmInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
n)
callClobberedRegs :: Platform -> [Reg]
callClobberedRegs :: Platform -> [Reg]
callClobberedRegs platform :: Platform
platform
| Platform -> Bool
target32Bit Platform
platform = [Reg
eax,Reg
ecx,Reg
edx] [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ (Int -> Reg) -> [Int] -> [Reg]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Reg
regSingle (Platform -> [Int]
floatregnos Platform
platform)
| Platform -> OS
platformOS Platform
platform OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
== OS
OSMinGW32
= [Reg
rax,Reg
rcx,Reg
rdx,Reg
r8,Reg
r9,Reg
r10,Reg
r11]
[Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ (Int -> Reg) -> [Int] -> [Reg]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Reg
regSingle [Int]
fakeregnos [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ (Int -> Reg) -> [Int] -> [Reg]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Reg
xmm [0 .. 5]
| Bool
otherwise
= [Reg
rax,Reg
rcx,Reg
rdx,Reg
rsi,Reg
rdi,Reg
r8,Reg
r9,Reg
r10,Reg
r11]
[Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ (Int -> Reg) -> [Int] -> [Reg]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Reg
regSingle (Platform -> [Int]
floatregnos Platform
platform)
allArgRegs :: Platform -> [(Reg, Reg)]
allArgRegs :: Platform -> [(Reg, Reg)]
allArgRegs platform :: Platform
platform
| Platform -> OS
platformOS Platform
platform OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
== OS
OSMinGW32 = [Reg] -> [Reg] -> [(Reg, Reg)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Reg
rcx,Reg
rdx,Reg
r8,Reg
r9]
((Int -> Reg) -> [Int] -> [Reg]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Reg
regSingle [Int
firstxmm ..])
| Bool
otherwise = String -> [(Reg, Reg)]
forall a. String -> a
panic "X86.Regs.allArgRegs: not defined for this arch"
allIntArgRegs :: Platform -> [Reg]
allIntArgRegs :: Platform -> [Reg]
allIntArgRegs platform :: Platform
platform
| (Platform -> OS
platformOS Platform
platform OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
== OS
OSMinGW32) Bool -> Bool -> Bool
|| Platform -> Bool
target32Bit Platform
platform
= String -> [Reg]
forall a. String -> a
panic "X86.Regs.allIntArgRegs: not defined for this platform"
| Bool
otherwise = [Reg
rdi,Reg
rsi,Reg
rdx,Reg
rcx,Reg
r8,Reg
r9]
allFPArgRegs :: Platform -> [Reg]
allFPArgRegs :: Platform -> [Reg]
allFPArgRegs platform :: Platform
platform
| Platform -> OS
platformOS Platform
platform OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
== OS
OSMinGW32
= String -> [Reg]
forall a. String -> a
panic "X86.Regs.allFPArgRegs: not defined for this platform"
| Bool
otherwise = (Int -> Reg) -> [Int] -> [Reg]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Reg
regSingle [Int
firstxmm .. Int
firstxmmInt -> Int -> Int
forall a. Num a => a -> a -> a
+7]
instrClobberedRegs :: Platform -> [Reg]
instrClobberedRegs :: Platform -> [Reg]
instrClobberedRegs platform :: Platform
platform
| Platform -> Bool
target32Bit Platform
platform = [ Reg
eax, Reg
ecx, Reg
edx ]
| Bool
otherwise = [ Reg
rax, Reg
rcx, Reg
rdx ]
allocatableRegs :: Platform -> [RealReg]
allocatableRegs :: Platform -> [RealReg]
allocatableRegs platform :: Platform
platform
= let isFree :: Int -> Bool
isFree i :: Int
i = Platform -> Int -> Bool
freeReg Platform
platform Int
i
in (Int -> RealReg) -> [Int] -> [RealReg]
forall a b. (a -> b) -> [a] -> [b]
map Int -> RealReg
RealRegSingle ([Int] -> [RealReg]) -> [Int] -> [RealReg]
forall a b. (a -> b) -> a -> b
$ (Int -> Bool) -> [Int] -> [Int]
forall a. (a -> Bool) -> [a] -> [a]
filter Int -> Bool
isFree (Platform -> [Int]
allMachRegNos Platform
platform)