Skip to content
Snippets Groups Projects
Commit b2682534 authored by Rodrigo Mesquita's avatar Rodrigo Mesquita :seedling: Committed by Marge Bot
Browse files

Document NcgImpl methods

Fixes #19914
parent 31b28cdb
No related branches found
No related tags found
No related merge requests found
......@@ -304,7 +304,7 @@ instance Outputable CmmStatic where
ppr (CmmString _) = text "CmmString"
ppr (CmmFileEmbed fp _) = text "CmmFileEmbed" <+> text fp
-- Static data before SRT generation
-- | Static data before or after SRT generation
data GenCmmStatics (rawOnly :: Bool) where
CmmStatics
:: CLabel -- Label of statics
......
......@@ -14,18 +14,16 @@ data JumpDest = DestBlockId BlockId
instance Outputable JumpDest where
ppr (DestBlockId bid) = text "jd<blk>:" <> ppr bid
-- TODO: documen what this does. See Ticket 19914
-- Implementations of the methods of 'NgcImpl'
getJumpDestBlockId :: JumpDest -> Maybe BlockId
getJumpDestBlockId (DestBlockId bid) = Just bid
-- TODO: document what this does. See Ticket 19914
canShortcut :: Instr -> Maybe JumpDest
canShortcut _ = Nothing
-- TODO: document what this does. See Ticket 19914
shortcutStatics :: (BlockId -> Maybe JumpDest) -> RawCmmStatics -> RawCmmStatics
shortcutStatics _ other_static = other_static
-- TODO: document what this does. See Ticket 19914
shortcutJump :: (BlockId -> Maybe JumpDest) -> Instr -> Instr
shortcutJump _ other = other
......@@ -73,20 +73,33 @@ import GHC.Utils.Misc
import GHC.CmmToAsm.CFG
import GHC.CmmToAsm.CFG.Weight
-- | A Native Code Generator implementation is parametrised over
-- * The type of static data (typically related to 'CmmStatics')
-- * The type of instructions
-- * The type of jump destinations
data NcgImpl statics instr jumpDest = NcgImpl {
ncgConfig :: !NCGConfig,
cmmTopCodeGen :: RawCmmDecl -> NatM [NatCmmDecl statics instr],
generateJumpTableForInstr :: instr -> Maybe (NatCmmDecl statics instr),
-- | Given a jump destination, if it refers to a block, return the block id of the destination.
getJumpDestBlockId :: jumpDest -> Maybe BlockId,
-- | Does this jump always jump to a single destination and is shortcutable?
--
-- We use this to determine shortcutable instructions - See Note [What is shortcutting]
-- We use this to determine whether the given instruction is a shortcutable
-- jump to some destination - See Note [supporting shortcutting]
-- Note that if we return a destination here we *most* support the relevant shortcutting in
-- shortcutStatics for jump tables and shortcutJump for the instructions itself.
canShortcut :: instr -> Maybe jumpDest,
-- | Replace references to blockIds with other destinations - used to update jump tables.
shortcutStatics :: (BlockId -> Maybe jumpDest) -> statics -> statics,
-- | Change the jump destination(s) of an instruction.
--
-- Rewrites the destination of a jump instruction to another
-- destination, if the given function returns a new jump destination for
-- the 'BlockId' of the original destination.
--
-- For instance, for a mapping @block_a -> dest_b@ and a instruction @goto block_a@ we would
-- rewrite the instruction to @goto dest_b@
shortcutJump :: (BlockId -> Maybe jumpDest) -> instr -> instr,
-- | 'Module' is only for printing internal labels. See Note [Internal proc
-- labels] in CLabel.
......
......@@ -1033,6 +1033,7 @@ instance Outputable JumpDest where
ppr (DestBlockId bid) = text "jd<blk>:" <> ppr bid
ppr (DestImm _imm) = text "jd<imm>:noShow"
-- Implementations of the methods of 'NgcImpl'
getJumpDestBlockId :: JumpDest -> Maybe BlockId
getJumpDestBlockId (DestBlockId bid) = Just bid
......@@ -1043,7 +1044,6 @@ canShortcut (JXX ALWAYS id) = Just (DestBlockId id)
canShortcut (JMP (OpImm imm) _) = Just (DestImm imm)
canShortcut _ = Nothing
-- This helper shortcuts a sequence of branches.
-- The blockset helps avoid following cycles.
shortcutJump :: (BlockId -> Maybe JumpDest) -> Instr -> Instr
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment