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