never executed always true always false
    1 
    2 -----------------------------------------------------------------------------
    3 --
    4 -- Machine-specific parts of the register allocator
    5 --
    6 -- (c) The University of Glasgow 1996-2004
    7 --
    8 -----------------------------------------------------------------------------
    9 module GHC.CmmToAsm.PPC.RegInfo (
   10         JumpDest( DestBlockId ), getJumpDestBlockId,
   11         canShortcut,
   12         shortcutJump,
   13 
   14         shortcutStatics
   15 )
   16 
   17 where
   18 
   19 import GHC.Prelude
   20 
   21 import GHC.CmmToAsm.PPC.Instr
   22 
   23 import GHC.Cmm.BlockId
   24 import GHC.Cmm
   25 import GHC.Cmm.CLabel
   26 
   27 import GHC.Types.Unique
   28 import GHC.Utils.Outputable (ppr, text, Outputable, (<>))
   29 
   30 data JumpDest = DestBlockId BlockId
   31 
   32 -- Debug Instance
   33 instance Outputable JumpDest where
   34   ppr (DestBlockId bid) = text "jd<blk>:" <> ppr bid
   35 
   36 getJumpDestBlockId :: JumpDest -> Maybe BlockId
   37 getJumpDestBlockId (DestBlockId bid) = Just bid
   38 
   39 canShortcut :: Instr -> Maybe JumpDest
   40 canShortcut _ = Nothing
   41 
   42 shortcutJump :: (BlockId -> Maybe JumpDest) -> Instr -> Instr
   43 shortcutJump _ other = other
   44 
   45 
   46 -- Here because it knows about JumpDest
   47 shortcutStatics :: (BlockId -> Maybe JumpDest) -> RawCmmStatics -> RawCmmStatics
   48 shortcutStatics fn (CmmStaticsRaw lbl statics)
   49   = CmmStaticsRaw lbl $ map (shortcutStatic fn) statics
   50   -- we need to get the jump tables, so apply the mapping to the entries
   51   -- of a CmmData too.
   52 
   53 shortcutLabel :: (BlockId -> Maybe JumpDest) -> CLabel -> CLabel
   54 shortcutLabel fn lab
   55   | Just blkId <- maybeLocalBlockLabel lab = shortBlockId fn blkId
   56   | otherwise                              = lab
   57 
   58 shortcutStatic :: (BlockId -> Maybe JumpDest) -> CmmStatic -> CmmStatic
   59 shortcutStatic fn (CmmStaticLit (CmmLabel lab))
   60   = CmmStaticLit (CmmLabel (shortcutLabel fn lab))
   61 shortcutStatic fn (CmmStaticLit (CmmLabelDiffOff lbl1 lbl2 off w))
   62   = CmmStaticLit (CmmLabelDiffOff (shortcutLabel fn lbl1) lbl2 off w)
   63         -- slightly dodgy, we're ignoring the second label, but this
   64         -- works with the way we use CmmLabelDiffOff for jump tables now.
   65 shortcutStatic _ other_static
   66         = other_static
   67 
   68 shortBlockId
   69         :: (BlockId -> Maybe JumpDest)
   70         -> BlockId
   71         -> CLabel
   72 
   73 shortBlockId fn blockid =
   74    case fn blockid of
   75       Nothing -> mkLocalBlockLabel uq
   76       Just (DestBlockId blockid')  -> shortBlockId fn blockid'
   77    where uq = getUnique blockid