{-# OPTIONS_GHC -fno-warn-orphans #-}
module GHC.CmmToAsm.PPC
   ( ncgPPC
   )
where
import GHC.Prelude
import GHC.CmmToAsm.Instr
import GHC.CmmToAsm.Monad
import GHC.CmmToAsm.Config
import GHC.CmmToAsm.Types
import qualified GHC.CmmToAsm.PPC.Instr   as PPC
import qualified GHC.CmmToAsm.PPC.Ppr     as PPC
import qualified GHC.CmmToAsm.PPC.CodeGen as PPC
import qualified GHC.CmmToAsm.PPC.Regs    as PPC
import qualified GHC.CmmToAsm.PPC.RegInfo as PPC
ncgPPC :: NCGConfig -> NcgImpl RawCmmStatics PPC.Instr PPC.JumpDest
ncgPPC :: NCGConfig -> NcgImpl RawCmmStatics Instr JumpDest
ncgPPC NCGConfig
config = NcgImpl :: forall statics instr jumpDest.
NCGConfig
-> (RawCmmDecl -> NatM [NatCmmDecl statics instr])
-> (instr -> Maybe (NatCmmDecl statics instr))
-> (jumpDest -> Maybe BlockId)
-> (instr -> Maybe jumpDest)
-> ((BlockId -> Maybe jumpDest) -> statics -> statics)
-> ((BlockId -> Maybe jumpDest) -> instr -> instr)
-> (NatCmmDecl statics instr -> SDoc)
-> Int
-> [RealReg]
-> ([NatCmmDecl statics instr] -> [NatCmmDecl statics instr])
-> (Int
    -> NatCmmDecl statics instr
    -> UniqSM (NatCmmDecl statics instr, [(BlockId, BlockId)]))
-> (LabelMap RawCmmStatics
    -> [NatBasicBlock instr] -> [NatBasicBlock instr])
-> ([instr] -> [UnwindPoint])
-> (Maybe CFG
    -> LabelMap RawCmmStatics
    -> [NatBasicBlock instr]
    -> [NatBasicBlock instr])
-> NcgImpl statics instr jumpDest
NcgImpl
   { ncgConfig :: NCGConfig
ncgConfig                 = NCGConfig
config
   , cmmTopCodeGen :: RawCmmDecl -> NatM [NatCmmDecl RawCmmStatics Instr]
cmmTopCodeGen             = RawCmmDecl -> NatM [NatCmmDecl RawCmmStatics Instr]
PPC.cmmTopCodeGen
   , generateJumpTableForInstr :: Instr -> Maybe (NatCmmDecl RawCmmStatics Instr)
generateJumpTableForInstr = NCGConfig -> Instr -> Maybe (NatCmmDecl RawCmmStatics Instr)
PPC.generateJumpTableForInstr NCGConfig
config
   , getJumpDestBlockId :: JumpDest -> Maybe BlockId
getJumpDestBlockId        = JumpDest -> Maybe BlockId
PPC.getJumpDestBlockId
   , canShortcut :: Instr -> Maybe JumpDest
canShortcut               = Instr -> Maybe JumpDest
PPC.canShortcut
   , shortcutStatics :: (BlockId -> Maybe JumpDest) -> RawCmmStatics -> RawCmmStatics
shortcutStatics           = (BlockId -> Maybe JumpDest) -> RawCmmStatics -> RawCmmStatics
PPC.shortcutStatics
   , shortcutJump :: (BlockId -> Maybe JumpDest) -> Instr -> Instr
shortcutJump              = (BlockId -> Maybe JumpDest) -> Instr -> Instr
PPC.shortcutJump
   , pprNatCmmDecl :: NatCmmDecl RawCmmStatics Instr -> SDoc
pprNatCmmDecl             = NCGConfig -> NatCmmDecl RawCmmStatics Instr -> SDoc
PPC.pprNatCmmDecl NCGConfig
config
   , maxSpillSlots :: Int
maxSpillSlots             = NCGConfig -> Int
PPC.maxSpillSlots NCGConfig
config
   , allocatableRegs :: [RealReg]
allocatableRegs           = Platform -> [RealReg]
PPC.allocatableRegs Platform
platform
   , ncgAllocMoreStack :: Int
-> NatCmmDecl RawCmmStatics Instr
-> UniqSM (NatCmmDecl RawCmmStatics Instr, [(BlockId, BlockId)])
ncgAllocMoreStack         = Platform
-> Int
-> NatCmmDecl RawCmmStatics Instr
-> UniqSM (NatCmmDecl RawCmmStatics Instr, [(BlockId, BlockId)])
forall statics.
Platform
-> Int
-> NatCmmDecl statics Instr
-> UniqSM (NatCmmDecl statics Instr, [(BlockId, BlockId)])
PPC.allocMoreStack Platform
platform
   , ncgExpandTop :: [NatCmmDecl RawCmmStatics Instr]
-> [NatCmmDecl RawCmmStatics Instr]
ncgExpandTop              = [NatCmmDecl RawCmmStatics Instr]
-> [NatCmmDecl RawCmmStatics Instr]
forall a. a -> a
id
   , ncgMakeFarBranches :: LabelMap RawCmmStatics
-> [NatBasicBlock Instr] -> [NatBasicBlock Instr]
ncgMakeFarBranches        = LabelMap RawCmmStatics
-> [NatBasicBlock Instr] -> [NatBasicBlock Instr]
PPC.makeFarBranches
   , extractUnwindPoints :: [Instr] -> [UnwindPoint]
extractUnwindPoints       = [UnwindPoint] -> [Instr] -> [UnwindPoint]
forall a b. a -> b -> a
const []
   , invertCondBranches :: Maybe CFG
-> LabelMap RawCmmStatics
-> [NatBasicBlock Instr]
-> [NatBasicBlock Instr]
invertCondBranches        = \Maybe CFG
_ LabelMap RawCmmStatics
_ -> [NatBasicBlock Instr] -> [NatBasicBlock Instr]
forall a. a -> a
id
   }
    where
      platform :: Platform
platform = NCGConfig -> Platform
ncgPlatform NCGConfig
config
instance Instruction PPC.Instr where
   regUsageOfInstr :: Platform -> Instr -> RegUsage
regUsageOfInstr     = Platform -> Instr -> RegUsage
PPC.regUsageOfInstr
   patchRegsOfInstr :: Instr -> (Reg -> Reg) -> Instr
patchRegsOfInstr    = Instr -> (Reg -> Reg) -> Instr
PPC.patchRegsOfInstr
   isJumpishInstr :: Instr -> Bool
isJumpishInstr      = Instr -> Bool
PPC.isJumpishInstr
   jumpDestsOfInstr :: Instr -> [BlockId]
jumpDestsOfInstr    = Instr -> [BlockId]
PPC.jumpDestsOfInstr
   patchJumpInstr :: Instr -> (BlockId -> BlockId) -> Instr
patchJumpInstr      = Instr -> (BlockId -> BlockId) -> Instr
PPC.patchJumpInstr
   mkSpillInstr :: NCGConfig -> Reg -> Int -> Int -> Instr
mkSpillInstr        = NCGConfig -> Reg -> Int -> Int -> Instr
PPC.mkSpillInstr
   mkLoadInstr :: NCGConfig -> Reg -> Int -> Int -> Instr
mkLoadInstr         = NCGConfig -> Reg -> Int -> Int -> Instr
PPC.mkLoadInstr
   takeDeltaInstr :: Instr -> Maybe Int
takeDeltaInstr      = Instr -> Maybe Int
PPC.takeDeltaInstr
   isMetaInstr :: Instr -> Bool
isMetaInstr         = Instr -> Bool
PPC.isMetaInstr
   mkRegRegMoveInstr :: Platform -> Reg -> Reg -> Instr
mkRegRegMoveInstr Platform
_ = Reg -> Reg -> Instr
PPC.mkRegRegMoveInstr
   takeRegRegMoveInstr :: Instr -> Maybe (Reg, Reg)
takeRegRegMoveInstr = Instr -> Maybe (Reg, Reg)
PPC.takeRegRegMoveInstr
   mkJumpInstr :: BlockId -> [Instr]
mkJumpInstr         = BlockId -> [Instr]
PPC.mkJumpInstr
   mkStackAllocInstr :: Platform -> Int -> [Instr]
mkStackAllocInstr   = Platform -> Int -> [Instr]
PPC.mkStackAllocInstr
   mkStackDeallocInstr :: Platform -> Int -> [Instr]
mkStackDeallocInstr = Platform -> Int -> [Instr]
PPC.mkStackDeallocInstr
   pprInstr :: Platform -> Instr -> SDoc
pprInstr            = Platform -> Instr -> SDoc
PPC.pprInstr