{-# LANGUAGE CPP #-}
module GHC.CmmToAsm.PPC.RegInfo (
JumpDest( DestBlockId ), getJumpDestBlockId,
canShortcut,
shortcutJump,
shortcutStatics
)
where
#include "HsVersions.h"
import GHC.Prelude
import GHC.CmmToAsm.PPC.Instr
import GHC.Cmm.BlockId
import GHC.Cmm
import GHC.Cmm.CLabel
import GHC.Types.Unique
import GHC.Utils.Outputable (ppr, text, Outputable, (<>))
data JumpDest = DestBlockId BlockId
instance Outputable JumpDest where
ppr :: JumpDest -> SDoc
ppr (DestBlockId BlockId
bid) = String -> SDoc
text String
"jd<blk>:" SDoc -> SDoc -> SDoc
<> BlockId -> SDoc
forall a. Outputable a => a -> SDoc
ppr BlockId
bid
getJumpDestBlockId :: JumpDest -> Maybe BlockId
getJumpDestBlockId :: JumpDest -> Maybe BlockId
getJumpDestBlockId (DestBlockId BlockId
bid) = BlockId -> Maybe BlockId
forall a. a -> Maybe a
Just BlockId
bid
canShortcut :: Instr -> Maybe JumpDest
canShortcut :: Instr -> Maybe JumpDest
canShortcut Instr
_ = Maybe JumpDest
forall a. Maybe a
Nothing
shortcutJump :: (BlockId -> Maybe JumpDest) -> Instr -> Instr
shortcutJump :: (BlockId -> Maybe JumpDest) -> Instr -> Instr
shortcutJump BlockId -> Maybe JumpDest
_ Instr
other = Instr
other
shortcutStatics :: (BlockId -> Maybe JumpDest) -> RawCmmStatics -> RawCmmStatics
shortcutStatics :: (BlockId -> Maybe JumpDest) -> RawCmmStatics -> RawCmmStatics
shortcutStatics BlockId -> Maybe JumpDest
fn (CmmStaticsRaw CLabel
lbl [CmmStatic]
statics)
= CLabel -> [CmmStatic] -> RawCmmStatics
forall (rawOnly :: Bool).
CLabel -> [CmmStatic] -> GenCmmStatics rawOnly
CmmStaticsRaw CLabel
lbl ([CmmStatic] -> RawCmmStatics) -> [CmmStatic] -> RawCmmStatics
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 BlockId -> Maybe JumpDest
fn CLabel
lab
| Just 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 BlockId -> Maybe JumpDest
fn (CmmStaticLit (CmmLabel CLabel
lab))
= CmmLit -> CmmStatic
CmmStaticLit (CLabel -> CmmLit
CmmLabel ((BlockId -> Maybe JumpDest) -> CLabel -> CLabel
shortcutLabel BlockId -> Maybe JumpDest
fn CLabel
lab))
shortcutStatic BlockId -> Maybe JumpDest
fn (CmmStaticLit (CmmLabelDiffOff CLabel
lbl1 CLabel
lbl2 Int
off 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 BlockId -> Maybe JumpDest
_ CmmStatic
other_static
= CmmStatic
other_static
shortBlockId
:: (BlockId -> Maybe JumpDest)
-> BlockId
-> CLabel
shortBlockId :: (BlockId -> Maybe JumpDest) -> BlockId -> CLabel
shortBlockId BlockId -> Maybe JumpDest
fn BlockId
blockid =
case BlockId -> Maybe JumpDest
fn BlockId
blockid of
Maybe JumpDest
Nothing -> Unique -> CLabel
mkLocalBlockLabel Unique
uq
Just (DestBlockId BlockId
blockid') -> (BlockId -> Maybe JumpDest) -> BlockId -> CLabel
shortBlockId BlockId -> Maybe JumpDest
fn BlockId
blockid'
where uq :: Unique
uq = BlockId -> Unique
forall a. Uniquable a => a -> Unique
getUnique BlockId
blockid