{-# OPTIONS_GHC -fno-warn-orphans #-}

-- | Native code generator for x86 and x86-64 architectures
module GHC.CmmToAsm.AArch64
   ( ncgAArch64 )
where

import GHC.Prelude

import GHC.CmmToAsm.Instr
import GHC.CmmToAsm.Monad
import GHC.CmmToAsm.Config
import GHC.CmmToAsm.Types

import qualified GHC.CmmToAsm.AArch64.Instr   as AArch64
import qualified GHC.CmmToAsm.AArch64.Ppr     as AArch64
import qualified GHC.CmmToAsm.AArch64.CodeGen as AArch64
import qualified GHC.CmmToAsm.AArch64.Regs    as AArch64
import qualified GHC.CmmToAsm.AArch64.RegInfo as AArch64

ncgAArch64 :: NCGConfig -> NcgImpl RawCmmStatics AArch64.Instr AArch64.JumpDest
ncgAArch64 :: NCGConfig -> NcgImpl RawCmmStatics Instr JumpDest
ncgAArch64 NCGConfig
config
 = NcgImpl {
        ncgConfig :: NCGConfig
ncgConfig                 = NCGConfig
config
       ,cmmTopCodeGen :: RawCmmDecl -> NatM [NatCmmDecl RawCmmStatics Instr]
cmmTopCodeGen             = RawCmmDecl -> NatM [NatCmmDecl RawCmmStatics Instr]
AArch64.cmmTopCodeGen
       ,generateJumpTableForInstr :: Instr -> Maybe (NatCmmDecl RawCmmStatics Instr)
generateJumpTableForInstr = NCGConfig -> Instr -> Maybe (NatCmmDecl RawCmmStatics Instr)
AArch64.generateJumpTableForInstr NCGConfig
config
       ,getJumpDestBlockId :: JumpDest -> Maybe BlockId
getJumpDestBlockId        = JumpDest -> Maybe BlockId
AArch64.getJumpDestBlockId
       ,canShortcut :: Instr -> Maybe JumpDest
canShortcut               = Instr -> Maybe JumpDest
AArch64.canShortcut
       ,shortcutStatics :: (BlockId -> Maybe JumpDest) -> RawCmmStatics -> RawCmmStatics
shortcutStatics           = (BlockId -> Maybe JumpDest) -> RawCmmStatics -> RawCmmStatics
AArch64.shortcutStatics
       ,shortcutJump :: (BlockId -> Maybe JumpDest) -> Instr -> Instr
shortcutJump              = (BlockId -> Maybe JumpDest) -> Instr -> Instr
AArch64.shortcutJump
       ,pprNatCmmDecl :: NatCmmDecl RawCmmStatics Instr -> SDoc
pprNatCmmDecl             = NCGConfig -> NatCmmDecl RawCmmStatics Instr -> SDoc
AArch64.pprNatCmmDecl NCGConfig
config
       ,maxSpillSlots :: Int
maxSpillSlots             = NCGConfig -> Int
AArch64.maxSpillSlots NCGConfig
config
       ,allocatableRegs :: [RealReg]
allocatableRegs           = Platform -> [RealReg]
AArch64.allocatableRegs Platform
platform
       ,ncgAllocMoreStack :: Int
-> NatCmmDecl RawCmmStatics Instr
-> UniqSM (NatCmmDecl RawCmmStatics Instr, [(BlockId, BlockId)])
ncgAllocMoreStack         = forall statics.
Platform
-> Int
-> NatCmmDecl statics Instr
-> UniqSM (NatCmmDecl statics Instr, [(BlockId, BlockId)])
AArch64.allocMoreStack Platform
platform
       ,ncgExpandTop :: [NatCmmDecl RawCmmStatics Instr]
-> [NatCmmDecl RawCmmStatics Instr]
ncgExpandTop              = forall a. a -> a
id
       ,ncgMakeFarBranches :: LabelMap RawCmmStatics
-> [NatBasicBlock Instr] -> [NatBasicBlock Instr]
ncgMakeFarBranches        = forall a b. a -> b -> a
const forall a. a -> a
id
       ,extractUnwindPoints :: [Instr] -> [UnwindPoint]
extractUnwindPoints       = forall a b. a -> b -> a
const []
       ,invertCondBranches :: Maybe CFG
-> LabelMap RawCmmStatics
-> [NatBasicBlock Instr]
-> [NatBasicBlock Instr]
invertCondBranches        = \Maybe CFG
_ LabelMap RawCmmStatics
_ -> forall a. a -> a
id
  }
    where
      platform :: Platform
platform = NCGConfig -> Platform
ncgPlatform NCGConfig
config

-- | Instruction instance for aarch64
instance Instruction AArch64.Instr where
        regUsageOfInstr :: Platform -> Instr -> RegUsage
regUsageOfInstr         = Platform -> Instr -> RegUsage
AArch64.regUsageOfInstr
        patchRegsOfInstr :: Instr -> (Reg -> Reg) -> Instr
patchRegsOfInstr        = Instr -> (Reg -> Reg) -> Instr
AArch64.patchRegsOfInstr
        isJumpishInstr :: Instr -> Bool
isJumpishInstr          = Instr -> Bool
AArch64.isJumpishInstr
        jumpDestsOfInstr :: Instr -> [BlockId]
jumpDestsOfInstr        = Instr -> [BlockId]
AArch64.jumpDestsOfInstr
        patchJumpInstr :: Instr -> (BlockId -> BlockId) -> Instr
patchJumpInstr          = Instr -> (BlockId -> BlockId) -> Instr
AArch64.patchJumpInstr
        mkSpillInstr :: NCGConfig -> Reg -> Int -> Int -> [Instr]
mkSpillInstr            = HasCallStack => NCGConfig -> Reg -> Int -> Int -> [Instr]
AArch64.mkSpillInstr
        mkLoadInstr :: NCGConfig -> Reg -> Int -> Int -> [Instr]
mkLoadInstr             = NCGConfig -> Reg -> Int -> Int -> [Instr]
AArch64.mkLoadInstr
        takeDeltaInstr :: Instr -> Maybe Int
takeDeltaInstr          = Instr -> Maybe Int
AArch64.takeDeltaInstr
        isMetaInstr :: Instr -> Bool
isMetaInstr             = Instr -> Bool
AArch64.isMetaInstr
        mkRegRegMoveInstr :: Platform -> Reg -> Reg -> Instr
mkRegRegMoveInstr Platform
_     = Reg -> Reg -> Instr
AArch64.mkRegRegMoveInstr
        takeRegRegMoveInstr :: Instr -> Maybe (Reg, Reg)
takeRegRegMoveInstr     = Instr -> Maybe (Reg, Reg)
AArch64.takeRegRegMoveInstr
        mkJumpInstr :: BlockId -> [Instr]
mkJumpInstr             = BlockId -> [Instr]
AArch64.mkJumpInstr
        mkStackAllocInstr :: Platform -> Int -> [Instr]
mkStackAllocInstr       = Platform -> Int -> [Instr]
AArch64.mkStackAllocInstr
        mkStackDeallocInstr :: Platform -> Int -> [Instr]
mkStackDeallocInstr     = Platform -> Int -> [Instr]
AArch64.mkStackDeallocInstr
        mkComment :: SDoc -> [Instr]
mkComment               = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. SDoc -> Instr
AArch64.COMMENT
        pprInstr :: Platform -> Instr -> SDoc
pprInstr                = Platform -> Instr -> SDoc
AArch64.pprInstr