{-# OPTIONS_GHC -fno-warn-orphans #-}
module GHC.CmmToAsm.AArch64.Regs where
import GHC.Prelude
import GHC.Data.FastString
import GHC.Platform.Reg
import GHC.Platform.Reg.Class.Unified
import GHC.CmmToAsm.Format
import GHC.Cmm
import GHC.Cmm.CLabel ( CLabel )
import GHC.Types.Unique
import GHC.Platform.Regs
import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Platform
allMachRegNos :: [RegNo]
allMachRegNos :: [RegNo]
allMachRegNos = [RegNo
0..RegNo
31] [RegNo] -> [RegNo] -> [RegNo]
forall a. [a] -> [a] -> [a]
++ [RegNo
32..RegNo
63]
allocatableRegs :: Platform -> [RealReg]
allocatableRegs :: Platform -> [RealReg]
allocatableRegs Platform
platform
= let isFree :: RegNo -> Bool
isFree RegNo
i = Platform -> RegNo -> Bool
freeReg Platform
platform RegNo
i
in (RegNo -> RealReg) -> [RegNo] -> [RealReg]
forall a b. (a -> b) -> [a] -> [b]
map RegNo -> RealReg
RealRegSingle ([RegNo] -> [RealReg]) -> [RegNo] -> [RealReg]
forall a b. (a -> b) -> a -> b
$ (RegNo -> Bool) -> [RegNo] -> [RegNo]
forall a. (a -> Bool) -> [a] -> [a]
filter RegNo -> Bool
isFree [RegNo]
allMachRegNos
allGpArgRegs :: [Reg]
allGpArgRegs :: [Reg]
allGpArgRegs = (RegNo -> Reg) -> [RegNo] -> [Reg]
forall a b. (a -> b) -> [a] -> [b]
map RegNo -> Reg
regSingle [RegNo
0..RegNo
7]
allFpArgRegs :: [Reg]
allFpArgRegs :: [Reg]
allFpArgRegs = (RegNo -> Reg) -> [RegNo] -> [Reg]
forall a b. (a -> b) -> [a] -> [b]
map RegNo -> Reg
regSingle [RegNo
32..RegNo
39]
data AddrMode
= AddrRegReg Reg Reg
| AddrRegImm Reg Imm
| AddrReg Reg
deriving (AddrMode -> AddrMode -> Bool
(AddrMode -> AddrMode -> Bool)
-> (AddrMode -> AddrMode -> Bool) -> Eq AddrMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AddrMode -> AddrMode -> Bool
== :: AddrMode -> AddrMode -> Bool
$c/= :: AddrMode -> AddrMode -> Bool
/= :: AddrMode -> AddrMode -> Bool
Eq, RegNo -> AddrMode -> ShowS
[AddrMode] -> ShowS
AddrMode -> String
(RegNo -> AddrMode -> ShowS)
-> (AddrMode -> String) -> ([AddrMode] -> ShowS) -> Show AddrMode
forall a.
(RegNo -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: RegNo -> AddrMode -> ShowS
showsPrec :: RegNo -> AddrMode -> ShowS
$cshow :: AddrMode -> String
show :: AddrMode -> String
$cshowList :: [AddrMode] -> ShowS
showList :: [AddrMode] -> ShowS
Show)
data Imm
= ImmInt Int
| ImmInteger Integer
| ImmCLbl CLabel
| ImmLit FastString
| ImmIndex CLabel Int
| ImmFloat Rational
| ImmDouble Rational
| ImmConstantSum Imm Imm
| ImmConstantDiff Imm Imm
deriving (Imm -> Imm -> Bool
(Imm -> Imm -> Bool) -> (Imm -> Imm -> Bool) -> Eq Imm
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Imm -> Imm -> Bool
== :: Imm -> Imm -> Bool
$c/= :: Imm -> Imm -> Bool
/= :: Imm -> Imm -> Bool
Eq, RegNo -> Imm -> ShowS
[Imm] -> ShowS
Imm -> String
(RegNo -> Imm -> ShowS)
-> (Imm -> String) -> ([Imm] -> ShowS) -> Show Imm
forall a.
(RegNo -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: RegNo -> Imm -> ShowS
showsPrec :: RegNo -> Imm -> ShowS
$cshow :: Imm -> String
show :: Imm -> String
$cshowList :: [Imm] -> ShowS
showList :: [Imm] -> ShowS
Show)
strImmLit :: FastString -> Imm
strImmLit :: FastString -> Imm
strImmLit FastString
s = FastString -> Imm
ImmLit FastString
s
litToImm :: CmmLit -> Imm
litToImm :: CmmLit -> Imm
litToImm (CmmInt Integer
i Width
w) = Integer -> Imm
ImmInteger (Width -> Integer -> Integer
narrowS Width
w Integer
i)
litToImm (CmmFloat Rational
f Width
W32) = Rational -> Imm
ImmFloat Rational
f
litToImm (CmmFloat Rational
f Width
W64) = Rational -> Imm
ImmDouble Rational
f
litToImm (CmmLabel CLabel
l) = CLabel -> Imm
ImmCLbl CLabel
l
litToImm (CmmLabelOff CLabel
l RegNo
off) = CLabel -> RegNo -> Imm
ImmIndex CLabel
l RegNo
off
litToImm (CmmLabelDiffOff CLabel
l1 CLabel
l2 RegNo
off Width
_)
= Imm -> Imm -> Imm
ImmConstantSum
(Imm -> Imm -> Imm
ImmConstantDiff (CLabel -> Imm
ImmCLbl CLabel
l1) (CLabel -> Imm
ImmCLbl CLabel
l2))
(RegNo -> Imm
ImmInt RegNo
off)
litToImm CmmLit
_ = String -> Imm
forall a. HasCallStack => String -> a
panic String
"AArch64.Regs.litToImm: no match"
{-# INLINE virtualRegSqueeze #-}
virtualRegSqueeze :: RegClass -> VirtualReg -> Int
virtualRegSqueeze :: RegClass -> VirtualReg -> RegNo
virtualRegSqueeze RegClass
cls VirtualReg
vr
= case RegClass
cls of
RegClass
RcInteger
-> case VirtualReg
vr of
VirtualRegI{} -> RegNo
1
VirtualRegHi{} -> RegNo
1
VirtualReg
_other -> RegNo
0
RegClass
RcFloatOrVector
-> case VirtualReg
vr of
VirtualRegD{} -> RegNo
1
VirtualRegV128{} -> RegNo
1
VirtualReg
_other -> RegNo
0
{-# INLINE realRegSqueeze #-}
realRegSqueeze :: RegClass -> RealReg -> Int
realRegSqueeze :: RegClass -> RealReg -> RegNo
realRegSqueeze RegClass
cls RealReg
rr
= case RegClass
cls of
RegClass
RcInteger
-> case RealReg
rr of
RealRegSingle RegNo
regNo
| RegNo
regNo RegNo -> RegNo -> Bool
forall a. Ord a => a -> a -> Bool
< RegNo
32 -> RegNo
1
| Bool
otherwise -> RegNo
0
RegClass
RcFloatOrVector
-> case RealReg
rr of
RealRegSingle RegNo
regNo
| RegNo
regNo RegNo -> RegNo -> Bool
forall a. Ord a => a -> a -> Bool
< RegNo
32 -> RegNo
0
| Bool
otherwise -> RegNo
1
mkVirtualReg :: Unique -> Format -> VirtualReg
mkVirtualReg :: Unique -> Format -> VirtualReg
mkVirtualReg Unique
u Format
format
| Bool -> Bool
not (Format -> Bool
isFloatFormat Format
format) = Unique -> VirtualReg
VirtualRegI Unique
u
| Bool
otherwise
= case Format
format of
Format
FF32 -> Unique -> VirtualReg
VirtualRegD Unique
u
Format
FF64 -> Unique -> VirtualReg
VirtualRegD Unique
u
Format
_ -> String -> VirtualReg
forall a. HasCallStack => String -> a
panic String
"AArch64.mkVirtualReg"
{-# INLINE classOfRealReg #-}
classOfRealReg :: RealReg -> RegClass
classOfRealReg :: RealReg -> RegClass
classOfRealReg (RealRegSingle RegNo
i)
| RegNo
i RegNo -> RegNo -> Bool
forall a. Ord a => a -> a -> Bool
< RegNo
32 = RegClass
RcInteger
| Bool
otherwise = RegClass
RcFloatOrVector
regDotColor :: RealReg -> SDoc
regDotColor :: RealReg -> SDoc
regDotColor RealReg
reg
= case RealReg -> RegClass
classOfRealReg RealReg
reg of
RegClass
RcInteger -> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"blue"
RegClass
RcFloatOrVector -> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"red"