{-# OPTIONS_GHC -fno-warn-orphans #-}
module GHC.CmmToAsm.X86
   ( ncgX86_64
   , ncgX86
   )
where
import GHC.Prelude
import GHC.CmmToAsm.Instr
import GHC.CmmToAsm.Monad
import GHC.CmmToAsm.Config
import GHC.CmmToAsm.Types
import GHC.Types.Basic (Alignment)
import qualified GHC.CmmToAsm.X86.Instr   as X86
import qualified GHC.CmmToAsm.X86.Ppr     as X86
import qualified GHC.CmmToAsm.X86.CodeGen as X86
import qualified GHC.CmmToAsm.X86.Regs    as X86
ncgX86 :: NCGConfig -> NcgImpl (Alignment, RawCmmStatics) X86.Instr X86.JumpDest
ncgX86 :: NCGConfig -> NcgImpl (Alignment, RawCmmStatics) Instr JumpDest
ncgX86 = NCGConfig -> NcgImpl (Alignment, RawCmmStatics) Instr JumpDest
ncgX86_64
ncgX86_64 :: NCGConfig -> NcgImpl (Alignment, RawCmmStatics) X86.Instr X86.JumpDest
ncgX86_64 :: NCGConfig -> NcgImpl (Alignment, RawCmmStatics) Instr JumpDest
ncgX86_64 NCGConfig
config = NcgImpl
   { ncgConfig :: NCGConfig
ncgConfig                 = NCGConfig
config
   , cmmTopCodeGen :: RawCmmDecl -> NatM [NatCmmDecl (Alignment, RawCmmStatics) Instr]
cmmTopCodeGen             = RawCmmDecl -> NatM [NatCmmDecl (Alignment, RawCmmStatics) Instr]
X86.cmmTopCodeGen
   , generateJumpTableForInstr :: Instr -> Maybe (NatCmmDecl (Alignment, RawCmmStatics) Instr)
generateJumpTableForInstr = NCGConfig
-> Instr -> Maybe (NatCmmDecl (Alignment, RawCmmStatics) Instr)
X86.generateJumpTableForInstr NCGConfig
config
   , getJumpDestBlockId :: JumpDest -> Maybe BlockId
getJumpDestBlockId        = JumpDest -> Maybe BlockId
X86.getJumpDestBlockId
   , canShortcut :: Instr -> Maybe JumpDest
canShortcut               = Instr -> Maybe JumpDest
X86.canShortcut
   , shortcutStatics :: (BlockId -> Maybe JumpDest)
-> (Alignment, RawCmmStatics) -> (Alignment, RawCmmStatics)
shortcutStatics           = (BlockId -> Maybe JumpDest)
-> (Alignment, RawCmmStatics) -> (Alignment, RawCmmStatics)
X86.shortcutStatics
   , shortcutJump :: (BlockId -> Maybe JumpDest) -> Instr -> Instr
shortcutJump              = (BlockId -> Maybe JumpDest) -> Instr -> Instr
X86.shortcutJump
   , pprNatCmmDeclS :: NatCmmDecl (Alignment, RawCmmStatics) Instr -> SDoc
pprNatCmmDeclS            = NCGConfig -> NatCmmDecl (Alignment, RawCmmStatics) Instr -> SDoc
forall doc.
IsDoc doc =>
NCGConfig -> NatCmmDecl (Alignment, RawCmmStatics) Instr -> doc
X86.pprNatCmmDecl NCGConfig
config
   , pprNatCmmDeclH :: NatCmmDecl (Alignment, RawCmmStatics) Instr -> HDoc
pprNatCmmDeclH            = NCGConfig -> NatCmmDecl (Alignment, RawCmmStatics) Instr -> HDoc
forall doc.
IsDoc doc =>
NCGConfig -> NatCmmDecl (Alignment, RawCmmStatics) Instr -> doc
X86.pprNatCmmDecl NCGConfig
config
   , maxSpillSlots :: Int
maxSpillSlots             = NCGConfig -> Int
X86.maxSpillSlots NCGConfig
config
   , allocatableRegs :: [RealReg]
allocatableRegs           = Platform -> [RealReg]
X86.allocatableRegs Platform
platform
   , ncgAllocMoreStack :: Int
-> NatCmmDecl (Alignment, RawCmmStatics) Instr
-> UniqSM
     (NatCmmDecl (Alignment, RawCmmStatics) Instr, [(BlockId, BlockId)])
ncgAllocMoreStack         = Platform
-> Int
-> NatCmmDecl (Alignment, RawCmmStatics) Instr
-> UniqSM
     (NatCmmDecl (Alignment, RawCmmStatics) Instr, [(BlockId, BlockId)])
forall statics.
Platform
-> Int
-> NatCmmDecl statics Instr
-> UniqSM (NatCmmDecl statics Instr, [(BlockId, BlockId)])
X86.allocMoreStack Platform
platform
   , ncgMakeFarBranches :: Platform
-> LabelMap RawCmmStatics
-> [NatBasicBlock Instr]
-> UniqSM [NatBasicBlock Instr]
ncgMakeFarBranches        = \Platform
_p LabelMap RawCmmStatics
_i [NatBasicBlock Instr]
bs -> [NatBasicBlock Instr] -> UniqSM [NatBasicBlock Instr]
forall a. a -> UniqSM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [NatBasicBlock Instr]
bs
   , extractUnwindPoints :: [Instr] -> [UnwindPoint]
extractUnwindPoints       = [Instr] -> [UnwindPoint]
X86.extractUnwindPoints
   , invertCondBranches :: Maybe CFG
-> LabelMap RawCmmStatics
-> [NatBasicBlock Instr]
-> [NatBasicBlock Instr]
invertCondBranches        = Maybe CFG
-> LabelMap RawCmmStatics
-> [NatBasicBlock Instr]
-> [NatBasicBlock Instr]
forall a.
Maybe CFG
-> LabelMap a -> [NatBasicBlock Instr] -> [NatBasicBlock Instr]
X86.invertCondBranches
   }
    where
      platform :: Platform
platform = NCGConfig -> Platform
ncgPlatform NCGConfig
config
instance Instruction X86.Instr where
   regUsageOfInstr :: Platform -> Instr -> RegUsage
regUsageOfInstr         = Platform -> Instr -> RegUsage
X86.regUsageOfInstr
   patchRegsOfInstr :: Instr -> (Reg -> Reg) -> Instr
patchRegsOfInstr        = Instr -> (Reg -> Reg) -> Instr
X86.patchRegsOfInstr
   isJumpishInstr :: Instr -> Bool
isJumpishInstr          = Instr -> Bool
X86.isJumpishInstr
   jumpDestsOfInstr :: Instr -> [BlockId]
jumpDestsOfInstr        = Instr -> [BlockId]
X86.jumpDestsOfInstr
   patchJumpInstr :: Instr -> (BlockId -> BlockId) -> Instr
patchJumpInstr          = Instr -> (BlockId -> BlockId) -> Instr
X86.patchJumpInstr
   mkSpillInstr :: NCGConfig -> Reg -> Int -> Int -> [Instr]
mkSpillInstr            = NCGConfig -> Reg -> Int -> Int -> [Instr]
X86.mkSpillInstr
   mkLoadInstr :: NCGConfig -> Reg -> Int -> Int -> [Instr]
mkLoadInstr             = NCGConfig -> Reg -> Int -> Int -> [Instr]
X86.mkLoadInstr
   takeDeltaInstr :: Instr -> Maybe Int
takeDeltaInstr          = Instr -> Maybe Int
X86.takeDeltaInstr
   isMetaInstr :: Instr -> Bool
isMetaInstr             = Instr -> Bool
X86.isMetaInstr
   mkRegRegMoveInstr :: Platform -> Reg -> Reg -> Instr
mkRegRegMoveInstr       = Platform -> Reg -> Reg -> Instr
X86.mkRegRegMoveInstr
   takeRegRegMoveInstr :: Instr -> Maybe (Reg, Reg)
takeRegRegMoveInstr     = Instr -> Maybe (Reg, Reg)
X86.takeRegRegMoveInstr
   mkJumpInstr :: BlockId -> [Instr]
mkJumpInstr             = BlockId -> [Instr]
X86.mkJumpInstr
   mkStackAllocInstr :: Platform -> Int -> [Instr]
mkStackAllocInstr       = Platform -> Int -> [Instr]
X86.mkStackAllocInstr
   mkStackDeallocInstr :: Platform -> Int -> [Instr]
mkStackDeallocInstr     = Platform -> Int -> [Instr]
X86.mkStackDeallocInstr
   pprInstr :: Platform -> Instr -> SDoc
pprInstr                = Platform -> Instr -> SDoc
forall doc. IsDoc doc => Platform -> Instr -> doc
X86.pprInstr
   mkComment :: FastString -> [Instr]
mkComment               = Instr -> [Instr]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Instr -> [Instr])
-> (FastString -> Instr) -> FastString -> [Instr]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FastString -> Instr
X86.COMMENT