module GHC.Platform.Regs
       (callerSaves, activeStgRegs, haveRegBase, globalRegMaybe, freeReg)
       where
import GHC.Prelude
import GHC.Cmm.Expr
import GHC.Platform
import GHC.Platform.Reg
import qualified GHC.Platform.ARM        as ARM
import qualified GHC.Platform.AArch64    as AArch64
import qualified GHC.Platform.PPC        as PPC
import qualified GHC.Platform.S390X      as S390X
import qualified GHC.Platform.X86        as X86
import qualified GHC.Platform.X86_64     as X86_64
import qualified GHC.Platform.RISCV64    as RISCV64
import qualified GHC.Platform.NoRegs     as NoRegs
callerSaves :: Platform -> GlobalReg -> Bool
callerSaves :: Platform -> GlobalReg -> Bool
callerSaves Platform
platform
 | Platform -> Bool
platformUnregisterised Platform
platform = GlobalReg -> Bool
NoRegs.callerSaves
 | Bool
otherwise
 = case Platform -> Arch
platformArch Platform
platform of
   Arch
ArchX86     -> GlobalReg -> Bool
X86.callerSaves
   Arch
ArchX86_64  -> GlobalReg -> Bool
X86_64.callerSaves
   Arch
ArchS390X   -> GlobalReg -> Bool
S390X.callerSaves
   ArchARM {}  -> GlobalReg -> Bool
ARM.callerSaves
   Arch
ArchAArch64 -> GlobalReg -> Bool
AArch64.callerSaves
   Arch
ArchRISCV64 -> GlobalReg -> Bool
RISCV64.callerSaves
   Arch
arch
    | Arch
arch Arch -> [Arch] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Arch
ArchPPC, PPC_64ABI -> Arch
ArchPPC_64 PPC_64ABI
ELF_V1, PPC_64ABI -> Arch
ArchPPC_64 PPC_64ABI
ELF_V2] ->
        GlobalReg -> Bool
PPC.callerSaves
    | Bool
otherwise -> GlobalReg -> Bool
NoRegs.callerSaves
activeStgRegs :: Platform -> [GlobalReg]
activeStgRegs :: Platform -> [GlobalReg]
activeStgRegs Platform
platform
 | Platform -> Bool
platformUnregisterised Platform
platform = [GlobalReg]
NoRegs.activeStgRegs
 | Bool
otherwise
 = case Platform -> Arch
platformArch Platform
platform of
   Arch
ArchX86     -> [GlobalReg]
X86.activeStgRegs
   Arch
ArchX86_64  -> [GlobalReg]
X86_64.activeStgRegs
   Arch
ArchS390X   -> [GlobalReg]
S390X.activeStgRegs
   ArchARM {}  -> [GlobalReg]
ARM.activeStgRegs
   Arch
ArchAArch64 -> [GlobalReg]
AArch64.activeStgRegs
   Arch
ArchRISCV64 -> [GlobalReg]
RISCV64.activeStgRegs
   Arch
arch
    | Arch
arch Arch -> [Arch] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Arch
ArchPPC, PPC_64ABI -> Arch
ArchPPC_64 PPC_64ABI
ELF_V1, PPC_64ABI -> Arch
ArchPPC_64 PPC_64ABI
ELF_V2] ->
        [GlobalReg]
PPC.activeStgRegs
    | Bool
otherwise -> [GlobalReg]
NoRegs.activeStgRegs
haveRegBase :: Platform -> Bool
haveRegBase :: Platform -> Bool
haveRegBase Platform
platform
 | Platform -> Bool
platformUnregisterised Platform
platform = Bool
NoRegs.haveRegBase
 | Bool
otherwise
 = case Platform -> Arch
platformArch Platform
platform of
   Arch
ArchX86     -> Bool
X86.haveRegBase
   Arch
ArchX86_64  -> Bool
X86_64.haveRegBase
   Arch
ArchS390X   -> Bool
S390X.haveRegBase
   ArchARM {}  -> Bool
ARM.haveRegBase
   Arch
ArchAArch64 -> Bool
AArch64.haveRegBase
   Arch
ArchRISCV64 -> Bool
RISCV64.haveRegBase
   Arch
arch
    | Arch
arch Arch -> [Arch] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Arch
ArchPPC, PPC_64ABI -> Arch
ArchPPC_64 PPC_64ABI
ELF_V1, PPC_64ABI -> Arch
ArchPPC_64 PPC_64ABI
ELF_V2] ->
        Bool
PPC.haveRegBase
    | Bool
otherwise -> Bool
NoRegs.haveRegBase
globalRegMaybe :: Platform -> GlobalReg -> Maybe RealReg
globalRegMaybe :: Platform -> GlobalReg -> Maybe RealReg
globalRegMaybe Platform
platform
 | Platform -> Bool
platformUnregisterised Platform
platform = GlobalReg -> Maybe RealReg
NoRegs.globalRegMaybe
 | Bool
otherwise
 = case Platform -> Arch
platformArch Platform
platform of
   Arch
ArchX86     -> GlobalReg -> Maybe RealReg
X86.globalRegMaybe
   Arch
ArchX86_64  -> GlobalReg -> Maybe RealReg
X86_64.globalRegMaybe
   Arch
ArchS390X   -> GlobalReg -> Maybe RealReg
S390X.globalRegMaybe
   ArchARM {}  -> GlobalReg -> Maybe RealReg
ARM.globalRegMaybe
   Arch
ArchAArch64 -> GlobalReg -> Maybe RealReg
AArch64.globalRegMaybe
   Arch
ArchRISCV64 -> GlobalReg -> Maybe RealReg
RISCV64.globalRegMaybe
   Arch
arch
    | Arch
arch Arch -> [Arch] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Arch
ArchPPC, PPC_64ABI -> Arch
ArchPPC_64 PPC_64ABI
ELF_V1, PPC_64ABI -> Arch
ArchPPC_64 PPC_64ABI
ELF_V2] ->
        GlobalReg -> Maybe RealReg
PPC.globalRegMaybe
    | Bool
otherwise -> GlobalReg -> Maybe RealReg
NoRegs.globalRegMaybe
freeReg :: Platform -> RegNo -> Bool
freeReg :: Platform -> RegNo -> Bool
freeReg Platform
platform
 | Platform -> Bool
platformUnregisterised Platform
platform = RegNo -> Bool
NoRegs.freeReg
 | Bool
otherwise
 = case Platform -> Arch
platformArch Platform
platform of
   Arch
ArchX86     -> RegNo -> Bool
X86.freeReg
   Arch
ArchX86_64  -> RegNo -> Bool
X86_64.freeReg
   Arch
ArchS390X   -> RegNo -> Bool
S390X.freeReg
   ArchARM {}  -> RegNo -> Bool
ARM.freeReg
   Arch
ArchAArch64 -> RegNo -> Bool
AArch64.freeReg
   Arch
ArchRISCV64 -> RegNo -> Bool
RISCV64.freeReg
   Arch
arch
    | Arch
arch Arch -> [Arch] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Arch
ArchPPC, PPC_64ABI -> Arch
ArchPPC_64 PPC_64ABI
ELF_V1, PPC_64ABI -> Arch
ArchPPC_64 PPC_64ABI
ELF_V2] ->
        RegNo -> Bool
PPC.freeReg
    | Bool
otherwise -> RegNo -> Bool
NoRegs.freeReg