module SPARC.ShortcutJump (
JumpDest(..), getJumpDestBlockId,
canShortcut,
shortcutJump,
shortcutStatics,
shortBlockId
)
where
import GhcPrelude
import SPARC.Instr
import SPARC.Imm
import CLabel
import BlockId
import Cmm
import Panic
import Outputable
data JumpDest
= DestBlockId BlockId
| DestImm Imm
instance Outputable JumpDest where
ppr :: JumpDest -> SDoc
ppr (DestBlockId bid :: BlockId
bid) = String -> SDoc
text "blk:" SDoc -> SDoc -> SDoc
<> BlockId -> SDoc
forall a. Outputable a => a -> SDoc
ppr BlockId
bid
ppr (DestImm _bid :: Imm
_bid) = String -> SDoc
text "imm:?"
getJumpDestBlockId :: JumpDest -> Maybe BlockId
getJumpDestBlockId :: JumpDest -> Maybe BlockId
getJumpDestBlockId (DestBlockId bid :: BlockId
bid) = BlockId -> Maybe BlockId
forall a. a -> Maybe a
Just BlockId
bid
getJumpDestBlockId _ = Maybe BlockId
forall a. Maybe a
Nothing
canShortcut :: Instr -> Maybe JumpDest
canShortcut :: Instr -> Maybe JumpDest
canShortcut _ = Maybe JumpDest
forall a. Maybe a
Nothing
shortcutJump :: (BlockId -> Maybe JumpDest) -> Instr -> Instr
shortcutJump :: (BlockId -> Maybe JumpDest) -> Instr -> Instr
shortcutJump _ other :: Instr
other = Instr
other
shortcutStatics :: (BlockId -> Maybe JumpDest) -> CmmStatics -> CmmStatics
shortcutStatics :: (BlockId -> Maybe JumpDest) -> CmmStatics -> CmmStatics
shortcutStatics fn :: BlockId -> Maybe JumpDest
fn (Statics lbl :: CLabel
lbl statics :: [CmmStatic]
statics)
= CLabel -> [CmmStatic] -> CmmStatics
Statics CLabel
lbl ([CmmStatic] -> CmmStatics) -> [CmmStatic] -> CmmStatics
forall a b. (a -> b) -> a -> b
$ (CmmStatic -> CmmStatic) -> [CmmStatic] -> [CmmStatic]
forall a b. (a -> b) -> [a] -> [b]
map ((BlockId -> Maybe JumpDest) -> CmmStatic -> CmmStatic
shortcutStatic BlockId -> Maybe JumpDest
fn) [CmmStatic]
statics
shortcutLabel :: (BlockId -> Maybe JumpDest) -> CLabel -> CLabel
shortcutLabel :: (BlockId -> Maybe JumpDest) -> CLabel -> CLabel
shortcutLabel fn :: BlockId -> Maybe JumpDest
fn lab :: CLabel
lab
| Just blkId :: BlockId
blkId <- CLabel -> Maybe BlockId
maybeLocalBlockLabel CLabel
lab = (BlockId -> Maybe JumpDest) -> BlockId -> CLabel
shortBlockId BlockId -> Maybe JumpDest
fn BlockId
blkId
| Bool
otherwise = CLabel
lab
shortcutStatic :: (BlockId -> Maybe JumpDest) -> CmmStatic -> CmmStatic
shortcutStatic :: (BlockId -> Maybe JumpDest) -> CmmStatic -> CmmStatic
shortcutStatic fn :: BlockId -> Maybe JumpDest
fn (CmmStaticLit (CmmLabel lab :: CLabel
lab))
= CmmLit -> CmmStatic
CmmStaticLit (CLabel -> CmmLit
CmmLabel ((BlockId -> Maybe JumpDest) -> CLabel -> CLabel
shortcutLabel BlockId -> Maybe JumpDest
fn CLabel
lab))
shortcutStatic fn :: BlockId -> Maybe JumpDest
fn (CmmStaticLit (CmmLabelDiffOff lbl1 :: CLabel
lbl1 lbl2 :: CLabel
lbl2 off :: Int
off w :: Width
w))
= CmmLit -> CmmStatic
CmmStaticLit (CLabel -> CLabel -> Int -> Width -> CmmLit
CmmLabelDiffOff ((BlockId -> Maybe JumpDest) -> CLabel -> CLabel
shortcutLabel BlockId -> Maybe JumpDest
fn CLabel
lbl1) CLabel
lbl2 Int
off Width
w)
shortcutStatic _ other_static :: CmmStatic
other_static
= CmmStatic
other_static
shortBlockId :: (BlockId -> Maybe JumpDest) -> BlockId -> CLabel
shortBlockId :: (BlockId -> Maybe JumpDest) -> BlockId -> CLabel
shortBlockId fn :: BlockId -> Maybe JumpDest
fn blockid :: BlockId
blockid =
case BlockId -> Maybe JumpDest
fn BlockId
blockid of
Nothing -> BlockId -> CLabel
blockLbl BlockId
blockid
Just (DestBlockId blockid' :: BlockId
blockid') -> (BlockId -> Maybe JumpDest) -> BlockId -> CLabel
shortBlockId BlockId -> Maybe JumpDest
fn BlockId
blockid'
Just (DestImm (ImmCLbl lbl :: CLabel
lbl)) -> CLabel
lbl
_other :: Maybe JumpDest
_other -> String -> CLabel
forall a. String -> a
panic "shortBlockId"