module GHC.CmmToAsm.AArch64.RegInfo where

import GHC.Prelude

import GHC.CmmToAsm.AArch64.Instr
import GHC.Cmm.BlockId
import GHC.Cmm

import GHC.Utils.Outputable

data JumpDest = DestBlockId BlockId

-- Debug Instance
instance Outputable JumpDest where
  ppr :: JumpDest -> SDoc
ppr (DestBlockId BlockId
bid) = String -> SDoc
text String
"jd<blk>:" SDoc -> SDoc -> SDoc
<> forall a. Outputable a => a -> SDoc
ppr BlockId
bid

-- TODO: documen what this does. See Ticket 19914
getJumpDestBlockId :: JumpDest -> Maybe BlockId
getJumpDestBlockId :: JumpDest -> Maybe BlockId
getJumpDestBlockId (DestBlockId BlockId
bid) = forall a. a -> Maybe a
Just BlockId
bid

-- TODO: document what this does. See Ticket 19914
canShortcut :: Instr -> Maybe JumpDest
canShortcut :: Instr -> Maybe JumpDest
canShortcut Instr
_ = forall a. Maybe a
Nothing

-- TODO: document what this does. See Ticket 19914
shortcutStatics :: (BlockId -> Maybe JumpDest) -> RawCmmStatics -> RawCmmStatics
shortcutStatics :: (BlockId -> Maybe JumpDest) -> RawCmmStatics -> RawCmmStatics
shortcutStatics BlockId -> Maybe JumpDest
_ RawCmmStatics
other_static = RawCmmStatics
other_static

-- TODO: document what this does. See Ticket 19914
shortcutJump :: (BlockId -> Maybe JumpDest) -> Instr -> Instr
shortcutJump :: (BlockId -> Maybe JumpDest) -> Instr -> Instr
shortcutJump BlockId -> Maybe JumpDest
_ Instr
other = Instr
other