From b2682534f1a707b6b3a955837ffd4d0e33d408d2 Mon Sep 17 00:00:00 2001
From: Rodrigo Mesquita <rodrigo.m.mesquita@gmail.com>
Date: Fri, 20 Oct 2023 12:03:23 +0200
Subject: [PATCH] Document NcgImpl methods

Fixes #19914
---
 compiler/GHC/Cmm.hs                      |  2 +-
 compiler/GHC/CmmToAsm/AArch64/RegInfo.hs |  6 ++----
 compiler/GHC/CmmToAsm/Monad.hs           | 15 ++++++++++++++-
 compiler/GHC/CmmToAsm/X86/Instr.hs       |  2 +-
 4 files changed, 18 insertions(+), 7 deletions(-)

diff --git a/compiler/GHC/Cmm.hs b/compiler/GHC/Cmm.hs
index f5aa039bd174..188fa13279ef 100644
--- a/compiler/GHC/Cmm.hs
+++ b/compiler/GHC/Cmm.hs
@@ -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
diff --git a/compiler/GHC/CmmToAsm/AArch64/RegInfo.hs b/compiler/GHC/CmmToAsm/AArch64/RegInfo.hs
index 8c3d081e9218..ed4eb47898c4 100644
--- a/compiler/GHC/CmmToAsm/AArch64/RegInfo.hs
+++ b/compiler/GHC/CmmToAsm/AArch64/RegInfo.hs
@@ -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
diff --git a/compiler/GHC/CmmToAsm/Monad.hs b/compiler/GHC/CmmToAsm/Monad.hs
index 2499259b1e42..b81e9b077db2 100644
--- a/compiler/GHC/CmmToAsm/Monad.hs
+++ b/compiler/GHC/CmmToAsm/Monad.hs
@@ -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.
diff --git a/compiler/GHC/CmmToAsm/X86/Instr.hs b/compiler/GHC/CmmToAsm/X86/Instr.hs
index 679849123ecc..8714fe488bdc 100644
--- a/compiler/GHC/CmmToAsm/X86/Instr.hs
+++ b/compiler/GHC/CmmToAsm/X86/Instr.hs
@@ -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
-- 
GitLab