module GHC.CmmToAsm.LA64.Regs where

import GHC.Prelude
import GHC.Cmm
import GHC.Cmm.CLabel           ( CLabel )
import GHC.CmmToAsm.Format
import GHC.Data.FastString
import GHC.Platform
import GHC.Platform.Reg
import GHC.Platform.Reg.Class
import GHC.Platform.Reg.Class.Separate
import GHC.Platform.Regs
import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Types.Unique

-- All machine register numbers.
allMachRegNos :: [RegNo]
allMachRegNos :: [RegNo]
allMachRegNos = [RegNo
0..RegNo
31] [RegNo] -> [RegNo] -> [RegNo]
forall a. [a] -> [a] -> [a]
++ [RegNo
32..RegNo
63]

zeroReg, raReg, tpMachReg, fpMachReg, spMachReg, tmpReg :: Reg
zeroReg :: Reg
zeroReg = RegNo -> Reg
regSingle RegNo
0
raReg :: Reg
raReg = RegNo -> Reg
regSingle RegNo
1
tpMachReg :: Reg
tpMachReg = RegNo -> Reg
regSingle RegNo
2
-- Not to be confused with the `CmmReg` `spReg`
spMachReg :: Reg
spMachReg = RegNo -> Reg
regSingle RegNo
3
fpMachReg :: Reg
fpMachReg = RegNo -> Reg
regSingle RegNo
22
-- Use t8(r20) for LA64 IP register.
tmpReg :: Reg
tmpReg = RegNo -> Reg
regSingle RegNo
20

-- Registers available to the register allocator.
allocatableRegs :: Platform -> [RealReg]
allocatableRegs :: Platform -> [RealReg]
allocatableRegs Platform
platform =
  let isFree :: RegNo -> Bool
isFree = Platform -> RegNo -> Bool
freeReg Platform
platform
   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

-- Integer argument registers according to the calling convention
allGpArgRegs :: [Reg]
allGpArgRegs :: [Reg]
allGpArgRegs = (RegNo -> Reg) -> [RegNo] -> [Reg]
forall a b. (a -> b) -> [a] -> [b]
map RegNo -> Reg
regSingle [RegNo
4..RegNo
11]

-- | Floating point argument registers according to the calling convention
allFpArgRegs :: [Reg]
allFpArgRegs :: [Reg]
allFpArgRegs = (RegNo -> Reg) -> [RegNo] -> [Reg]
forall a b. (a -> b) -> [a] -> [b]
map RegNo -> Reg
regSingle [RegNo
32..RegNo
39]

-- Addressing modes
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)

-- Immediates
data Imm
  = ImmInt      Int
  | ImmInteger  Integer     -- Sigh.
  | ImmCLbl     CLabel      -- AbstractC Label (with baggage)
  | 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)

-- Map CmmLit to Imm
litToImm :: CmmLit -> Imm
litToImm :: CmmLit -> Imm
litToImm (CmmInt Integer
i Width
w) = Integer -> Imm
ImmInteger (Width -> Integer -> Integer
narrowS Width
w Integer
i)
-- narrow to the width: a CmmInt might be out of
-- range, but we assume that ImmInteger only contains
-- in-range values.  A signed value should be fine here.
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
l = String -> Imm
forall a. HasCallStack => String -> a
panic (String -> Imm) -> String -> Imm
forall a b. (a -> b) -> a -> b
$ String
"LA64.Regs.litToImm: no match for " String -> ShowS
forall a. [a] -> [a] -> [a]
++ CmmLit -> String
forall a. Show a => a -> String
show CmmLit
l

-- == To satisfy GHC.CmmToAsm.Reg.Target =======================================

-- squeese functions for the graph allocator -----------------------------------
-- | regSqueeze_class reg
--      Calculate the maximum number of register colors that could be
--      denied to a node of this class due to having this reg
--      as a neighbour.
--
{-# 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
RcFloat ->
      case VirtualReg
vr of
        VirtualRegD {} -> RegNo
1
        VirtualReg
_other -> RegNo
0
    RegClass
RcVector ->
      case VirtualReg
vr of
        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
RcFloat ->
      case RealReg
rr of
        RealRegSingle RegNo
regNo
          |  RegNo
regNo RegNo -> RegNo -> Bool
forall a. Ord a => a -> a -> Bool
< RegNo
32
          Bool -> Bool -> Bool
|| RegNo
regNo RegNo -> RegNo -> Bool
forall a. Ord a => a -> a -> Bool
> RegNo
63
          -> RegNo
0
          | Bool
otherwise
          -> RegNo
1
    RegClass
RcVector ->
      case RealReg
rr of
        RealRegSingle RegNo
regNo
          | RegNo
regNo RegNo -> RegNo -> Bool
forall a. Ord a => a -> a -> Bool
> RegNo
63
          -> RegNo
1
          | Bool
otherwise
          -> RegNo
0

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
"LA64.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
   | RegNo
i RegNo -> RegNo -> Bool
forall a. Ord a => a -> a -> Bool
> RegNo
63 = RegClass
RcVector
   | Bool
otherwise = RegClass
RcFloat

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
RcFloat         -> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"red"
        RegClass
RcVector        -> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"green"