summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorTakenobu Tani <takenobu.hs@gmail.com>2020-05-30 23:11:59 +0900
committerMarge Bot <ben+marge-bot@smart-cactus.org>2020-06-10 03:39:59 -0400
commit2487912938f188cb264e4a11d21bf750adccc5e7 (patch)
tree13843cfd8f27bf6f1672a4e37d6af0e04bb34d18
parenta47e6442bc4be4a33339499d876792ba109e8d32 (diff)
downloadhaskell-2487912938f188cb264e4a11d21bf750adccc5e7.tar.gz
Clarify leaf module names for new module hierarchy
This updates comments only. This patch replaces leaf module names according to new module hierarchy [1][2] as followings: * Expand leaf names to easily find the module path: for instance, `Id.hs` to `GHC.Types.Id`. * Modify leaf names according to new module hierarchy: for instance, `Convert.hs` to `GHC.ThToHs`. * Fix typo: for instance, `GHC.Core.TyCo.Rep.hs` to `GHC.Core.TyCo.Rep` See also !3375 [1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular [2]: https://gitlab.haskell.org/ghc/ghc/issues/13009
-rw-r--r--compiler/GHC/Builtin/primops.txt.pp4
-rw-r--r--compiler/GHC/Cmm/DebugBlock.hs4
-rw-r--r--compiler/GHC/Cmm/Node.hs2
-rw-r--r--compiler/GHC/Cmm/Ppr/Expr.hs2
-rw-r--r--compiler/GHC/CmmToAsm.hs6
-rw-r--r--compiler/GHC/CmmToAsm/CFG.hs2
-rw-r--r--compiler/GHC/CmmToAsm/Dwarf.hs2
-rw-r--r--compiler/GHC/CmmToAsm/Monad.hs2
-rw-r--r--compiler/GHC/CmmToAsm/PPC/Ppr.hs2
-rw-r--r--compiler/GHC/CmmToAsm/SPARC/Ppr.hs2
-rw-r--r--compiler/GHC/CmmToAsm/X86/CodeGen.hs2
-rw-r--r--compiler/GHC/CmmToAsm/X86/Ppr.hs2
-rw-r--r--compiler/GHC/CmmToLlvm/Base.hs2
-rw-r--r--compiler/GHC/CmmToLlvm/Data.hs2
-rw-r--r--compiler/GHC/Core.hs2
-rw-r--r--compiler/GHC/Core/Coercion/Axiom.hs2
-rw-r--r--compiler/GHC/Core/FVs.hs2
-rw-r--r--compiler/GHC/Core/FamInstEnv.hs2
-rw-r--r--compiler/GHC/Core/Lint.hs6
-rw-r--r--compiler/GHC/Core/Opt/CprAnal.hs2
-rw-r--r--compiler/GHC/Core/Opt/DmdAnal.hs4
-rw-r--r--compiler/GHC/Core/Opt/FloatIn.hs2
-rw-r--r--compiler/GHC/Core/Opt/SetLevels.hs4
-rw-r--r--compiler/GHC/Core/Opt/Simplify.hs12
-rw-r--r--compiler/GHC/Core/Opt/SpecConstr.hs6
-rw-r--r--compiler/GHC/Core/Opt/Specialise.hs2
-rw-r--r--compiler/GHC/Core/TyCo/Rep.hs2
-rw-r--r--compiler/GHC/Core/Type.hs4
-rw-r--r--compiler/GHC/Core/Unfold.hs2
-rw-r--r--compiler/GHC/CoreToByteCode.hs2
-rw-r--r--compiler/GHC/Driver/Finder.hs2
-rw-r--r--compiler/GHC/Driver/Types.hs2
-rw-r--r--compiler/GHC/Hs/Expr.hs4
-rw-r--r--compiler/GHC/Hs/Pat.hs2
-rw-r--r--compiler/GHC/Hs/Utils.hs4
-rw-r--r--compiler/GHC/HsToCore/Binds.hs6
-rw-r--r--compiler/GHC/HsToCore/Expr.hs2
-rw-r--r--compiler/GHC/HsToCore/PmCheck.hs4
-rw-r--r--compiler/GHC/HsToCore/PmCheck/Ppr.hs2
-rw-r--r--compiler/GHC/HsToCore/PmCheck/Types.hs4
-rw-r--r--compiler/GHC/HsToCore/Quote.hs2
-rw-r--r--compiler/GHC/Iface/Load.hs2
-rw-r--r--compiler/GHC/Iface/Make.hs2
-rw-r--r--compiler/GHC/Iface/Syntax.hs2
-rw-r--r--compiler/GHC/Iface/Tidy.hs2
-rw-r--r--compiler/GHC/Iface/Type.hs6
-rw-r--r--compiler/GHC/Parser.y2
-rw-r--r--compiler/GHC/Parser/Lexer.x16
-rw-r--r--compiler/GHC/Plugins.hs2
-rw-r--r--compiler/GHC/Rename/Env.hs2
-rw-r--r--compiler/GHC/Rename/HsType.hs4
-rw-r--r--compiler/GHC/Rename/Names.hs4
-rw-r--r--compiler/GHC/Rename/Utils.hs8
-rw-r--r--compiler/GHC/Stg/CSE.hs2
-rw-r--r--compiler/GHC/StgToCmm/Bind.hs4
-rw-r--r--compiler/GHC/StgToCmm/Closure.hs2
-rw-r--r--compiler/GHC/StgToCmm/DataCon.hs2
-rw-r--r--compiler/GHC/StgToCmm/Env.hs2
-rw-r--r--compiler/GHC/Tc/Gen/Bind.hs4
-rw-r--r--compiler/GHC/Tc/Gen/Expr.hs4
-rw-r--r--compiler/GHC/Tc/Gen/HsType.hs2
-rw-r--r--compiler/GHC/Tc/Gen/Match.hs2
-rw-r--r--compiler/GHC/Tc/Gen/Pat.hs2
-rw-r--r--compiler/GHC/Tc/Solver.hs2
-rw-r--r--compiler/GHC/Tc/Solver/Monad.hs4
-rw-r--r--compiler/GHC/Tc/TyCl/PatSyn.hs2
-rw-r--r--compiler/GHC/Tc/Types.hs4
-rw-r--r--compiler/GHC/Tc/Types/Constraint.hs6
-rw-r--r--compiler/GHC/Tc/Utils/TcMType.hs2
-rw-r--r--compiler/GHC/Tc/Utils/TcType.hs4
-rw-r--r--compiler/GHC/Tc/Utils/Unify.hs6
-rw-r--r--compiler/GHC/ThToHs.hs4
-rw-r--r--compiler/GHC/Types/Basic.hs2
-rw-r--r--compiler/GHC/Types/Demand.hs4
-rw-r--r--compiler/GHC/Types/Id/Info.hs2
-rw-r--r--compiler/GHC/Types/Id/Make.hs4
-rw-r--r--compiler/GHC/Types/Name/Occurrence.hs2
-rw-r--r--compiler/GHC/Types/Var.hs4
-rw-r--r--compiler/GHC/Unit/Types.hs4
-rw-r--r--compiler/GHC/Utils/Encoding.hs2
80 files changed, 131 insertions, 131 deletions
diff --git a/compiler/GHC/Builtin/primops.txt.pp b/compiler/GHC/Builtin/primops.txt.pp
index 1e3b9b8af5..859fb99ae7 100644
--- a/compiler/GHC/Builtin/primops.txt.pp
+++ b/compiler/GHC/Builtin/primops.txt.pp
@@ -2602,7 +2602,7 @@ primop RaiseOp "raise#" GenPrimOp
-- Hence, it has 'botDiv', not 'exnDiv'.
-- For the same reasons, 'raise#' is marked as "can_fail" (which 'raiseIO#'
-- is not), but not as "has_side_effects" (which 'raiseIO#' is).
- -- See Note [PrimOp can_fail and has_side_effects] in PrimOp.hs.
+ -- See Note [PrimOp can_fail and has_side_effects] in "GHC.Builtin.PrimOps".
strictness = { \ _arity -> mkClosedStrictSig [topDmd] botDiv }
out_of_line = True
can_fail = True
@@ -2653,7 +2653,7 @@ primop RaiseOverflowOp "raiseOverflow#" GenPrimOp
primop RaiseIOOp "raiseIO#" GenPrimOp
a -> State# RealWorld -> (# State# RealWorld, b #)
with
- -- See Note [Precise exceptions and strictness analysis] in Demand.hs
+ -- See Note [Precise exceptions and strictness analysis] in "GHC.Types.Demand"
-- for why this is the *only* primop that has 'exnDiv'
strictness = { \ _arity -> mkClosedStrictSig [topDmd, topDmd] exnDiv }
out_of_line = True
diff --git a/compiler/GHC/Cmm/DebugBlock.hs b/compiler/GHC/Cmm/DebugBlock.hs
index 0cc3d5924f..fbd64b55b0 100644
--- a/compiler/GHC/Cmm/DebugBlock.hs
+++ b/compiler/GHC/Cmm/DebugBlock.hs
@@ -395,7 +395,7 @@ The flow of unwinding information through the compiler is a bit convoluted:
(by the Dwarf module) and emitted in the final object.
See also:
- Note [Unwinding information in the NCG] in AsmCodeGen,
+ Note [Unwinding information in the NCG] in "GHC.CmmToAsm",
Note [Unwind pseudo-instruction in Cmm],
Note [Debugging DWARF unwinding info].
@@ -460,7 +460,7 @@ symbols for gdb if you obtain it through a package manager.
Keep in mind that the current release of GDB has an instruction pointer handling
heuristic that works well for C-like languages, but doesn't always work for
-Haskell. See Note [Info Offset] in Dwarf.Types for more details.
+Haskell. See Note [Info Offset] in "GHC.CmmToAsm.Dwarf.Types" for more details.
Note [Unwind pseudo-instruction in Cmm]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
diff --git a/compiler/GHC/Cmm/Node.hs b/compiler/GHC/Cmm/Node.hs
index 5e13483fae..31a3d14a86 100644
--- a/compiler/GHC/Cmm/Node.hs
+++ b/compiler/GHC/Cmm/Node.hs
@@ -70,7 +70,7 @@ data CmmNode e x where
-- up one frame. Having unwind information for @Sp@ will allow the
-- debugger to "walk" the stack.
--
- -- See Note [What is this unwinding business?] in Debug
+ -- See Note [What is this unwinding business?] in "GHC.Cmm.DebugBlock"
CmmUnwind :: [(GlobalReg, Maybe CmmExpr)] -> CmmNode O O
CmmAssign :: !CmmReg -> !CmmExpr -> CmmNode O O
diff --git a/compiler/GHC/Cmm/Ppr/Expr.hs b/compiler/GHC/Cmm/Ppr/Expr.hs
index fb8e158a2d..5bed66d537 100644
--- a/compiler/GHC/Cmm/Ppr/Expr.hs
+++ b/compiler/GHC/Cmm/Ppr/Expr.hs
@@ -253,7 +253,7 @@ pprArea :: Area -> SDoc
pprArea Old = text "old"
pprArea (Young id) = hcat [ text "young<", ppr id, text ">" ]
--- needs to be kept in syn with CmmExpr.hs.GlobalReg
+-- needs to be kept in syn with 'GHC.Cmm.Expr.GlobalReg'
--
pprGlobalReg :: GlobalReg -> SDoc
pprGlobalReg gr
diff --git a/compiler/GHC/CmmToAsm.hs b/compiler/GHC/CmmToAsm.hs
index fa053e4e66..9252556b6a 100644
--- a/compiler/GHC/CmmToAsm.hs
+++ b/compiler/GHC/CmmToAsm.hs
@@ -289,7 +289,7 @@ data NativeGenAcc statics instr
, ngs_dwarfFiles :: !DwarfFiles
, ngs_unwinds :: !(LabelMap [UnwindPoint])
-- ^ see Note [Unwinding information in the NCG]
- -- and Note [What is this unwinding business?] in Debug.
+ -- and Note [What is this unwinding business?] in "GHC.Cmm.DebugBlock".
}
{-
@@ -314,7 +314,7 @@ field of NativeGenAcc. This is a label map which contains an entry for each
procedure, containing a list of unwinding points (e.g. a label and an associated
unwinding table).
-See also Note [What is this unwinding business?] in Debug.
+See also Note [What is this unwinding business?] in "GHC.Cmm.DebugBlock".
-}
nativeCodeGen' :: (Outputable statics, Outputable instr,Outputable jumpDest,
@@ -432,7 +432,7 @@ cmmNativeGenStream dflags this_mod modLoc ncgImpl h us cmm_stream ngs
dbgMap us cmms ngs 0
-- Link native code information into debug blocks
- -- See Note [What is this unwinding business?] in Debug.
+ -- See Note [What is this unwinding business?] in "GHC.Cmm.DebugBlock".
let !ldbgs = cmmDebugLink (ngs_labels ngs') (ngs_unwinds ngs') ndbgs
unless (null ldbgs) $
dumpIfSet_dyn dflags Opt_D_dump_debug "Debug Infos" FormatText
diff --git a/compiler/GHC/CmmToAsm/CFG.hs b/compiler/GHC/CmmToAsm/CFG.hs
index 5c68e77fd1..aea78e278f 100644
--- a/compiler/GHC/CmmToAsm/CFG.hs
+++ b/compiler/GHC/CmmToAsm/CFG.hs
@@ -251,7 +251,7 @@ filterEdges f cfg =
See Note [What is shortcutting] in the control flow optimization
code (GHC.Cmm.ContFlowOpt) for a slightly more in depth explanation on shortcutting.
-In the native backend we shortcut jumps at the assembly level. (AsmCodeGen.hs)
+In the native backend we shortcut jumps at the assembly level. ("GHC.CmmToAsm")
This means we remove blocks containing only one jump from the code
and instead redirecting all jumps targeting this block to the deleted
blocks jump target.
diff --git a/compiler/GHC/CmmToAsm/Dwarf.hs b/compiler/GHC/CmmToAsm/Dwarf.hs
index 5e52e12867..c0da6977a9 100644
--- a/compiler/GHC/CmmToAsm/Dwarf.hs
+++ b/compiler/GHC/CmmToAsm/Dwarf.hs
@@ -246,7 +246,7 @@ procToFrame initUws blk
-- | If the current procedure has an info table, then we also say that
-- its first block has one to ensure that it gets the necessary -1
-- offset applied to its start address.
- -- See Note [Info Offset] in Dwarf.Types.
+ -- See Note [Info Offset] in "GHC.CmmToAsm.Dwarf.Types".
setHasInfo :: [(DebugBlock, [UnwindPoint])]
-> [(DebugBlock, [UnwindPoint])]
setHasInfo [] = []
diff --git a/compiler/GHC/CmmToAsm/Monad.hs b/compiler/GHC/CmmToAsm/Monad.hs
index b973634d66..f1890fe02c 100644
--- a/compiler/GHC/CmmToAsm/Monad.hs
+++ b/compiler/GHC/CmmToAsm/Monad.hs
@@ -93,7 +93,7 @@ data NcgImpl statics instr jumpDest = NcgImpl {
extractUnwindPoints :: [instr] -> [UnwindPoint],
-- ^ given the instruction sequence of a block, produce a list of
-- the block's 'UnwindPoint's
- -- See Note [What is this unwinding business?] in Debug
+ -- See Note [What is this unwinding business?] in "GHC.Cmm.DebugBlock"
-- and Note [Unwinding information in the NCG] in this module.
invertCondBranches :: Maybe CFG -> LabelMap RawCmmStatics -> [NatBasicBlock instr]
-> [NatBasicBlock instr]
diff --git a/compiler/GHC/CmmToAsm/PPC/Ppr.hs b/compiler/GHC/CmmToAsm/PPC/Ppr.hs
index 521d8e0a76..bb8d412f52 100644
--- a/compiler/GHC/CmmToAsm/PPC/Ppr.hs
+++ b/compiler/GHC/CmmToAsm/PPC/Ppr.hs
@@ -144,7 +144,7 @@ pprBasicBlock config info_env (BasicBlock blockid instrs)
pprDatas :: Platform -> RawCmmStatics -> SDoc
--- See note [emit-time elimination of static indirections] in CLabel.
+-- See note [emit-time elimination of static indirections] in "GHC.Cmm.CLabel".
pprDatas _platform (CmmStaticsRaw alias [CmmStaticLit (CmmLabel lbl), CmmStaticLit ind, _, _])
| lbl == mkIndStaticInfoLabel
, let labelInd (CmmLabelOff l _) = Just l
diff --git a/compiler/GHC/CmmToAsm/SPARC/Ppr.hs b/compiler/GHC/CmmToAsm/SPARC/Ppr.hs
index 3943610346..d1e7dbfa38 100644
--- a/compiler/GHC/CmmToAsm/SPARC/Ppr.hs
+++ b/compiler/GHC/CmmToAsm/SPARC/Ppr.hs
@@ -103,7 +103,7 @@ pprBasicBlock platform info_env (BasicBlock blockid instrs)
pprDatas :: Platform -> RawCmmStatics -> SDoc
--- See note [emit-time elimination of static indirections] in CLabel.
+-- See note [emit-time elimination of static indirections] in "GHC.Cmm.CLabel".
pprDatas _platform (CmmStaticsRaw alias [CmmStaticLit (CmmLabel lbl), CmmStaticLit ind, _, _])
| lbl == mkIndStaticInfoLabel
, let labelInd (CmmLabelOff l _) = Just l
diff --git a/compiler/GHC/CmmToAsm/X86/CodeGen.hs b/compiler/GHC/CmmToAsm/X86/CodeGen.hs
index b8751238ea..dab4c62122 100644
--- a/compiler/GHC/CmmToAsm/X86/CodeGen.hs
+++ b/compiler/GHC/CmmToAsm/X86/CodeGen.hs
@@ -222,7 +222,7 @@ basicBlockCodeGen block = do
return (BasicBlock id top : other_blocks, statics)
-- | Convert 'DELTA' instructions into 'UNWIND' instructions to capture changes
--- in the @sp@ register. See Note [What is this unwinding business?] in Debug
+-- in the @sp@ register. See Note [What is this unwinding business?] in "GHC.Cmm.DebugBlock"
-- for details.
addSpUnwindings :: Instr -> NatM (OrdList Instr)
addSpUnwindings instr@(DELTA d) = do
diff --git a/compiler/GHC/CmmToAsm/X86/Ppr.hs b/compiler/GHC/CmmToAsm/X86/Ppr.hs
index 41c94f90c6..6ed5842389 100644
--- a/compiler/GHC/CmmToAsm/X86/Ppr.hs
+++ b/compiler/GHC/CmmToAsm/X86/Ppr.hs
@@ -150,7 +150,7 @@ pprBasicBlock config info_env (BasicBlock blockid instrs)
pprDatas :: NCGConfig -> (Alignment, RawCmmStatics) -> SDoc
--- See note [emit-time elimination of static indirections] in CLabel.
+-- See note [emit-time elimination of static indirections] in "GHC.Cmm.CLabel".
pprDatas _config (_, CmmStaticsRaw alias [CmmStaticLit (CmmLabel lbl), CmmStaticLit ind, _, _])
| lbl == mkIndStaticInfoLabel
, let labelInd (CmmLabelOff l _) = Just l
diff --git a/compiler/GHC/CmmToLlvm/Base.hs b/compiler/GHC/CmmToLlvm/Base.hs
index f5fa5ea1be..105254cfcc 100644
--- a/compiler/GHC/CmmToLlvm/Base.hs
+++ b/compiler/GHC/CmmToLlvm/Base.hs
@@ -568,7 +568,7 @@ generateExternDecls = do
-- | Here we take a global variable definition, rename it with a
-- @$def@ suffix, and generate the appropriate alias.
aliasify :: LMGlobal -> LlvmM [LMGlobal]
--- See note [emit-time elimination of static indirections] in CLabel.
+-- See note [emit-time elimination of static indirections] in "GHC.Cmm.CLabel".
-- Here we obtain the indirectee's precise type and introduce
-- fresh aliases to both the precise typed label (lbl$def) and the i8*
-- typed (regular) label of it with the matching new names.
diff --git a/compiler/GHC/CmmToLlvm/Data.hs b/compiler/GHC/CmmToLlvm/Data.hs
index aa91621cfd..b32f619640 100644
--- a/compiler/GHC/CmmToLlvm/Data.hs
+++ b/compiler/GHC/CmmToLlvm/Data.hs
@@ -43,7 +43,7 @@ linkage lbl = if externallyVisibleCLabel lbl
-- | Pass a CmmStatic section to an equivalent Llvm code.
genLlvmData :: (Section, RawCmmStatics) -> LlvmM LlvmData
--- See note [emit-time elimination of static indirections] in CLabel.
+-- See note [emit-time elimination of static indirections] in "GHC.Cmm.CLabel".
genLlvmData (_, CmmStaticsRaw alias [CmmStaticLit (CmmLabel lbl), CmmStaticLit ind, _, _])
| lbl == mkIndStaticInfoLabel
, let labelInd (CmmLabelOff l _) = Just l
diff --git a/compiler/GHC/Core.hs b/compiler/GHC/Core.hs
index b4e149af7e..ee19d87ff4 100644
--- a/compiler/GHC/Core.hs
+++ b/compiler/GHC/Core.hs
@@ -1538,7 +1538,7 @@ data UnfoldingSource
| InlineCompulsory -- Something that *has* no binding, so you *must* inline it
-- Only a few primop-like things have this property
- -- (see MkId.hs, calls to mkCompulsoryUnfolding).
+ -- (see "GHC.Types.Id.Make", calls to mkCompulsoryUnfolding).
-- Inline absolutely always, however boring the context.
diff --git a/compiler/GHC/Core/Coercion/Axiom.hs b/compiler/GHC/Core/Coercion/Axiom.hs
index 4c95da97bc..6a8ac41650 100644
--- a/compiler/GHC/Core/Coercion/Axiom.hs
+++ b/compiler/GHC/Core/Coercion/Axiom.hs
@@ -448,7 +448,7 @@ See also:
* Note [Newtype eta] in GHC.Core.TyCon. This is notionally separate
and deals with the axiom connecting a newtype with its representation
type; but it too is eta-reduced.
-* Note [Implementing eta reduction for data families] in TcInstDcls. This
+* Note [Implementing eta reduction for data families] in "GHC.Tc.TyCl.Instance". This
describes the implementation details of this eta reduction happen.
-}
diff --git a/compiler/GHC/Core/FVs.hs b/compiler/GHC/Core/FVs.hs
index b4430f4139..b562ffc38b 100644
--- a/compiler/GHC/Core/FVs.hs
+++ b/compiler/GHC/Core/FVs.hs
@@ -482,7 +482,7 @@ idRuleRhsVars is_active id
get_fvs (Rule { ru_fn = fn, ru_bndrs = bndrs
, ru_rhs = rhs, ru_act = act })
| is_active act
- -- See Note [Finding rule RHS free vars] in OccAnal.hs
+ -- See Note [Finding rule RHS free vars] in "GHC.Core.Opt.OccurAnal"
= delOneFromUniqSet_Directly fvs (getUnique fn)
-- Note [Rule free var hack]
where
diff --git a/compiler/GHC/Core/FamInstEnv.hs b/compiler/GHC/Core/FamInstEnv.hs
index c2308761b9..9d2c5c2f79 100644
--- a/compiler/GHC/Core/FamInstEnv.hs
+++ b/compiler/GHC/Core/FamInstEnv.hs
@@ -647,7 +647,7 @@ mkCoAxBranch :: [TyVar] -- original, possibly stale, tyvars
-> SrcSpan
-> CoAxBranch
mkCoAxBranch tvs eta_tvs cvs ax_tc lhs rhs roles loc
- = -- See Note [CoAxioms are homogeneous] in Core.Coercion.Axiom
+ = -- See Note [CoAxioms are homogeneous] in "GHC.Core.Coercion.Axiom"
ASSERT( typeKind (mkTyConApp ax_tc lhs) `eqType` typeKind rhs )
CoAxBranch { cab_tvs = tvs'
, cab_eta_tvs = eta_tvs'
diff --git a/compiler/GHC/Core/Lint.hs b/compiler/GHC/Core/Lint.hs
index 6648041805..314f9d0319 100644
--- a/compiler/GHC/Core/Lint.hs
+++ b/compiler/GHC/Core/Lint.hs
@@ -163,7 +163,7 @@ Note [Linting type lets]
In the desugarer, it's very very convenient to be able to say (in effect)
let a = Type Bool in
let x::a = True in <body>
-That is, use a type let. See Note [Type let] in CoreSyn.
+That is, use a type let. See Note [Type let] in "GHC.Core".
One place it is used is in mkWwArgs; see Note [Join points and beta-redexes]
in GHC.Core.Opt.WorkWrap.Utils. (Maybe there are other "clients" of this feature; I'm not sure).
@@ -468,7 +468,7 @@ lintCoreBindings dflags pass local_in_scope binds
all_pairs = flattenBinds binds
-- Put all the top-level binders in scope at the start
-- This is because rewrite rules can bring something
- -- into use 'unexpectedly'; see Note [Glomming] in OccurAnal
+ -- into use 'unexpectedly'; see Note [Glomming] in "GHC.Core.Opt.OccurAnal"
binders = map fst all_pairs
flags = defaultLintFlags
@@ -1834,7 +1834,7 @@ conceivably we could allow it. But we can always eta-expand such an
"undersaturated" rule (see 'GHC.Core.Opt.Arity.etaExpandToJoinPointRule'), and in fact
the simplifier would have to in order to deal with the RHS. So we take a
conservative view and don't allow undersaturated rules for join points. See
-Note [Rules and join points] in OccurAnal for further discussion.
+Note [Rules and join points] in "GHC.Core.Opt.OccurAnal" for further discussion.
-}
{-
diff --git a/compiler/GHC/Core/Opt/CprAnal.hs b/compiler/GHC/Core/Opt/CprAnal.hs
index 8bebbb6dde..bb8161a0b2 100644
--- a/compiler/GHC/Core/Opt/CprAnal.hs
+++ b/compiler/GHC/Core/Opt/CprAnal.hs
@@ -373,7 +373,7 @@ data AnalEnv
-- ^ Current approximation of signatures for local ids
, ae_virgin :: Bool
-- ^ True only on every first iteration in a fixed-point
- -- iteration. See Note [Initialising strictness] in "DmdAnal"
+ -- iteration. See Note [Initialising strictness] in "GHC.Core.Opt.DmdAnal"
, ae_fam_envs :: FamInstEnvs
-- ^ Needed when expanding type families and synonyms of product types.
}
diff --git a/compiler/GHC/Core/Opt/DmdAnal.hs b/compiler/GHC/Core/Opt/DmdAnal.hs
index 97c7e29622..c373b5cecb 100644
--- a/compiler/GHC/Core/Opt/DmdAnal.hs
+++ b/compiler/GHC/Core/Opt/DmdAnal.hs
@@ -225,7 +225,7 @@ dmdAnal' env dmd (Case scrut case_bndr ty [(DataAlt dc, bndrs, rhs)])
id_dmds = addCaseBndrDmd case_bndr_dmd dmds
fam_envs = ae_fam_envs env
alt_ty3
- -- See Note [Precise exceptions and strictness analysis] in Demand
+ -- See Note [Precise exceptions and strictness analysis] in "GHC.Types.Demand"
| exprMayThrowPreciseException fam_envs scrut
= deferAfterPreciseException alt_ty2
| otherwise
@@ -259,7 +259,7 @@ dmdAnal' env dmd (Case scrut case_bndr ty alts)
-- when there really are no alternatives
fam_envs = ae_fam_envs env
alt_ty2
- -- See Note [Precise exceptions and strictness analysis] in Demand
+ -- See Note [Precise exceptions and strictness analysis] in "GHC.Types.Demand"
| exprMayThrowPreciseException fam_envs scrut
= deferAfterPreciseException alt_ty
| otherwise
diff --git a/compiler/GHC/Core/Opt/FloatIn.hs b/compiler/GHC/Core/Opt/FloatIn.hs
index 9398435ee5..ff63540ed1 100644
--- a/compiler/GHC/Core/Opt/FloatIn.hs
+++ b/compiler/GHC/Core/Opt/FloatIn.hs
@@ -93,7 +93,7 @@ The fix is
to let bind the algebraic case scrutinees (done, I think) and
the case alternatives (except the ones with an
unboxed type)(not done, I think). This is best done in the
-GHC.Core.Opt.SetLevels.hs module, which tags things with their level numbers.
+GHC.Core.Opt.SetLevels module, which tags things with their level numbers.
\item
do the full laziness pass (floating lets outwards).
\item
diff --git a/compiler/GHC/Core/Opt/SetLevels.hs b/compiler/GHC/Core/Opt/SetLevels.hs
index 4bdf8545e1..beecd424b6 100644
--- a/compiler/GHC/Core/Opt/SetLevels.hs
+++ b/compiler/GHC/Core/Opt/SetLevels.hs
@@ -1047,8 +1047,8 @@ Note [Floating applications to coercions]
We don’t float out variables applied only to type arguments, since the
extra binding would be pointless: type arguments are completely erased.
But *coercion* arguments aren’t (see Note [Coercion tokens] in
-CoreToStg.hs and Note [Count coercion arguments in boring contexts] in
-CoreUnfold.hs), so we still want to float out variables applied only to
+"GHC.CoreToStg" and Note [Count coercion arguments in boring contexts] in
+"GHC.Core.Unfold"), so we still want to float out variables applied only to
coercion arguments.
Note [Escaping a value lambda]
diff --git a/compiler/GHC/Core/Opt/Simplify.hs b/compiler/GHC/Core/Opt/Simplify.hs
index 2e748beb28..15e1c0550a 100644
--- a/compiler/GHC/Core/Opt/Simplify.hs
+++ b/compiler/GHC/Core/Opt/Simplify.hs
@@ -173,7 +173,7 @@ simplTopBinds env0 binds0
-- so that if a rewrite rule has unexpectedly brought
-- anything into scope, then we don't get a complaint about that.
-- It's rather as if the top-level binders were imported.
- -- See note [Glomming] in OccurAnal.
+ -- See note [Glomming] in "GHC.Core.Opt.OccurAnal".
; env1 <- {-#SCC "simplTopBinds-simplRecBndrs" #-} simplRecBndrs env0 (bindersOfBinds binds0)
; (floats, env2) <- {-#SCC "simplTopBinds-simpl_binds" #-} simpl_binds env1 binds0
; freeTick SimplifierDone
@@ -480,7 +480,7 @@ prepareRhs mode top_lvl occ _ rhs0
is_exp = isExpandableApp fun n_val_args -- The fun a constructor or PAP
-- See Note [CONLIKE pragma] in GHC.Types.Basic
-- The definition of is_exp should match that in
- -- OccurAnal.occAnalApp
+ -- 'GHC.Core.Opt.OccurAnal.occAnalApp'
go n_val_args (Tick t rhs)
-- We want to be able to float bindings past this
@@ -2616,7 +2616,7 @@ inlined.
Historical note: we use to do the "case binder swap" in the Simplifier
so there were additional complications if the scrutinee was a variable.
Now the binder-swap stuff is done in the occurrence analyser; see
-OccurAnal Note [Binder swap].
+"GHC.Core.Opt.OccurAnal" Note [Binder swap].
Note [knownCon occ info]
~~~~~~~~~~~~~~~~~~~~~~~~
@@ -2897,8 +2897,8 @@ Note [Add unfolding for scrutinee]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
In general it's unlikely that a variable scrutinee will appear
in the case alternatives case x of { ...x unlikely to appear... }
-because the binder-swap in OccAnal has got rid of all such occurrences
-See Note [Binder swap] in OccAnal.
+because the binder-swap in OccurAnal has got rid of all such occurrences
+See Note [Binder swap] in "GHC.Core.Opt.OccurAnal".
BUT it is still VERY IMPORTANT to add a suitable unfolding for a
variable scrutinee, in simplAlt. Here's why
@@ -3637,7 +3637,7 @@ substitute the RULES and add them back onto the binders; this is done
cases where he really, really wanted a RULE for a recursive function
to apply in that function's own right-hand side.
-See Note [Forming Rec groups] in OccurAnal
+See Note [Forming Rec groups] in "GHC.Core.Opt.OccurAnal"
-}
addBndrRules :: SimplEnv -> InBndr -> OutBndr
diff --git a/compiler/GHC/Core/Opt/SpecConstr.hs b/compiler/GHC/Core/Opt/SpecConstr.hs
index 5b5a63a43a..b2b9f11b9e 100644
--- a/compiler/GHC/Core/Opt/SpecConstr.hs
+++ b/compiler/GHC/Core/Opt/SpecConstr.hs
@@ -2110,15 +2110,15 @@ argToPat env in_scope val_env (Tick _ arg) arg_occ
argToPat env in_scope val_env (Let _ arg) arg_occ
= argToPat env in_scope val_env arg arg_occ
- -- See Note [Matching lets] in Rule.hs
+ -- See Note [Matching lets] in "GHC.Core.Rules"
-- Look through let expressions
-- e.g. f (let v = rhs in (v,w))
-- Here we can specialise for f (v,w)
-- because the rule-matcher will look through the let.
-{- Disabled; see Note [Matching cases] in Rule.hs
+{- Disabled; see Note [Matching cases] in "GHC.Core.Rules"
argToPat env in_scope val_env (Case scrut _ _ [(_, _, rhs)]) arg_occ
- | exprOkForSpeculation scrut -- See Note [Matching cases] in Rule.hhs
+ | exprOkForSpeculation scrut -- See Note [Matching cases] in "GHC.Core.Rules"
= argToPat env in_scope val_env rhs arg_occ
-}
diff --git a/compiler/GHC/Core/Opt/Specialise.hs b/compiler/GHC/Core/Opt/Specialise.hs
index d3f185605f..44cfc460dd 100644
--- a/compiler/GHC/Core/Opt/Specialise.hs
+++ b/compiler/GHC/Core/Opt/Specialise.hs
@@ -1478,7 +1478,7 @@ specCalls mb_mod env existing_rules calls_for_me fn rhs
(spec_inl_prag, spec_unf)
| not is_local && isStrongLoopBreaker (idOccInfo fn)
= (neverInlinePragma, noUnfolding)
- -- See Note [Specialising imported functions] in OccurAnal
+ -- See Note [Specialising imported functions] in "GHC.Core.Opt.OccurAnal"
| InlinePragma { inl_inline = Inlinable } <- inl_prag
= (inl_prag { inl_inline = NoUserInline }, noUnfolding)
diff --git a/compiler/GHC/Core/TyCo/Rep.hs b/compiler/GHC/Core/TyCo/Rep.hs
index d07c424974..188e2a9b3b 100644
--- a/compiler/GHC/Core/TyCo/Rep.hs
+++ b/compiler/GHC/Core/TyCo/Rep.hs
@@ -107,7 +107,7 @@ Despite the fact that DataCon has to be imported via a hi-boot route,
this module seems the right place for TyThing, because it's needed for
funTyCon and all the types in GHC.Builtin.Types.Prim.
-It is also SOURCE-imported into Name.hs
+It is also SOURCE-imported into "GHC.Types.Name"
Note [ATyCon for classes]
diff --git a/compiler/GHC/Core/Type.hs b/compiler/GHC/Core/Type.hs
index 4c9f99a6a7..d12aafb9d7 100644
--- a/compiler/GHC/Core/Type.hs
+++ b/compiler/GHC/Core/Type.hs
@@ -597,7 +597,7 @@ monad and the particular mapper in use.
Even specialising to the monad alone made a 20% allocation difference
in perf/compiler/T5030.
-See Note [Specialising foldType] in TyCoRep for more details of this
+See Note [Specialising foldType] in "GHC.Core.TyCo.Rep" for more details of this
idiom.
-}
@@ -2381,7 +2381,7 @@ nonDetCmpTypesX _ _ [] = GT
-- | Compare two 'TyCon's. NB: This should /never/ see 'Constraint' (as
-- recognized by Kind.isConstraintKindCon) which is considered a synonym for
-- 'Type' in Core.
--- See Note [Kind Constraint and kind Type] in Kind.
+-- See Note [Kind Constraint and kind Type] in "GHC.Core.Type".
-- See Note [nonDetCmpType nondeterminism]
nonDetCmpTc :: TyCon -> TyCon -> Ordering
nonDetCmpTc tc1 tc2
diff --git a/compiler/GHC/Core/Unfold.hs b/compiler/GHC/Core/Unfold.hs
index e1195be42a..7e080367e8 100644
--- a/compiler/GHC/Core/Unfold.hs
+++ b/compiler/GHC/Core/Unfold.hs
@@ -571,7 +571,7 @@ treat coercions the same way.
However, this isn’t a good idea: unlike type arguments, which have
no runtime representation, coercion arguments *do* have a runtime
representation (albeit the zero-width VoidRep, see Note [Coercion tokens]
-in CoreToStg.hs). This caused trouble in #17787 for DataCon wrappers for
+in "GHC.CoreToStg"). This caused trouble in #17787 for DataCon wrappers for
nullary GADT constructors: the wrappers would be inlined and each use of
the constructor would lead to a separate allocation instead of just
sharing the wrapper closure.
diff --git a/compiler/GHC/CoreToByteCode.hs b/compiler/GHC/CoreToByteCode.hs
index 99a0e2849e..96f1f96e63 100644
--- a/compiler/GHC/CoreToByteCode.hs
+++ b/compiler/GHC/CoreToByteCode.hs
@@ -1455,7 +1455,7 @@ maybe_is_tagToEnum_call app
, isDataTyCon tyc
= map (getName . dataConWorkId) (tyConDataCons tyc)
-- NOTE: use the worker name, not the source name of
- -- the DataCon. See DataCon.hs for details.
+ -- the DataCon. See "GHC.Core.DataCon" for details.
| otherwise
= pprPanic "maybe_is_tagToEnum_call.extract_constr_Ids" (ppr ty)
diff --git a/compiler/GHC/Driver/Finder.hs b/compiler/GHC/Driver/Finder.hs
index f3a0ca5bc2..da59c6f611 100644
--- a/compiler/GHC/Driver/Finder.hs
+++ b/compiler/GHC/Driver/Finder.hs
@@ -349,7 +349,7 @@ findPackageModule hsc_env mod = do
-- | Look up the interface file associated with module @mod@. This function
-- requires a few invariants to be upheld: (1) the 'Module' in question must
-- be the module identifier of the *original* implementation of a module,
--- not a reexport (this invariant is upheld by @Packages.hs@) and (2)
+-- not a reexport (this invariant is upheld by "GHC.Unit.State") and (2)
-- the 'UnitInfo' must be consistent with the unit id in the 'Module'.
-- The redundancy is to avoid an extra lookup in the package state
-- for the appropriate config.
diff --git a/compiler/GHC/Driver/Types.hs b/compiler/GHC/Driver/Types.hs
index 171dce0f3b..0249d5cfad 100644
--- a/compiler/GHC/Driver/Types.hs
+++ b/compiler/GHC/Driver/Types.hs
@@ -3163,7 +3163,7 @@ data HsParsedModule = HsParsedModule {
* *
************************************************************************
-This stuff is in here, rather than (say) in Linker.hs, because the Linker.hs
+This stuff is in here, rather than (say) in "GHC.Runtime.Linker", because the "GHC.Runtime.Linker"
stuff is the *dynamic* linker, and isn't present in a stage-1 compiler
-}
diff --git a/compiler/GHC/Hs/Expr.hs b/compiler/GHC/Hs/Expr.hs
index a170594511..28eff0b6c9 100644
--- a/compiler/GHC/Hs/Expr.hs
+++ b/compiler/GHC/Hs/Expr.hs
@@ -139,7 +139,7 @@ type family SyntaxExprGhc (p :: Pass) = (r :: Data.Kind.Type) | r -> p where
-- | The function to use in rebindable syntax. See Note [NoSyntaxExpr].
data SyntaxExprRn = SyntaxExprRn (HsExpr GhcRn)
-- Why is the payload not just a Name?
- -- See Note [Monad fail : Rebindable syntax, overloaded strings] in RnExpr
+ -- See Note [Monad fail : Rebindable syntax, overloaded strings] in "GHC.Rename.Expr"
| NoSyntaxExprRn
-- | An expression with wrappers, used for rebindable syntax
@@ -170,7 +170,7 @@ noSyntaxExpr = case ghcPass @p of
-- | Make a 'SyntaxExpr GhcRn' from an expression
-- Used only in getMonadFailOp.
--- See Note [Monad fail : Rebindable syntax, overloaded strings] in RnExpr
+-- See Note [Monad fail : Rebindable syntax, overloaded strings] in "GHC.Rename.Expr"
mkSyntaxExpr :: HsExpr GhcRn -> SyntaxExprRn
mkSyntaxExpr = SyntaxExprRn
diff --git a/compiler/GHC/Hs/Pat.hs b/compiler/GHC/Hs/Pat.hs
index 7a3f91072d..0e29797b43 100644
--- a/compiler/GHC/Hs/Pat.hs
+++ b/compiler/GHC/Hs/Pat.hs
@@ -588,7 +588,7 @@ pprPat (ConPat { pat_con = con
GhcTc -> sdocOption sdocPrintTypecheckerElaboration $ \case
False -> pprUserCon (unLoc con) details
True ->
- -- Tiresome; in TcBinds.tcRhs we print out a typechecked Pat in an
+ -- Tiresome; in 'GHC.Tc.Gen.Bind.tcRhs' we print out a typechecked Pat in an
-- error message, and we want to make sure it prints nicely
ppr con
<> braces (sep [ hsep (map pprPatBndr (tvs ++ dicts))
diff --git a/compiler/GHC/Hs/Utils.hs b/compiler/GHC/Hs/Utils.hs
index f8199b3332..387536c2f2 100644
--- a/compiler/GHC/Hs/Utils.hs
+++ b/compiler/GHC/Hs/Utils.hs
@@ -293,7 +293,7 @@ mkHsComp ctxt stmts expr = mkHsDo ctxt (stmts ++ [last_stmt])
-- restricted to GhcPs because other phases might need a SyntaxExpr
mkHsIf :: LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs -> HsExpr GhcPs
mkHsIf c a b = HsIf True {- this might use rebindable syntax -} noSyntaxExpr c a b
- -- see Note [Rebindable if] in Hs.Expr
+ -- see Note [Rebindable if] in "GHC.Hs.Expr"
-- restricted to GhcPs because other phases might need a SyntaxExpr
mkHsCmdIf :: LHsExpr GhcPs -> LHsCmd GhcPs -> LHsCmd GhcPs -> HsCmd GhcPs
@@ -506,7 +506,7 @@ nlHsPar e = noLoc (HsPar noExtField e)
-- nlHsIf should generate if-expressions which are NOT subject to
-- RebindableSyntax, so the first field of HsIf is False. (#12080)
--- See Note [Rebindable if] in Hs.Expr
+-- See Note [Rebindable if] in "GHC.Hs.Expr"
nlHsIf :: LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs
nlHsIf cond true false = noLoc (HsIf False noSyntaxExpr cond true false)
diff --git a/compiler/GHC/HsToCore/Binds.hs b/compiler/GHC/HsToCore/Binds.hs
index 4c30aed8ff..8b53e87641 100644
--- a/compiler/GHC/HsToCore/Binds.hs
+++ b/compiler/GHC/HsToCore/Binds.hs
@@ -156,7 +156,7 @@ dsHsBind dflags b@(FunBind { fun_id = L loc fun
-- oracle.
-- addTyCsDs: Add type evidence to the refinement type
-- predicate of the coverage checker
- -- See Note [Type and Term Equality Propagation] in PmCheck
+ -- See Note [Type and Term Equality Propagation] in "GHC.HsToCore.PmCheck"
matchWrapper
(mkPrefixFunRhs (L loc (idName fun)))
Nothing matches
@@ -298,7 +298,7 @@ dsAbsBinds dflags tyvars dicts exports
; let mk_bind (ABE { abe_wrap = wrap
, abe_poly = global
, abe_mono = local, abe_prags = spec_prags })
- -- See Note [AbsBinds wrappers] in HsBinds
+ -- See Note [AbsBinds wrappers] in "GHC.Hs.Binds"
= do { tup_id <- newSysLocalDs tup_ty
; core_wrap <- dsHsWrapper wrap
; let rhs = core_wrap $ mkLams tyvars $ mkLams dicts $
@@ -962,7 +962,7 @@ Consider
After type checking the LHS becomes (foo alpha (C alpha)), where alpha
is an unbound meta-tyvar. The zonker in GHC.Tc.Utils.Zonk is careful not to
turn the free alpha into Any (as it usually does). Instead it turns it
-into a TyVar 'a'. See Note [Zonking the LHS of a RULE] in Ghc.Tc.Syntax.
+into a TyVar 'a'. See Note [Zonking the LHS of a RULE] in "GHC.Tc.Utils.Zonk".
Now we must quantify over that 'a'. It's /really/ inconvenient to do that
in the zonker, because the HsExpr data type is very large. But it's /easy/
diff --git a/compiler/GHC/HsToCore/Expr.hs b/compiler/GHC/HsToCore/Expr.hs
index fb3424c2f9..5e71fabb68 100644
--- a/compiler/GHC/HsToCore/Expr.hs
+++ b/compiler/GHC/HsToCore/Expr.hs
@@ -474,7 +474,7 @@ dsExpr (HsIf _ fun guard_expr then_expr else_expr)
= do { pred <- dsLExpr guard_expr
; b1 <- dsLExpr then_expr
; b2 <- dsLExpr else_expr
- ; case fun of -- See Note [Rebindable if] in Hs.Expr
+ ; case fun of -- See Note [Rebindable if] in "GHC.Hs.Expr"
(SyntaxExprTc {}) -> dsSyntaxExpr fun [pred, b1, b2]
NoSyntaxExprTc -> return $ mkIfThenElse pred b1 b2 }
diff --git a/compiler/GHC/HsToCore/PmCheck.hs b/compiler/GHC/HsToCore/PmCheck.hs
index ef56c35845..f09fd4ecbe 100644
--- a/compiler/GHC/HsToCore/PmCheck.hs
+++ b/compiler/GHC/HsToCore/PmCheck.hs
@@ -510,7 +510,7 @@ translatePat fam_insts x pat = case pat of
translateConPatOut fam_insts x con arg_tys ex_tvs dicts ps
NPat ty (L _ olit) mb_neg _ -> do
- -- See Note [Literal short cut] in GHC.HsToCore.Match.Literal.hs
+ -- See Note [Literal short cut] in "GHC.HsToCore.Match.Literal"
-- We inline the Literal short cut for @ty@ here, because @ty@ is more
-- precise than the field of OverLitTc, which is all that dsOverLit (which
-- normally does the literal short cut) can look at. Also @ty@ matches the
@@ -919,7 +919,7 @@ throttle limit old@(MkDeltas old_ds) new@(MkDeltas new_ds)
| otherwise = (Precise, new)
-- | Matching on a newtype doesn't force anything.
--- See Note [Divergence of Newtype matches] in Oracle.
+-- See Note [Divergence of Newtype matches] in "GHC.HsToCore.PmCheck.Oracle".
conMatchForces :: PmAltCon -> Bool
conMatchForces (PmAltConLike (RealDataCon dc))
| isNewTyCon (dataConTyCon dc) = False
diff --git a/compiler/GHC/HsToCore/PmCheck/Ppr.hs b/compiler/GHC/HsToCore/PmCheck/Ppr.hs
index f8619f9a1d..5845450d21 100644
--- a/compiler/GHC/HsToCore/PmCheck/Ppr.hs
+++ b/compiler/GHC/HsToCore/PmCheck/Ppr.hs
@@ -92,7 +92,7 @@ Unhandled constraints that refer to HsExpr are typically ignored by the solver
(it does not even substitute in HsExpr so they are even printed as wildcards).
Additionally, the oracle returns a substitution if it succeeds so we apply this
substitution to the vectors before printing them out (see function `pprOne' in
-Check.hs) to be more precise.
+"GHC.HsToCore.PmCheck") to be more precise.
-}
-- | Extract and assigns pretty names to constraint variables with refutable
diff --git a/compiler/GHC/HsToCore/PmCheck/Types.hs b/compiler/GHC/HsToCore/PmCheck/Types.hs
index 0c3c9f3286..50000d7ace 100644
--- a/compiler/GHC/HsToCore/PmCheck/Types.hs
+++ b/compiler/GHC/HsToCore/PmCheck/Types.hs
@@ -475,7 +475,7 @@ instance Outputable a => Outputable (SharedDIdEnv a) where
-- entries are possibly shared when we figure out that two variables must be
-- equal, thus represent the same set of values.
--
--- See Note [TmState invariants] in Oracle.
+-- See Note [TmState invariants] in "GHC.HsToCore.PmCheck.Oracle".
data TmState
= TmSt
{ ts_facts :: !(SharedDIdEnv VarInfo)
@@ -492,7 +492,7 @@ data TmState
-- Also caches the type ('vi_ty'), the 'PossibleMatches' of a COMPLETE set
-- ('vi_cache').
--
--- Subject to Note [The Pos/Neg invariant] in PmOracle.
+-- Subject to Note [The Pos/Neg invariant] in "GHC.HsToCore.PmCheck.Oracle".
data VarInfo
= VI
{ vi_ty :: !Type
diff --git a/compiler/GHC/HsToCore/Quote.hs b/compiler/GHC/HsToCore/Quote.hs
index d67f5b4509..e84a4cbb27 100644
--- a/compiler/GHC/HsToCore/Quote.hs
+++ b/compiler/GHC/HsToCore/Quote.hs
@@ -1018,7 +1018,7 @@ rep_ty_sig mk_sig loc sig_ty nm
rep_patsyn_ty_sig :: SrcSpan -> LHsSigType GhcRn -> Located Name
-> MetaM (SrcSpan, Core (M TH.Dec))
-- represents a pattern synonym type signature;
--- see Note [Pattern synonym type signatures and Template Haskell] in Convert
+-- see Note [Pattern synonym type signatures and Template Haskell] in "GHC.ThToHs"
--
-- Don't create the implicit and explicit variables when desugaring signatures,
-- see Note [Scoped type variables in class and instance declarations]
diff --git a/compiler/GHC/Iface/Load.hs b/compiler/GHC/Iface/Load.hs
index f21dc1e7a1..b04db0842d 100644
--- a/compiler/GHC/Iface/Load.hs
+++ b/compiler/GHC/Iface/Load.hs
@@ -558,7 +558,7 @@ we get "duplicate instance" warnings when we compile the "real"
instance in M itself. Hence the strange business of just updateing
the eps_PTE.
-This really happens in practice. The module HsExpr.hs gets
+This really happens in practice. The module "GHC.Hs.Expr" gets
"duplicate instance" errors if this hack is not present.
This is a mess.
diff --git a/compiler/GHC/Iface/Make.hs b/compiler/GHC/Iface/Make.hs
index e11ebd0dc7..89253a33c2 100644
--- a/compiler/GHC/Iface/Make.hs
+++ b/compiler/GHC/Iface/Make.hs
@@ -354,7 +354,7 @@ so we may need to split up a single Avail into multiple ones.
Note [Internal used_names]
~~~~~~~~~~~~~~~~~~~~~~~~~~
Most of the used_names are External Names, but we can have Internal
-Names too: see Note [Binders in Template Haskell] in Convert, and
+Names too: see Note [Binders in Template Haskell] in "GHC.ThToHs", and
#5362 for an example. Such Names are always
- Such Names are always for locally-defined things, for which we
don't gather usage info, so we can just ignore them in ent_map
diff --git a/compiler/GHC/Iface/Syntax.hs b/compiler/GHC/Iface/Syntax.hs
index cfa34ab7bb..a1ed078b5f 100644
--- a/compiler/GHC/Iface/Syntax.hs
+++ b/compiler/GHC/Iface/Syntax.hs
@@ -359,7 +359,7 @@ data IfaceUnfolding
| IfCompulsory IfaceExpr -- default methods and unsafeCoerce#
-- for more about unsafeCoerce#, see
- -- Note [Wiring in unsafeCoerce#] in Desugar
+ -- Note [Wiring in unsafeCoerce#] in "GHC.HsToCore"
| IfInlineRule Arity -- INLINE pragmas
Bool -- OK to inline even if *un*-saturated
diff --git a/compiler/GHC/Iface/Tidy.hs b/compiler/GHC/Iface/Tidy.hs
index b2701bb383..efb72dc77d 100644
--- a/compiler/GHC/Iface/Tidy.hs
+++ b/compiler/GHC/Iface/Tidy.hs
@@ -571,7 +571,7 @@ Oh: two other reasons for injecting them late:
There is one sort of implicit binding that is injected still later,
namely those for data constructor workers. Reason (I think): it's
really just a code generation trick.... binding itself makes no sense.
-See Note [Data constructor workers] in CorePrep.
+See Note [Data constructor workers] in "GHC.CoreToStg.Prep".
-}
getImplicitBinds :: TyCon -> [CoreBind]
diff --git a/compiler/GHC/Iface/Type.hs b/compiler/GHC/Iface/Type.hs
index 26f7c89445..4d64a5d579 100644
--- a/compiler/GHC/Iface/Type.hs
+++ b/compiler/GHC/Iface/Type.hs
@@ -129,8 +129,8 @@ ifaceBndrType (IfaceTvBndr (_, t)) = t
type IfaceLamBndr = (IfaceBndr, IfaceOneShot)
-data IfaceOneShot -- See Note [Preserve OneShotInfo] in CoreTicy
- = IfaceNoOneShot -- and Note [The oneShot function] in GHC.Types.Id.Make
+data IfaceOneShot -- See Note [Preserve OneShotInfo] in "GHC.Core.Tidy"
+ = IfaceNoOneShot -- and Note [The oneShot function] in "GHC.Types.Id.Make"
| IfaceOneShot
@@ -1273,7 +1273,7 @@ pprSpaceIfPromotedTyCon (IfaceTyConApp tyCon _)
pprSpaceIfPromotedTyCon _
= id
--- See equivalent function in GHC.Core.TyCo.Rep.hs
+-- See equivalent function in "GHC.Core.TyCo.Rep"
pprIfaceTyList :: PprPrec -> IfaceType -> IfaceType -> SDoc
-- Given a type-level list (t1 ': t2), see if we can print
-- it in list notation [t1, ...].
diff --git a/compiler/GHC/Parser.y b/compiler/GHC/Parser.y
index a081205033..1b04883fae 100644
--- a/compiler/GHC/Parser.y
+++ b/compiler/GHC/Parser.y
@@ -3853,7 +3853,7 @@ getPRIMSTRINGs (L _ (ITprimstring src _)) = src
getPRIMINTEGERs (L _ (ITprimint src _)) = src
getPRIMWORDs (L _ (ITprimword src _)) = src
--- See Note [Pragma source text] in BasicTypes for the following
+-- See Note [Pragma source text] in "GHC.Types.Basic" for the following
getINLINE_PRAGs (L _ (ITinline_prag src _ _)) = src
getSPEC_PRAGs (L _ (ITspec_prag src)) = src
getSPEC_INLINE_PRAGs (L _ (ITspec_inline_prag src _)) = src
diff --git a/compiler/GHC/Parser/Lexer.x b/compiler/GHC/Parser/Lexer.x
index 5633fd0b0d..1411ba32ff 100644
--- a/compiler/GHC/Parser/Lexer.x
+++ b/compiler/GHC/Parser/Lexer.x
@@ -724,7 +724,7 @@ data Token
| ITdependency
| ITrequires
- -- Pragmas, see note [Pragma source text] in BasicTypes
+ -- Pragmas, see note [Pragma source text] in "GHC.Types.Basic"
| ITinline_prag SourceText InlineSpec RuleMatchInfo
| ITspec_prag SourceText -- SPECIALISE
| ITspec_inline_prag SourceText Bool -- SPECIALISE INLINE (or NOINLINE)
@@ -803,15 +803,15 @@ data Token
| ITdupipvarid FastString -- GHC extension: implicit param: ?x
| ITlabelvarid FastString -- Overloaded label: #x
- | ITchar SourceText Char -- Note [Literal source text] in BasicTypes
- | ITstring SourceText FastString -- Note [Literal source text] in BasicTypes
- | ITinteger IntegralLit -- Note [Literal source text] in BasicTypes
+ | ITchar SourceText Char -- Note [Literal source text] in "GHC.Types.Basic"
+ | ITstring SourceText FastString -- Note [Literal source text] in "GHC.Types.Basic"
+ | ITinteger IntegralLit -- Note [Literal source text] in "GHC.Types.Basic"
| ITrational FractionalLit
- | ITprimchar SourceText Char -- Note [Literal source text] in BasicTypes
- | ITprimstring SourceText ByteString -- Note [Literal source text] @BasicTypes
- | ITprimint SourceText Integer -- Note [Literal source text] in BasicTypes
- | ITprimword SourceText Integer -- Note [Literal source text] in BasicTypes
+ | ITprimchar SourceText Char -- Note [Literal source text] in "GHC.Types.Basic"
+ | ITprimstring SourceText ByteString -- Note [Literal source text] in "GHC.Types.Basic"
+ | ITprimint SourceText Integer -- Note [Literal source text] in "GHC.Types.Basic"
+ | ITprimword SourceText Integer -- Note [Literal source text] in "GHC.Types.Basic"
| ITprimfloat FractionalLit
| ITprimdouble FractionalLit
diff --git a/compiler/GHC/Plugins.hs b/compiler/GHC/Plugins.hs
index 6f7356cc18..99fb30d7d2 100644
--- a/compiler/GHC/Plugins.hs
+++ b/compiler/GHC/Plugins.hs
@@ -126,7 +126,7 @@ import GHC.Tc.Errors.Hole.FitTypes
import qualified Language.Haskell.TH as TH
-{- This instance is defined outside GHC.Core.Opt.Monad.hs so that
+{- This instance is defined outside GHC.Core.Opt.Monad so that
GHC.Core.Opt.Monad does not depend on GHC.Tc.Utils.Env -}
instance MonadThings CoreM where
lookupThing name = do { hsc_env <- getHscEnv
diff --git a/compiler/GHC/Rename/Env.hs b/compiler/GHC/Rename/Env.hs
index 89d1e66311..7ef776cc99 100644
--- a/compiler/GHC/Rename/Env.hs
+++ b/compiler/GHC/Rename/Env.hs
@@ -167,7 +167,7 @@ newTopSrcBinder (L loc rdr_name)
; unless (this_mod == nameModule name)
(addErrAt loc (badOrigBinding rdr_name))
; return name }
- else -- See Note [Binders in Template Haskell] in Convert.hs
+ else -- See Note [Binders in Template Haskell] in "GHC.ThToHs"
do { this_mod <- getModule
; externaliseName this_mod name }
diff --git a/compiler/GHC/Rename/HsType.hs b/compiler/GHC/Rename/HsType.hs
index a13b15fe5d..df6a0f47a8 100644
--- a/compiler/GHC/Rename/HsType.hs
+++ b/compiler/GHC/Rename/HsType.hs
@@ -277,7 +277,7 @@ extraConstraintWildCardsAllowed env
TypeSigCtx {} -> True
ExprWithTySigCtx {} -> True
DerivDeclCtx {} -> True
- StandaloneKindSigCtx {} -> False -- See Note [Wildcards in standalone kind signatures] in GHC/Hs/Decls
+ StandaloneKindSigCtx {} -> False -- See Note [Wildcards in standalone kind signatures] in "GHC.Hs.Decls"
_ -> False
-- | When the NamedWildCards extension is enabled, partition_nwcs
@@ -812,7 +812,7 @@ wildCardsAllowed env
FamPatCtx {} -> True -- Not named wildcards though
GHCiCtx {} -> True
HsTypeCtx {} -> True
- StandaloneKindSigCtx {} -> False -- See Note [Wildcards in standalone kind signatures] in GHC/Hs/Decls
+ StandaloneKindSigCtx {} -> False -- See Note [Wildcards in standalone kind signatures] in "GHC.Hs.Decls"
_ -> False
diff --git a/compiler/GHC/Rename/Names.hs b/compiler/GHC/Rename/Names.hs
index 354954f19c..ccc72bac36 100644
--- a/compiler/GHC/Rename/Names.hs
+++ b/compiler/GHC/Rename/Names.hs
@@ -836,8 +836,8 @@ newRecordSelector overload_ok (dc:_) (L loc (FieldOcc _ (L _ fld)))
-- of an already renamer-resolved field and its use
-- sites. This is needed to correctly support record
-- selectors in Template Haskell. See Note [Binders in
- -- Template Haskell] in Convert.hs and Note [Looking up
- -- Exact RdrNames] in GHC.Rename.Env.
+ -- Template Haskell] in "GHC.ThToHs" and Note [Looking up
+ -- Exact RdrNames] in "GHC.Rename.Env".
| otherwise = mkRdrUnqual (flSelector qualFieldLbl)
{-
diff --git a/compiler/GHC/Rename/Utils.hs b/compiler/GHC/Rename/Utils.hs
index f7ab9496f5..f76939493f 100644
--- a/compiler/GHC/Rename/Utils.hs
+++ b/compiler/GHC/Rename/Utils.hs
@@ -71,7 +71,7 @@ newLocalBndrRn :: Located RdrName -> RnM Name
newLocalBndrRn (L loc rdr_name)
| Just name <- isExact_maybe rdr_name
= return name -- This happens in code generated by Template Haskell
- -- See Note [Binders in Template Haskell] in Convert.hs
+ -- See Note [Binders in Template Haskell] in "GHC.ThToHs"
| otherwise
= do { unless (isUnqual rdr_name)
(addErrAt loc (badQualBndrErr rdr_name))
@@ -113,7 +113,7 @@ checkDupRdrNames rdr_names_w_loc
checkDupNames :: [Name] -> RnM ()
-- Check for duplicated names in a binding group
checkDupNames names = check_dup_names (filterOut isSystemName names)
- -- See Note [Binders in Template Haskell] in Convert
+ -- See Note [Binders in Template Haskell] in "GHC.ThToHs"
check_dup_names :: [Name] -> RnM ()
check_dup_names names
@@ -128,7 +128,7 @@ checkShadowedRdrNames loc_rdr_names
; checkShadowedOccs envs get_loc_occ filtered_rdrs }
where
filtered_rdrs = filterOut (isExact . unLoc) loc_rdr_names
- -- See Note [Binders in Template Haskell] in Convert
+ -- See Note [Binders in Template Haskell] in "GHC.ThToHs"
get_loc_occ (L loc rdr) = (loc,rdrNameOcc rdr)
checkDupAndShadowedNames :: (GlobalRdrEnv, LocalRdrEnv) -> [Name] -> RnM ()
@@ -137,7 +137,7 @@ checkDupAndShadowedNames envs names
; checkShadowedOccs envs get_loc_occ filtered_names }
where
filtered_names = filterOut isSystemName names
- -- See Note [Binders in Template Haskell] in Convert
+ -- See Note [Binders in Template Haskell] in "GHC.ThToHs"
get_loc_occ name = (nameSrcSpan name, nameOccName name)
-------------------------------------
diff --git a/compiler/GHC/Stg/CSE.hs b/compiler/GHC/Stg/CSE.hs
index 404b7faffd..d7b0176b71 100644
--- a/compiler/GHC/Stg/CSE.hs
+++ b/compiler/GHC/Stg/CSE.hs
@@ -235,7 +235,7 @@ substVar env id = fromMaybe id $ lookupVarEnv (ce_subst env) id
-- This is much simpler than the equivalent code in GHC.Core.Subst:
-- * We do not substitute type variables, and
--- * There is nothing relevant in IdInfo at this stage
+-- * There is nothing relevant in GHC.Types.Id.Info at this stage
-- that needs substitutions.
-- Therefore, no special treatment for a recursive group is required.
diff --git a/compiler/GHC/StgToCmm/Bind.hs b/compiler/GHC/StgToCmm/Bind.hs
index 839d34b0e4..5402b6239b 100644
--- a/compiler/GHC/StgToCmm/Bind.hs
+++ b/compiler/GHC/StgToCmm/Bind.hs
@@ -82,7 +82,7 @@ cgTopRhsClosure dflags rec id ccs upd_flag args body =
-- shortcutting the whole process, and generating a lot less code
-- (#7308). Eventually the IND_STATIC closure will be eliminated
-- by assembly '.equiv' directives, where possible (#15155).
- -- See note [emit-time elimination of static indirections] in CLabel.
+ -- See note [emit-time elimination of static indirections] in "GHC.Cmm.CLabel".
--
-- Note: we omit the optimisation when this binding is part of a
-- recursive group, because the optimisation would inhibit the black
@@ -206,7 +206,7 @@ cgRhs id (StgRhsCon cc con args)
-- con args are always non-void,
-- see Note [Post-unarisation invariants] in GHC.Stg.Unarise
-{- See Note [GC recovery] in compiler/GHC.StgToCmm/Closure.hs -}
+{- See Note [GC recovery] in "GHC.StgToCmm.Closure" -}
cgRhs id (StgRhsClosure fvs cc upd_flag args body)
= do dflags <- getDynFlags
mkRhsClosure dflags id cc (nonVoidIds (dVarSetElems fvs)) upd_flag args body
diff --git a/compiler/GHC/StgToCmm/Closure.hs b/compiler/GHC/StgToCmm/Closure.hs
index 7f29d43bca..2c1176c197 100644
--- a/compiler/GHC/StgToCmm/Closure.hs
+++ b/compiler/GHC/StgToCmm/Closure.hs
@@ -870,7 +870,7 @@ mkClosureInfoTableLabel id lf_info
-- Make the _info pointer for the implicit datacon worker
-- binding local. The reason we can do this is that importing
-- code always either uses the _closure or _con_info. By the
- -- invariants in CorePrep anything else gets eta expanded.
+ -- invariants in "GHC.CoreToStg.Prep" anything else gets eta expanded.
thunkEntryLabel :: DynFlags -> Name -> CafInfo -> StandardFormInfo -> Bool -> CLabel
diff --git a/compiler/GHC/StgToCmm/DataCon.hs b/compiler/GHC/StgToCmm/DataCon.hs
index 752d4df681..3f4c94abdd 100644
--- a/compiler/GHC/StgToCmm/DataCon.hs
+++ b/compiler/GHC/StgToCmm/DataCon.hs
@@ -71,7 +71,7 @@ cgTopRhsCon dflags id con args
-- For External bindings we must keep the binding,
-- since importing modules will refer to it by name;
-- but for Internal ones we can drop it altogether
- -- See Note [About the NameSorts] in Name.hs for Internal/External
+ -- See Note [About the NameSorts] in "GHC.Types.Name" for Internal/External
(static_info, static_code)
-- Otherwise generate a closure for the constructor.
diff --git a/compiler/GHC/StgToCmm/Env.hs b/compiler/GHC/StgToCmm/Env.hs
index 03c53db979..9ee04c0617 100644
--- a/compiler/GHC/StgToCmm/Env.hs
+++ b/compiler/GHC/StgToCmm/Env.hs
@@ -136,7 +136,7 @@ getCgIdInfo id
let ext_lbl
| isUnliftedType (idType id) =
-- An unlifted external Id must refer to a top-level
- -- string literal. See Note [Bytes label] in CLabel.
+ -- string literal. See Note [Bytes label] in "GHC.Cmm.CLabel".
ASSERT( idType id `eqType` addrPrimTy )
mkBytesLabel name
| otherwise = mkClosureLabel name $ idCafInfo id
diff --git a/compiler/GHC/Tc/Gen/Bind.hs b/compiler/GHC/Tc/Gen/Bind.hs
index bd9d14e2d4..b88a672795 100644
--- a/compiler/GHC/Tc/Gen/Bind.hs
+++ b/compiler/GHC/Tc/Gen/Bind.hs
@@ -480,7 +480,7 @@ tc_group top_lvl sig_fn prag_fn (Recursive, binds) closed thing_inside
-- strongly-connected-component analysis, this time omitting
-- any references to variables with type signatures.
-- (This used to be optional, but isn't now.)
- -- See Note [Polymorphic recursion] in HsBinds.
+ -- See Note [Polymorphic recursion] in "GHC.Hs.Binds".
do { traceTc "tc_group rec" (pprLHsBinds binds)
; whenIsJust mbFirstPatSyn $ \lpat_syn ->
recursivePatSynErr (getLoc lpat_syn) binds
@@ -548,7 +548,7 @@ tc_single top_lvl sig_fn prag_fn lbind closed thing_inside
type BKey = Int -- Just number off the bindings
mkEdges :: TcSigFun -> LHsBinds GhcRn -> [Node BKey (LHsBind GhcRn)]
--- See Note [Polymorphic recursion] in HsBinds.
+-- See Note [Polymorphic recursion] in "GHC.Hs.Binds".
mkEdges sig_fn binds
= [ DigraphNode bind key [key | n <- nonDetEltsUniqSet (bind_fvs (unLoc bind)),
Just key <- [lookupNameEnv key_map n], no_sig n ]
diff --git a/compiler/GHC/Tc/Gen/Expr.hs b/compiler/GHC/Tc/Gen/Expr.hs
index b4c3b6275c..9294d5fe64 100644
--- a/compiler/GHC/Tc/Gen/Expr.hs
+++ b/compiler/GHC/Tc/Gen/Expr.hs
@@ -2038,7 +2038,7 @@ tcTagToEnum expr fun args app_res_ty res_ty
checkThLocalId :: Id -> TcM ()
-- The renamer has already done checkWellStaged,
--- in RnSplice.checkThLocalName, so don't repeat that here.
+-- in 'GHC.Rename.Splice.checkThLocalName', so don't repeat that here.
-- Here we just just add constraints fro cross-stage lifting
checkThLocalId id
= do { mb_local_use <- getStageAndBindLevel (idName id)
@@ -2122,7 +2122,7 @@ for the Lift class in TH.Syntax, because that can lead to overlapping-instance
errors in a polymorphic situation.
If this check fails (which isn't impossible) we get another chance; see
-Note [Converting strings] in Convert.hs
+Note [Converting strings] in "GHC.ThToHs"
Local record selectors
~~~~~~~~~~~~~~~~~~~~~~
diff --git a/compiler/GHC/Tc/Gen/HsType.hs b/compiler/GHC/Tc/Gen/HsType.hs
index 1cd4e27c8d..e6cad5f4f0 100644
--- a/compiler/GHC/Tc/Gen/HsType.hs
+++ b/compiler/GHC/Tc/Gen/HsType.hs
@@ -1085,7 +1085,7 @@ This table summarises this relation:
--------------------------------------------------------------------------
For more information regarding the interpretation of the resulting ArgFlag, see
-Note [VarBndrs, TyCoVarBinders, TyConBinders, and visibility] in TyCoRep.
+Note [VarBndrs, TyCoVarBinders, TyConBinders, and visibility] in "GHC.Core.TyCo.Rep".
-}
------------------------------------------
diff --git a/compiler/GHC/Tc/Gen/Match.hs b/compiler/GHC/Tc/Gen/Match.hs
index b9eaad4adb..b95899cc1f 100644
--- a/compiler/GHC/Tc/Gen/Match.hs
+++ b/compiler/GHC/Tc/Gen/Match.hs
@@ -932,7 +932,7 @@ tcDoStmt _ stmt _ _
-- The idea behind issuing MonadFail warnings is that we add them whenever a
-- failable pattern is encountered. However, instead of throwing a type error
-- when the constraint cannot be satisfied, we only issue a warning in
--- GHC.Tc.Errors.hs.
+-- "GHC.Tc.Errors".
tcMonadFailOp :: CtOrigin
-> LPat GhcTcId
diff --git a/compiler/GHC/Tc/Gen/Pat.hs b/compiler/GHC/Tc/Gen/Pat.hs
index 4e30d4bc33..830f04a89d 100644
--- a/compiler/GHC/Tc/Gen/Pat.hs
+++ b/compiler/GHC/Tc/Gen/Pat.hs
@@ -639,7 +639,7 @@ AST is used for the subtraction operation.
; let minus'' = case minus' of
NoSyntaxExprTc -> pprPanic "tc_pat NoSyntaxExprTc" (ppr minus')
-- this should be statically avoidable
- -- Case (3) from Note [NoSyntaxExpr] in Hs.Expr
+ -- Case (3) from Note [NoSyntaxExpr] in "GHC.Hs.Expr"
SyntaxExprTc { syn_expr = minus'_expr
, syn_arg_wraps = minus'_arg_wraps
, syn_res_wrap = minus'_res_wrap }
diff --git a/compiler/GHC/Tc/Solver.hs b/compiler/GHC/Tc/Solver.hs
index 8736206188..61477af714 100644
--- a/compiler/GHC/Tc/Solver.hs
+++ b/compiler/GHC/Tc/Solver.hs
@@ -795,7 +795,7 @@ It does *not* reduce type or data family applications or look through newtypes.
Why is this useful? As one example, when coverage-checking an EmptyCase
expression, it's possible that the type of the scrutinee will only reduce
if some local equalities are solved for. See "Wrinkle: Local equalities"
-in Note [Type normalisation] in Check.
+in Note [Type normalisation] in "GHC.HsToCore.PmCheck".
To accomplish its stated goal, tcNormalise first feeds the local constraints
into solveSimpleGivens, then uses flattenType to simplify the desired type
diff --git a/compiler/GHC/Tc/Solver/Monad.hs b/compiler/GHC/Tc/Solver/Monad.hs
index 20f4d4ea07..2ca57e8a23 100644
--- a/compiler/GHC/Tc/Solver/Monad.hs
+++ b/compiler/GHC/Tc/Solver/Monad.hs
@@ -1822,7 +1822,7 @@ kickOutAfterUnification new_tv
; setInertCans ics2
; return n_kicked }
--- See Wrinkle (2b) in Note [Equalities with incompatible kinds] in TcCanonical
+-- See Wrinkle (2b) in Note [Equalities with incompatible kinds] in "GHC.Tc.Solver.Canonical"
kickOutAfterFillingCoercionHole :: CoercionHole -> TcS ()
kickOutAfterFillingCoercionHole hole
= do { ics <- getInertCans
@@ -3232,7 +3232,7 @@ newFlattenSkolem flav loc tc xis
| otherwise -- Generate a [WD] for both Wanted and Derived
-- See Note [No Derived CFunEqCans]
= do { fmv <- wrapTcS (TcM.newFmvTyVar fam_ty)
- -- See (2a) in TcCanonical
+ -- See (2a) in "GHC.Tc.Solver.Canonical"
-- Note [Equalities with incompatible kinds]
; (ev, hole_co) <- newWantedEq_SI NoBlockSubst WDeriv loc Nominal
fam_ty (mkTyVarTy fmv)
diff --git a/compiler/GHC/Tc/TyCl/PatSyn.hs b/compiler/GHC/Tc/TyCl/PatSyn.hs
index a785fbbb7a..57dd16c8f8 100644
--- a/compiler/GHC/Tc/TyCl/PatSyn.hs
+++ b/compiler/GHC/Tc/TyCl/PatSyn.hs
@@ -408,7 +408,7 @@ tcCheckPatSynDecl psb@PSB{ psb_id = lname@(L _ name), psb_args = details
; let skol_info = SigSkol (PatSynCtxt name) pat_ty []
-- The type here is a bit bogus, but we do not print
-- the type for PatSynCtxt, so it doesn't matter
- -- See Note [Skolem info for pattern synonyms] in Origin
+ -- See Note [Skolem info for pattern synonyms] in "GHC.Tc.Types.Origin"
; (implics, ev_binds) <- buildImplicationFor tclvl skol_info univ_tvs req_dicts wanted
-- Solve the constraints now, because we are about to make a PatSyn,
diff --git a/compiler/GHC/Tc/Types.hs b/compiler/GHC/Tc/Types.hs
index 4da234ea08..2afb6bc234 100644
--- a/compiler/GHC/Tc/Types.hs
+++ b/compiler/GHC/Tc/Types.hs
@@ -317,7 +317,7 @@ data DsLclEnv = DsLclEnv {
dsl_meta :: DsMetaEnv, -- Template Haskell bindings
dsl_loc :: RealSrcSpan, -- To put in pattern-matching error msgs
- -- See Note [Note [Type and Term Equality Propagation] in Check.hs
+ -- See Note [Note [Type and Term Equality Propagation] in "GHC.HsToCore.PmCheck"
-- The set of reaching values Deltas is augmented as we walk inwards,
-- refined through each pattern match in turn
dsl_deltas :: Deltas
@@ -1167,7 +1167,7 @@ For (static e) to be valid, we need for every 'x' free in 'e',
that x's binding is floatable to the top level. Specifically:
* x's RhsNames must be empty
* x's type has no free variables
-See Note [Grand plan for static forms] in GHC.Iface.Tidy.StaticPtrTable.hs.
+See Note [Grand plan for static forms] in "GHC.Iface.Tidy.StaticPtrTable".
This test is made in GHC.Tc.Gen.Expr.checkClosedInStaticForm.
Actually knowing x's RhsNames (rather than just its emptiness
or otherwise) is just so we can produce better error messages
diff --git a/compiler/GHC/Tc/Types/Constraint.hs b/compiler/GHC/Tc/Types/Constraint.hs
index 3f01a7d03a..0f95d9f133 100644
--- a/compiler/GHC/Tc/Types/Constraint.hs
+++ b/compiler/GHC/Tc/Types/Constraint.hs
@@ -167,8 +167,8 @@ data Ct
-- * (TyEq:TV) If rhs (perhaps under the cast) is also a tv, then it is oriented
-- to give best chance of
-- unification happening; eg if rhs is touchable then lhs is too
- -- See TcCanonical Note [Canonical orientation for tyvar/tyvar equality constraints]
- -- * (TyEq:H) The RHS has no blocking coercion holes. See TcCanonical
+ -- See "GHC.Tc.Solver.Canonical" Note [Canonical orientation for tyvar/tyvar equality constraints]
+ -- * (TyEq:H) The RHS has no blocking coercion holes. See "GHC.Tc.Solver.Canonical"
-- Note [Equalities with incompatible kinds], wrinkle (2)
cc_ev :: CtEvidence, -- See Note [Ct/evidence invariant]
cc_tyvar :: TcTyVar,
@@ -267,7 +267,7 @@ data CtIrredStatus
= InsolubleCIS -- this constraint will never be solved
| BlockedCIS -- this constraint is blocked on a coercion hole
-- The hole will appear in the ctEvPred of the constraint with this status
- -- See Note [Equalities with incompatible kinds] in TcCanonical
+ -- See Note [Equalities with incompatible kinds] in "GHC.Tc.Solver.Canonical"
-- Wrinkle (4a)
| OtherCIS
diff --git a/compiler/GHC/Tc/Utils/TcMType.hs b/compiler/GHC/Tc/Utils/TcMType.hs
index 97267a8641..6326152797 100644
--- a/compiler/GHC/Tc/Utils/TcMType.hs
+++ b/compiler/GHC/Tc/Utils/TcMType.hs
@@ -2327,7 +2327,7 @@ tidySkolemInfo _ info = info
tidySigSkol :: TidyEnv -> UserTypeCtxt
-> TcType -> [(Name,TcTyVar)] -> SkolemInfo
-- We need to take special care when tidying SigSkol
--- See Note [SigSkol SkolemInfo] in Origin
+-- See Note [SigSkol SkolemInfo] in "GHC.Tc.Types.Origin"
tidySigSkol env cx ty tv_prs
= SigSkol cx (tidy_ty env ty) tv_prs'
where
diff --git a/compiler/GHC/Tc/Utils/TcType.hs b/compiler/GHC/Tc/Utils/TcType.hs
index c1d7af0120..f92861f1d0 100644
--- a/compiler/GHC/Tc/Utils/TcType.hs
+++ b/compiler/GHC/Tc/Utils/TcType.hs
@@ -447,8 +447,8 @@ A TcRhoType has no foralls or contexts at the top
TyVarDetails gives extra info about type variables, used during type
checking. It's attached to mutable type variables only.
-It's knot-tied back to Var.hs. There is no reason in principle
-why Var.hs shouldn't actually have the definition, but it "belongs" here.
+It's knot-tied back to "GHC.Types.Var". There is no reason in principle
+why "GHC.Types.Var" shouldn't actually have the definition, but it "belongs" here.
Note [Signature skolems]
~~~~~~~~~~~~~~~~~~~~~~~~
diff --git a/compiler/GHC/Tc/Utils/Unify.hs b/compiler/GHC/Tc/Utils/Unify.hs
index 8ca3ae7723..efe8301650 100644
--- a/compiler/GHC/Tc/Utils/Unify.hs
+++ b/compiler/GHC/Tc/Utils/Unify.hs
@@ -2049,7 +2049,7 @@ data MetaTyVarUpdateResult a
= MTVU_OK a
| MTVU_Bad -- Forall, predicate, or type family
| MTVU_HoleBlocker -- Blocking coercion hole
- -- See Note [Equalities with incompatible kinds] in TcCanonical
+ -- See Note [Equalities with incompatible kinds] in "GHC.Tc.Solver.Canonical"
| MTVU_Occurs
deriving (Functor)
@@ -2095,7 +2095,7 @@ metaTyVarUpdateOK :: DynFlags
-- (b) that ty does not have any foralls
-- (in the impredicative case), or type functions
-- (c) that ty does not have any blocking coercion holes
--- See Note [Equalities with incompatible kinds] in TcCanonical
+-- See Note [Equalities with incompatible kinds] in "GHC.Tc.Solver.Canonical"
--
-- We have two possible outcomes:
-- (1) Return the type to update the type variable with,
@@ -2181,7 +2181,7 @@ preCheck dflags ty_fam_ok tv ty
-- inferred
fast_check_co co | not (gopt Opt_DeferTypeErrors dflags)
, badCoercionHoleCo co = MTVU_HoleBlocker
- -- Wrinkle (4b) in TcCanonical Note [Equalities with incompatible kinds]
+ -- Wrinkle (4b) in "GHC.Tc.Solver.Canonical" Note [Equalities with incompatible kinds]
| tv `elemVarSet` tyCoVarsOfCo co = MTVU_Occurs
| otherwise = ok
diff --git a/compiler/GHC/ThToHs.hs b/compiler/GHC/ThToHs.hs
index 219072e824..9dea719093 100644
--- a/compiler/GHC/ThToHs.hs
+++ b/compiler/GHC/ThToHs.hs
@@ -1259,7 +1259,7 @@ cvtLit (BytesPrimL (Bytes fptr off sz)) = do
cvtLit _ = panic "Convert.cvtLit: Unexpected literal"
-- cvtLit should not be called on IntegerL, RationalL
-- That precondition is established right here in
- -- Convert.hs, hence panic
+ -- "GHC.ThToHs", hence panic
quotedSourceText :: String -> SourceText
quotedSourceText s = SourceText $ "\"" ++ s ++ "\""
@@ -1657,7 +1657,7 @@ This Convert module then converts the TH AST back to hsSyn AST.
In order to pretty-print this hsSyn AST, parens need to be adde back at certain
points so that the code is readable with its original meaning.
-So scattered through Convert.hs are various points where parens are added.
+So scattered through "GHC.ThToHs" are various points where parens are added.
See (among other closed issued) https://gitlab.haskell.org/ghc/ghc/issues/14289
-}
diff --git a/compiler/GHC/Types/Basic.hs b/compiler/GHC/Types/Basic.hs
index 0d34902b45..a831ab995e 100644
--- a/compiler/GHC/Types/Basic.hs
+++ b/compiler/GHC/Types/Basic.hs
@@ -658,7 +658,7 @@ instance Outputable Origin where
-}
-- | The semantics allowed for overlapping instances for a particular
--- instance. See Note [Safe Haskell isSafeOverlap] (in `InstEnv.hs`) for a
+-- instance. See Note [Safe Haskell isSafeOverlap] (in "GHC.Core.InstEnv") for a
-- explanation of the `isSafeOverlap` field.
--
-- - 'ApiAnnotation.AnnKeywordId' :
diff --git a/compiler/GHC/Types/Demand.hs b/compiler/GHC/Types/Demand.hs
index cbbbe6688d..fe3c30e311 100644
--- a/compiler/GHC/Types/Demand.hs
+++ b/compiler/GHC/Types/Demand.hs
@@ -1058,7 +1058,7 @@ terminate or throw an imprecise exception, until we have performed @foo x s@.
So we have to 'deferAfterPreciseException' (which 'lub's with 'exnDmdType' to
model the exceptional control flow) when @foo x s@ may throw a precise
exception. Motivated by T13380{d,e,f}.
-See Note [Which scrutinees may throw precise exceptions] in DmdAnal.
+See Note [Which scrutinees may throw precise exceptions] in "GHC.Core.Opt.DmdAnal".
We have to be careful not to discard dead-end Divergence from case
alternatives, though (#18086):
@@ -1864,7 +1864,7 @@ where f has usage signature
Then argsOneShots returns a [[OneShotInfo]] of
[[OneShot,NoOneShotInfo,OneShot], [OneShot]]
The occurrence analyser propagates this one-shot infor to the
-binders \pqr and \xyz; see Note [Use one-shot information] in OccurAnal.
+binders \pqr and \xyz; see Note [Use one-shot information] in "GHC.Core.Opt.OccurAnal".
-}
-- | Returns true if an application to n args would diverge or throw an
diff --git a/compiler/GHC/Types/Id/Info.hs b/compiler/GHC/Types/Id/Info.hs
index 82ab98bc09..42a042d481 100644
--- a/compiler/GHC/Types/Id/Info.hs
+++ b/compiler/GHC/Types/Id/Info.hs
@@ -528,7 +528,7 @@ data RuleInfo
DVarSet -- Locally-defined free vars of *both* LHS and RHS
-- of rules. I don't think it needs to include the
-- ru_fn though.
- -- Note [Rule dependency info] in OccurAnal
+ -- Note [Rule dependency info] in "GHC.Core.Opt.OccurAnal"
-- | Assume that no specializations exist: always safe
emptyRuleInfo :: RuleInfo
diff --git a/compiler/GHC/Types/Id/Make.hs b/compiler/GHC/Types/Id/Make.hs
index 176eebc090..6e3edbf7ba 100644
--- a/compiler/GHC/Types/Id/Make.hs
+++ b/compiler/GHC/Types/Id/Make.hs
@@ -1490,7 +1490,7 @@ Note [seqId magic]
a) Its fixity is set in GHC.Iface.Load.ghcPrimIface
b) It has quite a bit of desugaring magic.
- See GHC.HsToCore.Utils.hs Note [Desugaring seq (1)] and (2) and (3)
+ See GHC.HsToCore.Utils Note [Desugaring seq (1)] and (2) and (3)
c) There is some special rule handing: Note [User-defined RULES for seq]
@@ -1711,7 +1711,7 @@ voidArgId :: Id -- Local lambda-bound :: Void#
voidArgId = mkSysLocal (fsLit "void") voidArgIdKey voidPrimTy
coercionTokenId :: Id -- :: () ~ ()
-coercionTokenId -- See Note [Coercion tokens] in CoreToStg.hs
+coercionTokenId -- See Note [Coercion tokens] in "GHC.CoreToStg"
= pcMiscPrelId coercionTokenName
(mkTyConApp eqPrimTyCon [liftedTypeKind, liftedTypeKind, unitTy, unitTy])
noCafIdInfo
diff --git a/compiler/GHC/Types/Name/Occurrence.hs b/compiler/GHC/Types/Name/Occurrence.hs
index 04f81c3129..2062d5449b 100644
--- a/compiler/GHC/Types/Name/Occurrence.hs
+++ b/compiler/GHC/Types/Name/Occurrence.hs
@@ -289,7 +289,7 @@ Note [Suppressing uniques in OccNames]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
This is a hack to de-wobblify the OccNames that contain uniques from
Template Haskell that have been turned into a string in the OccName.
-See Note [Unique OccNames from Template Haskell] in Convert.hs
+See Note [Unique OccNames from Template Haskell] in "GHC.ThToHs"
************************************************************************
* *
diff --git a/compiler/GHC/Types/Var.hs b/compiler/GHC/Types/Var.hs
index b08001c6e2..fc578851f6 100644
--- a/compiler/GHC/Types/Var.hs
+++ b/compiler/GHC/Types/Var.hs
@@ -116,7 +116,7 @@ import Data.Data
* *
************************************************************************
-- These synonyms are here and not in Id because otherwise we need a very
--- large number of SOURCE imports of Id.hs :-(
+-- large number of SOURCE imports of "GHC.Types.Id" :-(
-}
-- | Identifier
@@ -703,7 +703,7 @@ idDetails (Id { id_details = details }) = details
idDetails other = pprPanic "idDetails" (ppr other)
-- The next three have a 'Var' suffix even though they always build
--- Ids, because Id.hs uses 'mkGlobalId' etc with different types
+-- Ids, because "GHC.Types.Id" uses 'mkGlobalId' etc with different types
mkGlobalVar :: IdDetails -> Name -> Type -> IdInfo -> Id
mkGlobalVar details name ty info
= mk_id name ty GlobalId details info
diff --git a/compiler/GHC/Unit/Types.hs b/compiler/GHC/Unit/Types.hs
index 04db40a154..6e04526607 100644
--- a/compiler/GHC/Unit/Types.hs
+++ b/compiler/GHC/Unit/Types.hs
@@ -609,7 +609,7 @@ Make sure you change 'GHC.Unit.State.findWiredInPackages' if you add an entry he
For `integer-gmp`/`integer-simple` we also change the base name to
`integer-wired-in`, but this is fundamentally no different.
-See Note [The integer library] in PrelNames.
+See Note [The integer library] in "GHC.Builtin.Names".
-}
integerUnitId, primUnitId,
@@ -617,7 +617,7 @@ integerUnitId, primUnitId,
thUnitId, mainUnitId, thisGhcUnitId, interactiveUnitId :: Unit
primUnitId = fsToUnit (fsLit "ghc-prim")
integerUnitId = fsToUnit (fsLit "integer-wired-in")
- -- See Note [The integer library] in PrelNames
+ -- See Note [The integer library] in "GHC.Builtin.Names"
baseUnitId = fsToUnit (fsLit "base")
rtsUnitId = fsToUnit (fsLit "rts")
thUnitId = fsToUnit (fsLit "template-haskell")
diff --git a/compiler/GHC/Utils/Encoding.hs b/compiler/GHC/Utils/Encoding.hs
index 165aa05e5b..9d4bc33935 100644
--- a/compiler/GHC/Utils/Encoding.hs
+++ b/compiler/GHC/Utils/Encoding.hs
@@ -57,7 +57,7 @@ import GHC.Exts
--
-- We assume we can ignore overflow when parsing a multibyte character here.
-- To make this safe, we add extra sentinel bytes to unparsed UTF-8 sequences
--- before decoding them (see StringBuffer.hs).
+-- before decoding them (see "GHC.Data.StringBuffer").
{-# INLINE utf8DecodeChar# #-}
utf8DecodeChar# :: Addr# -> (# Char#, Int# #)