module CodeGen.Platform
(callerSaves, activeStgRegs, haveRegBase, globalRegMaybe, freeReg)
where
import GhcPrelude
import CmmExpr
import Platform
import Reg
import qualified CodeGen.Platform.ARM as ARM
import qualified CodeGen.Platform.ARM64 as ARM64
import qualified CodeGen.Platform.PPC as PPC
import qualified CodeGen.Platform.SPARC as SPARC
import qualified CodeGen.Platform.X86 as X86
import qualified CodeGen.Platform.X86_64 as X86_64
import qualified CodeGen.Platform.NoRegs as NoRegs
callerSaves :: Platform -> GlobalReg -> Bool
callerSaves :: Platform -> GlobalReg -> Bool
callerSaves platform :: Platform
platform
| Platform -> Bool
platformUnregisterised Platform
platform = GlobalReg -> Bool
NoRegs.callerSaves
| Bool
otherwise
= case Platform -> Arch
platformArch Platform
platform of
ArchX86 -> GlobalReg -> Bool
X86.callerSaves
ArchX86_64 -> GlobalReg -> Bool
X86_64.callerSaves
ArchSPARC -> GlobalReg -> Bool
SPARC.callerSaves
ArchARM {} -> GlobalReg -> Bool
ARM.callerSaves
ArchARM64 -> GlobalReg -> Bool
ARM64.callerSaves
arch :: 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
| Platform -> Bool
platformUnregisterised Platform
platform = [GlobalReg]
NoRegs.activeStgRegs
| Bool
otherwise
= case Platform -> Arch
platformArch Platform
platform of
ArchX86 -> [GlobalReg]
X86.activeStgRegs
ArchX86_64 -> [GlobalReg]
X86_64.activeStgRegs
ArchSPARC -> [GlobalReg]
SPARC.activeStgRegs
ArchARM {} -> [GlobalReg]
ARM.activeStgRegs
ArchARM64 -> [GlobalReg]
ARM64.activeStgRegs
arch :: 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
| Platform -> Bool
platformUnregisterised Platform
platform = Bool
NoRegs.haveRegBase
| Bool
otherwise
= case Platform -> Arch
platformArch Platform
platform of
ArchX86 -> Bool
X86.haveRegBase
ArchX86_64 -> Bool
X86_64.haveRegBase
ArchSPARC -> Bool
SPARC.haveRegBase
ArchARM {} -> Bool
ARM.haveRegBase
ArchARM64 -> Bool
ARM64.haveRegBase
arch :: 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
| Platform -> Bool
platformUnregisterised Platform
platform = GlobalReg -> Maybe RealReg
NoRegs.globalRegMaybe
| Bool
otherwise
= case Platform -> Arch
platformArch Platform
platform of
ArchX86 -> GlobalReg -> Maybe RealReg
X86.globalRegMaybe
ArchX86_64 -> GlobalReg -> Maybe RealReg
X86_64.globalRegMaybe
ArchSPARC -> GlobalReg -> Maybe RealReg
SPARC.globalRegMaybe
ArchARM {} -> GlobalReg -> Maybe RealReg
ARM.globalRegMaybe
ArchARM64 -> GlobalReg -> Maybe RealReg
ARM64.globalRegMaybe
arch :: 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
| Platform -> Bool
platformUnregisterised Platform
platform = RegNo -> Bool
NoRegs.freeReg
| Bool
otherwise
= case Platform -> Arch
platformArch Platform
platform of
ArchX86 -> RegNo -> Bool
X86.freeReg
ArchX86_64 -> RegNo -> Bool
X86_64.freeReg
ArchSPARC -> RegNo -> Bool
SPARC.freeReg
ArchARM {} -> RegNo -> Bool
ARM.freeReg
ArchARM64 -> RegNo -> Bool
ARM64.freeReg
arch :: 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